mirror of
https://github.com/anoma/juvix.git
synced 2024-11-30 14:13:27 +03:00
Support module imports in Juvix REPL (#2029)
This PR adds support for importing modules from within a Juvix project in the Juvix REPL. The imported module is checked (parsed, arity-checked, type-checked etc) as normal and added to the REPL session scope. Any errors during the checking phase is reported to the user. ### Notes: * You must load a file before using `import`. This is because the REPL needs to know which Juvix project is active. * You may only import modules from within the same Juvix project. ### Examples After launching `juvix repl`: #### `open import` ``` Stdlib.Prelude> open import Stdlib.Data.Int.Ord Stdlib.Prelude> 1 == 1 true ``` #### `import as` ``` Stdlib.Prelude> import Stdlib.Data.Int.Ord as Int Stdlib.Prelude> 1 Int.== 1 true ``` #### `import`then `open` ``` Stdlib.Prelude> import Stdlib.Data.Int.Ord as Int Stdlib.Prelude> open Int Stdlib.Prelude> 1 == 1 true ``` #### Line-terminating semicolons are ignored: ``` Stdlib.Prelude> import Stdlib.Data.Int.Ord as Int;;;;; Stdlib.Prelude> 1 Int.== 1 true ``` * Closes https://github.com/anoma/juvix/issues/1951 --------- Co-authored-by: Jonathan Cubides <jonathan.cubides@uib.no>
This commit is contained in:
parent
70f27fcede
commit
6894300e5a
@ -22,6 +22,7 @@ import Juvix.Compiler.Core.Transformation qualified as Core
|
||||
import Juvix.Compiler.Core.Transformation.DisambiguateNames (disambiguateNames)
|
||||
import Juvix.Compiler.Internal.Language qualified as Internal
|
||||
import Juvix.Compiler.Internal.Pretty qualified as Internal
|
||||
import Juvix.Compiler.Pipeline.Repl
|
||||
import Juvix.Compiler.Pipeline.Setup (entrySetup)
|
||||
import Juvix.Data.Error.GenericError qualified as Error
|
||||
import Juvix.Extra.Paths
|
||||
@ -157,20 +158,26 @@ runCommand opts = do
|
||||
evalRes <- compileThenEval ctx' input
|
||||
case evalRes of
|
||||
Left err -> printError err
|
||||
Right n
|
||||
Right (Just n)
|
||||
| Info.member Info.kNoDisplayInfo (Core.getInfo n) -> return ()
|
||||
Right n
|
||||
Right (Just n)
|
||||
| opts ^. replPrintValues ->
|
||||
renderOut (Core.ppOut opts (toValue tab n))
|
||||
| otherwise ->
|
||||
renderOut (Core.ppOut opts n)
|
||||
Right Nothing -> return ()
|
||||
Nothing -> noFileLoadedMsg
|
||||
where
|
||||
defaultLoc :: Interval
|
||||
defaultLoc = singletonInterval (mkInitialLoc replPath)
|
||||
|
||||
compileThenEval :: ReplContext -> String -> Repl (Either JuvixError Core.Node)
|
||||
compileThenEval ctx s = bindEither compileString eval
|
||||
compileThenEval :: ReplContext -> String -> Repl (Either JuvixError (Maybe Core.Node))
|
||||
compileThenEval ctx s = do
|
||||
mn <- compileString
|
||||
case mn of
|
||||
Left err -> return (Left err)
|
||||
Right Nothing -> return (Right Nothing)
|
||||
Right (Just n) -> fmap Just <$> eval n
|
||||
where
|
||||
artif :: Artifacts
|
||||
artif = ctx ^. replContextArtifacts
|
||||
@ -195,21 +202,22 @@ runCommand opts = do
|
||||
mapLeft (JuvixError @Core.CoreError)
|
||||
<$> doEvalIO False defaultLoc (artif' ^. artifactCoreTable) n
|
||||
|
||||
compileString :: Repl (Either JuvixError Core.Node)
|
||||
compileString = liftIO $ compileExpressionIO' ctx (strip (pack s))
|
||||
|
||||
bindEither :: (Monad m) => m (Either e a) -> (a -> m (Either e b)) -> m (Either e b)
|
||||
bindEither x f = join <$> (x >>= mapM f)
|
||||
compileString :: Repl (Either JuvixError (Maybe Core.Node))
|
||||
compileString = do
|
||||
(artifacts, res) <- liftIO $ compileReplInputIO' ctx (strip (pack s))
|
||||
State.modify (over (replStateContext . _Just) (set replContextArtifacts artifacts))
|
||||
return res
|
||||
|
||||
core :: String -> Repl ()
|
||||
core input = Repline.dontCrash $ do
|
||||
ctx <- State.gets (^. replStateContext)
|
||||
case ctx of
|
||||
Just ctx' -> do
|
||||
compileRes <- liftIO (compileExpressionIO' ctx' (strip (pack input)))
|
||||
compileRes <- snd <$> liftIO (compileReplInputIO' ctx' (strip (pack input)))
|
||||
case compileRes of
|
||||
Left err -> printError err
|
||||
Right n -> renderOut (Core.ppOut opts n)
|
||||
Right (Just n) -> renderOut (Core.ppOut opts n)
|
||||
Right Nothing -> return ()
|
||||
Nothing -> noFileLoadedMsg
|
||||
|
||||
inferType :: String -> Repl ()
|
||||
@ -337,13 +345,23 @@ inferExpressionIO' :: ReplContext -> Text -> IO (Either JuvixError Internal.Expr
|
||||
inferExpressionIO' ctx txt =
|
||||
runM
|
||||
. evalState (ctx ^. replContextArtifacts)
|
||||
. runReader (ctx ^. replContextEntryPoint)
|
||||
$ inferExpressionIO replPath txt
|
||||
|
||||
compileExpressionIO' :: ReplContext -> Text -> IO (Either JuvixError Core.Node)
|
||||
compileExpressionIO' ctx txt =
|
||||
compileReplInputIO' :: ReplContext -> Text -> IO (Artifacts, (Either JuvixError (Maybe Core.Node)))
|
||||
compileReplInputIO' ctx txt =
|
||||
runM
|
||||
. evalState (ctx ^. replContextArtifacts)
|
||||
$ compileExpressionIO replPath txt
|
||||
. runState (ctx ^. replContextArtifacts)
|
||||
. runReader (ctx ^. replContextEntryPoint)
|
||||
$ do
|
||||
r <- compileReplInputIO replPath txt
|
||||
return (extractNode <$> r)
|
||||
where
|
||||
extractNode :: ReplPipelineResult -> Maybe Core.Node
|
||||
extractNode = \case
|
||||
ReplPipelineResultNode n -> Just n
|
||||
ReplPipelineResultImport {} -> Nothing
|
||||
ReplPipelineResultOpenImport {} -> Nothing
|
||||
|
||||
render' :: (P.HasAnsiBackend a, P.HasTextBackend a) => a -> Repl ()
|
||||
render' t = do
|
||||
|
@ -64,5 +64,8 @@ toState = reinterpret $ \case
|
||||
runInfoTableBuilder :: Sem (InfoTableBuilder ': r) a -> Sem r (InfoTable, a)
|
||||
runInfoTableBuilder = runState emptyInfoTable . toState
|
||||
|
||||
runInfoTableBuilder' :: InfoTable -> Sem (InfoTableBuilder ': r) a -> Sem r (InfoTable, a)
|
||||
runInfoTableBuilder' t = runState t . toState
|
||||
|
||||
ignoreInfoTableBuilder :: Sem (InfoTableBuilder ': r) a -> Sem r a
|
||||
ignoreInfoTableBuilder = fmap snd . runInfoTableBuilder
|
||||
|
@ -17,21 +17,16 @@ import Juvix.Compiler.Concrete.Translation.FromParsed.Analysis.Scoping.Error
|
||||
import Juvix.Data.NameKind
|
||||
import Juvix.Prelude
|
||||
|
||||
newtype ModulesCache = ModulesCache
|
||||
{_cachedModules :: HashMap S.NameId Abstract.TopModule}
|
||||
|
||||
makeLenses ''ModulesCache
|
||||
|
||||
unsupported :: Text -> a
|
||||
unsupported msg = error $ msg <> "Scoped to Abstract: not yet supported"
|
||||
|
||||
fromConcrete :: (Members '[Error JuvixError, Builtins, NameIdGen] r) => Scoper.ScoperResult -> Sem r AbstractResult
|
||||
fromConcrete _resultScoper =
|
||||
mapError (JuvixError @ScoperError) $ do
|
||||
(_resultTable, _resultModules) <-
|
||||
(_resultTable, (_resultModulesCache, _resultModules)) <-
|
||||
runInfoTableBuilder $
|
||||
runReader @Pragmas mempty $
|
||||
evalState (ModulesCache mempty) $
|
||||
runState (ModulesCache mempty) $
|
||||
mapM goTopModule ms
|
||||
let _resultExports = _resultScoper ^. Scoper.resultExports
|
||||
return AbstractResult {..}
|
||||
@ -41,6 +36,18 @@ fromConcrete _resultScoper =
|
||||
fromConcreteExpression :: (Members '[Error JuvixError, NameIdGen] r) => Scoper.Expression -> Sem r Abstract.Expression
|
||||
fromConcreteExpression = mapError (JuvixError @ScoperError) . ignoreInfoTableBuilder . runReader @Pragmas mempty . goExpression
|
||||
|
||||
fromConcreteImport ::
|
||||
Members '[Error JuvixError, NameIdGen, Builtins, InfoTableBuilder, State ModulesCache] r =>
|
||||
Scoper.Import 'Scoped ->
|
||||
Sem r Abstract.TopModule
|
||||
fromConcreteImport = mapError (JuvixError @ScoperError) . runReader @Pragmas mempty . goImport
|
||||
|
||||
fromConcreteOpenImport ::
|
||||
Members '[Error JuvixError, NameIdGen, Builtins, InfoTableBuilder, State ModulesCache] r =>
|
||||
Scoper.OpenModule 'Scoped ->
|
||||
Sem r (Maybe Abstract.TopModule)
|
||||
fromConcreteOpenImport = mapError (JuvixError @ScoperError) . runReader @Pragmas mempty . goOpenModule'
|
||||
|
||||
goTopModule ::
|
||||
(Members '[InfoTableBuilder, Error ScoperError, Builtins, NameIdGen, Reader Pragmas, State ModulesCache] r) =>
|
||||
Module 'Scoped 'ModuleTop ->
|
||||
@ -146,6 +153,13 @@ goModuleBody ss' = do
|
||||
sigs :: [Indexed (TypeSignature 'Scoped)]
|
||||
sigs = [Indexed i t | (Indexed i (StatementTypeSignature t)) <- ss]
|
||||
|
||||
goImport ::
|
||||
forall r.
|
||||
(Members '[InfoTableBuilder, Error ScoperError, Builtins, NameIdGen, State ModulesCache, Reader Pragmas] r) =>
|
||||
Import 'Scoped ->
|
||||
Sem r Abstract.TopModule
|
||||
goImport t = goModule (t ^. importModule . moduleRefModule)
|
||||
|
||||
goStatement ::
|
||||
forall r.
|
||||
(Members '[InfoTableBuilder, Error ScoperError, Builtins, NameIdGen, Reader Pragmas, State ModulesCache] r) =>
|
||||
@ -154,7 +168,7 @@ goStatement ::
|
||||
goStatement (Indexed idx s) =
|
||||
fmap (Indexed idx) <$> case s of
|
||||
StatementAxiom d -> Just . Abstract.StatementAxiom <$> goAxiom d
|
||||
StatementImport t -> Just . Abstract.StatementImport <$> goModule (t ^. importModule . moduleRefModule)
|
||||
StatementImport t -> Just . Abstract.StatementImport <$> goImport t
|
||||
StatementOperator {} -> return Nothing
|
||||
StatementOpenModule o -> goOpenModule o
|
||||
StatementInductive i -> Just . Abstract.StatementInductive <$> goInductive i
|
||||
@ -162,19 +176,24 @@ goStatement (Indexed idx s) =
|
||||
StatementTypeSignature {} -> return Nothing
|
||||
StatementFunctionClause {} -> return Nothing
|
||||
|
||||
goOpenModule' ::
|
||||
forall r.
|
||||
(Members '[InfoTableBuilder, Error ScoperError, Builtins, NameIdGen, State ModulesCache, Reader Pragmas] r) =>
|
||||
OpenModule 'Scoped ->
|
||||
Sem r (Maybe Abstract.TopModule)
|
||||
goOpenModule' o
|
||||
| isJust (o ^. openModuleImportKw) =
|
||||
case o ^. openModuleName of
|
||||
ModuleRef' (SModuleTop :&: m) -> Just <$> goModule (m ^. moduleRefModule)
|
||||
_ -> impossible
|
||||
| otherwise = return Nothing
|
||||
|
||||
goOpenModule ::
|
||||
forall r.
|
||||
(Members '[InfoTableBuilder, Error ScoperError, Builtins, NameIdGen, Reader Pragmas, State ModulesCache] r) =>
|
||||
OpenModule 'Scoped ->
|
||||
Sem r (Maybe Abstract.Statement)
|
||||
goOpenModule o
|
||||
| isJust (o ^. openModuleImportKw) =
|
||||
case o ^. openModuleName of
|
||||
ModuleRef' (SModuleTop :&: m) ->
|
||||
Just . Abstract.StatementImport
|
||||
<$> goModule (m ^. moduleRefModule)
|
||||
_ -> impossible
|
||||
| otherwise = return Nothing
|
||||
goOpenModule o = fmap Abstract.StatementImport <$> goOpenModule' o
|
||||
|
||||
goLetFunctionDef ::
|
||||
(Members '[InfoTableBuilder, Reader Pragmas, Error ScoperError] r) =>
|
||||
|
@ -6,19 +6,26 @@ where
|
||||
|
||||
import Juvix.Compiler.Abstract.Data.InfoTable
|
||||
import Juvix.Compiler.Abstract.Language
|
||||
import Juvix.Compiler.Abstract.Language qualified as Abstract
|
||||
import Juvix.Compiler.Concrete.Data.ScopedName qualified as S
|
||||
import Juvix.Compiler.Concrete.Translation.FromParsed qualified as Concrete
|
||||
import Juvix.Compiler.Concrete.Translation.FromSource qualified as Concrete
|
||||
import Juvix.Compiler.Pipeline.EntryPoint qualified as E
|
||||
import Juvix.Prelude
|
||||
|
||||
newtype ModulesCache = ModulesCache
|
||||
{_cachedModules :: HashMap S.NameId Abstract.TopModule}
|
||||
|
||||
data AbstractResult = AbstractResult
|
||||
{ _resultScoper :: Concrete.ScoperResult,
|
||||
_resultTable :: InfoTable,
|
||||
_resultModules :: NonEmpty TopModule,
|
||||
_resultExports :: HashSet NameId
|
||||
_resultExports :: HashSet NameId,
|
||||
_resultModulesCache :: ModulesCache
|
||||
}
|
||||
|
||||
makeLenses ''AbstractResult
|
||||
makeLenses ''ModulesCache
|
||||
|
||||
abstractResultEntryPoint :: Lens' AbstractResult E.EntryPoint
|
||||
abstractResultEntryPoint = resultScoper . Concrete.resultParserResult . Concrete.resultEntry
|
||||
|
@ -1,18 +1,4 @@
|
||||
module Juvix.Compiler.Concrete.Data.ParsedInfoTableBuilder
|
||||
( InfoTableBuilder,
|
||||
registerLiteral,
|
||||
registerDelimiter,
|
||||
registerKeyword,
|
||||
registerJudocText,
|
||||
registerPragmas,
|
||||
registerSpaceSpan,
|
||||
registerModule,
|
||||
moduleVisited,
|
||||
visitModule,
|
||||
runParserInfoTableBuilder,
|
||||
module Juvix.Compiler.Concrete.Data.ParsedInfoTable,
|
||||
)
|
||||
where
|
||||
module Juvix.Compiler.Concrete.Data.ParsedInfoTableBuilder where
|
||||
|
||||
import Data.HashMap.Strict qualified as HashMap
|
||||
import Data.HashSet qualified as HashSet
|
||||
@ -108,10 +94,9 @@ build st =
|
||||
registerItem' :: Members '[State BuilderState] r => ParsedItem -> Sem r ()
|
||||
registerItem' i = modify' (over stateItems (i :))
|
||||
|
||||
runParserInfoTableBuilder :: Sem (InfoTableBuilder ': r) a -> Sem r (InfoTable, a)
|
||||
runParserInfoTableBuilder =
|
||||
fmap (first build)
|
||||
. runState iniState
|
||||
runParserInfoTableBuilder' :: BuilderState -> Sem (InfoTableBuilder ': r) a -> Sem r (BuilderState, a)
|
||||
runParserInfoTableBuilder' s =
|
||||
runState s
|
||||
. reinterpret
|
||||
( \case
|
||||
ModuleVisited i -> HashSet.member i <$> gets (^. stateVisited)
|
||||
@ -129,3 +114,8 @@ runParserInfoTableBuilder =
|
||||
_parsedTag = ParsedTagComment
|
||||
}
|
||||
)
|
||||
|
||||
runParserInfoTableBuilder :: Sem (InfoTableBuilder ': r) a -> Sem r (BuilderState, InfoTable, a)
|
||||
runParserInfoTableBuilder m = do
|
||||
(builderState, x) <- runParserInfoTableBuilder' iniState m
|
||||
return (builderState, build builderState, x)
|
||||
|
@ -14,7 +14,6 @@ import Data.List.NonEmpty qualified as NonEmpty
|
||||
import Juvix.Compiler.Concrete.Data.InfoTableBuilder
|
||||
import Juvix.Compiler.Concrete.Data.Name qualified as N
|
||||
import Juvix.Compiler.Concrete.Data.Scope
|
||||
import Juvix.Compiler.Concrete.Data.Scope qualified as S
|
||||
import Juvix.Compiler.Concrete.Data.ScopedName qualified as S
|
||||
import Juvix.Compiler.Concrete.Extra qualified as P
|
||||
import Juvix.Compiler.Concrete.Language
|
||||
@ -58,25 +57,24 @@ scopeCheck pr modules =
|
||||
_resultScoperTable = st,
|
||||
_resultModules = ms,
|
||||
_resultExports = exp,
|
||||
_resultScope = scoperSt ^. scoperScope
|
||||
_resultScope = scoperSt ^. scoperScope,
|
||||
_resultScoperState = scoperSt
|
||||
}
|
||||
|
||||
scopeCheckExpression ::
|
||||
forall r.
|
||||
(Members '[Error JuvixError, NameIdGen] r) =>
|
||||
(Members '[Error JuvixError, NameIdGen, State Scope] r) =>
|
||||
InfoTable ->
|
||||
S.Scope ->
|
||||
ExpressionAtoms 'Parsed ->
|
||||
Sem r Expression
|
||||
scopeCheckExpression tab scope as = mapError (JuvixError @ScoperError) $ do
|
||||
scopeCheckExpression tab as = mapError (JuvixError @ScoperError) $ do
|
||||
snd
|
||||
<$> runInfoTableBuilder
|
||||
tab
|
||||
( runReader iniScopeParameters $
|
||||
evalState iniScoperState $
|
||||
evalState scope $
|
||||
withLocalScope $
|
||||
checkParseExpressionAtoms as
|
||||
withLocalScope $
|
||||
checkParseExpressionAtoms as
|
||||
)
|
||||
where
|
||||
iniScopeParameters :: ScopeParameters
|
||||
@ -92,6 +90,20 @@ checkParseExpressionAtoms' ::
|
||||
Sem r Expression
|
||||
checkParseExpressionAtoms' = checkExpressionAtoms >=> parseExpressionAtoms
|
||||
|
||||
scopeCheckImport ::
|
||||
forall r.
|
||||
Members '[Error JuvixError, InfoTableBuilder, NameIdGen, State Scope, Reader ScopeParameters, State ScoperState] r =>
|
||||
Import 'Parsed ->
|
||||
Sem r (Import 'Scoped)
|
||||
scopeCheckImport i = mapError (JuvixError @ScoperError) $ checkImport i
|
||||
|
||||
scopeCheckOpenModule ::
|
||||
forall r.
|
||||
Members '[Error JuvixError, InfoTableBuilder, NameIdGen, State Scope, Reader ScopeParameters, State ScoperState] r =>
|
||||
OpenModule 'Parsed ->
|
||||
Sem r (OpenModule 'Scoped)
|
||||
scopeCheckOpenModule i = mapError (JuvixError @ScoperError) $ checkOpenModule i
|
||||
|
||||
freshVariable :: Members '[NameIdGen, State ScoperFixities, State Scope, State ScoperState] r => Symbol -> Sem r S.Symbol
|
||||
freshVariable = freshSymbol S.KNameLocal
|
||||
|
||||
@ -316,7 +328,7 @@ lookInExport sym remaining e = case remaining of
|
||||
-- modules due to nesting.
|
||||
lookupQualifiedSymbol ::
|
||||
forall r.
|
||||
Members '[State Scope, State ScoperState] r =>
|
||||
Members '[State Scope] r =>
|
||||
([Symbol], Symbol) ->
|
||||
Sem r [SymbolEntry]
|
||||
lookupQualifiedSymbol (path, sym) = do
|
||||
|
@ -17,7 +17,8 @@ data ScoperResult = ScoperResult
|
||||
_resultScoperTable :: InfoTable,
|
||||
_resultModules :: NonEmpty (Module 'Scoped 'ModuleTop),
|
||||
_resultExports :: HashSet NameId,
|
||||
_resultScope :: HashMap TopModulePath Scope
|
||||
_resultScope :: HashMap TopModulePath Scope,
|
||||
_resultScoperState :: ScoperState
|
||||
}
|
||||
|
||||
makeLenses ''ScoperResult
|
||||
|
@ -39,7 +39,7 @@ fromSource ::
|
||||
EntryPoint ->
|
||||
Sem r ParserResult
|
||||
fromSource e = mapError (JuvixError @ParserError) $ do
|
||||
(_resultTable, _resultModules) <- runParserInfoTableBuilder (runReader e getParsedModuleTops)
|
||||
(_resultBuilderState, _resultTable, _resultModules) <- runParserInfoTableBuilder (runReader e getParsedModuleTops)
|
||||
let _resultEntry = e
|
||||
return ParserResult {..}
|
||||
where
|
||||
@ -78,6 +78,11 @@ fromSource e = mapError (JuvixError @ParserError) $ do
|
||||
return txt
|
||||
| otherwise = readFile' fp
|
||||
|
||||
data ReplInput
|
||||
= ReplExpression (ExpressionAtoms 'Parsed)
|
||||
| ReplImport (Import 'Parsed)
|
||||
| ReplOpenImport (OpenModule 'Parsed)
|
||||
|
||||
expressionFromTextSource ::
|
||||
Members '[Error JuvixError, NameIdGen] r =>
|
||||
Path Abs File ->
|
||||
@ -89,6 +94,27 @@ expressionFromTextSource fp txt = mapError (JuvixError @ParserError) $ do
|
||||
Left e -> throw e
|
||||
Right exp' -> return exp'
|
||||
|
||||
replInputFromTextSource ::
|
||||
Members '[Error JuvixError, NameIdGen, Files, PathResolver, InfoTableBuilder] r =>
|
||||
Path Abs File ->
|
||||
Text ->
|
||||
Sem r ReplInput
|
||||
replInputFromTextSource fp txt = mapError (JuvixError @ParserError) $ runReplInputParser fp txt
|
||||
|
||||
runReplInputParser ::
|
||||
Members '[Files, NameIdGen, Error ParserError, PathResolver, InfoTableBuilder] r =>
|
||||
Path Abs File ->
|
||||
Text ->
|
||||
Sem r ReplInput
|
||||
runReplInputParser fileName input = do
|
||||
m <-
|
||||
evalState (Nothing @ParsedPragmas) $
|
||||
evalState (Nothing @(Judoc 'Parsed)) $
|
||||
P.runParserT replInput (toFilePath fileName) input
|
||||
case m of
|
||||
Left err -> throw (ErrMegaparsec (MegaparsecError err))
|
||||
Right r -> return r
|
||||
|
||||
runModuleParser :: Members '[Error ParserError, Files, PathResolver, NameIdGen, InfoTableBuilder] r => Path Abs File -> Text -> Sem r (Either ParserError (Module 'Parsed 'ModuleTop))
|
||||
runModuleParser fileName input = do
|
||||
m <-
|
||||
@ -124,8 +150,8 @@ runExpressionParser fileName input = do
|
||||
evalState (Nothing @(Judoc 'Parsed)) $
|
||||
P.runParserT parseExpressionAtoms (toFilePath fileName) input
|
||||
case m of
|
||||
(_, Left err) -> return (Left (ErrMegaparsec (MegaparsecError err)))
|
||||
(_, Right r) -> return (Right r)
|
||||
(_, _, Left err) -> return (Left (ErrMegaparsec (MegaparsecError err)))
|
||||
(_, _, Right r) -> return (Right r)
|
||||
|
||||
-- | The first pipe is optional, and thus we need a `Maybe`. The rest of the elements are guaranted to be given a `Just`.
|
||||
pipeSep1 :: Member InfoTableBuilder r => (Irrelevant (Maybe KeywordRef) -> ParsecS r a) -> ParsecS r (NonEmpty a)
|
||||
@ -172,6 +198,13 @@ topModuleDef = do
|
||||
}
|
||||
)
|
||||
|
||||
replInput :: forall r. Members '[Files, PathResolver, InfoTableBuilder, JudocStash, NameIdGen, Error ParserError, State (Maybe ParsedPragmas)] r => ParsecS r ReplInput
|
||||
replInput =
|
||||
P.label "<repl input>" $
|
||||
(ReplExpression <$> parseExpressionAtoms)
|
||||
<|> (ReplImport <$> import_)
|
||||
<|> (ReplOpenImport <$> openModule)
|
||||
|
||||
--------------------------------------------------------------------------------
|
||||
-- Symbols and names
|
||||
--------------------------------------------------------------------------------
|
||||
|
@ -5,6 +5,7 @@ module Juvix.Compiler.Concrete.Translation.FromSource.Data.Context
|
||||
where
|
||||
|
||||
import Juvix.Compiler.Concrete.Data.ParsedInfoTable
|
||||
import Juvix.Compiler.Concrete.Data.ParsedInfoTableBuilder (BuilderState)
|
||||
import Juvix.Compiler.Concrete.Language
|
||||
import Juvix.Compiler.Pipeline.EntryPoint
|
||||
import Juvix.Prelude
|
||||
@ -12,8 +13,9 @@ import Juvix.Prelude
|
||||
data ParserResult = ParserResult
|
||||
{ _resultEntry :: EntryPoint,
|
||||
_resultTable :: InfoTable,
|
||||
_resultModules :: NonEmpty (Module 'Parsed 'ModuleTop)
|
||||
_resultModules :: NonEmpty (Module 'Parsed 'ModuleTop),
|
||||
_resultBuilderState :: BuilderState
|
||||
}
|
||||
deriving stock (Eq, Show)
|
||||
deriving stock (Show)
|
||||
|
||||
makeLenses ''ParserResult
|
||||
|
@ -1,10 +1,11 @@
|
||||
module Juvix.Compiler.Internal.Translation.FromAbstract
|
||||
( module Juvix.Compiler.Internal.Translation.FromAbstract.Data.Context,
|
||||
module Juvix.Compiler.Internal.Translation.FromAbstract.Analysis.Termination,
|
||||
TranslationState,
|
||||
TranslationState (..),
|
||||
iniState,
|
||||
fromAbstract,
|
||||
fromAbstractExpression,
|
||||
fromAbstractImport,
|
||||
)
|
||||
where
|
||||
|
||||
@ -76,6 +77,12 @@ fromAbstractExpression e = runReader depInfo (goExpression e)
|
||||
depInfo :: NameDependencyInfo
|
||||
depInfo = buildDependencyInfoExpr e
|
||||
|
||||
fromAbstractImport ::
|
||||
Members '[Reader ExportsTable, State TranslationState, NameIdGen] r =>
|
||||
Abstract.TopModule ->
|
||||
Sem r (Maybe Include)
|
||||
fromAbstractImport = goImport
|
||||
|
||||
goModule ::
|
||||
(Members '[Reader ExportsTable, State TranslationState, NameIdGen] r) =>
|
||||
Abstract.TopModule ->
|
||||
|
@ -5,6 +5,8 @@ module Juvix.Compiler.Internal.Translation.FromInternal
|
||||
typeCheckExpression,
|
||||
arityCheckExpression,
|
||||
inferExpressionType,
|
||||
arityCheckInclude,
|
||||
typeCheckInclude,
|
||||
)
|
||||
where
|
||||
|
||||
@ -47,6 +49,17 @@ arityCheckExpression exp = do
|
||||
. runNameIdGenArtifacts
|
||||
$ ArityChecking.inferReplExpression exp
|
||||
|
||||
arityCheckInclude ::
|
||||
Members '[Error JuvixError, State Artifacts] r =>
|
||||
Include ->
|
||||
Sem r Include
|
||||
arityCheckInclude i = do
|
||||
let table = buildTable [i ^. includeModule]
|
||||
mapError (JuvixError @ArityChecking.ArityCheckerError)
|
||||
$ runReader table
|
||||
. runNameIdGenArtifacts
|
||||
$ ArityChecking.checkInclude i
|
||||
|
||||
typeCheckExpressionType ::
|
||||
forall r.
|
||||
(Members '[Error JuvixError, State Artifacts] r) =>
|
||||
@ -71,6 +84,23 @@ typeCheckExpression ::
|
||||
Sem r Expression
|
||||
typeCheckExpression exp = (^. typedExpression) <$> typeCheckExpressionType exp
|
||||
|
||||
typeCheckInclude ::
|
||||
Members '[Reader EntryPoint, Error JuvixError, State Artifacts] r =>
|
||||
Include ->
|
||||
Sem r Include
|
||||
typeCheckInclude i = do
|
||||
let table = buildTable [i ^. includeModule]
|
||||
modify (set artifactInternalTypedTable table)
|
||||
mapError (JuvixError @TypeCheckerError)
|
||||
$ runTypesTableArtifacts
|
||||
. runFunctionsTableArtifacts
|
||||
. runBuiltinsArtifacts
|
||||
. runNameIdGenArtifacts
|
||||
. ignoreOutput @Example
|
||||
. runReader table
|
||||
. withEmptyVars
|
||||
$ checkInclude i
|
||||
|
||||
inferExpressionType ::
|
||||
(Members '[Error JuvixError, State Artifacts] r) =>
|
||||
Expression ->
|
||||
|
@ -15,11 +15,14 @@ import Juvix.Compiler.Backend qualified as Backend
|
||||
import Juvix.Compiler.Backend.C qualified as C
|
||||
import Juvix.Compiler.Backend.Geb qualified as Geb
|
||||
import Juvix.Compiler.Builtins
|
||||
import Juvix.Compiler.Concrete.Data.ParsedInfoTableBuilder qualified as Concrete
|
||||
import Juvix.Compiler.Concrete.Data.Scope
|
||||
import Juvix.Compiler.Concrete.Language
|
||||
import Juvix.Compiler.Concrete.Translation.FromParsed qualified as Scoper
|
||||
import Juvix.Compiler.Concrete.Translation.FromParsed.Analysis.PathResolver
|
||||
import Juvix.Compiler.Concrete.Translation.FromParsed.Analysis.PathResolver qualified as PathResolver
|
||||
import Juvix.Compiler.Concrete.Translation.FromParsed.Analysis.Scoping.Data.Context qualified as Scoped
|
||||
import Juvix.Compiler.Concrete.Translation.FromSource qualified as P
|
||||
import Juvix.Compiler.Concrete.Translation.FromSource qualified as Parser
|
||||
import Juvix.Compiler.Core qualified as Core
|
||||
import Juvix.Compiler.Core.Translation.Stripped.FromCore qualified as Stripped
|
||||
@ -38,80 +41,6 @@ type PipelineEff = '[PathResolver, Reader EntryPoint, Files, NameIdGen, Builtins
|
||||
|
||||
type TopPipelineEff = '[PathResolver, Reader EntryPoint, Files, NameIdGen, Builtins, State Artifacts, Error JuvixError, Embed IO]
|
||||
|
||||
arityCheckExpression ::
|
||||
Members '[Error JuvixError, State Artifacts] r =>
|
||||
Path Abs File ->
|
||||
Text ->
|
||||
Sem r Internal.Expression
|
||||
arityCheckExpression fp txt = do
|
||||
mainScope <- fromJust <$> gets (^. artifactMainModuleScope)
|
||||
scopeTable <- gets (^. artifactScopeTable)
|
||||
( runNameIdGenArtifacts
|
||||
. runBuiltinsArtifacts
|
||||
)
|
||||
$ Parser.expressionFromTextSource fp txt
|
||||
>>= Scoper.scopeCheckExpression scopeTable mainScope
|
||||
>>= Abstract.fromConcreteExpression
|
||||
>>= Internal.fromAbstractExpression
|
||||
>>= Internal.arityCheckExpression
|
||||
|
||||
inferExpression ::
|
||||
Members '[Error JuvixError, State Artifacts] r =>
|
||||
Path Abs File ->
|
||||
Text ->
|
||||
Sem r Internal.Expression
|
||||
inferExpression fp txt =
|
||||
( runNameIdGenArtifacts
|
||||
. runBuiltinsArtifacts
|
||||
)
|
||||
$ arityCheckExpression fp txt
|
||||
>>= Internal.inferExpressionType
|
||||
|
||||
compileExpression ::
|
||||
Members '[Error JuvixError, State Artifacts] r =>
|
||||
Path Abs File ->
|
||||
Text ->
|
||||
Sem r Core.Node
|
||||
compileExpression fp txt =
|
||||
( runNameIdGenArtifacts
|
||||
. runBuiltinsArtifacts
|
||||
)
|
||||
$ arityCheckExpression fp txt
|
||||
>>= Internal.typeCheckExpression
|
||||
>>= fromInternalExpression
|
||||
|
||||
fromInternalExpression :: Members '[State Artifacts] r => Internal.Expression -> Sem r Core.Node
|
||||
fromInternalExpression exp = do
|
||||
typedTable <- gets (^. artifactInternalTypedTable)
|
||||
runReader typedTable
|
||||
. tmpCoreInfoTableBuilderArtifacts
|
||||
. runFunctionsTableArtifacts
|
||||
. readerTypesTableArtifacts
|
||||
. runReader Core.initIndexTable
|
||||
$ Core.goExpression exp
|
||||
|
||||
compileExpressionIO ::
|
||||
Members '[State Artifacts, Embed IO] r =>
|
||||
Path Abs File ->
|
||||
Text ->
|
||||
Sem r (Either JuvixError Core.Node)
|
||||
compileExpressionIO fp txt =
|
||||
runError
|
||||
. runNameIdGenArtifacts
|
||||
. runBuiltinsArtifacts
|
||||
$ compileExpression fp txt
|
||||
|
||||
inferExpressionIO ::
|
||||
Members '[State Artifacts, Embed IO] r =>
|
||||
Path Abs File ->
|
||||
Text ->
|
||||
Sem r (Either JuvixError Internal.Expression)
|
||||
inferExpressionIO fp txt =
|
||||
runError
|
||||
. runNameIdGenArtifacts
|
||||
. runBuiltinsArtifacts
|
||||
$ inferExpression fp txt
|
||||
|
||||
--------------------------------------------------------------------------------
|
||||
-- Workflows
|
||||
--------------------------------------------------------------------------------
|
||||
@ -297,27 +226,40 @@ corePipelineIOEither entry = do
|
||||
. Internal.resultAbstract
|
||||
. Abstract.resultScoper
|
||||
|
||||
parserResult :: P.ParserResult
|
||||
parserResult = scopedResult ^. Scoped.resultParserResult
|
||||
|
||||
resultScoperTable :: Scoped.InfoTable
|
||||
resultScoperTable = scopedResult ^. Scoped.resultScoperTable
|
||||
|
||||
mainModuleScope_ :: Scope
|
||||
mainModuleScope_ = Scoped.mainModuleSope scopedResult
|
||||
|
||||
abstractResult :: Abstract.AbstractResult
|
||||
abstractResult = typedResult ^. Typed.resultInternalArityResult . Arity.resultInternalResult . Internal.resultAbstract
|
||||
in Right $
|
||||
foldl'
|
||||
(flip ($))
|
||||
art
|
||||
[ set artifactMainModuleScope (Just mainModuleScope_),
|
||||
set artifactParsing (parserResult ^. P.resultBuilderState),
|
||||
set artifactAbstractInfoTable (abstractResult ^. Abstract.resultTable),
|
||||
set artifactInternalTypedTable typedTable,
|
||||
set artifactCoreTable coreTable,
|
||||
set artifactScopeTable resultScoperTable,
|
||||
set artifactScopeExports (scopedResult ^. Scoped.resultExports),
|
||||
set artifactTypes typesTable,
|
||||
set artifactFunctions functionsTable
|
||||
set artifactFunctions functionsTable,
|
||||
set artifactAbstractModuleCache (abstractResult ^. Abstract.resultModulesCache),
|
||||
set artifactScoperState (scopedResult ^. Scoped.resultScoperState)
|
||||
]
|
||||
where
|
||||
initialArtifacts :: Artifacts
|
||||
initialArtifacts =
|
||||
Artifacts
|
||||
{ _artifactMainModuleScope = Nothing,
|
||||
{ _artifactParsing = Concrete.iniState,
|
||||
_artifactAbstractInfoTable = Abstract.emptyInfoTable,
|
||||
_artifactMainModuleScope = Nothing,
|
||||
_artifactInternalTypedTable = mempty,
|
||||
_artifactTypes = mempty,
|
||||
_artifactResolver = PathResolver.iniResolverState,
|
||||
@ -325,5 +267,9 @@ corePipelineIOEither entry = do
|
||||
_artifactFunctions = mempty,
|
||||
_artifactCoreTable = Core.emptyInfoTable,
|
||||
_artifactScopeTable = Scoped.emptyInfoTable,
|
||||
_artifactBuiltins = iniBuiltins
|
||||
_artifactBuiltins = iniBuiltins,
|
||||
_artifactScopeExports = mempty,
|
||||
_artifactInternalTranslationState = Internal.TranslationState mempty,
|
||||
_artifactAbstractModuleCache = Abstract.ModulesCache mempty,
|
||||
_artifactScoperState = Scoper.iniScoperState
|
||||
}
|
||||
|
@ -5,13 +5,21 @@
|
||||
-- `runStateLikeArtifacts` wrapper.
|
||||
module Juvix.Compiler.Pipeline.Artifacts where
|
||||
|
||||
import Juvix.Compiler.Abstract.Data.InfoTableBuilder qualified as Abstract
|
||||
import Juvix.Compiler.Abstract.Translation.FromConcrete qualified as Abstract
|
||||
import Juvix.Compiler.Builtins
|
||||
import Juvix.Compiler.Concrete.Data.InfoTable qualified as Scoped
|
||||
import Juvix.Compiler.Concrete.Data.InfoTableBuilder qualified as Scoped
|
||||
import Juvix.Compiler.Concrete.Data.ParsedInfoTableBuilder (BuilderState)
|
||||
import Juvix.Compiler.Concrete.Data.ParsedInfoTableBuilder qualified as Concrete
|
||||
import Juvix.Compiler.Concrete.Data.Scope
|
||||
import Juvix.Compiler.Concrete.Data.Scope qualified as S
|
||||
import Juvix.Compiler.Concrete.Data.Scope qualified as Scoped
|
||||
import Juvix.Compiler.Concrete.Translation.FromParsed.Analysis.PathResolver
|
||||
import Juvix.Compiler.Core.Data.InfoTableBuilder qualified as Core
|
||||
import Juvix.Compiler.Internal.Data.InfoTable qualified as Internal
|
||||
import Juvix.Compiler.Internal.Language qualified as Internal
|
||||
import Juvix.Compiler.Internal.Translation.FromAbstract qualified as Internal
|
||||
import Juvix.Compiler.Internal.Translation.FromInternal.Analysis.TypeChecking.Data.Context
|
||||
import Juvix.Compiler.Pipeline.EntryPoint
|
||||
import Juvix.Prelude
|
||||
@ -19,17 +27,25 @@ import Juvix.Prelude
|
||||
-- | `Artifacts` contains enough information so that the pipeline can be
|
||||
-- restarted while preserving existing state.
|
||||
data Artifacts = Artifacts
|
||||
{ -- Scoping
|
||||
{ _artifactParsing :: BuilderState,
|
||||
_artifactAbstractInfoTable :: Abstract.InfoTable,
|
||||
-- Scoping
|
||||
_artifactResolver :: ResolverState,
|
||||
_artifactBuiltins :: BuiltinsState,
|
||||
_artifactNameIdState :: Stream NameId,
|
||||
_artifactScopeTable :: Scoped.InfoTable,
|
||||
_artifactScopeExports :: HashSet NameId,
|
||||
_artifactMainModuleScope :: Maybe Scope,
|
||||
_artifactScoperState :: Scoped.ScoperState,
|
||||
-- Typechecking
|
||||
_artifactTypes :: TypesTable,
|
||||
_artifactFunctions :: FunctionsTable,
|
||||
-- | This includes the InfoTable from all type checked modules
|
||||
_artifactInternalTypedTable :: Internal.InfoTable,
|
||||
-- Concrete -> Abstract
|
||||
_artifactAbstractModuleCache :: Abstract.ModulesCache,
|
||||
-- Abstract -> Internal
|
||||
_artifactInternalTranslationState :: Internal.TranslationState,
|
||||
-- Core
|
||||
_artifactCoreTable :: Core.InfoTable
|
||||
}
|
||||
@ -56,6 +72,22 @@ runPathResolverArtifacts = runStateLikeArtifacts runPathResolverPipe' artifactRe
|
||||
runBuiltinsArtifacts :: Members '[Error JuvixError, State Artifacts] r => Sem (Builtins ': r) a -> Sem r a
|
||||
runBuiltinsArtifacts = runStateLikeArtifacts runBuiltins artifactBuiltins
|
||||
|
||||
runAbstractInfoTableBuilderArtifacts :: Members '[State Artifacts] r => Sem (Abstract.InfoTableBuilder : r) a -> Sem r a
|
||||
runAbstractInfoTableBuilderArtifacts = runStateLikeArtifacts Abstract.runInfoTableBuilder' artifactAbstractInfoTable
|
||||
|
||||
runParserInfoTableBuilderArtifacts :: Members '[State Artifacts] r => Sem (Concrete.InfoTableBuilder : r) a -> Sem r a
|
||||
runParserInfoTableBuilderArtifacts = runStateLikeArtifacts Concrete.runParserInfoTableBuilder' artifactParsing
|
||||
|
||||
runScoperInfoTableBuilderArtifacts :: Members '[State Artifacts] r => Sem (Scoped.InfoTableBuilder : r) a -> Sem r a
|
||||
runScoperInfoTableBuilderArtifacts = runStateLikeArtifacts Scoped.runInfoTableBuilder artifactScopeTable
|
||||
|
||||
runScoperScopeArtifacts :: Members '[State Artifacts] r => Sem (State S.Scope : r) a -> Sem r a
|
||||
runScoperScopeArtifacts m = do
|
||||
s <- fromJust <$> gets (^. artifactMainModuleScope)
|
||||
(s', a) <- runState s m
|
||||
modify' (set artifactMainModuleScope (Just s'))
|
||||
return a
|
||||
|
||||
runNameIdGenArtifacts ::
|
||||
Members '[State Artifacts] r =>
|
||||
Sem (NameIdGen ': r) a ->
|
||||
|
188
src/Juvix/Compiler/Pipeline/Repl.hs
Normal file
188
src/Juvix/Compiler/Pipeline/Repl.hs
Normal file
@ -0,0 +1,188 @@
|
||||
module Juvix.Compiler.Pipeline.Repl where
|
||||
|
||||
import Juvix.Compiler.Abstract.Translation qualified as Abstract
|
||||
import Juvix.Compiler.Concrete.Data.ParsedInfoTableBuilder qualified as C
|
||||
import Juvix.Compiler.Concrete.Data.Scope qualified as Scoper
|
||||
import Juvix.Compiler.Concrete.Language
|
||||
import Juvix.Compiler.Concrete.Translation.FromParsed qualified as Scoper
|
||||
import Juvix.Compiler.Concrete.Translation.FromParsed.Analysis.PathResolver
|
||||
import Juvix.Compiler.Concrete.Translation.FromSource qualified as Parser
|
||||
import Juvix.Compiler.Core qualified as Core
|
||||
import Juvix.Compiler.Internal qualified as Internal
|
||||
import Juvix.Compiler.Pipeline.Artifacts
|
||||
import Juvix.Compiler.Pipeline.EntryPoint
|
||||
import Juvix.Prelude
|
||||
|
||||
arityCheckExpression ::
|
||||
Members '[Error JuvixError, State Artifacts] r =>
|
||||
ExpressionAtoms 'Parsed ->
|
||||
Sem r Internal.Expression
|
||||
arityCheckExpression p = do
|
||||
scopeTable <- gets (^. artifactScopeTable)
|
||||
( runNameIdGenArtifacts
|
||||
. runBuiltinsArtifacts
|
||||
. runScoperScopeArtifacts
|
||||
)
|
||||
$ Scoper.scopeCheckExpression scopeTable p
|
||||
>>= Abstract.fromConcreteExpression
|
||||
>>= Internal.fromAbstractExpression
|
||||
>>= Internal.arityCheckExpression
|
||||
|
||||
openImportToInternal ::
|
||||
Members '[Reader EntryPoint, Error JuvixError, State Artifacts] r =>
|
||||
OpenModule 'Parsed ->
|
||||
Sem r (Maybe Internal.Include)
|
||||
openImportToInternal o = do
|
||||
parsedModules <- gets (^. artifactParsing . C.stateModules)
|
||||
( runNameIdGenArtifacts
|
||||
. runBuiltinsArtifacts
|
||||
. runAbstractInfoTableBuilderArtifacts
|
||||
. runScoperInfoTableBuilderArtifacts
|
||||
. runScoperScopeArtifacts
|
||||
. runStateArtifacts artifactInternalTranslationState
|
||||
. runReaderArtifacts artifactScopeExports
|
||||
. runReader (Scoper.ScopeParameters mempty parsedModules)
|
||||
. runStateArtifacts artifactAbstractModuleCache
|
||||
. runStateArtifacts artifactScoperState
|
||||
)
|
||||
$ do
|
||||
mTopModule <-
|
||||
Scoper.scopeCheckOpenModule o
|
||||
>>= Abstract.fromConcreteOpenImport
|
||||
case mTopModule of
|
||||
Nothing -> return Nothing
|
||||
Just m -> Internal.fromAbstractImport m
|
||||
|
||||
importToInternal ::
|
||||
Members '[Reader EntryPoint, Error JuvixError, State Artifacts] r =>
|
||||
Import 'Parsed ->
|
||||
Sem r (Maybe Internal.Include)
|
||||
importToInternal i = do
|
||||
parsedModules <- gets (^. artifactParsing . C.stateModules)
|
||||
( runNameIdGenArtifacts
|
||||
. runBuiltinsArtifacts
|
||||
. runAbstractInfoTableBuilderArtifacts
|
||||
. runScoperInfoTableBuilderArtifacts
|
||||
. runScoperScopeArtifacts
|
||||
. runStateArtifacts artifactInternalTranslationState
|
||||
. runReaderArtifacts artifactScopeExports
|
||||
. runReader (Scoper.ScopeParameters mempty parsedModules)
|
||||
. runStateArtifacts artifactAbstractModuleCache
|
||||
. runStateArtifacts artifactScoperState
|
||||
)
|
||||
$ Scoper.scopeCheckImport i
|
||||
>>= Abstract.fromConcreteImport
|
||||
>>= Internal.fromAbstractImport
|
||||
|
||||
importToInternal' ::
|
||||
Members '[Reader EntryPoint, Error JuvixError, State Artifacts] r =>
|
||||
Internal.Include ->
|
||||
Sem r Internal.Include
|
||||
importToInternal' = Internal.arityCheckInclude >=> Internal.typeCheckInclude
|
||||
|
||||
parseExpression ::
|
||||
Members '[State Artifacts, Error JuvixError] r =>
|
||||
Path Abs File ->
|
||||
Text ->
|
||||
Sem r (ExpressionAtoms 'Parsed)
|
||||
parseExpression fp txt =
|
||||
( runNameIdGenArtifacts
|
||||
. runBuiltinsArtifacts
|
||||
)
|
||||
$ Parser.expressionFromTextSource fp txt
|
||||
|
||||
parseReplInput ::
|
||||
Members '[PathResolver, Files, State Artifacts, Error JuvixError] r =>
|
||||
Path Abs File ->
|
||||
Text ->
|
||||
Sem r Parser.ReplInput
|
||||
parseReplInput fp txt =
|
||||
( runNameIdGenArtifacts
|
||||
. runBuiltinsArtifacts
|
||||
. runParserInfoTableBuilderArtifacts
|
||||
)
|
||||
$ Parser.replInputFromTextSource fp txt
|
||||
|
||||
inferExpression ::
|
||||
Members '[Error JuvixError, State Artifacts] r =>
|
||||
Path Abs File ->
|
||||
Text ->
|
||||
Sem r Internal.Expression
|
||||
inferExpression fp txt = do
|
||||
p <- parseExpression fp txt
|
||||
arityCheckExpression p
|
||||
>>= Internal.inferExpressionType
|
||||
|
||||
compileExpression ::
|
||||
Members '[Error JuvixError, State Artifacts] r =>
|
||||
ExpressionAtoms 'Parsed ->
|
||||
Sem r Core.Node
|
||||
compileExpression p = do
|
||||
arityCheckExpression p
|
||||
>>= Internal.typeCheckExpression
|
||||
>>= fromInternalExpression
|
||||
|
||||
registerImport ::
|
||||
Members '[Error JuvixError, State Artifacts, Reader EntryPoint] r =>
|
||||
Import 'Parsed ->
|
||||
Sem r ()
|
||||
registerImport i = do
|
||||
mInclude <- importToInternal i
|
||||
whenJust mInclude (importToInternal' >=> fromInternalInclude)
|
||||
|
||||
registerOpenImport ::
|
||||
Members '[Error JuvixError, State Artifacts, Reader EntryPoint] r =>
|
||||
OpenModule 'Parsed ->
|
||||
Sem r ()
|
||||
registerOpenImport o = do
|
||||
mInclude <- openImportToInternal o
|
||||
whenJust mInclude (importToInternal' >=> fromInternalInclude)
|
||||
|
||||
fromInternalInclude :: Members '[State Artifacts] r => Internal.Include -> Sem r ()
|
||||
fromInternalInclude i = do
|
||||
let table = Internal.buildTable [i ^. Internal.includeModule]
|
||||
runReader table
|
||||
. runCoreInfoTableBuilderArtifacts
|
||||
. runFunctionsTableArtifacts
|
||||
. readerTypesTableArtifacts
|
||||
. runReader Core.initIndexTable
|
||||
$ Core.goTopModule (i ^. Internal.includeModule)
|
||||
|
||||
fromInternalExpression :: Members '[State Artifacts] r => Internal.Expression -> Sem r Core.Node
|
||||
fromInternalExpression exp = do
|
||||
typedTable <- gets (^. artifactInternalTypedTable)
|
||||
runReader typedTable
|
||||
. tmpCoreInfoTableBuilderArtifacts
|
||||
. runFunctionsTableArtifacts
|
||||
. readerTypesTableArtifacts
|
||||
. runReader Core.initIndexTable
|
||||
$ Core.goExpression exp
|
||||
|
||||
data ReplPipelineResult
|
||||
= ReplPipelineResultNode Core.Node
|
||||
| ReplPipelineResultImport TopModulePath
|
||||
| ReplPipelineResultOpenImport Name
|
||||
|
||||
compileReplInputIO ::
|
||||
Members '[Reader EntryPoint, State Artifacts, Embed IO] r =>
|
||||
Path Abs File ->
|
||||
Text ->
|
||||
Sem r (Either JuvixError ReplPipelineResult)
|
||||
compileReplInputIO fp txt =
|
||||
runError
|
||||
. runFilesIO
|
||||
. runPathResolverArtifacts
|
||||
$ do
|
||||
p <- parseReplInput fp txt
|
||||
case p of
|
||||
Parser.ReplExpression e -> ReplPipelineResultNode <$> compileExpression e
|
||||
Parser.ReplImport i -> registerImport i $> ReplPipelineResultImport (i ^. importModule)
|
||||
Parser.ReplOpenImport i -> registerOpenImport i $> ReplPipelineResultOpenImport (i ^. openModuleName)
|
||||
|
||||
inferExpressionIO ::
|
||||
Members '[State Artifacts, Embed IO] r =>
|
||||
Path Abs File ->
|
||||
Text ->
|
||||
Sem r (Either JuvixError Internal.Expression)
|
||||
inferExpressionIO fp txt =
|
||||
runError (inferExpression fp txt)
|
1
tests/positive/NoDependencies/Empty.juvix
Normal file
1
tests/positive/NoDependencies/Empty.juvix
Normal file
@ -0,0 +1 @@
|
||||
module Empty;
|
4
tests/positive/NoDependencies/Foo.juvix
Normal file
4
tests/positive/NoDependencies/Foo.juvix
Normal file
@ -0,0 +1,4 @@
|
||||
module Foo;
|
||||
|
||||
type Bar :=
|
||||
| bar : Bar;
|
1
tests/positive/NoDependencies/juvix.yaml
Normal file
1
tests/positive/NoDependencies/juvix.yaml
Normal file
@ -0,0 +1 @@
|
||||
dependencies: []
|
@ -285,3 +285,88 @@ tests:
|
||||
stdout:
|
||||
contains: |
|
||||
String → Int → Int
|
||||
|
||||
- name: repl-import-no-dependencies
|
||||
command:
|
||||
shell:
|
||||
- bash
|
||||
script: |
|
||||
cd positive/NoDependencies && juvix repl Empty.juvix
|
||||
stdin: "import Foo\nFoo.bar"
|
||||
stdout:
|
||||
contains:
|
||||
bar
|
||||
exit-status: 0
|
||||
|
||||
- name: repl-import-no-dependencies-type
|
||||
command:
|
||||
shell:
|
||||
- bash
|
||||
script: |
|
||||
cd positive/NoDependencies && juvix repl Empty.juvix
|
||||
stdin: "import Foo\n:t Foo.bar"
|
||||
stdout:
|
||||
contains:
|
||||
Bar
|
||||
exit-status: 0
|
||||
|
||||
- name: repl-invalid-import
|
||||
command:
|
||||
shell:
|
||||
- bash
|
||||
script: |
|
||||
cd positive/NoDependencies && juvix repl Empty.juvix
|
||||
stdin: "import Invalid"
|
||||
stdout:
|
||||
contains: OK loaded
|
||||
stderr:
|
||||
contains:
|
||||
The module Invalid does not exist
|
||||
exit-status: 0
|
||||
|
||||
- name: repl-import-type-error
|
||||
command:
|
||||
shell:
|
||||
- bash
|
||||
script: |
|
||||
temp=$(mktemp -d)
|
||||
trap 'rm -rf -- "$temp"' EXIT
|
||||
cp negative/Internal/WrongType.juvix $temp
|
||||
cd $temp
|
||||
echo "module Empty;" > Empty.juvix
|
||||
touch juvix.yaml
|
||||
juvix repl Empty.juvix
|
||||
stdin: "import WrongType"
|
||||
stdout:
|
||||
contains: OK loaded
|
||||
stderr:
|
||||
contains:
|
||||
is expected to have type
|
||||
exit-status: 0
|
||||
|
||||
- name: import-from-stdlib
|
||||
command:
|
||||
- juvix
|
||||
- repl
|
||||
stdin: "import Stdlib.Data.Int.Ord as Int\n1 Int.== 1"
|
||||
stdout:
|
||||
contains: "true"
|
||||
exit-status: 0
|
||||
|
||||
- name: import-then-open-from-stdlib
|
||||
command:
|
||||
- juvix
|
||||
- repl
|
||||
stdin: "import Stdlib.Data.Int.Ord as Int\nopen Int\n1 == 1"
|
||||
stdout:
|
||||
contains: "true"
|
||||
exit-status: 0
|
||||
|
||||
- name: open-import-from-stdlib
|
||||
command:
|
||||
- juvix
|
||||
- repl
|
||||
stdin: "open import Stdlib.Data.Int.Ord\n1 == 1"
|
||||
stdout:
|
||||
contains: "true"
|
||||
exit-status: 0
|
||||
|
Loading…
Reference in New Issue
Block a user