summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorPéter Diviánszky <divipp@gmail.com>2016-04-29 12:52:37 +0200
committerPéter Diviánszky <divipp@gmail.com>2016-04-29 12:52:37 +0200
commite57768c37bc8cbc85b58bf47a71562d0d782c698 (patch)
tree471ede50cbdc347faab61667e19c2e3350f4c200
parent58a479b781935155e09f565d2488693850bf21c6 (diff)
use Doc instead of String is several places
-rw-r--r--backendtest/EditorExamplesTest.hs2
-rw-r--r--src/LambdaCube/Compiler.hs44
-rw-r--r--src/LambdaCube/Compiler/DesugaredSource.hs5
-rw-r--r--src/LambdaCube/Compiler/Infer.hs55
-rw-r--r--src/LambdaCube/Compiler/Parser.hs31
-rw-r--r--src/LambdaCube/Compiler/Pretty.hs10
-rw-r--r--test/runTests.hs6
-rw-r--r--testdata/Builtins.out11
-rw-r--r--testdata/Prelude.out12
-rw-r--r--testdata/adhoc.reject.out2
-rw-r--r--testdata/complex.out10
-rw-r--r--testdata/data.out25
-rw-r--r--testdata/framebuffer02.reject.out2
-rw-r--r--testdata/language-features/adt/adt02.reject.out2
-rw-r--r--testdata/language-features/adt/gadt04.reject.out4
-rw-r--r--testdata/language-features/as-pattern/as-pattern02.reject.out1
-rw-r--r--testdata/language-features/basic-list/list07.reject.out2
-rw-r--r--testdata/language-features/basic-list/list10.reject.out2
-rw-r--r--testdata/language-features/basic-list/list14.reject.out2
-rw-r--r--testdata/language-features/basic-list/list15.reject.out2
-rw-r--r--testdata/language-features/basic-list/list16.reject.out2
-rw-r--r--testdata/language-features/basic-list/listcomp08.reject.out2
-rw-r--r--testdata/language-features/basic-values/case03.reject.out2
-rw-r--r--testdata/language-features/basic-values/case04.reject.out2
-rw-r--r--testdata/language-features/basic-values/case05.out1
-rw-r--r--testdata/language-features/basic-values/def02.reject.out1
-rw-r--r--testdata/language-features/basic-values/def03.out3
-rw-r--r--testdata/language-features/basic-values/def07.reject.out8
-rw-r--r--testdata/language-features/basic-values/if03.reject.out2
-rw-r--r--testdata/language-features/basic-values/if04.reject.out2
-rw-r--r--testdata/language-features/basic-values/operator02.reject.out4
-rw-r--r--testdata/language-features/basic-values/operator07.reject.out4
-rw-r--r--testdata/language-features/basic-values/operator08.reject.out4
-rw-r--r--testdata/language-features/basic-values/redefine01.reject.out4
-rw-r--r--testdata/language-features/basic-values/typesyn03.reject.out4
-rw-r--r--testdata/language-features/basic-values/typesyn04.reject.out4
-rw-r--r--testdata/language-features/guard/guard02.reject.out2
-rw-r--r--testdata/language-features/guard/guard05.reject.out2
-rw-r--r--testdata/language-features/guard/guard12.reject.out2
-rw-r--r--testdata/language-features/module/import04.reject.out4
-rw-r--r--testdata/language-features/module/import10.reject.out4
-rw-r--r--testdata/language-features/module/import11.reject.out4
-rw-r--r--testdata/language-features/pattern/uncovered.out5
-rw-r--r--testdata/record01.reject.out2
-rw-r--r--testdata/typesig.reject.out4
-rw-r--r--testdata/typesigctx.reject.out2
-rw-r--r--tool/Compiler.hs4
47 files changed, 134 insertions, 180 deletions
diff --git a/backendtest/EditorExamplesTest.hs b/backendtest/EditorExamplesTest.hs
index 0bbdb572..a4434d2d 100644
--- a/backendtest/EditorExamplesTest.hs
+++ b/backendtest/EditorExamplesTest.hs
@@ -80,7 +80,7 @@ getRenderJob = do
80 ppls <- forM tests $ \name -> do 80 ppls <- forM tests $ \name -> do
81 putStrLn $ "compile: " ++ name 81 putStrLn $ "compile: " ++ name
82 LambdaCube.compileMain [path] OpenGL33 name >>= \case 82 LambdaCube.compileMain [path] OpenGL33 name >>= \case
83 Left err -> fail $ "compile error:\n" ++ err 83 Left err -> fail $ "compile error:\n" ++ show err
84 Right ppl -> return $ PipelineInfo 84 Right ppl -> return $ PipelineInfo
85 { pipelineName = path </> name 85 { pipelineName = path </> name
86 , pipeline = ppl 86 , pipeline = ppl
diff --git a/src/LambdaCube/Compiler.hs b/src/LambdaCube/Compiler.hs
index 017d629c..4c1b7fd8 100644
--- a/src/LambdaCube/Compiler.hs
+++ b/src/LambdaCube/Compiler.hs
@@ -118,14 +118,14 @@ moduleNameToFileName n = hn n ++ ".lc"
118 h acc ('.':cs) = reverse acc </> hn cs 118 h acc ('.':cs) = reverse acc </> hn cs
119 h acc (c: cs) = h (c: acc) cs 119 h acc (c: cs) = h (c: acc) cs
120 120
121type ModuleFetcher m = Maybe FilePath -> Either FilePath MName -> m (Either String (FilePath, MName, m SourceCode)) 121type ModuleFetcher m = Maybe FilePath -> Either FilePath MName -> m (Either Doc (FilePath, MName, m SourceCode))
122 122
123ioFetch :: MonadIO m => [FilePath] -> ModuleFetcher (MMT m x) 123ioFetch :: MonadIO m => [FilePath] -> ModuleFetcher (MMT m x)
124ioFetch paths' imp n = do 124ioFetch paths' imp n = do
125 preludePath <- (</> "lc") <$> liftIO getDataDir 125 preludePath <- (</> "lc") <$> liftIO getDataDir
126 let paths = paths' ++ [preludePath] 126 let paths = paths' ++ [preludePath]
127 find ((x, mn): xs) = liftIO (readFile' x) >>= maybe (find xs) (\src -> return $ Right (x, mn, liftIO src)) 127 find ((x, mn): xs) = liftIO (readFile' x) >>= maybe (find xs) (\src -> return $ Right (x, mn, liftIO src))
128 find [] = return $ Left $ show $ "can't find " <+> either (("lc file" <+>) . text) (("module" <+>) . text) n 128 find [] = return $ Left $ "can't find" <+> either (("lc file" <+>) . text) (("module" <+>) . text) n
129 <+> "in path" <+> hsep (map text (paths' ++ ["<<installed-prelude-path>>"]{-todo-})) 129 <+> "in path" <+> hsep (map text (paths' ++ ["<<installed-prelude-path>>"]{-todo-}))
130 find $ nubBy ((==) `on` fst) $ map (first normalise . lcModuleFile) paths 130 find $ nubBy ((==) `on` fst) $ map (first normalise . lcModuleFile) paths
131 where 131 where
@@ -160,7 +160,7 @@ removeFromCache f = modify $ \m@(Modules nm im ni) -> case Map.lookup f nm of
160 Nothing -> m 160 Nothing -> m
161 Just i -> Modules (Map.delete f nm) (IM.delete i im) ni 161 Just i -> Modules (Map.delete f nm) (IM.delete i im) ni
162 162
163type Module' x = (SourceCode, Either String{-error msg-} (Module, x, Either String{-error msg-} (DesugarInfo, GlobalEnv))) 163type Module' x = (SourceCode, Either Doc{-error msg-} (Module, x, Either Doc{-error msg-} (DesugarInfo, GlobalEnv)))
164 164
165data Modules x = Modules 165data Modules x = Modules
166 { moduleIds :: !(Map FilePath Int) 166 { moduleIds :: !(Map FilePath Int)
@@ -170,7 +170,7 @@ data Modules x = Modules
170 170
171(<&>) = flip (<$>) 171(<&>) = flip (<$>)
172 172
173loadModule :: MonadMask m => ((Infos, [Stmt]) -> x) -> Maybe FilePath -> Either FilePath MName -> MMT m x (Either String (FilePath, Module' x)) 173loadModule :: MonadMask m => ((Infos, [Stmt]) -> x) -> Maybe FilePath -> Either FilePath MName -> MMT m x (Either Doc (FilePath, Module' x))
174loadModule ex imp mname_ = do 174loadModule ex imp mname_ = do
175 r <- ask >>= \fetch -> fetch imp mname_ 175 r <- ask >>= \fetch -> fetch imp mname_
176 case r of 176 case r of
@@ -184,34 +184,34 @@ loadModule ex imp mname_ = do
184 fid <- gets nextMId 184 fid <- gets nextMId
185 modify $ \(Modules nm im ni) -> Modules (Map.insert fname fid nm) im $ ni+1 185 modify $ \(Modules nm im ni) -> Modules (Map.insert fname fid nm) im $ ni+1
186 res <- case parseLC $ FileInfo fid fname src of 186 res <- case parseLC $ FileInfo fid fname src of
187 Left e -> return $ Left $ show e 187 Left e -> return $ Left $ text $ show e
188 Right e -> do 188 Right e -> do
189 modify $ \(Modules nm im ni) -> Modules nm (IM.insert fid (fname, (src, Right (e, ex mempty, Left $ show $ "cycles in module imports:" <+> pShow mname <+> pShow (fst <$> moduleImports e)))) im) ni 189 modify $ \(Modules nm im ni) -> Modules nm (IM.insert fid (fname, (src, Right (e, ex mempty, Left $ "cycles in module imports:" <+> pShow mname <+> pShow (fst <$> moduleImports e)))) im) ni
190 ms <- forM (moduleImports e) $ \(m, is) -> loadModule ex (Just fname) (Right $ sName m) <&> \r -> case r of 190 ms <- forM (moduleImports e) $ \(m, is) -> loadModule ex (Just fname) (Right $ sName m) <&> \r -> case r of
191 Left err -> Left $ sName m ++ " couldn't be found" 191 Left err -> Left $ pShow m <+> "is not found"
192 Right (fb, (src, dsge)) -> 192 Right (fb, (src, dsge)) ->
193 either (Left . const (sName m ++ " couldn't be parsed")) 193 either (Left . const (pShow m <+> "couldn't be parsed"))
194 (\(pm, x, e) -> either 194 (\(pm, x, e) -> either
195 (Left . const (sName m ++ " couldn't be typechecked")) 195 (Left . const (pShow m <+> "couldn't be typechecked"))
196 (\(ds, ge) -> Right (ds{-todo: filter-}, Map.filterWithKey (\k _ -> filterImports is k) ge)) 196 (\(ds, ge) -> Right (ds{-todo: filter-}, Map.filterWithKey (\k _ -> filterImports is k) ge))
197 e) 197 e)
198 dsge 198 dsge
199 199
200 let (res, err) = case sequence ms of 200 let (res, err) = case sequence ms of
201 Left err -> (ex mempty, Left err) 201 Left err -> (ex mempty, Left $ pShow err)
202 Right ms@(mconcat -> (ds, ge)) -> case runExcept $ runDefParser ds $ definitions e of 202 Right ms@(mconcat -> (ds, ge)) -> case runExcept $ runDefParser ds $ definitions e of
203 Left err -> (ex mempty, Left $ show err) 203 Left err -> (ex mempty, Left $ pShow err)
204 Right (defs, warnings, dsinfo) -> (,) (ex (map ParseWarning warnings ++ is, defs)) $ case res of 204 Right (defs, warnings, dsinfo) -> (,) (ex (map ParseWarning warnings ++ is, defs)) $ case res of
205 Left err -> Left (show err) 205 Left err -> Left $ pShow err
206 Right (mconcat -> newge) -> 206 Right (mconcat -> newge) ->
207 right mconcat $ forM (fromMaybe [ExportModule $ SIName mempty mname] $ moduleExports e) $ \case 207 right mconcat $ forM (fromMaybe [ExportModule $ SIName mempty mname] $ moduleExports e) $ \case
208 ExportId (sName -> d) -> case Map.lookup d newge of 208 ExportId (sName -> d) -> case Map.lookup d newge of
209 Just def -> Right (mempty{-TODO-}, Map.singleton d def) 209 Just def -> Right (mempty{-TODO-}, Map.singleton d def)
210 Nothing -> Left $ d ++ " is not defined" 210 Nothing -> Left $ text d <+> "is not defined"
211 ExportModule (sName -> m) | m == mname -> Right (dsinfo, newge) 211 ExportModule (sName -> m) | m == mname -> Right (dsinfo, newge)
212 ExportModule m -> case [ x | ((m', _), x) <- zip (moduleImports e) ms, m' == m] of 212 ExportModule m -> case [ x | ((m', _), x) <- zip (moduleImports e) ms, m' == m] of
213 [x] -> Right x 213 [x] -> Right x
214 [] -> Left $ "empty export list: " ++ show (fname, m, map fst $ moduleImports e, mname) 214 [] -> Left $ "empty export list in module" <+> text fname -- m, map fst $ moduleImports e, mname)
215 _ -> error "export list: internal error" 215 _ -> error "export list: internal error"
216 where 216 where
217 (res, is) = runWriter . flip runReaderT (extensions e, initEnv <> ge) . runExceptT $ inference defs 217 (res, is) = runWriter . flip runReaderT (extensions e, initEnv <> ge) . runExceptT $ inference defs
@@ -224,7 +224,7 @@ loadModule ex imp mname_ = do
224 filterImports (ImportJust ns) = (`elem` map sName ns) 224 filterImports (ImportJust ns) = (`elem` map sName ns)
225 225
226-- used in runTests 226-- used in runTests
227getDef :: MonadMask m => FilePath -> SName -> Maybe Exp -> MMT m Infos (Infos, Either String (FilePath, Either String (Exp, Exp))) 227getDef :: MonadMask m => FilePath -> SName -> Maybe Exp -> MMT m Infos (Infos, Either Doc (FilePath, Either Doc (Exp, Exp)))
228getDef = getDef_ fst 228getDef = getDef_ fst
229 229
230getDef_ ex m d ty = loadModule ex Nothing (Left m) <&> \case 230getDef_ ex m d ty = loadModule ex Nothing (Left m) <&> \case
@@ -236,37 +236,37 @@ getDef_ ex m d ty = loadModule ex Nothing (Left m) <&> \case
236 , case Map.lookup d ge of 236 , case Map.lookup d ge of
237 Just (e, thy, si) 237 Just (e, thy, si)
238 | Just False <- (== thy) <$> ty -- TODO: better type comparison 238 | Just False <- (== thy) <$> ty -- TODO: better type comparison
239 -> Left $ "type of " ++ d ++ " should be " ++ show ty ++ " instead of " ++ ppShow thy 239 -> Left $ "type of" <+> text d <+> "should be" <+> pShow ty <+> "instead of" <+> pShow thy
240 | otherwise -> Right (e, thy) 240 | otherwise -> Right (e, thy)
241 Nothing -> Left $ d ++ " is not found" 241 Nothing -> Left $ text d <+> "is not found"
242 ) 242 )
243 243
244compilePipeline' ex backend m 244compilePipeline' ex backend m
245 = second (either Left (fmap (compilePipeline backend) . snd)) <$> getDef_ ex m "main" (Just outputType) 245 = second (either Left (fmap (compilePipeline backend) . snd)) <$> getDef_ ex m "main" (Just outputType)
246 246
247-- | most commonly used interface for end users 247-- | most commonly used interface for end users
248compileMain :: [FilePath] -> IR.Backend -> MName -> IO (Either String IR.Pipeline) 248compileMain :: [FilePath] -> IR.Backend -> MName -> IO (Either Doc IR.Pipeline)
249compileMain path backend fname 249compileMain path backend fname
250 = fmap snd $ runMM (ioFetch path) $ compilePipeline' (const ()) backend fname 250 = fmap snd $ runMM (ioFetch path) $ compilePipeline' (const ()) backend fname
251 251
252parseModule :: [FilePath] -> MName -> IO (Either String String) 252parseModule :: [FilePath] -> MName -> IO (Either Doc String)
253parseModule path fname = runMM (ioFetch path) $ loadModule snd Nothing (Left fname) <&> \case 253parseModule path fname = runMM (ioFetch path) $ loadModule snd Nothing (Left fname) <&> \case
254 Left err -> Left err 254 Left err -> Left err
255 Right (fname, (src, Left err)) -> Left err 255 Right (fname, (src, Left err)) -> Left err
256 Right (fname, (src, Right (pm, infos, _))) -> Right $ pPrintStmts infos 256 Right (fname, (src, Right (pm, infos, _))) -> Right $ pPrintStmts infos
257 257
258-- used by the compiler-service of the online editor 258-- used by the compiler-service of the online editor
259preCompile :: (MonadMask m, MonadIO m) => [FilePath] -> [FilePath] -> Backend -> FilePath -> IO (String -> m (Either String IR.Pipeline, (Infos, String))) 259preCompile :: (MonadMask m, MonadIO m) => [FilePath] -> [FilePath] -> Backend -> FilePath -> IO (String -> m (Either Doc IR.Pipeline, (Infos, String)))
260preCompile paths paths' backend mod = do 260preCompile paths paths' backend mod = do
261 res <- runMM (ioFetch paths) $ loadModule ex Nothing $ Left mod 261 res <- runMM (ioFetch paths) $ loadModule ex Nothing $ Left mod
262 case res of 262 case res of
263 Left err -> error $ "Prelude could not compiled: " ++ err 263 Left err -> error $ "Prelude could not compiled:" ++ show err
264 Right (src, prelude) -> return compile 264 Right (src, prelude) -> return compile
265 where 265 where
266 compile src = runMM fetch $ do 266 compile src = runMM fetch $ do
267 let pname = "." </> "Prelude.lc" 267 let pname = "." </> "Prelude.lc"
268 modify $ \(Modules nm im ni) -> Modules (Map.insert pname ni nm) (IM.insert ni (pname, prelude) im) (ni+1) 268 modify $ \(Modules nm im ni) -> Modules (Map.insert pname ni nm) (IM.insert ni (pname, prelude) im) (ni+1)
269 ((left plainShow . snd) &&& fst) <$> compilePipeline' ex backend "Main" 269 (snd &&& fst) <$> compilePipeline' ex backend "Main"
270 where 270 where
271 fetch imp = \case 271 fetch imp = \case
272 Left "Prelude" -> return $ Right ("./Prelude.lc", "Prelude", undefined) 272 Left "Prelude" -> return $ Right ("./Prelude.lc", "Prelude", undefined)
diff --git a/src/LambdaCube/Compiler/DesugaredSource.hs b/src/LambdaCube/Compiler/DesugaredSource.hs
index c2317615..6fb1cbaa 100644
--- a/src/LambdaCube/Compiler/DesugaredSource.hs
+++ b/src/LambdaCube/Compiler/DesugaredSource.hs
@@ -136,9 +136,10 @@ instance PShow SI where
136 pShow (RangeSI r) = pShow r 136 pShow (RangeSI r) = pShow r
137 137
138-- long version 138-- long version
139-- TODO: merge with pShow
139showSI x = case sourceInfo x of 140showSI x = case sourceInfo x of
140 RangeSI r -> show $ showRange r 141 RangeSI r -> showRange r
141 x -> ppShow x 142 x -> pShow x
142 143
143hashPos :: FileInfo -> SPos -> Int 144hashPos :: FileInfo -> SPos -> Int
144hashPos fn (SPos r c) = fileId fn `shiftL` 32 .|. r `shiftL` 16 .|. c 145hashPos fn (SPos r c) = fileId fn `shiftL` 32 .|. r `shiftL` 16 .|. c
diff --git a/src/LambdaCube/Compiler/Infer.hs b/src/LambdaCube/Compiler/Infer.hs
index 74e0c4d6..e7c52d9a 100644
--- a/src/LambdaCube/Compiler/Infer.hs
+++ b/src/LambdaCube/Compiler/Infer.hs
@@ -1,3 +1,4 @@
1{-# LANGUAGE OverloadedStrings #-}
1{-# LANGUAGE LambdaCase #-} 2{-# LANGUAGE LambdaCase #-}
2{-# LANGUAGE ViewPatterns #-} 3{-# LANGUAGE ViewPatterns #-}
3{-# LANGUAGE PatternSynonyms #-} 4{-# LANGUAGE PatternSynonyms #-}
@@ -881,30 +882,31 @@ appTy t x = error $ "appTy: " ++ show t
881-------------------------------------------------------------------------------- error messages 882-------------------------------------------------------------------------------- error messages
882 883
883data ErrorMsg 884data ErrorMsg
884 = ErrorMsg String 885 = ErrorMsg Doc
885 | ECantFind SName SI 886 | ECantFind SName SI
886 | ETypeError String SI 887 | ETypeError Doc SI
887 | ERedefined SName SI SI 888 | ERedefined SName SI SI
888 889
889instance NFData ErrorMsg where 890instance NFData ErrorMsg where rnf = rnf . ppShow
891{-
890 rnf = \case 892 rnf = \case
891 ErrorMsg m -> rnf m 893 ErrorMsg m -> rnf m
892 ECantFind a b -> rnf (a, b) 894 ECantFind a b -> rnf (a, b)
893 ETypeError a b -> rnf (a, b) 895 ETypeError a b -> rnf (a, b)
894 ERedefined a b c -> rnf (a, b, c) 896 ERedefined a b c -> rnf (a, b, c)
895 897-}
896errorRange_ = \case 898errorRange_ = \case
897 ErrorMsg s -> [] 899 ErrorMsg s -> []
898 ECantFind s si -> [si] 900 ECantFind s si -> [si]
899 ETypeError msg si -> [si] 901 ETypeError msg si -> [si]
900 ERedefined s si si' -> [si, si'] 902 ERedefined s si si' -> [si, si']
901 903
902instance Show ErrorMsg where 904instance PShow ErrorMsg where
903 show = \case 905 pShow = \case
904 ErrorMsg s -> s 906 ErrorMsg s -> s
905 ECantFind s si -> "can't find: " ++ s ++ " in " ++ showSI si 907 ECantFind s si -> "can't find:" <+> text s <+> "in" <+> showSI si
906 ETypeError msg si -> "type error: " ++ msg ++ "\nin " ++ showSI si ++ "\n" 908 ETypeError msg si -> "type error:" <+> msg <$$> "in" <+> showSI si
907 ERedefined s si si' -> "already defined " ++ s ++ " at " ++ showSI si ++ "\n and at " ++ showSI si' 909 ERedefined s si si' -> "already defined" <+> text s <+> "at" <+> showSI si <$$> "and at" <+> showSI si'
908 910
909 911
910-------------------------------------------------------------------------------- inference 912-------------------------------------------------------------------------------- inference
@@ -1051,7 +1053,7 @@ inferN_ tellTrace = infer where
1051 EBind2_ si BMeta tt_ te 1053 EBind2_ si BMeta tt_ te
1052 | ELabelEnd te' <- te -> refocus (ELabelEnd $ EBind2_ si BMeta tt_ te') eet 1054 | ELabelEnd te' <- te -> refocus (ELabelEnd $ EBind2_ si BMeta tt_ te') eet
1053 | Unit <- tt -> refocus te $ subst 0 TT eet 1055 | Unit <- tt -> refocus te $ subst 0 TT eet
1054 | Empty msg <- tt -> throwError' $ ETypeError msg si 1056 | Empty msg <- tt -> throwError' $ ETypeError (text msg) si
1055 | T2 x y <- tt, let te' = EBind2_ si BMeta (up 1 y) $ EBind2_ si BMeta x te 1057 | T2 x y <- tt, let te' = EBind2_ si BMeta (up 1 y) $ EBind2_ si BMeta x te
1056 -> refocus te' $ subst 2 (t2C (Var 1) (Var 0)) $ up 2 eet 1058 -> refocus te' $ subst 2 (t2C (Var 1) (Var 0)) $ up 2 eet
1057 | CstrT t a b <- tt, Just r <- cst (a, t) b -> r 1059 | CstrT t a b <- tt, Just r <- cst (a, t) b -> r
@@ -1117,8 +1119,8 @@ inferN_ tellTrace = infer where
1117 1119
1118 EGlobal{} -> return eet 1120 EGlobal{} -> return eet
1119 _ -> case eet of 1121 _ -> case eet of
1120 MEnd x -> throwError' $ ErrorMsg $ "focus todo: " ++ ppShow x 1122 MEnd x -> throwError' $ ErrorMsg $ "focus todo:" <+> pShow x
1121 _ -> throwError' $ ErrorMsg $ "focus checkMetas: " ++ ppShow env ++ "\n" ++ ppShow (fst <$> eet) 1123 _ -> throwError' $ ErrorMsg $ "focus checkMetas:" <+> pShow env <$$> pShow (fst <$> eet)
1122 where 1124 where
1123 refocus_ :: (Env -> CEnv ExpType -> IM m ExpType') -> Env -> CEnv ExpType -> IM m ExpType' 1125 refocus_ :: (Env -> CEnv ExpType -> IM m ExpType') -> Env -> CEnv ExpType -> IM m ExpType'
1124 refocus_ _ e (MEnd at) = focus_ e at 1126 refocus_ _ e (MEnd at) = focus_ e at
@@ -1255,12 +1257,13 @@ initEnv = Map.fromList
1255 1257
1256data Info 1258data Info
1257 = Info Range String 1259 = Info Range String
1258 | IType String String 1260 | IType SIName Exp
1259 | ITrace String String 1261 | ITrace String String
1260 | IError ErrorMsg 1262 | IError ErrorMsg
1261 | ParseWarning ParseWarning 1263 | ParseWarning ParseWarning
1262 1264
1263instance NFData Info 1265instance NFData Info where rnf = rnf . ppShow
1266{-
1264 where 1267 where
1265 rnf = \case 1268 rnf = \case
1266 Info r s -> rnf (r, s) 1269 Info r s -> rnf (r, s)
@@ -1268,14 +1271,14 @@ instance NFData Info
1268 ITrace i s -> rnf (i, s) 1271 ITrace i s -> rnf (i, s)
1269 IError x -> rnf x 1272 IError x -> rnf x
1270 ParseWarning w -> rnf w 1273 ParseWarning w -> rnf w
1271 1274-}
1272instance Show Info where 1275instance PShow Info where
1273 show = \case 1276 pShow = \case
1274 Info r s -> ppShow r ++ " " ++ s 1277 Info r s -> pShow r <+> "" <+> text s
1275 IType a b -> a ++ " :: " ++ b 1278 IType a b -> shAnn False (pShow a) (pShow b)
1276 ITrace i s -> i ++ ": " ++ s 1279 ITrace i s -> text i <> ": " <+> text s
1277 IError e -> "!" ++ show e 1280 IError e -> "!" <> pShow e
1278 ParseWarning w -> show w 1281 ParseWarning w -> pShow w
1279 1282
1280errorRange is = [r | IError e <- is, RangeSI r <- errorRange_ e ] 1283errorRange is = [r | IError e <- is, RangeSI r <- errorRange_ e ]
1281 1284
@@ -1288,12 +1291,12 @@ mkInfoItem _ _ = mempty
1288 1291
1289listAllInfos m = h "trace" (listTraceInfos m) 1292listAllInfos m = h "trace" (listTraceInfos m)
1290 ++ h "tooltips" [ ppShow r ++ " " ++ intercalate " | " is | (r, is) <- listTypeInfos m ] 1293 ++ h "tooltips" [ ppShow r ++ " " ++ intercalate " | " is | (r, is) <- listTypeInfos m ]
1291 ++ h "warnings" [ show w | ParseWarning w <- m ] 1294 ++ h "warnings" [ ppShow w | ParseWarning w <- m ]
1292 where 1295 where
1293 h x [] = [] 1296 h x [] = []
1294 h x xs = ("------------ " ++ x) : xs 1297 h x xs = ("------------ " ++ x) : xs
1295 1298
1296listTraceInfos m = [show i | i <- m, case i of Info{} -> False; ParseWarning{} -> False; _ -> True] 1299listTraceInfos m = [ppShow i | i <- m, case i of Info{} -> False; ParseWarning{} -> False; _ -> True]
1297listTypeInfos m = map (second Set.toList) $ Map.toList $ Map.unionsWith (<>) [Map.singleton r $ Set.singleton i | Info r i <- m] 1300listTypeInfos m = map (second Set.toList) $ Map.toList $ Map.unionsWith (<>) [Map.singleton r $ Set.singleton i | Info r i <- m]
1298 1301
1299-------------------------------------------------------------------------------- inference for statements 1302-------------------------------------------------------------------------------- inference for statements
@@ -1428,10 +1431,10 @@ inferType :: Monad m => SExp2 -> IM m Type
1428inferType t = fmap (closedExp . fst . recheck "inferType" EGlobal . flip (,) TType . replaceMetas (Pi Hidden) . fmap fst) $ inferN (CheckType_ (debugSI "inferType CheckType_") TType EGlobal) t 1431inferType t = fmap (closedExp . fst . recheck "inferType" EGlobal . flip (,) TType . replaceMetas (Pi Hidden) . fmap fst) $ inferN (CheckType_ (debugSI "inferType CheckType_") TType EGlobal) t
1429 1432
1430addToEnv :: Monad m => SIName -> ExpType -> IM m GlobalEnv 1433addToEnv :: Monad m => SIName -> ExpType -> IM m GlobalEnv
1431addToEnv (SIName si s) (x, t) = do 1434addToEnv sn@(SIName si s) (x, t) = do
1432-- maybe (pure ()) throwError_ $ ambiguityCheck s t -- TODO 1435-- maybe (pure ()) throwError_ $ ambiguityCheck s t -- TODO
1433-- b <- asks $ (TraceTypeCheck `elem`) . fst 1436-- b <- asks $ (TraceTypeCheck `elem`) . fst
1434 tell [IType s $ ppShow t] 1437 tell [IType sn t]
1435 v <- asks $ Map.lookup s . snd 1438 v <- asks $ Map.lookup s . snd
1436 case v of 1439 case v of
1437 Nothing -> return $ Map.singleton s (closedExp x, closedExp t, si) 1440 Nothing -> return $ Map.singleton s (closedExp x, closedExp t, si)
diff --git a/src/LambdaCube/Compiler/Parser.hs b/src/LambdaCube/Compiler/Parser.hs
index ce830f2a..a4dfa229 100644
--- a/src/LambdaCube/Compiler/Parser.hs
+++ b/src/LambdaCube/Compiler/Parser.hs
@@ -67,24 +67,21 @@ instance NFData ParseWarning
67 Unreachable r -> rnf r 67 Unreachable r -> rnf r
68 Uncovered si r -> rnf si -- TODO --rnf r 68 Uncovered si r -> rnf si -- TODO --rnf r
69 69
70instance Show LCParseError where 70instance PShow LCParseError where
71 show = \case 71 pShow = \case
72 MultiplePatternVars xs -> unlines $ "multiple pattern vars:": 72 MultiplePatternVars xs -> vcat $ "multiple pattern vars:":
73 concat [(sName (head ns) ++ " is defined at"): map showSI ns | ns <- xs] 73 concat [(pShow (head ns) <+> "is defined at"): map showSI ns | ns <- xs]
74 OperatorMismatch op op' -> "Operator precedences don't match:\n" ++ show (fromJust $ getFixity_ op) ++ " at " ++ showSI op ++ "\n" ++ show (fromJust $ getFixity_ op') ++ " at " ++ showSI op' 74 OperatorMismatch op op' -> "Operator precedences don't match:" <$$> pShow (fromJust $ getFixity_ op) <+> "at" <+> showSI op <$$> pShow (fromJust $ getFixity_ op') <+> "at" <+> showSI op'
75 UndefinedConstructor n -> "Constructor " ++ show n ++ " is not defined at " ++ showSI n 75 UndefinedConstructor n -> "Constructor" <+> pShow n <+> "is not defined at" <+> showSI n
76 ParseError p -> show p 76 ParseError p -> text $ show p
77 77
78instance Show ParseWarning where 78instance PShow ParseWarning where
79 show = \case 79 pShow = \case
80 Unreachable si -> "Source code is not reachable: " ++ show (showRange si) 80 Unreachable si -> "Source code is not reachable:" <+> showRange si
81 Uncovered si pss -> "Uncovered pattern(s) at " ++ showSI si ++ "\nMissing case(s):\n" ++ 81 Uncovered si pss -> "Uncovered pattern(s) at" <+> showSI si <$$> "Missing case(s):" <$$>
82 unlines [" " ++ unwords (map ppShow ps) ++ 82 vcat [" " <> hsep (map pShow ps) <+>
83 " | " +++ intercalate ", " [ppShow p ++ " <- " ++ ppShow e | (p, e) <- gs] 83 hsep [se <+> pShow p <+> "<-" <+> pShow e | (se, (p, e)) <- zip ("|": repeat ",") gs]
84 | (ps, gs) <- pss] 84 | (ps, gs) <- pss]
85 where
86 s +++ "" = ""
87 s +++ s' = s ++ s'
88 85
89trackSI p = do 86trackSI p = do
90 x <- p 87 x <- p
diff --git a/src/LambdaCube/Compiler/Pretty.hs b/src/LambdaCube/Compiler/Pretty.hs
index a8fdf851..42e06ad3 100644
--- a/src/LambdaCube/Compiler/Pretty.hs
+++ b/src/LambdaCube/Compiler/Pretty.hs
@@ -17,6 +17,7 @@ import Data.String
17--import qualified Data.Map as Map 17--import qualified Data.Map as Map
18import Control.Monad.Reader 18import Control.Monad.Reader
19import Control.Monad.State 19import Control.Monad.State
20import Control.DeepSeq
20--import Debug.Trace 21--import Debug.Trace
21 22
22import qualified Text.PrettyPrint.ANSI.Leijen as P 23import qualified Text.PrettyPrint.ANSI.Leijen as P
@@ -66,6 +67,12 @@ data Fixity
66 | InfixR !Int 67 | InfixR !Int
67 deriving (Eq, Show) 68 deriving (Eq, Show)
68 69
70instance PShow Fixity where
71 pShow = \case
72 Infix i -> "infix" `DApp` pShow i
73 InfixL i -> "infixl" `DApp` pShow i
74 InfixR i -> "infixr" `DApp` pShow i
75
69precedence, leftPrecedence, rightPrecedence :: Fixity -> Int 76precedence, leftPrecedence, rightPrecedence :: Fixity -> Int
70 77
71precedence = \case 78precedence = \case
@@ -107,6 +114,9 @@ instance Monoid Doc where
107 mempty = text "" 114 mempty = text ""
108 a `mappend` b = DDoc $ DOHCat a b 115 a `mappend` b = DDoc $ DOHCat a b
109 116
117instance NFData Doc where
118 rnf x = rnf $ show x -- TODO
119
110pattern DColor c a = DDoc (DOColor c a) 120pattern DColor c a = DDoc (DOColor c a)
111 121
112strip :: Doc -> Doc 122strip :: Doc -> Doc
diff --git a/test/runTests.hs b/test/runTests.hs
index a0edf147..77ed43ea 100644
--- a/test/runTests.hs
+++ b/test/runTests.hs
@@ -204,15 +204,15 @@ doTest Config{..} (i, fn) = do
204 Right (fname, x@Right{}) -> Right (fname, x) <$ removeFromCache fname 204 Right (fname, x@Right{}) -> Right (fname, x) <$ removeFromCache fname
205 205
206 f (i, e) | not $ isReject fn = case e of 206 f (i, e) | not $ isReject fn = case e of
207 Left e -> Left (unlines $ tab "!Failed" e: listTraceInfos i, Failed) 207 Left (show -> e) -> Left (unlines $ tab "!Failed" e: listTraceInfos i, Failed)
208 Right (fname, Left e) -> Right ("typechecked module" , unlines $ e: listAllInfos i) 208 Right (fname, Left (show -> e)) -> Right ("typechecked module" , unlines $ e: listAllInfos i)
209 Right (fname, Right (e, te)) 209 Right (fname, Right (e, te))
210 | te == outputType -> Right ("compiled pipeline", prettyShowUnlines $ compilePipeline OpenGL33 (e, te)) 210 | te == outputType -> Right ("compiled pipeline", prettyShowUnlines $ compilePipeline OpenGL33 (e, te))
211 | e == trueExp -> Right ("reducted main", ppShow $ unfixlabel e) 211 | e == trueExp -> Right ("reducted main", ppShow $ unfixlabel e)
212 | te == boolType -> Left (tab "!Failed" $ "main should be True but it is \n" ++ ppShow e, Failed) 212 | te == boolType -> Left (tab "!Failed" $ "main should be True but it is \n" ++ ppShow e, Failed)
213 | otherwise -> Right ("reduced main " ++ ppShow te, ppShow e) 213 | otherwise -> Right ("reduced main " ++ ppShow te, ppShow e)
214 | otherwise = case e of 214 | otherwise = case e of
215 Left e -> Right ("error message", unlines $ e: listAllInfos i) 215 Left (show -> e) -> Right ("error message", unlines $ e: listAllInfos i)
216 Right _ -> Left (tab "!Failed" "failed to catch error", Failed) 216 Right _ -> Left (tab "!Failed" "failed to catch error", Failed)
217 217
218 tab msg 218 tab msg
diff --git a/testdata/Builtins.out b/testdata/Builtins.out
index e5e3cf55..31c370e3 100644
--- a/testdata/Builtins.out
+++ b/testdata/Builtins.out
@@ -2983,8 +2983,7 @@ Uncovered pattern(s) at testdata/Builtins.lc:201:1:
2983head (x: _) = x 2983head (x: _) = x
2984^^^^ 2984^^^^
2985Missing case(s): 2985Missing case(s):
2986 Nil 2986 Nil
2987
2988Uncovered pattern(s) at testdata/Builtins.lc:340:1: 2987Uncovered pattern(s) at testdata/Builtins.lc:340:1:
2989swizzscalar (V2 x y) Sx = x 2988swizzscalar (V2 x y) Sx = x
2990swizzscalar (V2 x y) Sy = y 2989swizzscalar (V2 x y) Sy = y
@@ -2996,13 +2995,11 @@ swizzscalar (V4 x y z w) Sy = y
2996swizzscalar (V4 x y z w) Sz = z 2995swizzscalar (V4 x y z w) Sz = z
2997swizzscalar (V4 x y z w) Sw = w 2996swizzscalar (V4 x y z w) Sw = w
2998Missing case(s): 2997Missing case(s):
2999 V2 Sz 2998 V2 Sz
3000 V2 Sw 2999 V2 Sw
3001 V3 Sw 3000 V3 Sw
3002
3003Uncovered pattern(s) at testdata/Builtins.lc:357:1: 3001Uncovered pattern(s) at testdata/Builtins.lc:357:1:
3004swizzvector v w | definedVec v = mapVec (swizzscalar v) w 3002swizzvector v w | definedVec v = mapVec (swizzscalar v) w
3005^^^^^^^^^^^ 3003^^^^^^^^^^^
3006Missing case(s): 3004Missing case(s):
3007 _ _ | False <- definedVec _b 3005 _ _ | False <- definedVec _b
3008
diff --git a/testdata/Prelude.out b/testdata/Prelude.out
index 7299d40d..23dd4a4a 100644
--- a/testdata/Prelude.out
+++ b/testdata/Prelude.out
@@ -1594,23 +1594,19 @@ Uncovered pattern(s) at testdata/Prelude.lc:50:1:
1594tail (_: xs) = xs 1594tail (_: xs) = xs
1595^^^^ 1595^^^^
1596Missing case(s): 1596Missing case(s):
1597 Nil 1597 Nil
1598
1599Uncovered pattern(s) at testdata/Prelude.lc:58:1: 1598Uncovered pattern(s) at testdata/Prelude.lc:58:1:
1600foldr1 f (x: xs) = foldr f x xs 1599foldr1 f (x: xs) = foldr f x xs
1601^^^^^^ 1600^^^^^^
1602Missing case(s): 1601Missing case(s):
1603 _ Nil 1602 _ Nil
1604
1605Uncovered pattern(s) at testdata/Prelude.lc:137:1: 1603Uncovered pattern(s) at testdata/Prelude.lc:137:1:
1606project @a @('RecItem s' a': xs) s @_ (RecordCons ts) | s == s' = fstTup (unsafeCoerce @_ @(HList '(a : map recItemType xs)) ts) 1604project @a @('RecItem s' a': xs) s @_ (RecordCons ts) | s == s' = fstTup (unsafeCoerce @_ @(HList '(a : map recItemType xs)) ts)
1607project @a @('RecItem s' a': xs) s @_ (RecordCons ts) = project @a @xs s @(undefined @(isKeyC s a xs)) (RecordCons (sndTup (unsafeCoerce @_ @(HList '(a : map recItemType xs)) ts))) 1605project @a @('RecItem s' a': xs) s @_ (RecordCons ts) = project @a @xs s @(undefined @(isKeyC s a xs)) (RecordCons (sndTup (unsafeCoerce @_ @(HList '(a : map recItemType xs)) ts)))
1608Missing case(s): 1606Missing case(s):
1609 _ Nil _ _ _ 1607 _ Nil _ _ _
1610
1611Uncovered pattern(s) at testdata/Prelude.lc:388:10: 1608Uncovered pattern(s) at testdata/Prelude.lc:388:10:
1612(x : _) !! 0 = x 1609(x : _) !! 0 = x
1613(_ : xs) !! n = xs !! (n-1) 1610(_ : xs) !! n = xs !! (n-1)
1614Missing case(s): 1611Missing case(s):
1615 Nil _ 1612 Nil _
1616
diff --git a/testdata/adhoc.reject.out b/testdata/adhoc.reject.out
index f9fa8c49..511e62b1 100644
--- a/testdata/adhoc.reject.out
+++ b/testdata/adhoc.reject.out
@@ -2,7 +2,6 @@ type error: no instance of 'Component on ???
2in testdata/adhoc.reject.lc:4:5: 2in testdata/adhoc.reject.lc:4:5:
3x = one :: Vec 4 A 3x = one :: Vec 4 A
4 ^^^ 4 ^^^
5
6------------ trace 5------------ trace
7'A :: Type 6'A :: Type
8A :: 'A 7A :: 'A
@@ -12,7 +11,6 @@ match'A :: (a :: Type -> Type) -> a 'A[0
12in testdata/adhoc.reject.lc:4:5: 11in testdata/adhoc.reject.lc:4:5:
13x = one :: Vec 4 A 12x = one :: Vec 4 A
14 ^^^ 13 ^^^
15
16------------ tooltips 14------------ tooltips
17testdata/adhoc.reject.lc 2:6-2:7 Type 15testdata/adhoc.reject.lc 2:6-2:7 Type
18testdata/adhoc.reject.lc 2:6-2:11 Type 16testdata/adhoc.reject.lc 2:6-2:11 Type
diff --git a/testdata/complex.out b/testdata/complex.out
index c7a8df09..43a60b85 100644
--- a/testdata/complex.out
+++ b/testdata/complex.out
@@ -383,13 +383,11 @@ Uncovered pattern(s) at testdata/complex.lc:114:1:
383add @'Normal @'Normal (Complex a b) (Complex c d) = Complex (a + c) (b + d) 383add @'Normal @'Normal (Complex a b) (Complex c d) = Complex (a + c) (b + d)
384^^^ 384^^^
385Missing case(s): 385Missing case(s):
386 Normal Polar _ _ 386 Normal Polar _ _
387 Polar _ _ _ 387 Polar _ _ _
388
389Uncovered pattern(s) at testdata/complex.lc:129:1: 388Uncovered pattern(s) at testdata/complex.lc:129:1:
390mul @'Normal @'Normal (Complex a b) (Complex c d) = Complex (a*c - b*d) (b*c + a*d) 389mul @'Normal @'Normal (Complex a b) (Complex c d) = Complex (a*c - b*d) (b*c + a*d)
391^^^ 390^^^
392Missing case(s): 391Missing case(s):
393 Normal Polar _ _ 392 Normal Polar _ _
394 Polar _ _ _ 393 Polar _ _ _
395
diff --git a/testdata/data.out b/testdata/data.out
index 3d54c617..ac7874a8 100644
--- a/testdata/data.out
+++ b/testdata/data.out
@@ -87,34 +87,29 @@ Uncovered pattern(s) at testdata/data.lc:6:23:
87 | Data22 { x :: Int, y::Int } 87 | Data22 { x :: Int, y::Int }
88 ^ 88 ^
89Missing case(s): 89Missing case(s):
90 Data21 90 Data21
91 Data24 91 Data24
92
93Uncovered pattern(s) at testdata/data.lc:6:33: 92Uncovered pattern(s) at testdata/data.lc:6:33:
94 | Data22 { x :: Int, y::Int } 93 | Data22 { x :: Int, y::Int }
95 ^ 94 ^
96Missing case(s): 95Missing case(s):
97 Data21 96 Data21
98 Data23 97 Data23
99 Data24 98 Data24
100
101Uncovered pattern(s) at testdata/data.lc:10:32: 99Uncovered pattern(s) at testdata/data.lc:10:32:
102data Data5 a5 b5 c5 = Data51 { a5::a5} 100data Data5 a5 b5 c5 = Data51 { a5::a5}
103 ^^ 101 ^^
104Missing case(s): 102Missing case(s):
105 Data53 103 Data53
106
107Uncovered pattern(s) at testdata/data.lc:11:40: 104Uncovered pattern(s) at testdata/data.lc:11:40:
108 | Data52 { a5::a5, b5::b5, c5::c5 } 105 | Data52 { a5::a5, b5::b5, c5::c5 }
109 ^^ 106 ^^
110Missing case(s): 107Missing case(s):
111 Data51 108 Data51
112 Data53 109 Data53
113
114Uncovered pattern(s) at testdata/data.lc:11:48: 110Uncovered pattern(s) at testdata/data.lc:11:48:
115 | Data52 { a5::a5, b5::b5, c5::c5 } 111 | Data52 { a5::a5, b5::b5, c5::c5 }
116 ^^ 112 ^^
117Missing case(s): 113Missing case(s):
118 Data51 114 Data51
119 Data53 115 Data53
120
diff --git a/testdata/framebuffer02.reject.out b/testdata/framebuffer02.reject.out
index 9ae2b9aa..f9650704 100644
--- a/testdata/framebuffer02.reject.out
+++ b/testdata/framebuffer02.reject.out
@@ -8,7 +8,6 @@ in testdata/framebuffer02.reject.lc:2:17:
8 ,ColorImage @2 (V4 1.0 1.0 1.0 1.0) 8 ,ColorImage @2 (V4 1.0 1.0 1.0 1.0)
9 ,colorImage1 1.0 9 ,colorImage1 1.0
10 ) 10 )
11
12------------ trace 11------------ trace
13!type error: can not unify 12!type error: can not unify
140 130
@@ -20,7 +19,6 @@ in testdata/framebuffer02.reject.lc:2:17:
20 ,ColorImage @2 (V4 1.0 1.0 1.0 1.0) 19 ,ColorImage @2 (V4 1.0 1.0 1.0 1.0)
21 ,colorImage1 1.0 20 ,colorImage1 1.0
22 ) 21 )
23
24------------ tooltips 22------------ tooltips
25testdata/framebuffer02.reject.lc 2:17-2:28 forall (a :: List Type) . 'sameLayerCounts a => HList a -> FrameBuffer (ImageLC ('head Type a)) ('map Type ImageKind GetImageKind a) 23testdata/framebuffer02.reject.lc 2:17-2:28 forall (a :: List Type) . 'sameLayerCounts a => HList a -> FrameBuffer (ImageLC ('head Type a)) ('map Type ImageKind GetImageKind a)
26testdata/framebuffer02.reject.lc 2:17-5:30 FrameBuffer 1 ('map Type ImageKind GetImageKind ('Cons (Image 1 ('Color (VecScalar 4 Float))) ('Cons (Image 2 ('Color (VecScalar 4 Float))) ('Cons (Image 1 ('Color (VecScalar 1 Float))) 'Nil)))) 24testdata/framebuffer02.reject.lc 2:17-5:30 FrameBuffer 1 ('map Type ImageKind GetImageKind ('Cons (Image 1 ('Color (VecScalar 4 Float))) ('Cons (Image 2 ('Color (VecScalar 4 Float))) ('Cons (Image 1 ('Color (VecScalar 1 Float))) 'Nil))))
diff --git a/testdata/language-features/adt/adt02.reject.out b/testdata/language-features/adt/adt02.reject.out
index 34674b0a..44db093f 100644
--- a/testdata/language-features/adt/adt02.reject.out
+++ b/testdata/language-features/adt/adt02.reject.out
@@ -4,7 +4,6 @@ with
4'Int 4'Int
5 5
6in proj 6in proj
7
8------------ trace 7------------ trace
9'Data3 :: Type 8'Data3 :: Type
10Data3 :: 'Bool -> 'Char -> 'Bool -> 'Data3 9Data3 :: 'Bool -> 'Char -> 'Bool -> 'Data3
@@ -17,7 +16,6 @@ with
17'Int 16'Int
18 17
19in proj 18in proj
20
21------------ tooltips 19------------ tooltips
22testdata/language-features/adt/adt02.reject.lc 2:6-2:11 Type 20testdata/language-features/adt/adt02.reject.lc 2:6-2:11 Type
23testdata/language-features/adt/adt02.reject.lc 2:6-5:25 Type 21testdata/language-features/adt/adt02.reject.lc 2:6-5:25 Type
diff --git a/testdata/language-features/adt/gadt04.reject.out b/testdata/language-features/adt/gadt04.reject.out
index 425f7213..fc2b7c30 100644
--- a/testdata/language-features/adt/gadt04.reject.out
+++ b/testdata/language-features/adt/gadt04.reject.out
@@ -1,7 +1,7 @@
1already defined Value at testdata/language-features/adt/gadt04.reject.lc:6:3: 1already defined Value at testdata/language-features/adt/gadt04.reject.lc:6:3:
2 Value :: a -> forall m . M2 a m 2 Value :: a -> forall m . M2 a m
3 ^^^^^ 3 ^^^^^
4 and at testdata/language-features/adt/gadt04.reject.lc:3:3: 4and at testdata/language-features/adt/gadt04.reject.lc:3:3:
5 Value :: a -> forall m . M a m 5 Value :: a -> forall m . M a m
6 ^^^^^ 6 ^^^^^
7------------ trace 7------------ trace
@@ -14,7 +14,7 @@ Value :: forall a . a -> forall (b :: 'String) . 'M2 a[0;
14!already defined Value at testdata/language-features/adt/gadt04.reject.lc:6:3: 14!already defined Value at testdata/language-features/adt/gadt04.reject.lc:6:3:
15 Value :: a -> forall m . M2 a m 15 Value :: a -> forall m . M2 a m
16 ^^^^^ 16 ^^^^^
17 and at testdata/language-features/adt/gadt04.reject.lc:3:3: 17and at testdata/language-features/adt/gadt04.reject.lc:3:3:
18 Value :: a -> forall m . M a m 18 Value :: a -> forall m . M a m
19 ^^^^^ 19 ^^^^^
20------------ tooltips 20------------ tooltips
diff --git a/testdata/language-features/as-pattern/as-pattern02.reject.out b/testdata/language-features/as-pattern/as-pattern02.reject.out
index cca9bd79..9e6ac4ce 100644
--- a/testdata/language-features/as-pattern/as-pattern02.reject.out
+++ b/testdata/language-features/as-pattern/as-pattern02.reject.out
@@ -6,4 +6,3 @@ f x@[x:xs] = x:xs
6testdata/language-features/as-pattern/as-pattern02.reject.lc:2:6: 6testdata/language-features/as-pattern/as-pattern02.reject.lc:2:6:
7f x@[x:xs] = x:xs 7f x@[x:xs] = x:xs
8 ^ 8 ^
9
diff --git a/testdata/language-features/basic-list/list07.reject.out b/testdata/language-features/basic-list/list07.reject.out
index 01bf6d20..27c8a2e3 100644
--- a/testdata/language-features/basic-list/list07.reject.out
+++ b/testdata/language-features/basic-list/list07.reject.out
@@ -4,7 +4,6 @@ with
4'Char 4'Char
5 5
6in builtin Nil 6in builtin Nil
7
8------------ trace 7------------ trace
9!type error: can not unify 8!type error: can not unify
10'Float 9'Float
@@ -12,7 +11,6 @@ with
12'Char 11'Char
13 12
14in builtin Nil 13in builtin Nil
15
16------------ tooltips 14------------ tooltips
17testdata/language-features/basic-list/list07.reject.lc 1:10-1:11 _b 15testdata/language-features/basic-list/list07.reject.lc 1:10-1:11 _b
18testdata/language-features/basic-list/list07.reject.lc 1:12-1:15 Float 16testdata/language-features/basic-list/list07.reject.lc 1:12-1:15 Float
diff --git a/testdata/language-features/basic-list/list10.reject.out b/testdata/language-features/basic-list/list10.reject.out
index 0855f067..186dc9c6 100644
--- a/testdata/language-features/basic-list/list10.reject.out
+++ b/testdata/language-features/basic-list/list10.reject.out
@@ -4,7 +4,6 @@ with
4'Float 4'Float
5 5
6in builtin Nil 6in builtin Nil
7
8------------ trace 7------------ trace
9!type error: can not unify 8!type error: can not unify
10'Int 9'Int
@@ -12,7 +11,6 @@ with
12'Float 11'Float
13 12
14in builtin Nil 13in builtin Nil
15
16------------ tooltips 14------------ tooltips
17testdata/language-features/basic-list/list10.reject.lc 1:10-1:11 _b 15testdata/language-features/basic-list/list10.reject.lc 1:10-1:11 _b
18testdata/language-features/basic-list/list10.reject.lc 1:12-1:15 Float 16testdata/language-features/basic-list/list10.reject.lc 1:12-1:15 Float
diff --git a/testdata/language-features/basic-list/list14.reject.out b/testdata/language-features/basic-list/list14.reject.out
index bfd60997..c8abf9be 100644
--- a/testdata/language-features/basic-list/list14.reject.out
+++ b/testdata/language-features/basic-list/list14.reject.out
@@ -6,7 +6,6 @@ with
6in testdata/language-features/basic-list/list14.reject.lc:1:17: 6in testdata/language-features/basic-list/list14.reject.lc:1:17:
7value = 'h':'i':() 7value = 'h':'i':()
8 ^^ 8 ^^
9
10------------ trace 9------------ trace
11!type error: can not unify 10!type error: can not unify
12'List 'Char 11'List 'Char
@@ -16,7 +15,6 @@ with
16in testdata/language-features/basic-list/list14.reject.lc:1:17: 15in testdata/language-features/basic-list/list14.reject.lc:1:17:
17value = 'h':'i':() 16value = 'h':'i':()
18 ^^ 17 ^^
19
20------------ tooltips 18------------ tooltips
21testdata/language-features/basic-list/list14.reject.lc 1:9-1:12 Char 19testdata/language-features/basic-list/list14.reject.lc 1:9-1:12 Char
22testdata/language-features/basic-list/list14.reject.lc 1:9-1:13 List Char -> List Char 20testdata/language-features/basic-list/list14.reject.lc 1:9-1:13 List Char -> List Char
diff --git a/testdata/language-features/basic-list/list15.reject.out b/testdata/language-features/basic-list/list15.reject.out
index 081eabad..96a8907d 100644
--- a/testdata/language-features/basic-list/list15.reject.out
+++ b/testdata/language-features/basic-list/list15.reject.out
@@ -6,7 +6,6 @@ with
6in testdata/language-features/basic-list/list15.reject.lc:1:20: 6in testdata/language-features/basic-list/list15.reject.lc:1:20:
7value = 'h':'i':():[] 7value = 'h':'i':():[]
8 ^^ 8 ^^
9
10------------ trace 9------------ trace
11!type error: can not unify 10!type error: can not unify
12'Char 11'Char
@@ -16,7 +15,6 @@ with
16in testdata/language-features/basic-list/list15.reject.lc:1:20: 15in testdata/language-features/basic-list/list15.reject.lc:1:20:
17value = 'h':'i':():[] 16value = 'h':'i':():[]
18 ^^ 17 ^^
19
20------------ tooltips 18------------ tooltips
21testdata/language-features/basic-list/list15.reject.lc 1:9-1:12 Char 19testdata/language-features/basic-list/list15.reject.lc 1:9-1:12 Char
22testdata/language-features/basic-list/list15.reject.lc 1:9-1:13 List Char -> List Char 20testdata/language-features/basic-list/list15.reject.lc 1:9-1:13 List Char -> List Char
diff --git a/testdata/language-features/basic-list/list16.reject.out b/testdata/language-features/basic-list/list16.reject.out
index 4f8d50a1..e109192d 100644
--- a/testdata/language-features/basic-list/list16.reject.out
+++ b/testdata/language-features/basic-list/list16.reject.out
@@ -6,7 +6,6 @@ with
6in testdata/language-features/basic-list/list16.reject.lc:1:13: 6in testdata/language-features/basic-list/list16.reject.lc:1:13:
7value = 'h':'i' 7value = 'h':'i'
8 ^^^ 8 ^^^
9
10------------ trace 9------------ trace
11!type error: can not unify 10!type error: can not unify
12'List 'Char 11'List 'Char
@@ -16,7 +15,6 @@ with
16in testdata/language-features/basic-list/list16.reject.lc:1:13: 15in testdata/language-features/basic-list/list16.reject.lc:1:13:
17value = 'h':'i' 16value = 'h':'i'
18 ^^^ 17 ^^^
19
20------------ tooltips 18------------ tooltips
21testdata/language-features/basic-list/list16.reject.lc 1:9-1:12 Char 19testdata/language-features/basic-list/list16.reject.lc 1:9-1:12 Char
22testdata/language-features/basic-list/list16.reject.lc 1:9-1:13 List Char -> List Char 20testdata/language-features/basic-list/list16.reject.lc 1:9-1:13 List Char -> List Char
diff --git a/testdata/language-features/basic-list/listcomp08.reject.out b/testdata/language-features/basic-list/listcomp08.reject.out
index 35f2448e..3a989de0 100644
--- a/testdata/language-features/basic-list/listcomp08.reject.out
+++ b/testdata/language-features/basic-list/listcomp08.reject.out
@@ -6,7 +6,6 @@ with
6in testdata/language-features/basic-list/listcomp08.reject.lc:1:23: 6in testdata/language-features/basic-list/listcomp08.reject.lc:1:23:
7value = [x | x <- [], "not Bool"] 7value = [x | x <- [], "not Bool"]
8 ^^^^^^^^^^ 8 ^^^^^^^^^^
9
10------------ trace 9------------ trace
11!type error: can not unify 10!type error: can not unify
12'Bool 11'Bool
@@ -16,7 +15,6 @@ with
16in testdata/language-features/basic-list/listcomp08.reject.lc:1:23: 15in testdata/language-features/basic-list/listcomp08.reject.lc:1:23:
17value = [x | x <- [], "not Bool"] 16value = [x | x <- [], "not Bool"]
18 ^^^^^^^^^^ 17 ^^^^^^^^^^
19
20------------ tooltips 18------------ tooltips
21testdata/language-features/basic-list/listcomp08.reject.lc 1:10-1:33 _b -> List _a 19testdata/language-features/basic-list/listcomp08.reject.lc 1:10-1:33 _b -> List _a
22testdata/language-features/basic-list/listcomp08.reject.lc 1:23-1:33 String 20testdata/language-features/basic-list/listcomp08.reject.lc 1:23-1:33 String
diff --git a/testdata/language-features/basic-values/case03.reject.out b/testdata/language-features/basic-values/case03.reject.out
index 314fa80e..a964eb15 100644
--- a/testdata/language-features/basic-values/case03.reject.out
+++ b/testdata/language-features/basic-values/case03.reject.out
@@ -3,14 +3,12 @@ in testdata/language-features/basic-values/case03.reject.lc:1:10:
3value1 = case () of 3value1 = case () of
4 1 -> () 4 1 -> ()
5 _ -> () 5 _ -> ()
6
7------------ trace 6------------ trace
8!type error: no instance of 'Num on ??? 7!type error: no instance of 'Num on ???
9in testdata/language-features/basic-values/case03.reject.lc:1:10: 8in testdata/language-features/basic-values/case03.reject.lc:1:10:
10value1 = case () of 9value1 = case () of
11 1 -> () 10 1 -> ()
12 _ -> () 11 _ -> ()
13
14------------ tooltips 12------------ tooltips
15testdata/language-features/basic-values/case03.reject.lc 1:10-3:10 () 13testdata/language-features/basic-values/case03.reject.lc 1:10-3:10 ()
16testdata/language-features/basic-values/case03.reject.lc 1:15-1:17 () 14testdata/language-features/basic-values/case03.reject.lc 1:15-1:17 ()
diff --git a/testdata/language-features/basic-values/case04.reject.out b/testdata/language-features/basic-values/case04.reject.out
index 7bb41248..ff2abacc 100644
--- a/testdata/language-features/basic-values/case04.reject.out
+++ b/testdata/language-features/basic-values/case04.reject.out
@@ -6,7 +6,6 @@ with
6in testdata/language-features/basic-values/case04.reject.lc:2:8: 6in testdata/language-features/basic-values/case04.reject.lc:2:8:
7 1 -> '1' 7 1 -> '1'
8 ^^^ 8 ^^^
9
10------------ trace 9------------ trace
11!type error: can not unify 10!type error: can not unify
12() 11()
@@ -16,7 +15,6 @@ with
16in testdata/language-features/basic-values/case04.reject.lc:2:8: 15in testdata/language-features/basic-values/case04.reject.lc:2:8:
17 1 -> '1' 16 1 -> '1'
18 ^^^ 17 ^^^
19
20------------ tooltips 18------------ tooltips
21testdata/language-features/basic-values/case04.reject.lc 2:8-2:11 Char 19testdata/language-features/basic-values/case04.reject.lc 2:8-2:11 Char
22testdata/language-features/basic-values/case04.reject.lc 3:8-3:10 () 20testdata/language-features/basic-values/case04.reject.lc 3:8-3:10 ()
diff --git a/testdata/language-features/basic-values/case05.out b/testdata/language-features/basic-values/case05.out
index cfd1d9af..717b0920 100644
--- a/testdata/language-features/basic-values/case05.out
+++ b/testdata/language-features/basic-values/case05.out
@@ -12,4 +12,3 @@ value x = case x of
12 ^ 12 ^
13Missing case(s): 13Missing case(s):
14 _ | False <- fromInt 1 == _a 14 _ | False <- fromInt 1 == _a
15
diff --git a/testdata/language-features/basic-values/def02.reject.out b/testdata/language-features/basic-values/def02.reject.out
index 615d9afa..eca7cb70 100644
--- a/testdata/language-features/basic-values/def02.reject.out
+++ b/testdata/language-features/basic-values/def02.reject.out
@@ -6,4 +6,3 @@ fun1 x x = 'c'
6testdata/language-features/basic-values/def02.reject.lc:1:8: 6testdata/language-features/basic-values/def02.reject.lc:1:8:
7fun1 x x = 'c' 7fun1 x x = 'c'
8 ^ 8 ^
9
diff --git a/testdata/language-features/basic-values/def03.out b/testdata/language-features/basic-values/def03.out
index 02db7cba..bd9e7133 100644
--- a/testdata/language-features/basic-values/def03.out
+++ b/testdata/language-features/basic-values/def03.out
@@ -11,5 +11,4 @@ Uncovered pattern(s) at testdata/language-features/basic-values/def03.lc:1:1:
11fun 1 = '1' 11fun 1 = '1'
12fun 2 = '2' 12fun 2 = '2'
13Missing case(s): 13Missing case(s):
14 _ | False <- fromInt 1 == _a, False <- fromInt 2 == _a 14 _ | False <- fromInt 1 == _a , False <- fromInt 2 == _a
15
diff --git a/testdata/language-features/basic-values/def07.reject.out b/testdata/language-features/basic-values/def07.reject.out
index be624025..c52ecc70 100644
--- a/testdata/language-features/basic-values/def07.reject.out
+++ b/testdata/language-features/basic-values/def07.reject.out
@@ -1,7 +1,7 @@
1already defined fun at testdata/language-features/basic-values/def07.reject.lc:4:1: 1already defined fun at testdata/language-features/basic-values/def07.reject.lc:4:1:
2fun _ = '_' 2fun _ = '_'
3^^^ 3^^^
4 and at testdata/language-features/basic-values/def07.reject.lc:1:1: 4and at testdata/language-features/basic-values/def07.reject.lc:1:1:
5fun 1 = '1' 5fun 1 = '1'
6^^^ 6^^^
7------------ trace 7------------ trace
@@ -11,7 +11,7 @@ fun :: forall a . a -> 'Char
11!already defined fun at testdata/language-features/basic-values/def07.reject.lc:4:1: 11!already defined fun at testdata/language-features/basic-values/def07.reject.lc:4:1:
12fun _ = '_' 12fun _ = '_'
13^^^ 13^^^
14 and at testdata/language-features/basic-values/def07.reject.lc:1:1: 14and at testdata/language-features/basic-values/def07.reject.lc:1:1:
15fun 1 = '1' 15fun 1 = '1'
16^^^ 16^^^
17------------ tooltips 17------------ tooltips
@@ -28,11 +28,9 @@ Uncovered pattern(s) at testdata/language-features/basic-values/def07.reject.lc:
28fun 1 = '1' 28fun 1 = '1'
29fun 2 = '2' 29fun 2 = '2'
30Missing case(s): 30Missing case(s):
31 _ | False <- fromInt 1 == _a, False <- fromInt 2 == _a 31 _ | False <- fromInt 1 == _a , False <- fromInt 2 == _a
32
33Uncovered pattern(s) at testdata/language-features/basic-values/def07.reject.lc:3:1: 32Uncovered pattern(s) at testdata/language-features/basic-values/def07.reject.lc:3:1:
34fun2 1 _ = '1' 33fun2 1 _ = '1'
35^^^^ 34^^^^
36Missing case(s): 35Missing case(s):
37 _ _ | False <- fromInt 1 == _b 36 _ _ | False <- fromInt 1 == _b
38
diff --git a/testdata/language-features/basic-values/if03.reject.out b/testdata/language-features/basic-values/if03.reject.out
index 83ed5e90..125dd5b5 100644
--- a/testdata/language-features/basic-values/if03.reject.out
+++ b/testdata/language-features/basic-values/if03.reject.out
@@ -6,7 +6,6 @@ with
6in testdata/language-features/basic-values/if03.reject.lc:1:13: 6in testdata/language-features/basic-values/if03.reject.lc:1:13:
7value1 = if () then () else () 7value1 = if () then () else ()
8 ^^ 8 ^^
9
10------------ trace 9------------ trace
11!type error: can not unify 10!type error: can not unify
12'Bool 11'Bool
@@ -16,6 +15,5 @@ with
16in testdata/language-features/basic-values/if03.reject.lc:1:13: 15in testdata/language-features/basic-values/if03.reject.lc:1:13:
17value1 = if () then () else () 16value1 = if () then () else ()
18 ^^ 17 ^^
19
20------------ tooltips 18------------ tooltips
21testdata/language-features/basic-values/if03.reject.lc 1:13-1:15 () 19testdata/language-features/basic-values/if03.reject.lc 1:13-1:15 ()
diff --git a/testdata/language-features/basic-values/if04.reject.out b/testdata/language-features/basic-values/if04.reject.out
index 23a77a44..6313eddc 100644
--- a/testdata/language-features/basic-values/if04.reject.out
+++ b/testdata/language-features/basic-values/if04.reject.out
@@ -6,7 +6,6 @@ with
6in testdata/language-features/basic-values/if04.reject.lc:1:31: 6in testdata/language-features/basic-values/if04.reject.lc:1:31:
7value1 = if True then () else '_' 7value1 = if True then () else '_'
8 ^^^ 8 ^^^
9
10------------ trace 9------------ trace
11!type error: can not unify 10!type error: can not unify
12() 11()
@@ -16,7 +15,6 @@ with
16in testdata/language-features/basic-values/if04.reject.lc:1:31: 15in testdata/language-features/basic-values/if04.reject.lc:1:31:
17value1 = if True then () else '_' 16value1 = if True then () else '_'
18 ^^^ 17 ^^^
19
20------------ tooltips 18------------ tooltips
21testdata/language-features/basic-values/if04.reject.lc 1:13-1:17 Bool 19testdata/language-features/basic-values/if04.reject.lc 1:13-1:17 Bool
22testdata/language-features/basic-values/if04.reject.lc 1:13-1:25 () -> () 20testdata/language-features/basic-values/if04.reject.lc 1:13-1:25 () -> ()
diff --git a/testdata/language-features/basic-values/operator02.reject.out b/testdata/language-features/basic-values/operator02.reject.out
index 93092e52..cbf2cb0f 100644
--- a/testdata/language-features/basic-values/operator02.reject.out
+++ b/testdata/language-features/basic-values/operator02.reject.out
@@ -1,7 +1,7 @@
1already defined #$# at testdata/language-features/basic-values/operator02.reject.lc:3:3: 1already defined #$# at testdata/language-features/basic-values/operator02.reject.lc:3:3:
2a #$# b = () 2a #$# b = ()
3 ^^^ 3 ^^^
4 and at testdata/language-features/basic-values/operator02.reject.lc:1:3: 4and at testdata/language-features/basic-values/operator02.reject.lc:1:3:
5a #$# b = () 5a #$# b = ()
6 ^^^ 6 ^^^
7------------ trace 7------------ trace
@@ -11,7 +11,7 @@ fun :: forall a . a -> ()
11!already defined #$# at testdata/language-features/basic-values/operator02.reject.lc:3:3: 11!already defined #$# at testdata/language-features/basic-values/operator02.reject.lc:3:3:
12a #$# b = () 12a #$# b = ()
13 ^^^ 13 ^^^
14 and at testdata/language-features/basic-values/operator02.reject.lc:1:3: 14and at testdata/language-features/basic-values/operator02.reject.lc:1:3:
15a #$# b = () 15a #$# b = ()
16 ^^^ 16 ^^^
17------------ tooltips 17------------ tooltips
diff --git a/testdata/language-features/basic-values/operator07.reject.out b/testdata/language-features/basic-values/operator07.reject.out
index be6ea8f3..bc594c9e 100644
--- a/testdata/language-features/basic-values/operator07.reject.out
+++ b/testdata/language-features/basic-values/operator07.reject.out
@@ -1,7 +1,7 @@
1Operator precedences don't match: 1Operator precedences don't match:
2Infix 5 at testdata/language-features/basic-values/operator07.reject.lc:11:11: 2infix 5 at testdata/language-features/basic-values/operator07.reject.lc:11:11:
3main = () @&> () <@& () 3main = () @&> () <@& ()
4 ^^^ 4 ^^^
5InfixL 5 at testdata/language-features/basic-values/operator07.reject.lc:11:18: 5infixl 5 at testdata/language-features/basic-values/operator07.reject.lc:11:18:
6main = () @&> () <@& () 6main = () @&> () <@& ()
7 ^^^ 7 ^^^
diff --git a/testdata/language-features/basic-values/operator08.reject.out b/testdata/language-features/basic-values/operator08.reject.out
index 8721d19f..eb50a28a 100644
--- a/testdata/language-features/basic-values/operator08.reject.out
+++ b/testdata/language-features/basic-values/operator08.reject.out
@@ -1,7 +1,7 @@
1Operator precedences don't match: 1Operator precedences don't match:
2Infix 5 at testdata/language-features/basic-values/operator08.reject.lc:10:6: 2infix 5 at testdata/language-features/basic-values/operator08.reject.lc:10:6:
3x = (@&> () <@& ()) 3x = (@&> () <@& ())
4 ^^^ 4 ^^^
5InfixL 5 at testdata/language-features/basic-values/operator08.reject.lc:10:13: 5infixl 5 at testdata/language-features/basic-values/operator08.reject.lc:10:13:
6x = (@&> () <@& ()) 6x = (@&> () <@& ())
7 ^^^ 7 ^^^
diff --git a/testdata/language-features/basic-values/redefine01.reject.out b/testdata/language-features/basic-values/redefine01.reject.out
index 04a3868f..5bd93d2a 100644
--- a/testdata/language-features/basic-values/redefine01.reject.out
+++ b/testdata/language-features/basic-values/redefine01.reject.out
@@ -1,7 +1,7 @@
1already defined unit at testdata/language-features/basic-values/redefine01.reject.lc:3:1: 1already defined unit at testdata/language-features/basic-values/redefine01.reject.lc:3:1:
2unit = () 2unit = ()
3^^^^ 3^^^^
4 and at testdata/language-features/basic-values/redefine01.reject.lc:1:1: 4and at testdata/language-features/basic-values/redefine01.reject.lc:1:1:
5unit = () 5unit = ()
6^^^^ 6^^^^
7------------ trace 7------------ trace
@@ -11,7 +11,7 @@ unit :: ()
11!already defined unit at testdata/language-features/basic-values/redefine01.reject.lc:3:1: 11!already defined unit at testdata/language-features/basic-values/redefine01.reject.lc:3:1:
12unit = () 12unit = ()
13^^^^ 13^^^^
14 and at testdata/language-features/basic-values/redefine01.reject.lc:1:1: 14and at testdata/language-features/basic-values/redefine01.reject.lc:1:1:
15unit = () 15unit = ()
16^^^^ 16^^^^
17------------ tooltips 17------------ tooltips
diff --git a/testdata/language-features/basic-values/typesyn03.reject.out b/testdata/language-features/basic-values/typesyn03.reject.out
index c0fb5268..cf08db7a 100644
--- a/testdata/language-features/basic-values/typesyn03.reject.out
+++ b/testdata/language-features/basic-values/typesyn03.reject.out
@@ -1,7 +1,7 @@
1already defined 'MyUnit at testdata/language-features/basic-values/typesyn03.reject.lc:2:6: 1already defined 'MyUnit at testdata/language-features/basic-values/typesyn03.reject.lc:2:6:
2type MyUnit = () 2type MyUnit = ()
3 ^^^^^^ 3 ^^^^^^
4 and at testdata/language-features/basic-values/typesyn03.reject.lc:1:6: 4and at testdata/language-features/basic-values/typesyn03.reject.lc:1:6:
5type MyUnit = () 5type MyUnit = ()
6 ^^^^^^ 6 ^^^^^^
7------------ trace 7------------ trace
@@ -10,7 +10,7 @@ type MyUnit = ()
10!already defined 'MyUnit at testdata/language-features/basic-values/typesyn03.reject.lc:2:6: 10!already defined 'MyUnit at testdata/language-features/basic-values/typesyn03.reject.lc:2:6:
11type MyUnit = () 11type MyUnit = ()
12 ^^^^^^ 12 ^^^^^^
13 and at testdata/language-features/basic-values/typesyn03.reject.lc:1:6: 13and at testdata/language-features/basic-values/typesyn03.reject.lc:1:6:
14type MyUnit = () 14type MyUnit = ()
15 ^^^^^^ 15 ^^^^^^
16------------ tooltips 16------------ tooltips
diff --git a/testdata/language-features/basic-values/typesyn04.reject.out b/testdata/language-features/basic-values/typesyn04.reject.out
index c903ddb8..94fc1e8c 100644
--- a/testdata/language-features/basic-values/typesyn04.reject.out
+++ b/testdata/language-features/basic-values/typesyn04.reject.out
@@ -1,7 +1,7 @@
1already defined 'MyUnit at testdata/language-features/basic-values/typesyn04.reject.lc:2:6: 1already defined 'MyUnit at testdata/language-features/basic-values/typesyn04.reject.lc:2:6:
2type MyUnit = () 2type MyUnit = ()
3 ^^^^^^ 3 ^^^^^^
4 and at testdata/language-features/basic-values/typesyn04.reject.lc:1:6: 4and at testdata/language-features/basic-values/typesyn04.reject.lc:1:6:
5type MyUnit = () 5type MyUnit = ()
6 ^^^^^^ 6 ^^^^^^
7------------ trace 7------------ trace
@@ -10,7 +10,7 @@ type MyUnit = ()
10!already defined 'MyUnit at testdata/language-features/basic-values/typesyn04.reject.lc:2:6: 10!already defined 'MyUnit at testdata/language-features/basic-values/typesyn04.reject.lc:2:6:
11type MyUnit = () 11type MyUnit = ()
12 ^^^^^^ 12 ^^^^^^
13 and at testdata/language-features/basic-values/typesyn04.reject.lc:1:6: 13and at testdata/language-features/basic-values/typesyn04.reject.lc:1:6:
14type MyUnit = () 14type MyUnit = ()
15 ^^^^^^ 15 ^^^^^^
16------------ tooltips 16------------ tooltips
diff --git a/testdata/language-features/guard/guard02.reject.out b/testdata/language-features/guard/guard02.reject.out
index 3cff76bd..cd5b17c1 100644
--- a/testdata/language-features/guard/guard02.reject.out
+++ b/testdata/language-features/guard/guard02.reject.out
@@ -6,7 +6,6 @@ with
6in testdata/language-features/guard/guard02.reject.lc:2:12: 6in testdata/language-features/guard/guard02.reject.lc:2:12:
7 | True = () 7 | True = ()
8 ^^ 8 ^^
9
10------------ trace 9------------ trace
11!type error: can not unify 10!type error: can not unify
12'String 11'String
@@ -16,7 +15,6 @@ with
16in testdata/language-features/guard/guard02.reject.lc:2:12: 15in testdata/language-features/guard/guard02.reject.lc:2:12:
17 | True = () 16 | True = ()
18 ^^ 17 ^^
19
20------------ tooltips 18------------ tooltips
21testdata/language-features/guard/guard02.reject.lc 2:12-2:14 () 19testdata/language-features/guard/guard02.reject.lc 2:12-2:14 ()
22testdata/language-features/guard/guard02.reject.lc 3:5-3:10 Bool 20testdata/language-features/guard/guard02.reject.lc 3:5-3:10 Bool
diff --git a/testdata/language-features/guard/guard05.reject.out b/testdata/language-features/guard/guard05.reject.out
index 99275e00..23bf1739 100644
--- a/testdata/language-features/guard/guard05.reject.out
+++ b/testdata/language-features/guard/guard05.reject.out
@@ -6,7 +6,6 @@ with
6in testdata/language-features/guard/guard05.reject.lc:1:9: 6in testdata/language-features/guard/guard05.reject.lc:1:9:
7value | () = "wrong" 7value | () = "wrong"
8 ^^ 8 ^^
9
10------------ trace 9------------ trace
11!type error: can not unify 10!type error: can not unify
12'Bool 11'Bool
@@ -16,7 +15,6 @@ with
16in testdata/language-features/guard/guard05.reject.lc:1:9: 15in testdata/language-features/guard/guard05.reject.lc:1:9:
17value | () = "wrong" 16value | () = "wrong"
18 ^^ 17 ^^
19
20------------ tooltips 18------------ tooltips
21testdata/language-features/guard/guard05.reject.lc 1:9-1:11 () 19testdata/language-features/guard/guard05.reject.lc 1:9-1:11 ()
22testdata/language-features/guard/guard05.reject.lc 1:14-1:21 String 20testdata/language-features/guard/guard05.reject.lc 1:14-1:21 String
diff --git a/testdata/language-features/guard/guard12.reject.out b/testdata/language-features/guard/guard12.reject.out
index ca6c50ab..f1f024d7 100644
--- a/testdata/language-features/guard/guard12.reject.out
+++ b/testdata/language-features/guard/guard12.reject.out
@@ -6,7 +6,6 @@ with
6in testdata/language-features/guard/guard12.reject.lc:1:13: 6in testdata/language-features/guard/guard12.reject.lc:1:13:
7fun x | x = () | otherwise = 'a' 7fun x | x = () | otherwise = 'a'
8 ^^ 8 ^^
9
10------------ trace 9------------ trace
11!type error: can not unify 10!type error: can not unify
12'Char 11'Char
@@ -16,7 +15,6 @@ with
16in testdata/language-features/guard/guard12.reject.lc:1:13: 15in testdata/language-features/guard/guard12.reject.lc:1:13:
17fun x | x = () | otherwise = 'a' 16fun x | x = () | otherwise = 'a'
18 ^^ 17 ^^
19
20------------ tooltips 18------------ tooltips
21testdata/language-features/guard/guard12.reject.lc 1:13-1:15 () 19testdata/language-features/guard/guard12.reject.lc 1:13-1:15 ()
22testdata/language-features/guard/guard12.reject.lc 1:30-1:33 Char 20testdata/language-features/guard/guard12.reject.lc 1:30-1:33 Char
diff --git a/testdata/language-features/module/import04.reject.out b/testdata/language-features/module/import04.reject.out
index 82543ceb..85752b47 100644
--- a/testdata/language-features/module/import04.reject.out
+++ b/testdata/language-features/module/import04.reject.out
@@ -1,7 +1,7 @@
1already defined hello at testdata/language-features/module/import04.reject.lc:4:1: 1already defined hello at testdata/language-features/module/import04.reject.lc:4:1:
2hello = "hello" 2hello = "hello"
3^^^^^ 3^^^^^
4 and at testdata/language-features/module/Hello01.lc:3:1: 4and at testdata/language-features/module/Hello01.lc:3:1:
5hello = "hello" 5hello = "hello"
6^^^^^ 6^^^^^
7------------ trace 7------------ trace
@@ -9,7 +9,7 @@ hello :: 'String
9!already defined hello at testdata/language-features/module/import04.reject.lc:4:1: 9!already defined hello at testdata/language-features/module/import04.reject.lc:4:1:
10hello = "hello" 10hello = "hello"
11^^^^^ 11^^^^^
12 and at testdata/language-features/module/Hello01.lc:3:1: 12and at testdata/language-features/module/Hello01.lc:3:1:
13hello = "hello" 13hello = "hello"
14^^^^^ 14^^^^^
15------------ tooltips 15------------ tooltips
diff --git a/testdata/language-features/module/import10.reject.out b/testdata/language-features/module/import10.reject.out
index 7f8c8d2d..5a61239c 100644
--- a/testdata/language-features/module/import10.reject.out
+++ b/testdata/language-features/module/import10.reject.out
@@ -1,7 +1,7 @@
1already defined 'MyUnit at testdata/language-features/module/import10.reject.lc:3:6: 1already defined 'MyUnit at testdata/language-features/module/import10.reject.lc:3:6:
2type MyUnit = () 2type MyUnit = ()
3 ^^^^^^ 3 ^^^^^^
4 and at testdata/language-features/module/TypeSyn01Mod.lc:2:6: 4and at testdata/language-features/module/TypeSyn01Mod.lc:2:6:
5type MyUnit = () 5type MyUnit = ()
6 ^^^^^^ 6 ^^^^^^
7------------ trace 7------------ trace
@@ -9,7 +9,7 @@ type MyUnit = ()
9!already defined 'MyUnit at testdata/language-features/module/import10.reject.lc:3:6: 9!already defined 'MyUnit at testdata/language-features/module/import10.reject.lc:3:6:
10type MyUnit = () 10type MyUnit = ()
11 ^^^^^^ 11 ^^^^^^
12 and at testdata/language-features/module/TypeSyn01Mod.lc:2:6: 12and at testdata/language-features/module/TypeSyn01Mod.lc:2:6:
13type MyUnit = () 13type MyUnit = ()
14 ^^^^^^ 14 ^^^^^^
15------------ tooltips 15------------ tooltips
diff --git a/testdata/language-features/module/import11.reject.out b/testdata/language-features/module/import11.reject.out
index 531e98a6..f686f7e8 100644
--- a/testdata/language-features/module/import11.reject.out
+++ b/testdata/language-features/module/import11.reject.out
@@ -1,7 +1,7 @@
1already defined 'MyUnit at testdata/language-features/module/import11.reject.lc:3:6: 1already defined 'MyUnit at testdata/language-features/module/import11.reject.lc:3:6:
2type MyUnit = () 2type MyUnit = ()
3 ^^^^^^ 3 ^^^^^^
4 and at testdata/language-features/module/TypeSyn01Mod.lc:2:6: 4and at testdata/language-features/module/TypeSyn01Mod.lc:2:6:
5type MyUnit = () 5type MyUnit = ()
6 ^^^^^^ 6 ^^^^^^
7------------ trace 7------------ trace
@@ -9,7 +9,7 @@ type MyUnit = ()
9!already defined 'MyUnit at testdata/language-features/module/import11.reject.lc:3:6: 9!already defined 'MyUnit at testdata/language-features/module/import11.reject.lc:3:6:
10type MyUnit = () 10type MyUnit = ()
11 ^^^^^^ 11 ^^^^^^
12 and at testdata/language-features/module/TypeSyn01Mod.lc:2:6: 12and at testdata/language-features/module/TypeSyn01Mod.lc:2:6:
13type MyUnit = () 13type MyUnit = ()
14 ^^^^^^ 14 ^^^^^^
15------------ tooltips 15------------ tooltips
diff --git a/testdata/language-features/pattern/uncovered.out b/testdata/language-features/pattern/uncovered.out
index e24ca6ec..f51d2e84 100644
--- a/testdata/language-features/pattern/uncovered.out
+++ b/testdata/language-features/pattern/uncovered.out
@@ -15,6 +15,5 @@ f _ True False = 0
15f False _ True = 1 15f False _ True = 1
16f True False _ = 2 16f True False _ = 2
17Missing case(s): 17Missing case(s):
18 False False False 18 False False False
19 True True True 19 True True True
20
diff --git a/testdata/record01.reject.out b/testdata/record01.reject.out
index 01aefa45..b03f9397 100644
--- a/testdata/record01.reject.out
+++ b/testdata/record01.reject.out
@@ -6,7 +6,6 @@ with
6in testdata/record01.reject.lc:26:15: 6in testdata/record01.reject.lc:26:15:
7 in ScreenOut record.fieldA 7 in ScreenOut record.fieldA
8 ^^^^^^ 8 ^^^^^^
9
10------------ trace 9------------ trace
11!type error: can not unify 10!type error: can not unify
12'FrameBuffer _b _a 11'FrameBuffer _b _a
@@ -16,7 +15,6 @@ with
16in testdata/record01.reject.lc:26:15: 15in testdata/record01.reject.lc:26:15:
17 in ScreenOut record.fieldA 16 in ScreenOut record.fieldA
18 ^^^^^^ 17 ^^^^^^
19
20------------ tooltips 18------------ tooltips
21testdata/record01.reject.lc 2:16-2:21 (BlendEquation, BlendEquation) -> ((BlendingFactor, BlendingFactor), (BlendingFactor, BlendingFactor)) -> Vec 4 Float -> Blending Float 19testdata/record01.reject.lc 2:16-2:21 (BlendEquation, BlendEquation) -> ((BlendingFactor, BlendingFactor), (BlendingFactor, BlendingFactor)) -> Vec 4 Float -> Blending Float
22testdata/record01.reject.lc 2:16-2:23 ((BlendingFactor, BlendingFactor), (BlendingFactor, BlendingFactor)) -> Vec 4 Float -> Blending Float 20testdata/record01.reject.lc 2:16-2:23 ((BlendingFactor, BlendingFactor), (BlendingFactor, BlendingFactor)) -> Vec 4 Float -> Blending Float
diff --git a/testdata/typesig.reject.out b/testdata/typesig.reject.out
index 1b78a5c8..cc45ae6e 100644
--- a/testdata/typesig.reject.out
+++ b/testdata/typesig.reject.out
@@ -1,12 +1,12 @@
1focus checkMetas: \a -> (\(b :: Type) -> primFix a b) (\(a := Type) -> \(c :: Type) -> <<HERE>>) 1focus checkMetas: \a -> (\(b :: Type) -> primFix a b) (\(a := Type) -> \(c :: Type) -> <<HERE>>)
2\(a :: Type ~ _a) (b :: _a ~ 'X) -> typeAnn _a (labend X) 2\(d :: Type ~ _a) (e :: _a ~ 'X) -> typeAnn _a (labend X)
3------------ trace 3------------ trace
4'X :: Type 4'X :: Type
5X :: 'X 5X :: 'X
6'XCase :: (a :: 'X -> Type) -> a X -> (b :: 'X) -> a b 6'XCase :: (a :: 'X -> Type) -> a X -> (b :: 'X) -> a b
7match'X :: (a :: Type -> Type) -> a 'X -> (b :: Type) -> a b -> a b 7match'X :: (a :: Type -> Type) -> a 'X -> (b :: Type) -> a b -> a b
8!focus checkMetas: \a -> (\(b :: Type) -> primFix a b) (\(a := Type) -> \(c :: Type) -> <<HERE>>) 8!focus checkMetas: \a -> (\(b :: Type) -> primFix a b) (\(a := Type) -> \(c :: Type) -> <<HERE>>)
9\(a :: Type ~ _a) (b :: _a ~ 'X) -> typeAnn _a (labend X) 9\(d :: Type ~ _a) (e :: _a ~ 'X) -> typeAnn _a (labend X)
10------------ tooltips 10------------ tooltips
11testdata/typesig.reject.lc 4:6-4:7 Type 11testdata/typesig.reject.lc 4:6-4:7 Type
12testdata/typesig.reject.lc 4:6-4:11 Type 12testdata/typesig.reject.lc 4:6-4:11 Type
diff --git a/testdata/typesigctx.reject.out b/testdata/typesigctx.reject.out
index 3d32979e..a1052bcd 100644
--- a/testdata/typesigctx.reject.out
+++ b/testdata/typesigctx.reject.out
@@ -1,6 +1,5 @@
1type error: no instance of 'Show' on ??? 1type error: no instance of 'Show' on ???
2in Wildcard2 builtin 'Type 2in Wildcard2 builtin 'Type
3
4------------ trace 3------------ trace
5'X :: Type 4'X :: Type
6X :: 'X 5X :: 'X
@@ -10,7 +9,6 @@ match'X :: (a :: Type -> Type) -> a 'X[0
10show' :: forall a . 'Show' a => a -> 'X 9show' :: forall a . 'Show' a => a -> 'X
11!type error: no instance of 'Show' on ??? 10!type error: no instance of 'Show' on ???
12in Wildcard2 builtin 'Type 11in Wildcard2 builtin 'Type
13
14------------ tooltips 12------------ tooltips
15testdata/typesigctx.reject.lc 1:6-1:7 Type 13testdata/typesigctx.reject.lc 1:6-1:7 Type
16testdata/typesigctx.reject.lc 1:6-1:11 Type 14testdata/typesigctx.reject.lc 1:6-1:11 Type
diff --git a/tool/Compiler.hs b/tool/Compiler.hs
index 359b23d6..e3fdd7a3 100644
--- a/tool/Compiler.hs
+++ b/tool/Compiler.hs
@@ -46,7 +46,7 @@ prettyPrint srcName output = do
46parse srcName backend includePaths output = do 46parse srcName backend includePaths output = do
47 pplRes <- parseModule includePaths srcName 47 pplRes <- parseModule includePaths srcName
48 case pplRes of 48 case pplRes of
49 Left err -> fail err 49 Left err -> fail $ show err
50 Right ppl -> maybe (putStrLn ppl) (`writeFile` ppl) output 50 Right ppl -> maybe (putStrLn ppl) (`writeFile` ppl) output
51 51
52compile srcName backend includePaths output = do 52compile srcName backend includePaths output = do
@@ -57,7 +57,7 @@ compile srcName backend includePaths output = do
57 do 57 do
58 pplRes <- compileMain includePaths backend srcName 58 pplRes <- compileMain includePaths backend srcName
59 case pplRes of 59 case pplRes of
60 Left err -> fail err 60 Left err -> fail $ show err
61 Right ppl -> B.writeFile (withOutName $ baseName <> ".json") $ encode ppl 61 Right ppl -> B.writeFile (withOutName $ baseName <> ".json") $ encode ppl
62-- True -> writeFile (withOutName $ baseName <> ".ppl") $ prettyShowUnlines ppl 62-- True -> writeFile (withOutName $ baseName <> ".ppl") $ prettyShowUnlines ppl
63 63