less prototype, less bad code implementation of CCHM type theory
You can not select more than 25 topics Topics must start with a letter or number, can include dashes ('-') and can be up to 35 characters long.

187 lines
6.1 KiB

  1. {-# LANGUAGE LambdaCase #-}
  2. {-# LANGUAGE BlockArguments #-}
  3. {-# LANGUAGE OverloadedStrings #-}
  4. {-# LANGUAGE ScopedTypeVariables #-}
  5. {-# LANGUAGE DeriveAnyClass #-}
  6. module Main where
  7. import Control.Monad.IO.Class
  8. import Control.Monad.Reader
  9. import Control.Exception
  10. import qualified Data.ByteString.Lazy as Bsl
  11. import qualified Data.Text.Encoding as T
  12. import qualified Data.Map.Strict as Map
  13. import qualified Data.Text.IO as T
  14. import qualified Data.Text as T
  15. import Data.Text ( Text )
  16. import Data.Foldable
  17. import Elab.Monad hiding (switch)
  18. import Elab.WiredIn
  19. import Elab.Eval
  20. import Elab
  21. import Options.Applicative
  22. import Presyntax.Presyntax (Posn(Posn))
  23. import Presyntax.Parser
  24. import Presyntax.Lexer
  25. import Prettyprinter
  26. import Syntax.Pretty
  27. import Syntax
  28. import System.Console.Haskeline
  29. import System.Exit
  30. import qualified Data.Set as Set
  31. import Data.Maybe
  32. import Presyntax.Tokens
  33. import Debug.Trace
  34. main :: IO ()
  35. main = do
  36. opts <- execParser parser
  37. case opts of
  38. Load files -> do
  39. env <- checkFiles files
  40. enterReplIn env
  41. Check files verbose -> do
  42. env <- checkFiles files
  43. when verbose $ dumpEnv env
  44. Repl -> enterReplIn emptyEnv
  45. enterReplIn :: ElabEnv -> IO ()
  46. enterReplIn env = runInputT defaultSettings (loop env') where
  47. env' = env { commHook = T.putStrLn . render . prettyTm . quote . zonk }
  48. loop :: ElabEnv -> InputT IO ()
  49. loop env = do
  50. inp <- fmap T.pack <$> getInputLine "% "
  51. case inp of
  52. Nothing -> pure ()
  53. Just inp ->
  54. case runAlex (Bsl.fromStrict (T.encodeUtf8 inp)) parseRepl of
  55. Left e -> do
  56. liftIO $ print e
  57. loop env
  58. Right st -> do
  59. env <- liftIO $
  60. runElab (checkStatement st ask) env
  61. `catch` \e -> do
  62. displayExceptions' inp (e :: SomeException)
  63. pure env
  64. loop env
  65. checkFiles :: [String] -> IO ElabEnv
  66. checkFiles files = runElab (go files ask) emptyEnv where
  67. go [] k = do
  68. env <- ask
  69. for_ (Map.toList (nameMap env)) \case
  70. (_, v@Defined{})
  71. | Set.member v (definedNames env) -> pure ()
  72. | otherwise ->
  73. let
  74. pos = fromJust (Map.lookup v (whereBound env))
  75. in withSpan (fst pos) (snd pos) $ throwElab $ DeclaredUndefined v
  76. _ -> pure ()
  77. k
  78. go (x:xs) k = do
  79. code <- liftIO $ Bsl.readFile x
  80. case runAlex (code <> Bsl.singleton 10) parseProg of
  81. Left e -> liftIO $ print e *> error (show e)
  82. Right prog ->
  83. checkProgram prog (go xs k)
  84. `catchElab` \e -> liftIO $ displayAndDie (T.decodeUtf8 (Bsl.toStrict code)) (e :: SomeException)
  85. dumpEnv :: ElabEnv -> IO ()
  86. dumpEnv env = for_ (Map.toList (nameMap env)) $ \(_, name) ->
  87. let nft = fst $ getEnv env Map.! name in
  88. T.putStrLn $ render (pretty name <+> align (nest (negate 1) (colon <+> prettyTm (quote (zonk nft)))))
  89. parser :: ParserInfo Opts
  90. parser = info (subparser (load <> check) <|> pure Repl <**> helper) (header "cubical - a cubical programming language")
  91. where
  92. load = command "load" $ info (fmap Load (some (argument str (metavar "file..."))) <**> helper) (progDesc "Check and load a list of files in the REPL")
  93. check = command "check" $
  94. info ((Check <$> some (argument str (metavar "file..."))
  95. <*> switch ( long "verbose"
  96. <> short 'v'
  97. <> help "Print the types of all declared/defined values"))
  98. <**> helper)
  99. (progDesc "Check a list of files")
  100. data Opts
  101. = Load { files :: [String] }
  102. | Check { files :: [String], verbose :: Bool }
  103. | Repl
  104. deriving (Eq, Show, Ord)
  105. displayAndDie :: Exception e => Text -> e -> IO a
  106. displayAndDie lines e = do
  107. () <- throwIO e `catches` displayExceptions lines
  108. exitFailure
  109. displayExceptions :: Text -> [Handler ()]
  110. displayExceptions lines =
  111. [ Handler \(WhileChecking a b e) -> do
  112. T.putStrLn $ squiggleUnder a b lines
  113. displayExceptions' lines e
  114. , Handler \(SeeAlso a b e) -> do
  115. displayExceptions' lines e
  116. T.putStrLn $ squiggleUnder a b lines
  117. , Handler \(AttachedNote n e) -> do
  118. displayExceptions' lines e
  119. T.putStrLn $ "\x1b[1;32mnote\x1b[0m: " <> render n
  120. , Handler \(WhenCheckingEndpoint le ri ep e) -> do
  121. displayExceptions' lines e
  122. let
  123. endp = case ep of
  124. VI0 -> T.pack "left"
  125. VI1 -> T.pack "right"
  126. _ -> T.pack $ show (prettyTm (quote ep))
  127. T.putStrLn . T.unlines $
  128. [ "\x1b[1;32mnote\x1b[0m: This path was expected to fill the diagram"
  129. , "\t " <> render (prettyTm (quote le)) <> " " <> T.replicate 7 (T.singleton '\x2500') <> " " <> render (prettyTm (quote ri))
  130. , "\x1b[1;32mnote\x1b[0m: the " <> endp <> " endpoint is incorrect"
  131. ]
  132. , Handler \(NotEqual ta tb) -> do
  133. putStrLn . unlines $
  134. [ "\x1b[1;31merror\x1b[0m: Mismatch between actual and expected types:"
  135. , " * \x1b[1mActual\x1b[0m: " ++ showValue (zonk ta)
  136. , " * \x1b[1mExpected\x1b[0m: " ++ showValue (zonk tb)
  137. ]
  138. , Handler \(NoSuchPrimitive x) -> do
  139. putStrLn $ "Unknown primitive: " ++ T.unpack x
  140. , Handler \(NotInScope x) -> do
  141. putStrLn $ "Variable not in scope: " ++ show (pretty x)
  142. , Handler \(DeclaredUndefined n) -> do
  143. putStrLn $ "Name declared but not defined: " ++ show (pretty n)
  144. ]
  145. displayExceptions' :: Exception e => Text -> e -> IO ()
  146. displayExceptions' lines e = displayAndDie lines e `catch` \(_ :: ExitCode) -> pure ()
  147. squiggleUnder :: Posn -> Posn -> Text -> Text
  148. squiggleUnder (Posn l c) (Posn l' c') file
  149. | l == l' =
  150. let
  151. line = T.pack (show l) <> " | " <> T.lines file !! (l - 1)
  152. padding = T.replicate (length (show l)) (T.singleton ' ') <> " |"
  153. squiggle = T.replicate c " " <> T.pack "\x1b[1;31m" <> T.replicate (c' - c) "~" <> T.pack "\x1b[0m"
  154. in T.unlines [ padding, line, padding <> squiggle ]
  155. | otherwise = T.unlines (take (l' - l) (drop l (T.lines file)))
  156. newtype DeclaredUndefined = DeclaredUndefined { declaredUndefName :: Name }
  157. deriving (Eq, Show, Exception)
  158. dumpTokens :: Alex ()
  159. dumpTokens = do
  160. t <- alexMonadScan
  161. case tokenClass t of
  162. TokEof -> pure ()
  163. _ -> do
  164. traceM (show t)
  165. dumpTokens