1
1
mirror of https://github.com/anoma/juvix.git synced 2025-01-05 22:46:08 +03:00

Clean up import list in Pipeline (#1499)

This commit is contained in:
Jonathan Cubides 2022-08-31 18:51:26 +02:00 committed by GitHub
parent 65489ff092
commit ff39db3319
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
9 changed files with 115 additions and 102 deletions

View File

@ -0,0 +1,12 @@
module Juvix.Compiler.Internal
( module Juvix.Compiler.Internal.Language,
module Juvix.Compiler.Internal.Data,
module Juvix.Compiler.Internal.Pretty,
module Juvix.Compiler.Internal.Translation,
)
where
import Juvix.Compiler.Internal.Data
import Juvix.Compiler.Internal.Language
import Juvix.Compiler.Internal.Pretty
import Juvix.Compiler.Internal.Translation

View File

@ -1 +1,8 @@
module Juvix.Compiler.Internal.Data where
module Juvix.Compiler.Internal.Data
( module Juvix.Compiler.Internal.Data.InfoTable,
module Juvix.Compiler.Internal.Data.LocalVars,
)
where
import Juvix.Compiler.Internal.Data.InfoTable
import Juvix.Compiler.Internal.Data.LocalVars

View File

@ -1,8 +1,14 @@
module Juvix.Compiler.Internal.Translation
( module Juvix.Compiler.Internal.Language,
module Juvix.Compiler.Internal.Translation.FromAbstract,
module Juvix.Compiler.Internal.Translation.FromAbstract.Data,
module Juvix.Compiler.Internal.Translation.FromInternal,
module Juvix.Compiler.Internal.Translation.FromInternal.Data,
)
where
import Juvix.Compiler.Internal.Language
import Juvix.Compiler.Internal.Translation.FromAbstract
import Juvix.Compiler.Internal.Translation.FromAbstract.Data
import Juvix.Compiler.Internal.Translation.FromInternal
import Juvix.Compiler.Internal.Translation.FromInternal.Data

View File

@ -1,7 +1,9 @@
module Juvix.Compiler.Internal.Translation.FromAbstract
( module Juvix.Compiler.Internal.Translation.FromAbstract,
module Juvix.Compiler.Internal.Translation.FromAbstract.Data.Context,
( module Juvix.Compiler.Internal.Translation.FromAbstract.Data.Context,
module Juvix.Compiler.Internal.Translation.FromAbstract.Analysis.Termination,
TranslationState,
iniState,
fromAbstract,
)
where

View File

@ -1 +1,6 @@
module Juvix.Compiler.Internal.Translation.FromAbstract.Data where
module Juvix.Compiler.Internal.Translation.FromAbstract.Data
( module Juvix.Compiler.Internal.Translation.FromAbstract.Data.Context,
)
where
import Juvix.Compiler.Internal.Translation.FromAbstract.Data.Context

View File

@ -1,6 +1,7 @@
module Juvix.Compiler.Internal.Translation.FromInternal
( module Juvix.Compiler.Internal.Translation.FromInternal,
module Juvix.Compiler.Internal.Translation.FromInternal.Analysis.Reachability,
( module Juvix.Compiler.Internal.Translation.FromInternal.Analysis.Reachability,
arityChecking,
typeChecking,
)
where

View File

@ -0,0 +1,10 @@
module Juvix.Compiler.Internal.Translation.FromInternal.Analysis.TypeChecking.Data
( module Juvix.Compiler.Internal.Translation.FromInternal.Analysis.TypeChecking.Data.Context,
module Juvix.Compiler.Internal.Translation.FromInternal.Analysis.TypeChecking.Data.FunctionsTable,
module Juvix.Compiler.Internal.Translation.FromInternal.Analysis.TypeChecking.Data.Inference,
)
where
import Juvix.Compiler.Internal.Translation.FromInternal.Analysis.TypeChecking.Data.Context
import Juvix.Compiler.Internal.Translation.FromInternal.Analysis.TypeChecking.Data.FunctionsTable
import Juvix.Compiler.Internal.Translation.FromInternal.Analysis.TypeChecking.Data.Inference

View File

@ -0,0 +1,8 @@
module Juvix.Compiler.Internal.Translation.FromInternal.Data
( Arity.InternalArityResult,
Typechecking.InternalTypedResult,
)
where
import Juvix.Compiler.Internal.Translation.FromInternal.Analysis.ArityChecking.Data qualified as Arity
import Juvix.Compiler.Internal.Translation.FromInternal.Analysis.TypeChecking.Data qualified as Typechecking

View File

@ -4,29 +4,15 @@ module Juvix.Compiler.Pipeline
)
where
-- import Juvix.Compiler.Abstract.Translation.FromConcrete qualified as Abstract
import Juvix.Compiler.Abstract.Translation qualified as Abstract
import Juvix.Compiler.Backend.C qualified as C
import Juvix.Compiler.Backend.C.Translation.FromInternal qualified as MiniC
import Juvix.Compiler.Builtins
import Juvix.Compiler.Concrete qualified as Concrete
--------------------------------------------------------------------------------
import Juvix.Compiler.Concrete.Translation.FromParsed qualified as Scoper
import Juvix.Compiler.Concrete.Translation.FromSource qualified as Parser
import Juvix.Compiler.Internal.Translation.FromAbstract qualified as Internal
import Juvix.Compiler.Internal.Translation.FromInternal qualified as FromInternal
import Juvix.Compiler.Internal.Translation.FromInternal qualified as Internal
import Juvix.Compiler.Internal.Translation.FromInternal.Analysis.ArityChecking qualified as Internal
import Juvix.Compiler.Internal.Translation.FromInternal.Analysis.TypeChecking.Checker qualified as Internal
( TypeCheckerError,
)
import Juvix.Compiler.Internal.Translation.FromInternal.Analysis.TypeChecking.Data.Context qualified as Internal
( InternalTypedResult,
)
import Juvix.Compiler.Internal qualified as Internal
import Juvix.Compiler.Pipeline.EntryPoint
import Juvix.Compiler.Pipeline.Setup qualified as Setup
import Juvix.Compiler.Pipeline.Setup
import Juvix.Prelude
type PipelineEff = '[Files, NameIdGen, Builtins, Error JuvixError, Embed IO]
@ -35,11 +21,11 @@ type PipelineEff = '[Files, NameIdGen, Builtins, Error JuvixError, Embed IO]
-- Workflows
--------------------------------------------------------------------------------
typechecking ::
typecheck ::
Members PipelineEff r =>
EntryPoint ->
Sem r Internal.InternalTypedResult
typechecking =
typecheck =
do
Concrete.fromSource
>=> Abstract.fromConcrete
@ -47,11 +33,63 @@ typechecking =
>=> Internal.arityChecking
>=> Internal.typeChecking
toC ::
compile ::
Members PipelineEff r =>
EntryPoint ->
Sem r C.MiniCResult
toC = typechecking >=> C.fromInternal
compile = typecheck >=> C.fromInternal
--------------------------------------------------------------------------------
upToParsing ::
Members '[Files, Error JuvixError, NameIdGen] r =>
EntryPoint ->
Sem r Parser.ParserResult
upToParsing = entrySetup >=> Parser.fromSource
upToScoping ::
Members '[Files, NameIdGen, Error JuvixError] r =>
EntryPoint ->
Sem r Scoper.ScoperResult
upToScoping = upToParsing >=> Scoper.fromParsed
upToAbstract ::
Members '[Files, NameIdGen, Builtins, Error JuvixError] r =>
EntryPoint ->
Sem r Abstract.AbstractResult
upToAbstract = upToScoping >=> Abstract.fromConcrete
upToInternal ::
Members '[Files, NameIdGen, Builtins, Error JuvixError] r =>
EntryPoint ->
Sem r Internal.InternalResult
upToInternal = upToAbstract >=> Internal.fromAbstract
upToInternalArity ::
Members '[Files, NameIdGen, Builtins, Error JuvixError] r =>
EntryPoint ->
Sem r Internal.InternalArityResult
upToInternalArity = upToInternal >=> Internal.arityChecking
upToInternalTyped ::
Members '[Files, NameIdGen, Builtins, Error JuvixError] r =>
EntryPoint ->
Sem r Internal.InternalTypedResult
upToInternalTyped = upToInternalArity >=> Internal.typeChecking
upToInternalReachability ::
Members '[Files, NameIdGen, Builtins, Error JuvixError] r =>
EntryPoint ->
Sem r Internal.InternalTypedResult
upToInternalReachability =
upToInternalTyped
>=> return . Internal.filterUnreachable
upToMiniC ::
Members '[Files, NameIdGen, Builtins, Error JuvixError] r =>
EntryPoint ->
Sem r C.MiniCResult
upToMiniC = upToInternalReachability >=> C.fromInternal
--------------------------------------------------------------------------------
@ -65,79 +103,3 @@ runIO = runIOEither >=> mayThrow
mayThrow = \case
Left err -> printErrorAnsiSafe err >> exitFailure
Right r -> return r
upToSetup ::
Member Files r =>
EntryPoint ->
Sem r EntryPoint
upToSetup = Setup.entrySetup
upToParsing ::
Members '[Files, Error JuvixError, NameIdGen] r =>
EntryPoint ->
Sem r Parser.ParserResult
upToParsing = upToSetup >=> Parser.fromSource
upToScoping ::
Members '[Files, NameIdGen, Error JuvixError] r =>
EntryPoint ->
Sem r Scoper.ScoperResult
upToScoping = upToParsing >=> Scoper.fromParsed
upToAbstract ::
Members '[Files, NameIdGen, Builtins, Error JuvixError] r =>
EntryPoint ->
Sem r Abstract.AbstractResult
upToAbstract = upToScoping >=> pipelineAbstract
upToInternal ::
Members '[Files, NameIdGen, Builtins, Error JuvixError] r =>
EntryPoint ->
Sem r Internal.InternalResult
upToInternal = upToAbstract >=> Internal.fromAbstract
upToInternalArity ::
Members '[Files, NameIdGen, Builtins, Error JuvixError] r =>
EntryPoint ->
Sem r Internal.InternalArityResult
upToInternalArity = upToInternal >=> FromInternal.arityChecking
upToInternalTyped ::
Members '[Files, NameIdGen, Builtins, Error JuvixError] r =>
EntryPoint ->
Sem r Internal.InternalTypedResult
upToInternalTyped = upToInternalArity >=> pipelineInternalTyped
upToInternalReachability ::
Members '[Files, NameIdGen, Builtins, Error JuvixError] r =>
EntryPoint ->
Sem r Internal.InternalTypedResult
upToInternalReachability = upToInternalTyped >=> pipelineInternalReachability
upToMiniC ::
Members '[Files, NameIdGen, Builtins, Error JuvixError] r =>
EntryPoint ->
Sem r MiniC.MiniCResult
upToMiniC = upToInternalReachability >=> pipelineMiniC
pipelineAbstract ::
Members '[Error JuvixError, Builtins, NameIdGen] r =>
Scoper.ScoperResult ->
Sem r Abstract.AbstractResult
pipelineAbstract = mapError (JuvixError @Scoper.ScoperError) . Abstract.fromConcrete
pipelineInternalTyped ::
Members '[Files, NameIdGen, Error JuvixError, Builtins] r =>
Internal.InternalArityResult ->
Sem r Internal.InternalTypedResult
pipelineInternalTyped =
mapError (JuvixError @Internal.TypeCheckerError) . FromInternal.typeChecking
pipelineInternalReachability :: Internal.InternalTypedResult -> Sem r Internal.InternalTypedResult
pipelineInternalReachability = return . FromInternal.filterUnreachable
pipelineMiniC ::
Member Builtins r =>
Internal.InternalTypedResult ->
Sem r MiniC.MiniCResult
pipelineMiniC = MiniC.fromInternal