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.

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