refactor[core]: Ast
module is now Core
This commit is contained in:
parent
13c3e4d007
commit
45c02e7e54
10 changed files with 24 additions and 24 deletions
12
scalie.cabal
12
scalie.cabal
|
@ -20,16 +20,16 @@ extra-source-files:
|
|||
library
|
||||
exposed-modules:
|
||||
Data.Map.Implicit
|
||||
Language.Scalie.Ast.Definition
|
||||
Language.Scalie.Ast.Expression
|
||||
Language.Scalie.Ast.Module
|
||||
Language.Scalie.Ast.Pattern
|
||||
Language.Scalie.Ast.Provenance
|
||||
Language.Scalie.Ast.Provenance.SourceLocation
|
||||
Language.Scalie.Bytecode.Instruction
|
||||
Language.Scalie.Bytecode.Object
|
||||
Language.Scalie.Bytecode.Object.Builder
|
||||
Language.Scalie.Compiler.Bytecode
|
||||
Language.Scalie.Core.Definition
|
||||
Language.Scalie.Core.Expression
|
||||
Language.Scalie.Core.Module
|
||||
Language.Scalie.Core.Pattern
|
||||
Language.Scalie.Core.Provenance
|
||||
Language.Scalie.Core.Provenance.SourceLocation
|
||||
Language.Scalie.Domain.Type
|
||||
other-modules:
|
||||
Paths_scalie
|
||||
|
|
|
@ -6,9 +6,9 @@
|
|||
module Language.Scalie.Bytecode.Object (Object(..)) where
|
||||
import Data.Kind (Type)
|
||||
import Data.Vector (Vector)
|
||||
import Language.Scalie.Ast.Provenance (Provenance)
|
||||
import Language.Scalie.Core.Provenance (Provenance)
|
||||
import Language.Scalie.Bytecode.Instruction (Instruction)
|
||||
import Language.Scalie.Ast.Provenance.SourceLocation (SourceLocation)
|
||||
import Language.Scalie.Core.Provenance.SourceLocation (SourceLocation)
|
||||
import Text.Show (Show)
|
||||
import Text.Read (Read)
|
||||
import Data.Semigroup (Semigroup)
|
||||
|
|
|
@ -1,10 +1,10 @@
|
|||
{-# LANGUAGE Trustworthy #-} -- uses vector operations
|
||||
{-# LANGUAGE OverloadedRecordDot #-}
|
||||
module Language.Scalie.Compiler.Bytecode (EntryPoint, compile, CompilationError(..)) where
|
||||
import Language.Scalie.Ast.Module (Module (definitions))
|
||||
import Language.Scalie.Core.Module (Module (definitions))
|
||||
import Data.Text (Text)
|
||||
import Language.Scalie.Ast.Provenance (Provenance (value, Provenance, source))
|
||||
import Language.Scalie.Ast.Provenance.SourceLocation (SourceLocation)
|
||||
import Language.Scalie.Core.Provenance (Provenance (value, Provenance, source))
|
||||
import Language.Scalie.Core.Provenance.SourceLocation (SourceLocation)
|
||||
import Language.Scalie.Bytecode.Object qualified as Bytecode
|
||||
import Data.Kind (Type)
|
||||
import Data.Either (Either (Left, Right))
|
||||
|
@ -14,8 +14,8 @@ import Data.Function (($))
|
|||
import Data.Functor ((<$>))
|
||||
import Data.Map.Implicit qualified as ImplicitMap
|
||||
import Data.Maybe (Maybe(Nothing, Just))
|
||||
import Language.Scalie.Ast.Definition (Definition(body, name))
|
||||
import Language.Scalie.Ast.Expression (Expression(RawInt))
|
||||
import Language.Scalie.Core.Definition (Definition(body, name))
|
||||
import Language.Scalie.Core.Expression (Expression(RawInt))
|
||||
import Language.Scalie.Bytecode.Instruction qualified as Instruction
|
||||
|
||||
-- | The name of the entrypoint function
|
||||
|
|
|
@ -5,7 +5,7 @@
|
|||
{-# LANGUAGE UndecidableInstances #-}
|
||||
{-# LANGUAGE FlexibleInstances #-}
|
||||
{-# LANGUAGE OverloadedRecordDot #-}
|
||||
module Language.Scalie.Ast.Definition (Definition(..)) where
|
||||
module Language.Scalie.Core.Definition (Definition(..)) where
|
||||
|
||||
import Data.Kind (Type)
|
||||
import Data.Text (Text)
|
||||
|
@ -13,7 +13,7 @@ import Data.Text (Text)
|
|||
import Data.Map.Implicit (ImplicitKeyOf (KeyType, keyOf))
|
||||
|
||||
import Language.Scalie.Domain.Type qualified as Scalie.Domain
|
||||
import Language.Scalie.Ast.Expression (Expression)
|
||||
import Language.Scalie.Core.Expression (Expression)
|
||||
import Text.Show (Show)
|
||||
import Text.Read (Read)
|
||||
import Data.Eq (Eq)
|
||||
|
@ -24,7 +24,7 @@ import Data.Text qualified as Text
|
|||
import Control.Category (Category((.)))
|
||||
import Test.QuickCheck.Modifiers (UnicodeString(getUnicodeString))
|
||||
import Data.Functor (Functor)
|
||||
import Language.Scalie.Ast.Provenance (Provenance (value))
|
||||
import Language.Scalie.Core.Provenance (Provenance (value))
|
||||
import Data.Functor.Identity (Identity)
|
||||
import Data.Maybe (Maybe)
|
||||
|
||||
|
@ -33,7 +33,7 @@ import Data.Maybe (Maybe)
|
|||
-- >>> import Data.Functor.Identity (Identity(Identity))
|
||||
-- >>> import Data.Function (($))
|
||||
-- >>> :set -XOverloadedStrings
|
||||
-- >>> import Language.Scalie.Ast.Expression qualified as Expression
|
||||
-- >>> import Language.Scalie.Core.Expression qualified as Expression
|
||||
-- >>> Definition (Identity Scalie.Domain.RawInt) (Identity "x") (Identity (Expression.RawInt 5))
|
||||
-- Definition {signature = Identity RawInt, name = Identity "x", body = Identity (RawInt 5)}
|
||||
--
|
|
@ -1,6 +1,6 @@
|
|||
{-# LANGUAGE Safe #-}
|
||||
{-# LANGUAGE InstanceSigs #-}
|
||||
module Language.Scalie.Ast.Expression (Expression(..)) where
|
||||
module Language.Scalie.Core.Expression (Expression(..)) where
|
||||
|
||||
import Prelude (Integer)
|
||||
import Data.Kind (Type)
|
|
@ -3,10 +3,10 @@
|
|||
{-# LANGUAGE StandaloneDeriving #-} -- to specify contexts
|
||||
{-# LANGUAGE FlexibleContexts #-} -- 'non type-variable argument'
|
||||
{-# LANGUAGE UndecidableInstances #-} -- instance head no smaller...
|
||||
module Language.Scalie.Ast.Module (Module(..)) where
|
||||
module Language.Scalie.Core.Module (Module(..)) where
|
||||
|
||||
import Data.Kind (Type)
|
||||
import Language.Scalie.Ast.Definition (Definition)
|
||||
import Language.Scalie.Core.Definition (Definition)
|
||||
import Data.Map.Implicit (ImplicitMap)
|
||||
import Text.Show (Show)
|
||||
import Text.Read (Read)
|
|
@ -1,6 +1,6 @@
|
|||
{-# LANGUAGE Safe #-}
|
||||
{-# LANGUAGE DerivingStrategies #-}
|
||||
module Language.Scalie.Ast.Pattern (Pattern(..)) where
|
||||
module Language.Scalie.Core.Pattern (Pattern(..)) where
|
||||
import Prelude (Integer)
|
||||
import Text.Show (Show)
|
||||
import Text.Read (Read)
|
|
@ -1,7 +1,7 @@
|
|||
{-# LANGUAGE Safe #-}
|
||||
{-# LANGUAGE InstanceSigs #-}
|
||||
{-# LANGUAGE DeriveTraversable #-} -- implies DeriveFunctor and DeriveFoldable
|
||||
module Language.Scalie.Ast.Provenance (Provenance(..)) where
|
||||
module Language.Scalie.Core.Provenance (Provenance(..)) where
|
||||
import Data.Kind (Type)
|
||||
import Text.Show (Show)
|
||||
import Text.Read (Read)
|
|
@ -1,5 +1,5 @@
|
|||
{-# LANGUAGE Safe #-}
|
||||
module Language.Scalie.Ast.Provenance.SourceLocation (SourceLocation(..)) where
|
||||
module Language.Scalie.Core.Provenance.SourceLocation (SourceLocation(..)) where
|
||||
import Data.Kind (Type)
|
||||
import Text.Show (Show)
|
||||
import Text.Read (Read)
|
|
@ -8,7 +8,7 @@ import Text.Show (show)
|
|||
import Text.Read (read)
|
||||
import Data.Map.Implicit (ImplicitMap)
|
||||
import Data.Bool (Bool)
|
||||
import Language.Scalie.Ast.Definition (Definition)
|
||||
import Language.Scalie.Core.Definition (Definition)
|
||||
import Data.Functor.Identity (Identity)
|
||||
import Test.QuickCheck (Property, allProperties)
|
||||
import Data.String (String)
|
||||
|
|
Loading…
Add table
Add a link
Reference in a new issue