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.

206 lines
6.9 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. import Data.IORef
  35. import Data.Sequence (Seq)
  36. main :: IO ()
  37. main = do
  38. opts <- execParser parser
  39. case opts of
  40. Load files -> do
  41. env <- checkFiles files
  42. enterReplIn env
  43. Check files verbose -> do
  44. env <- checkFiles files
  45. when verbose $ dumpEnv env
  46. Repl -> enterReplIn =<< emptyEnv
  47. enterReplIn :: ElabEnv -> IO ()
  48. enterReplIn env = runInputT defaultSettings (loop env') where
  49. env' = env { commHook = T.putStrLn . render . prettyTm . quote . zonk }
  50. loop :: ElabEnv -> InputT IO ()
  51. loop env = do
  52. inp <- fmap T.pack <$> getInputLine "% "
  53. case inp of
  54. Nothing -> pure ()
  55. Just inp ->
  56. case runAlex (Bsl.fromStrict (T.encodeUtf8 inp)) parseRepl of
  57. Left e -> do
  58. liftIO $ print e
  59. loop env
  60. Right st -> do
  61. env <- liftIO $
  62. runElab (checkStatement st ask) env
  63. `catch` \e -> do
  64. displayExceptions' inp (e :: SomeException)
  65. pure env
  66. loop env
  67. checkFiles :: [String] -> IO ElabEnv
  68. checkFiles files = runElab (go files ask) =<< emptyEnv where
  69. go [] k = do
  70. env <- ask
  71. for_ (Map.toList (nameMap env)) \case
  72. (_, v@Defined{})
  73. | Set.member v (definedNames env) -> pure ()
  74. | otherwise ->
  75. let
  76. pos = fromJust (Map.lookup v (whereBound env))
  77. in withSpan (fst pos) (snd pos) $ throwElab $ DeclaredUndefined v
  78. _ -> pure ()
  79. metas <- liftIO $ readIORef (unsolvedMetas env)
  80. unless (Map.null metas) $ do
  81. liftIO $ reportUnsolved metas
  82. k
  83. go (x:xs) k = do
  84. code <- liftIO $ Bsl.readFile x
  85. case runAlex (code <> Bsl.singleton 10) parseProg of
  86. Left e -> liftIO $ print e *> error (show e)
  87. Right prog ->
  88. local (\e -> e { currentFile = Just (T.pack x) }) (checkProgram prog (go xs k))
  89. `catchElab` \e -> liftIO $ displayAndDie (T.decodeUtf8 (Bsl.toStrict code)) (e :: SomeException)
  90. dumpEnv :: ElabEnv -> IO ()
  91. dumpEnv env = for_ (Map.toList (nameMap env)) $ \(_, name) ->
  92. let nft = fst $ getEnv env Map.! name in
  93. T.putStrLn $ render (pretty name <+> align (nest (negate 1) (colon <+> prettyTm (quote (zonk nft)))))
  94. parser :: ParserInfo Opts
  95. parser = info (subparser (load <> check) <|> pure Repl <**> helper) (header "cubical - a cubical programming language")
  96. where
  97. load = command "load" $ info (fmap Load (some (argument str (metavar "file..."))) <**> helper) (progDesc "Check and load a list of files in the REPL")
  98. check = command "check" $
  99. info ((Check <$> some (argument str (metavar "file..."))
  100. <*> switch ( long "verbose"
  101. <> short 'v'
  102. <> help "Print the types of all declared/defined values"))
  103. <**> helper)
  104. (progDesc "Check a list of files")
  105. data Opts
  106. = Load { files :: [String] }
  107. | Check { files :: [String], verbose :: Bool }
  108. | Repl
  109. deriving (Eq, Show, Ord)
  110. displayAndDie :: Exception e => Text -> e -> IO a
  111. displayAndDie lines e = do
  112. () <- throwIO e `catches` displayExceptions lines
  113. exitFailure
  114. displayExceptions :: Text -> [Handler ()]
  115. displayExceptions lines =
  116. [ Handler \(WhileChecking a b e) -> do
  117. T.putStrLn $ squiggleUnder a b lines
  118. displayExceptions' lines e
  119. , Handler \(SeeAlso a b e) -> do
  120. displayExceptions' lines e
  121. T.putStrLn $ squiggleUnder a b lines
  122. , Handler \(AttachedNote n e) -> do
  123. displayExceptions' lines e
  124. T.putStrLn $ "\x1b[1;32mnote\x1b[0m: " <> render n
  125. , Handler \(WhenCheckingEndpoint le ri ep e) -> do
  126. displayExceptions' lines e
  127. let
  128. endp = case ep of
  129. VI0 -> T.pack "left"
  130. VI1 -> T.pack "right"
  131. _ -> T.pack $ show (prettyTm (quote ep))
  132. T.putStrLn . T.unlines $
  133. [ "\x1b[1;32mnote\x1b[0m: This path was expected to fill the diagram"
  134. , "\t " <> render (prettyTm (quote le)) <> " " <> T.replicate 7 (T.singleton '\x2500') <> " " <> render (prettyTm (quote ri))
  135. , "\x1b[1;32mnote\x1b[0m: the " <> endp <> " endpoint is incorrect"
  136. ]
  137. , Handler \(NotEqual ta tb) -> do
  138. putStrLn . unlines $
  139. [ "\x1b[1;31merror\x1b[0m: Mismatch between actual and expected types:"
  140. , " * \x1b[1mActual\x1b[0m: " ++ showValue (zonk ta)
  141. , " * \x1b[1mExpected\x1b[0m: " ++ showValue (zonk tb)
  142. ]
  143. , Handler \(NoSuchPrimitive x) -> do
  144. putStrLn $ "Unknown primitive: " ++ T.unpack x
  145. , Handler \(NotInScope x) -> do
  146. putStrLn $ "Variable not in scope: " ++ show (pretty x)
  147. , Handler \(DeclaredUndefined n) -> do
  148. putStrLn $ "Name declared but not defined: " ++ show (pretty n)
  149. ]
  150. reportUnsolved :: Foldable t => Map.Map MV (t (Seq Projection, Value)) -> IO ()
  151. reportUnsolved metas = do
  152. for_ (Map.toList metas) \(m, p) -> do
  153. case mvSpan m of
  154. Just (f, s, e) -> T.putStrLn . squiggleUnder s e =<< T.readFile (T.unpack f)
  155. Nothing -> pure ()
  156. T.putStrLn . render $
  157. "Unsolved metavariable" <+> prettyTm (Meta m) <+> pretty ':' <+> prettyTm (quote (mvType m)) <+> "should satisfy:"
  158. for_ p \p ->
  159. T.putStrLn . render $ indent 2 $ prettyTm (quote (VNe (HMeta m) (fst p))) <+> pretty '≡' <+> prettyTm (quote (snd p))
  160. displayExceptions' :: Exception e => Text -> e -> IO ()
  161. displayExceptions' lines e = displayAndDie lines e `catch` \(_ :: ExitCode) -> pure ()
  162. squiggleUnder :: Posn -> Posn -> Text -> Text
  163. squiggleUnder (Posn l c) (Posn l' c') file
  164. | l == l' =
  165. let
  166. line = T.pack (show l) <> " | " <> T.lines file !! (l - 1)
  167. padding = T.replicate (length (show l)) (T.singleton ' ') <> " |"
  168. squiggle = T.replicate c " " <> T.pack "\x1b[1;31m" <> T.replicate (c' - c) "~" <> T.pack "\x1b[0m"
  169. in T.unlines [ padding, line, padding <> squiggle ]
  170. | otherwise = T.unlines (take (l' - l) (drop l (T.lines file)))
  171. newtype DeclaredUndefined = DeclaredUndefined { declaredUndefName :: Name }
  172. deriving (Eq, Show, Exception)
  173. dumpTokens :: Alex ()
  174. dumpTokens = do
  175. t <- alexMonadScan
  176. case tokenClass t of
  177. TokEof -> pure ()
  178. _ -> do
  179. traceM (show t)
  180. dumpTokens