Skip to content

Commit

Permalink
fix repl
Browse files Browse the repository at this point in the history
  • Loading branch information
lukaszcz committed Dec 21, 2023
1 parent 3993587 commit d7f0afe
Show file tree
Hide file tree
Showing 4 changed files with 23 additions and 15 deletions.
29 changes: 15 additions & 14 deletions app/Commands/Repl.hs
Original file line number Diff line number Diff line change
Expand Up @@ -31,6 +31,7 @@ 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.Run
import Juvix.Compiler.Store.Extra
import Juvix.Data.CodeAnn (Ann)
import Juvix.Data.Error.GenericError qualified as Error
import Juvix.Data.NameKind
Expand Down Expand Up @@ -255,6 +256,12 @@ replParseIdentifiers input =
err :: Repl a
err = replError (mkAnsiText @Text ":def expects one or more identifiers")

getScopedInfoTable :: Repl Scoped.InfoTable
getScopedInfoTable = do
artifs <- (^. replContextArtifacts) <$> replGetContext
let tab0 = artifs ^. artifactScopeTable
return $ tab0 <> computeCombinedScopedInfoTable (artifs ^. artifactModuleTable)

printDocumentation :: String -> Repl ()
printDocumentation = replParseIdentifiers >=> printIdentifiers
where
Expand All @@ -263,9 +270,6 @@ printDocumentation = replParseIdentifiers >=> printIdentifiers
printIdentifier d
whenJust (nonEmpty ds) $ \ds' -> replNewline >> printIdentifiers ds'
where
getInfoTable :: Repl Scoped.InfoTable
getInfoTable = (^. replContextArtifacts . artifactScopeTable) <$> replGetContext

printIdentifier :: Concrete.ScopedIden -> Repl ()
printIdentifier s = do
let n = s ^. Concrete.scopedIdenFinal . Scoped.nameId
Expand All @@ -291,25 +295,25 @@ printDocumentation = replParseIdentifiers >=> printIdentifiers

getDocFunction :: Scoped.NameId -> Repl (Maybe (Concrete.Judoc 'Concrete.Scoped))
getDocFunction fun = do
tbl :: Scoped.InfoTable <- getInfoTable
tbl :: Scoped.InfoTable <- getScopedInfoTable
let def = tbl ^?! Scoped.infoFunctions . at fun . _Just
return (def ^. Concrete.signDoc)

getDocInductive :: Scoped.NameId -> Repl (Maybe (Concrete.Judoc 'Concrete.Scoped))
getDocInductive ind = do
tbl :: Scoped.InfoTable <- (^. replContextArtifacts . artifactScopeTable) <$> replGetContext
tbl :: Scoped.InfoTable <- getScopedInfoTable
let def :: Concrete.InductiveDef 'Concrete.Scoped = tbl ^?! Scoped.infoInductives . at ind . _Just
return (def ^. Concrete.inductiveDoc)

getDocAxiom :: Scoped.NameId -> Repl (Maybe (Concrete.Judoc 'Concrete.Scoped))
getDocAxiom ax = do
tbl :: Scoped.InfoTable <- (^. replContextArtifacts . artifactScopeTable) <$> replGetContext
tbl :: Scoped.InfoTable <- getScopedInfoTable
let def :: Concrete.AxiomDef 'Concrete.Scoped = tbl ^?! Scoped.infoAxioms . at ax . _Just
return (def ^. Concrete.axiomDoc)

getDocConstructor :: Scoped.NameId -> Repl (Maybe (Concrete.Judoc 'Concrete.Scoped))
getDocConstructor c = do
tbl :: Scoped.InfoTable <- (^. replContextArtifacts . artifactScopeTable) <$> replGetContext
tbl :: Scoped.InfoTable <- getScopedInfoTable
let def = tbl ^?! Scoped.infoConstructors . at c . _Just
return (def ^. Concrete.constructorDoc)

Expand All @@ -321,9 +325,6 @@ printDefinition = replParseIdentifiers >=> printIdentifiers
printIdentifier d
whenJust (nonEmpty ds) $ \ds' -> replNewline >> printIdentifiers ds'
where
getInfoTable :: Repl Scoped.InfoTable
getInfoTable = (^. replContextArtifacts . artifactScopeTable) <$> replGetContext

printIdentifier :: Concrete.ScopedIden -> Repl ()
printIdentifier s =
let n = s ^. Concrete.scopedIdenFinal . Scoped.nameId
Expand All @@ -346,7 +347,7 @@ printDefinition = replParseIdentifiers >=> printIdentifiers

printFunction :: Scoped.NameId -> Repl ()
printFunction fun = do
tbl :: Scoped.InfoTable <- getInfoTable
tbl :: Scoped.InfoTable <- getScopedInfoTable
case tbl ^. Scoped.infoFunctions . at fun of
Just def -> do
printLocation def
Expand All @@ -355,21 +356,21 @@ printDefinition = replParseIdentifiers >=> printIdentifiers

printInductive :: Scoped.NameId -> Repl ()
printInductive ind = do
tbl :: Scoped.InfoTable <- (^. replContextArtifacts . artifactScopeTable) <$> replGetContext
tbl :: Scoped.InfoTable <- getScopedInfoTable
let def :: Concrete.InductiveDef 'Concrete.Scoped = tbl ^?! Scoped.infoInductives . at ind . _Just
printLocation def
printConcreteLn def

printAxiom :: Scoped.NameId -> Repl ()
printAxiom ax = do
tbl :: Scoped.InfoTable <- (^. replContextArtifacts . artifactScopeTable) <$> replGetContext
tbl :: Scoped.InfoTable <- getScopedInfoTable
let def :: Concrete.AxiomDef 'Concrete.Scoped = tbl ^?! Scoped.infoAxioms . at ax . _Just
printLocation def
printConcreteLn def

printConstructor :: Scoped.NameId -> Repl ()
printConstructor c = do
tbl :: Scoped.InfoTable <- (^. replContextArtifacts . artifactScopeTable) <$> replGetContext
tbl :: Scoped.InfoTable <- getScopedInfoTable
let ind = tbl ^?! Scoped.infoConstructors . at c . _Just . Concrete.constructorInductiveName
printInductive (ind ^. Scoped.nameId)

Expand Down
1 change: 1 addition & 0 deletions src/Juvix/Compiler/Pipeline/Artifacts.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,6 +27,7 @@ appendArtifactsModuleTable :: ModuleTable -> Artifacts -> Artifacts
appendArtifactsModuleTable mtab =
over artifactInternalTypedTable (computeCombinedInfoTable importTab <>)
. over (artifactCoreModule . Core.moduleImportsTable) (computeCombinedCoreInfoTable mtab <>)
. over artifactModuleTable (mtab <>)
where
importTab :: Internal.InternalModuleTable
importTab = getInternalModuleTable mtab
Expand Down
3 changes: 2 additions & 1 deletion src/Juvix/Compiler/Pipeline/Repl.hs
Original file line number Diff line number Diff line change
Expand Up @@ -116,12 +116,13 @@ registerImport i = do
let mtab' = Store.insertModule (i ^. importModulePath) mi mtab
modify' (appendArtifactsModuleTable mtab')
scopeTable <- gets (^. artifactScopeTable)
mtab'' <- gets (^. artifactModuleTable)
void
. runNameIdGenArtifacts
. runBuiltinsArtifacts
. runScoperScopeArtifacts
. runStateArtifacts artifactScoperState
$ Scoper.scopeCheckImport (Store.getScopedModuleTable mtab') scopeTable i
$ Scoper.scopeCheckImport (Store.getScopedModuleTable mtab'') scopeTable i

fromInternalExpression :: (Members '[State Artifacts] r) => Internal.Expression -> Sem r Core.Node
fromInternalExpression exp = do
Expand Down
5 changes: 5 additions & 0 deletions src/Juvix/Compiler/Store/Extra.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,7 @@ import Juvix.Compiler.Core.Data.InfoTable qualified as Core
import Juvix.Compiler.Store.Core.Extra
import Juvix.Compiler.Store.Internal.Language
import Juvix.Compiler.Store.Language
import Juvix.Compiler.Store.Scoped.Data.InfoTable qualified as Scoped
import Juvix.Compiler.Store.Scoped.Language
import Juvix.Prelude

Expand Down Expand Up @@ -34,6 +35,10 @@ lookupModule mtab n = fromJust $ HashMap.lookup n (mtab ^. moduleTable)
insertModule :: TopModulePath -> ModuleInfo -> ModuleTable -> ModuleTable
insertModule p mi = over moduleTable (HashMap.insert p mi)

computeCombinedScopedInfoTable :: ModuleTable -> Scoped.InfoTable
computeCombinedScopedInfoTable mtab =
mconcatMap (^. moduleInfoScopedModule . scopedModuleInfoTable) (HashMap.elems (mtab ^. moduleTable))

computeCombinedCoreInfoTable :: ModuleTable -> Core.InfoTable
computeCombinedCoreInfoTable mtab =
mconcatMap (toCore . (^. moduleInfoCoreTable)) (HashMap.elems (mtab ^. moduleTable))

0 comments on commit d7f0afe

Please sign in to comment.