Skip to content

Commit

Permalink
Get all dependencies building
Browse files Browse the repository at this point in the history
Still have a runtime exception when assembling the final JS though. Very
close!
  • Loading branch information
changlinli committed Nov 27, 2023
1 parent 3cd9b96 commit 85d5118
Show file tree
Hide file tree
Showing 36 changed files with 322 additions and 65 deletions.
1 change: 1 addition & 0 deletions builder/src/Deps/Solver.hs
Original file line number Diff line number Diff line change
Expand Up @@ -96,6 +96,7 @@ data Result a

data Details =
Details V.Version (Map.Map Pkg.Name C.Constraint) -- First argument is the version, second is the set of dependencies that the package depends on
deriving Show


verify :: Stuff.PackageCache -> Connection -> Registry.ZelmRegistries -> Map.Map Pkg.Name C.Constraint -> IO (Result (Map.Map Pkg.Name Details))
Expand Down
185 changes: 146 additions & 39 deletions builder/src/Elm/Details.hs

Large diffs are not rendered by default.

4 changes: 4 additions & 0 deletions builder/src/Elm/Outline.hs
Original file line number Diff line number Diff line change
Expand Up @@ -51,6 +51,7 @@ import Data.Maybe (mapMaybe)
data Outline
= App AppOutline
| Pkg PkgOutline
deriving Show


data AppOutline =
Expand All @@ -63,6 +64,7 @@ data AppOutline =
, _app_test_indirect :: Map.Map Pkg.Name V.Version
, _app_zelm_package_overrides :: [PkgOverride.PackageOverrideData]
}
deriving Show


data PkgOutline =
Expand All @@ -76,11 +78,13 @@ data PkgOutline =
, _pkg_test_deps :: Map.Map Pkg.Name Con.Constraint
, _pkg_elm_version :: Con.Constraint
}
deriving Show


data Exposed
= ExposedList [ModuleName.Raw]
| ExposedDict [(Json.String, [ModuleName.Raw])]
deriving Show


data SrcDir
Expand Down
1 change: 1 addition & 0 deletions builder/src/Http.hs
Original file line number Diff line number Diff line change
Expand Up @@ -116,6 +116,7 @@ data Error
= BadUrl String String
| BadHttp String HttpExceptionContent
| BadMystery String SomeException
deriving Show


handleHttpException :: String -> (Error -> e) -> HttpException -> IO (Either e a)
Expand Down
4 changes: 4 additions & 0 deletions builder/src/Reporting/Exit.hs
Original file line number Diff line number Diff line change
Expand Up @@ -1037,6 +1037,7 @@ data Outline
| OutlineNoAppCore
| OutlineNoAppJson
| OutlinePkgOverridesDoNotMatchDeps Pkg.Name V.Version
deriving Show


data OutlineProblem
Expand All @@ -1050,6 +1051,7 @@ data OutlineProblem
| OP_BadLicense Json.String [Json.String]
| OP_BadSummaryTooLong
| OP_NoSrcDirs
deriving Show


toOutlineReport :: Outline -> Help.Report
Expand Down Expand Up @@ -1368,6 +1370,7 @@ data Details
data DetailsBadDep
= BD_BadDownload Pkg.Name V.Version PackageProblem
| BD_BadBuild Pkg.Name V.Version (Map.Map Pkg.Name V.Version)
deriving Show


toDetailsReport :: Details -> Help.Report
Expand Down Expand Up @@ -1505,6 +1508,7 @@ data PackageProblem
| PP_BadArchiveHash String String String
-- FIXME: Change away from String
| PP_PackageNotInRegistry [String] Pkg.Name V.Version
deriving Show


toPackageProblemReport :: Pkg.Name -> V.Version -> PackageProblem -> Help.Report
Expand Down
23 changes: 15 additions & 8 deletions compiler/src/AST/Canonical.hs
Original file line number Diff line number Diff line change
Expand Up @@ -105,14 +105,17 @@ data Expr_
| Unit
| Tuple Expr Expr (Maybe Expr)
| Shader Shader.Source Shader.Types
deriving Show


data CaseBranch =
CaseBranch Pattern Expr
deriving Show


data FieldUpdate =
FieldUpdate A.Region Expr
deriving Show



Expand All @@ -122,6 +125,7 @@ data FieldUpdate =
data Def
= Def (A.Located Name) [Pattern] Expr
| TypedDef (A.Located Name) FreeVars [(Pattern, Type)] Expr Type
deriving Show



Expand All @@ -132,6 +136,7 @@ data Decls
= Declare Def Decls
| DeclareRec Def [Def] Decls
| SaveTheEnvironment
deriving Show



Expand Down Expand Up @@ -167,6 +172,7 @@ data Pattern_
-- CACHE _p_index to replace _p_name in PROD code gen
-- CACHE _p_opts to allocate less in PROD code gen
-- CACHE _p_alts and _p_numAlts for exhaustiveness checker
deriving Show


data PatternCtorArg =
Expand All @@ -175,14 +181,15 @@ data PatternCtorArg =
, _type :: Type -- CACHE for type inference
, _arg :: Pattern
}
deriving Show



-- TYPES


data Annotation = Forall FreeVars Type
deriving (Eq)
deriving (Eq, Show)


type FreeVars = Map.Map Name ()
Expand All @@ -196,17 +203,17 @@ data Type
| TUnit
| TTuple Type Type (Maybe Type)
| TAlias ModuleName.Canonical Name [(Name, Type)] AliasType
deriving (Eq)
deriving (Eq, Show)


data AliasType
= Holey Type
| Filled Type
deriving (Eq)
deriving (Eq, Show)


data FieldType = FieldType {-# UNPACK #-} !Word16 Type
deriving (Eq)
deriving (Eq, Show)


-- NOTE: The Word16 marks the source order, but it may not be available
Expand Down Expand Up @@ -243,7 +250,7 @@ data Module =


data Alias = Alias [Name] Type
deriving (Eq)
deriving (Eq, Show)


data Binop = Binop_ Binop.Associativity Binop.Precedence Name
Expand All @@ -257,18 +264,18 @@ data Union =
, _u_numAlts :: Int -- CACHE numAlts for exhaustiveness checking
, _u_opts :: CtorOpts -- CACHE which optimizations are available
}
deriving (Eq)
deriving (Eq, Show)


data CtorOpts
= Normal
| Enum
| Unbox
deriving (Eq, Ord)
deriving (Eq, Ord, Show)


data Ctor = Ctor Name Index.ZeroBased Int [Type] -- CACHE length args
deriving (Eq)
deriving (Eq, Show)



Expand Down
12 changes: 12 additions & 0 deletions compiler/src/AST/Optimized.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
{-# OPTIONS_GHC -Wall #-}
{-# LANGUAGE StandaloneDeriving #-}
module AST.Optimized
( Def(..)
, Expr(..)
Expand Down Expand Up @@ -72,9 +73,11 @@ data Expr
| Unit
| Tuple Expr Expr (Maybe Expr)
| Shader Shader.Source (Set.Set Name) (Set.Set Name)
deriving Show


data Global = Global ModuleName.Canonical Name
deriving Show



Expand All @@ -84,17 +87,20 @@ data Global = Global ModuleName.Canonical Name
data Def
= Def Name Expr
| TailDef Name [Name] Expr
deriving Show


data Destructor =
Destructor Name Path
deriving Show


data Path
= Index Index.ZeroBased Path
| Field Name Path
| Unbox Path
| Root Name
deriving Show



Expand All @@ -115,10 +121,13 @@ data Decider a
}
deriving (Eq)

deriving instance Show a => Show (Decider a)


data Choice
= Inline Expr
| Jump Int
deriving Show



Expand All @@ -130,6 +139,7 @@ data GlobalGraph =
{ _g_nodes :: Map.Map Global Node
, _g_fields :: Map.Map Name Int
}
deriving Show


data LocalGraph =
Expand Down Expand Up @@ -160,9 +170,11 @@ data Node
| Kernel [K.Chunk] (Set.Set Global)
| PortIncoming Expr (Set.Set Global)
| PortOutgoing Expr (Set.Set Global)
deriving Show


data EffectsType = Cmd | Sub | Fx
deriving Show



Expand Down
19 changes: 19 additions & 0 deletions compiler/src/AST/Source.hs
Original file line number Diff line number Diff line change
Expand Up @@ -65,9 +65,11 @@ data Expr_
| Unit
| Tuple Expr Expr [Expr]
| Shader Shader.Source Shader.Types
deriving Show


data VarType = LowVar | CapVar
deriving Show



Expand All @@ -77,6 +79,7 @@ data VarType = LowVar | CapVar
data Def
= Define (A.Located Name) [Pattern] Expr (Maybe Type)
| Destruct Pattern Expr
deriving Show



Expand All @@ -100,6 +103,7 @@ data Pattern_
| PChr ES.String
| PStr ES.String
| PInt Int
deriving Show



Expand All @@ -118,6 +122,7 @@ data Type_
| TRecord [(A.Located Name, Type)] (Maybe (A.Located Name))
| TUnit
| TTuple Type Type [Type]
deriving Show



Expand All @@ -136,6 +141,7 @@ data Module =
, _binops :: [A.Located Infix]
, _effects :: Effects
}
deriving Show


getName :: Module -> Name
Expand All @@ -159,34 +165,44 @@ data Import =
, _alias :: Maybe Name
, _exposing :: Exposing
}
deriving Show


data Value = Value (A.Located Name) [Pattern] Expr (Maybe Type)
deriving Show
data Union = Union (A.Located Name) [A.Located Name] [(A.Located Name, [Type])]
deriving Show
data Alias = Alias (A.Located Name) [A.Located Name] Type
deriving Show
data Infix = Infix Name Binop.Associativity Binop.Precedence Name
deriving Show
data Port = Port (A.Located Name) Type
deriving Show


data Effects
= NoEffects
| Ports [Port]
| Manager A.Region Manager
deriving Show


data Manager
= Cmd (A.Located Name)
| Sub (A.Located Name)
| Fx (A.Located Name) (A.Located Name)
deriving Show


data Docs
= NoDocs A.Region
| YesDocs Comment [(Name, Comment)]
deriving Show


newtype Comment =
Comment P.Snippet
deriving Show



Expand All @@ -196,14 +212,17 @@ newtype Comment =
data Exposing
= Open
| Explicit [Exposed]
deriving Show


data Exposed
= Lower (A.Located Name)
| Upper (A.Located Name) Privacy
| Operator A.Region Name
deriving Show


data Privacy
= Public A.Region
| Private
deriving Show
4 changes: 2 additions & 2 deletions compiler/src/AST/Utils/Binop.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,14 +16,14 @@ import Data.Binary


newtype Precedence = Precedence Int
deriving (Eq, Ord)
deriving (Eq, Ord, Show)


data Associativity
= Left
| Non
| Right
deriving (Eq)
deriving (Eq, Show)



Expand Down
Loading

0 comments on commit 85d5118

Please sign in to comment.