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.

168 lines
5.0 KiB

  1. {-# LANGUAGE DeriveAnyClass #-}
  2. {-# LANGUAGE GeneralizedNewtypeDeriving #-}
  3. {-# LANGUAGE DerivingVia #-}
  4. {-# LANGUAGE DeriveAnyClass #-}
  5. module Elab.Monad where
  6. import Control.Monad.Reader
  7. import Control.Exception
  8. import Data.Text.Prettyprint.Doc.Render.Terminal (AnsiStyle)
  9. import qualified Data.Map.Strict as Map
  10. import Data.Text.Prettyprint.Doc
  11. import Data.Map.Strict (Map)
  12. import Data.Text (Text)
  13. import Data.Set (Set)
  14. import Data.Typeable
  15. import qualified Presyntax.Presyntax as P
  16. import Syntax
  17. import Data.IORef
  18. import Data.Sequence (Seq)
  19. data ElabEnv =
  20. ElabEnv { getEnv :: Map Name (NFType, Value)
  21. , nameMap :: Map Text Name
  22. , pingPong :: {-# UNPACK #-} !Int
  23. , commHook :: Value -> IO ()
  24. , currentSpan :: Maybe (P.Posn, P.Posn)
  25. , currentFile :: Maybe Text
  26. , whereBound :: Map Name (P.Posn, P.Posn)
  27. , definedNames :: Set Name
  28. , unsolvedMetas :: {-# UNPACK #-} !(IORef (Map MV [(Seq Projection, Value)]))
  29. }
  30. newtype ElabM a = ElabM { runElab :: ElabEnv -> IO a }
  31. deriving (Functor, Applicative, Monad, MonadReader ElabEnv, MonadIO)
  32. via ReaderT ElabEnv IO
  33. emptyEnv :: IO ElabEnv
  34. emptyEnv = ElabEnv mempty mempty 0 (const (pure ())) Nothing Nothing mempty mempty <$> newIORef mempty
  35. assume :: Name -> Value -> (Name -> ElabM a) -> ElabM a
  36. assume nm ty k = defineInternal nm ty VVar k
  37. define :: Name -> Value -> Value -> (Name -> ElabM a) -> ElabM a
  38. define nm vty val = defineInternal nm vty (const val)
  39. assumes :: [Name] -> Value -> ([Name] -> ElabM a) -> ElabM a
  40. assumes nms ty k = do
  41. let
  42. go acc [] k = k acc
  43. go acc (x:xs) k = assume x ty $ \n -> go (n:acc) xs k
  44. in go [] nms k
  45. defineInternal :: Name -> Value -> (Name -> Value) -> (Name -> ElabM a) -> ElabM a
  46. defineInternal nm vty val k =
  47. do
  48. env <- ask
  49. let (env', name') = go env
  50. local (const env') (k name')
  51. where
  52. go x =
  53. let
  54. nm' = case Map.lookup (getNameText nm) (nameMap x) of
  55. Just name -> incName nm name
  56. Nothing -> nm
  57. in ( x { getEnv = Map.insert nm' (vty, val nm') (getEnv x)
  58. , nameMap = Map.insert (getNameText nm) nm' (nameMap x)
  59. , whereBound = maybe (whereBound x) (flip (Map.insert nm') (whereBound x)) (currentSpan x)
  60. }
  61. , nm')
  62. redefine :: Name -> Value -> Value -> ElabM a -> ElabM a
  63. redefine nm vty val = local go where
  64. go x = x { getEnv = Map.insert nm (vty, val) (getEnv x)
  65. , nameMap = Map.insert (getNameText nm) nm (nameMap x)
  66. , whereBound = maybe (whereBound x) (flip (Map.insert nm) (whereBound x)) (currentSpan x)
  67. }
  68. getValue :: Name -> ElabM Value
  69. getValue nm = do
  70. vl <- asks (Map.lookup nm . getEnv)
  71. case vl of
  72. Just v -> pure (snd v)
  73. Nothing -> throwElab $ NotInScope nm
  74. getNfType :: Name -> ElabM NFType
  75. getNfType nm = do
  76. vl <- asks (Map.lookup nm . getEnv)
  77. case vl of
  78. Just v -> pure (fst v)
  79. Nothing -> throwElab $ NotInScope nm
  80. getNameFor :: Text -> ElabM Name
  81. getNameFor x = do
  82. vl <- asks (Map.lookup x . nameMap)
  83. case vl of
  84. Just v -> pure v
  85. Nothing -> liftIO . throwIO $ NotInScope (Bound x 0)
  86. switch :: ElabM a -> ElabM a
  87. switch k =
  88. do
  89. depth <- asks pingPong
  90. when (depth >= 128) $ throwElab StackOverflow
  91. local go k
  92. where go e = e { pingPong = pingPong e + 1 }
  93. newtype NotInScope = NotInScope { nameNotInScope :: Name }
  94. deriving (Show, Typeable)
  95. deriving anyclass (Exception)
  96. data AttachedNote = AttachedNote { getNote :: Doc AnsiStyle, getExc :: SomeException }
  97. deriving (Show, Typeable)
  98. deriving anyclass (Exception)
  99. withNote :: ElabM a -> Doc AnsiStyle -> ElabM a
  100. withNote k note = do
  101. env <- ask
  102. liftIO $
  103. runElab k env
  104. `catch` \e -> throwIO (AttachedNote note e)
  105. data WhileChecking = WhileChecking { startPos :: P.Posn, endPos :: P.Posn, exc :: SomeException }
  106. deriving (Show, Typeable, Exception)
  107. withSpan :: P.Posn -> P.Posn -> ElabM a -> ElabM a
  108. withSpan a b k = do
  109. env <- ask
  110. liftIO $
  111. runElab k env{ currentSpan = Just (a, b) }
  112. `catches` [ Handler $ \e@WhileChecking{} -> throwIO e
  113. , Handler $ \e -> throwIO (WhileChecking a b e)
  114. ]
  115. data SeeAlso = SeeAlso { saStartPos :: P.Posn, saEndPos :: P.Posn, saExc :: SomeException }
  116. deriving (Show, Typeable, Exception)
  117. seeAlso :: ElabM a -> Name -> ElabM a
  118. seeAlso k nm = do
  119. env <- ask
  120. case Map.lookup nm (whereBound env) of
  121. Just l ->
  122. liftIO $ runElab k env
  123. `catch` \e -> throwIO (SeeAlso (fst l) (snd l) e)
  124. Nothing -> k
  125. catchElab :: Exception e => ElabM a -> (e -> ElabM a) -> ElabM a
  126. catchElab k h = do
  127. env <- ask
  128. liftIO $ runElab k env `catch` \e -> runElab (h e) env
  129. tryElab :: Exception e => ElabM a -> ElabM (Either e a)
  130. tryElab k = do
  131. env <- ask
  132. liftIO $ (Right <$> runElab k env) `catch` \e -> pure (Left e)
  133. throwElab :: Exception e => e -> ElabM a
  134. throwElab = liftIO . throwIO
  135. incName :: Name -> Name -> Name
  136. incName (Bound x _) n = Bound x (getNameNum n + 1)
  137. incName (Defined x _) n = Defined x (getNameNum n + 1)