Skip to content
Commits on Source (12)
......@@ -439,6 +439,21 @@ validate-x86_64-linux-deb9-unreg:
CONFIGURE_ARGS: --enable-unregisterised
TEST_ENV: "x86_64-linux-deb9-unreg"
release-x86_64-linux-deb9-dwarf:
extends: .validate-linux
stage: build
image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb9:$DOCKER_REV"
allow_failure: true
variables:
CONFIGURE_ARGS: "--enable-dwarf-unwind"
BUILD_FLAVOUR: dwarf
TEST_ENV: "x86_64-linux-deb9"
artifacts:
when: always
expire_in: 2 week
cache:
key: linux-x86_64-deb9
#################################
# x86_64-linux-deb8
......
......@@ -81,6 +81,7 @@ import Data.IORef
import Data.Maybe ( fromMaybe )
import Data.Ord
import Data.Time
import Debug.Trace
import Control.Monad
import Control.Monad.IO.Class
import System.IO
......@@ -608,9 +609,10 @@ fatalErrorMsg'' :: FatalMessager -> String -> IO ()
fatalErrorMsg'' fm msg = fm msg
compilationProgressMsg :: DynFlags -> String -> IO ()
compilationProgressMsg dflags msg
= ifVerbose dflags 1 $
logOutput dflags (defaultUserStyle dflags) (text msg)
compilationProgressMsg dflags msg = do
traceEventIO $ "GHC progress: " ++ msg
ifVerbose dflags 1 $
logOutput dflags (defaultUserStyle dflags) (text msg)
showPass :: DynFlags -> String -> IO ()
showPass dflags what
......@@ -651,10 +653,12 @@ withTiming getDFlags what force_result action
if verbosity dflags >= 2 || dopt Opt_D_dump_timings dflags
then do liftIO $ logInfo dflags (defaultUserStyle dflags)
$ text "***" <+> what <> colon
liftIO $ traceEventIO $ showSDocOneLine dflags $ text "GHC:started:" <+> what
alloc0 <- liftIO getAllocationCounter
start <- liftIO getCPUTime
!r <- action
() <- pure $ force_result r
liftIO $ traceEventIO $ showSDocOneLine dflags $ text "GHC:finished:" <+> what
end <- liftIO getCPUTime
alloc1 <- liftIO getAllocationCounter
-- recall that allocation counter counts down
......
......@@ -1374,7 +1374,7 @@ However, consider this case:
f :: Int -> Int
g x = x
We don't want to say 'f' is out of scope; instead, we want to
return the imported 'f', so that later on the reanamer will
return the imported 'f', so that later on the renamer will
correctly report "misplaced type sig".
Note [Signatures for top level things]
......@@ -1472,18 +1472,23 @@ lookupBindGroupOcc ctxt what rdr_name
lookup_top keep_me
= do { env <- getGlobalRdrEnv
; let all_gres = lookupGlobalRdrEnv env (rdrNameOcc rdr_name)
; let candidates_msg = candidates $ map gre_name
$ filter isLocalGRE
$ globalRdrEnvElts env
; case filter (keep_me . gre_name) all_gres of
[] | null all_gres -> bale_out_with Outputable.empty
[] | null all_gres -> bale_out_with candidates_msg
| otherwise -> bale_out_with local_msg
(gre:_) -> return (Right (gre_name gre)) }
lookup_group bound_names -- Look in the local envt (not top level)
= do { mname <- lookupLocalOccRn_maybe rdr_name
; env <- getLocalRdrEnv
; let candidates_msg = candidates $ localRdrEnvElts env
; case mname of
Just n
| n `elemNameSet` bound_names -> return (Right n)
| otherwise -> bale_out_with local_msg
Nothing -> bale_out_with Outputable.empty }
Nothing -> bale_out_with candidates_msg }
bale_out_with msg
= return (Left (sep [ text "The" <+> what
......@@ -1494,6 +1499,22 @@ lookupBindGroupOcc ctxt what rdr_name
local_msg = parens $ text "The" <+> what <+> ptext (sLit "must be given where")
<+> quotes (ppr rdr_name) <+> text "is declared"
-- Identify all similar names and produce a message listing them
candidates :: [Name] -> MsgDoc
candidates names_in_scope
= case similar_names of
[] -> Outputable.empty
[n] -> text "Perhaps you meant" <+> pp_item n
_ -> sep [ text "Perhaps you meant one of these:"
, nest 2 (pprWithCommas pp_item similar_names) ]
where
similar_names
= fuzzyLookup (unpackFS $ occNameFS $ rdrNameOcc rdr_name)
$ map (\x -> ((unpackFS $ occNameFS $ nameOccName x), x))
names_in_scope
pp_item x = quotes (ppr x) <+> parens (pprDefinedAt x)
---------------
lookupLocalTcNames :: HsSigCtxt -> SDoc -> RdrName -> RnM [(RdrName, Name)]
......
This diff is collapsed.
This diff is collapsed.
This diff is collapsed.
This diff is collapsed.
......@@ -56,6 +56,8 @@ library
GHCi.Signals
GHCi.TH
include-dirs: @FFIIncludeDir@
exposed-modules:
GHCi.BreakArray
GHCi.BinaryArray
......
This diff is collapsed.
This diff is collapsed.
-- Type signature and definition with name typo
module M where
-- Both in global scope
simpleFuntcion :: Int -> Bool
simpleFunction i = i > 5
simpleFunction2 i = i < 5
-- Both in local scope
f x = anotherFunction x
where anotherFunction :: Int -> Bool
anotherFuntcion i = i > 5
-- Global signature, local definition
nonexistentFuntcion :: Int -> Bool
g x = nonexistentFunction x
where nonexistentFunction i = i > 5
T16504.hs:5:1: error:
The type signature for ‘simpleFuntcion’
lacks an accompanying binding
Perhaps you meant one of these:
‘simpleFunction’ (Defined at T16504.hs:6:1),
‘simpleFunction2’ (Defined at T16504.hs:7:1)
T16504.hs:11:9: error:
The type signature for ‘anotherFunction’
lacks an accompanying binding
Perhaps you meant ‘anotherFuntcion’ (Defined at T16504.hs:12:9)
T16504.hs:15:1: error:
The type signature for ‘nonexistentFuntcion’
lacks an accompanying binding
......@@ -148,3 +148,4 @@ test('T16116b', normal, compile_fail, [''])
test('ExplicitForAllRules2', normal, compile_fail, [''])
test('T15957_Fail', normal, compile_fail, ['-Werror -Wall -Wno-missing-signatures'])
test('T16385', normal, compile_fail, [''])
test('T16504', normal, compile_fail, [''])
#!/usr/bin/env bash
# Script to update autoconf scripts in the GHC tree. Should be run prior to
# release.
set -e
tmp=`mktemp -d`
git -C $tmp clone https://git.savannah.gnu.org/git/config.git
commit=`git -C $tmp/config rev-parse HEAD`
echo "Updating to $commit..."
files=
for i in $(git ls-files | grep config.guess); do
echo $i
cp $tmp/config/config.guess $i
files="$i $files"
done
for i in $(git ls-files | grep config.sub); do
echo $i
cp $tmp/config/config.sub $i
files="$i $files"
done
git commit $files -m "Update autoconf scripts" -m "Scripts taken from autoconf $commit"
rm -Rf $tmp