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.

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