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.

172 lines
5.2 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. , 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. makeLetDef :: Name -> Value -> Value -> (Name -> ElabM a) -> ElabM a
  40. makeLetDef nm vty val = defineInternal nm vty (\nm -> GluedVl (HVar nm) mempty val)
  41. assumes :: [Name] -> Value -> ([Name] -> ElabM a) -> ElabM a
  42. assumes nms ty k = do
  43. let
  44. go acc [] k = k acc
  45. go acc (x:xs) k = assume x ty $ \n -> go (n:acc) xs k
  46. in go [] nms k
  47. defineInternal :: Name -> Value -> (Name -> Value) -> (Name -> ElabM a) -> ElabM a
  48. defineInternal nm vty val k =
  49. do
  50. env <- ask
  51. let (env', name') = go env
  52. local (const env') (k name')
  53. where
  54. go x =
  55. let
  56. nm' = case Map.lookup (getNameText nm) (nameMap x) of
  57. Just name -> incName nm name
  58. Nothing -> nm
  59. in ( x { getEnv = Map.insert nm' (vty, val nm') (getEnv x)
  60. , nameMap = Map.insert (getNameText nm) nm' (nameMap x)
  61. , whereBound = maybe (whereBound x) (flip (Map.insert nm') (whereBound x)) (currentSpan x)
  62. }
  63. , nm')
  64. redefine :: Name -> Value -> Value -> ElabM a -> ElabM a
  65. redefine nm vty val = local go where
  66. go x = x { getEnv = Map.insert nm (vty, val) (getEnv x)
  67. , nameMap = Map.insert (getNameText nm) nm (nameMap x)
  68. , whereBound = maybe (whereBound x) (flip (Map.insert nm) (whereBound x)) (currentSpan x)
  69. }
  70. getValue :: Name -> ElabM Value
  71. getValue nm = do
  72. vl <- asks (Map.lookup nm . getEnv)
  73. case vl of
  74. Just v -> pure (snd v)
  75. Nothing -> throwElab $ NotInScope nm
  76. getNfType :: Name -> ElabM NFType
  77. getNfType nm = do
  78. vl <- asks (Map.lookup nm . getEnv)
  79. case vl of
  80. Just v -> pure (fst v)
  81. Nothing -> throwElab $ NotInScope nm
  82. getNameFor :: Text -> ElabM Name
  83. getNameFor x = do
  84. vl <- asks (Map.lookup x . nameMap)
  85. case vl of
  86. Just v -> pure v
  87. Nothing -> liftIO . throwIO $ NotInScope (Bound x 0)
  88. switch :: ElabM a -> ElabM a
  89. switch k =
  90. do
  91. depth <- asks pingPong
  92. when (depth >= 128) $ throwElab StackOverflow
  93. local go k
  94. where go e = e { pingPong = pingPong e + 1 }
  95. newtype NotInScope = NotInScope { nameNotInScope :: Name }
  96. deriving (Show, Typeable)
  97. deriving anyclass (Exception)
  98. data AttachedNote = AttachedNote { getNote :: Doc AnsiStyle, getExc :: SomeException }
  99. deriving (Show, Typeable)
  100. deriving anyclass (Exception)
  101. withNote :: ElabM a -> Doc AnsiStyle -> ElabM a
  102. withNote k note = do
  103. env <- ask
  104. liftIO $
  105. runElab k env
  106. `catch` \e -> throwIO (AttachedNote note e)
  107. data WhileChecking = WhileChecking { startPos :: P.Posn, endPos :: P.Posn, exc :: SomeException }
  108. deriving (Show, Typeable, Exception)
  109. withSpan :: P.Posn -> P.Posn -> ElabM a -> ElabM a
  110. withSpan a b k = do
  111. env <- ask
  112. liftIO $
  113. runElab k env{ currentSpan = Just (a, b) }
  114. `catches` [ Handler $ \e@WhileChecking{} -> throwIO e
  115. , Handler $ \e -> throwIO (WhileChecking a b e)
  116. ]
  117. data SeeAlso = SeeAlso { saStartPos :: P.Posn, saEndPos :: P.Posn, saExc :: SomeException }
  118. deriving (Show, Typeable, Exception)
  119. seeAlso :: ElabM a -> Name -> ElabM a
  120. seeAlso k nm = do
  121. env <- ask
  122. case Map.lookup nm (whereBound env) of
  123. Just l ->
  124. liftIO $ runElab k env
  125. `catch` \e -> throwIO (SeeAlso (fst l) (snd l) e)
  126. Nothing -> k
  127. catchElab :: Exception e => ElabM a -> (e -> ElabM a) -> ElabM a
  128. catchElab k h = do
  129. env <- ask
  130. liftIO $ runElab k env `catch` \e -> runElab (h e) env
  131. tryElab :: Exception e => ElabM a -> ElabM (Either e a)
  132. tryElab k = do
  133. env <- ask
  134. liftIO $ (Right <$> runElab k env) `catch` \e -> pure (Left e)
  135. throwElab :: Exception e => e -> ElabM a
  136. throwElab = liftIO . throwIO
  137. incName :: Name -> Name -> Name
  138. incName (Bound x _) n = Bound x (getNameNum n + 1)
  139. incName (Defined x _) n = Defined x (getNameNum n + 1)
  140. incName (ConName x _ s a) n = ConName x (getNameNum n + 1) s a