Skip to content

Commit

Permalink
style
Browse files Browse the repository at this point in the history
  • Loading branch information
janmasrovira committed Nov 20, 2024
1 parent 3aeec44 commit 1101462
Show file tree
Hide file tree
Showing 2 changed files with 34 additions and 10 deletions.
18 changes: 12 additions & 6 deletions src/Juvix/Compiler/Concrete/Data/InfoTableBuilder.hs
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,7 @@ data InfoTableBuilder :: Effect where
RegisterRecordInfo :: S.NameId -> RecordInfo -> InfoTableBuilder m ()
RegisterAlias :: S.NameId -> PreSymbolEntry -> InfoTableBuilder m ()
RegisterLocalModule :: ScopedModule -> InfoTableBuilder m ()
GetInfoTable :: InfoTableBuilder m InfoTable
GetBuilderInfoTable :: InfoTableBuilder m InfoTable
GetBuiltinSymbol' :: Interval -> BuiltinPrim -> InfoTableBuilder m S.Symbol
RegisterBuiltin' :: BuiltinPrim -> S.Symbol -> InfoTableBuilder m ()

Expand Down Expand Up @@ -92,7 +92,7 @@ runInfoTableBuilder ini = reinterpret (runState ini) $ \case
modify (over infoScoperAlias (HashMap.insert uid a))
RegisterLocalModule m ->
mapM_ (uncurry registerBuiltinHelper) (m ^. scopedModuleInfoTable . infoBuiltins . to HashMap.toList)
GetInfoTable ->
GetBuilderInfoTable ->
get
GetBuiltinSymbol' i b -> do
tbl <- get @InfoTable
Expand Down Expand Up @@ -153,16 +153,22 @@ anameFromScopedIden s =
_anameVerbatim = s ^. scopedIdenSrcName . nameVerbatim
}

lookupInfo :: (Members '[InfoTableBuilder, Reader InfoTable] r) => (InfoTable -> Maybe a) -> Sem r a
getInfo :: (Members '[InfoTableBuilder, Reader InfoTable] r) => (InfoTable -> Maybe a) -> Sem r a
getInfo f = do
tab1 <- ask
fromMaybe (fromJust (f tab1)) . f <$> getBuilderInfoTable

lookupInfo :: (Members '[InfoTableBuilder, Reader InfoTable] r) => (InfoTable -> Maybe a) -> Sem r (Maybe a)
lookupInfo f = do
tab1 <- ask
fromMaybe (fromJust (f tab1)) . f <$> getInfoTable
tab2 <- getBuilderInfoTable
return (f tab1 <|> f tab2)

lookupFixity :: (Members '[InfoTableBuilder, Reader InfoTable] r) => S.NameId -> Sem r FixityDef
lookupFixity uid = lookupInfo (HashMap.lookup uid . (^. infoFixities))
lookupFixity uid = getInfo (^. infoFixities . at uid)

getPrecedenceGraph :: (Members '[InfoTableBuilder, Reader InfoTable] r) => Sem r PrecedenceGraph
getPrecedenceGraph = do
tab <- ask
tab' <- getInfoTable
tab' <- getBuilderInfoTable
return $ combinePrecedenceGraphs (tab ^. infoPrecedenceGraph) (tab' ^. infoPrecedenceGraph)
Original file line number Diff line number Diff line change
Expand Up @@ -726,7 +726,11 @@ lookupQualifiedSymbol ::
([Symbol], Symbol) ->
Sem r (HashSet PreSymbolEntry, HashSet ModuleSymbolEntry, HashSet FixitySymbolEntry)
lookupQualifiedSymbol sms = do
(es, (ms, fs)) <- runOutputHashSet . runOutputHashSet . execOutputHashSet $ go sms
(es, (ms, fs)) <-
runOutputHashSet
. runOutputHashSet
. execOutputHashSet
$ go sms
return (es, ms, fs)
where
go ::
Expand Down Expand Up @@ -1156,7 +1160,21 @@ checkInductiveParameters params = do

checkInductiveDef ::
forall r.
(Members '[HighlightBuilder, Reader ScopeParameters, Error ScoperError, State Scope, State ScoperState, InfoTableBuilder, Reader InfoTable, NameIdGen, Reader PackageId, State ScoperSyntax, Reader BindingStrategy] r) =>
( Members
'[ HighlightBuilder,
Reader ScopeParameters,
Error ScoperError,
State Scope,
State ScoperState,
InfoTableBuilder,
Reader InfoTable,
NameIdGen,
Reader PackageId,
State ScoperSyntax,
Reader BindingStrategy
]
r
) =>
InductiveDef 'Parsed ->
Sem r (InductiveDef 'Scoped)
checkInductiveDef InductiveDef {..} = do
Expand Down Expand Up @@ -1824,9 +1842,9 @@ checkLocalModule ::
Sem r (Module 'Scoped 'ModuleLocal)
checkLocalModule md@Module {..} = do
tab1 <- ask @InfoTable
tab2 <- getInfoTable
tab2 <- getBuilderInfoTable
(tab, (moduleExportInfo, moduleBody', moduleDoc')) <-
withLocalScope $ runReader (tab1 <> tab2) $ runInfoTableBuilder mempty $ do
withLocalScope . runReader (tab1 <> tab2) . runInfoTableBuilder mempty $ do
inheritScope
(e, b) <- checkModuleBody _moduleBody
doc' <- mapM checkJudoc _moduleDoc
Expand Down

0 comments on commit 1101462

Please sign in to comment.