feat[bytecode]: A lot of scaffolding for setup
This commit is contained in:
parent
766528677f
commit
f9ea61d348
7 changed files with 130 additions and 0 deletions
|
@ -24,6 +24,12 @@ library
|
|||
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.Domain.Type
|
||||
other-modules:
|
||||
Paths_scalie
|
||||
|
|
37
src/Language/Scalie/Ast/Provenance.hs
Normal file
37
src/Language/Scalie/Ast/Provenance.hs
Normal file
|
@ -0,0 +1,37 @@
|
|||
{-# LANGUAGE Safe #-}
|
||||
{-# LANGUAGE InstanceSigs #-}
|
||||
{-# LANGUAGE DeriveTraversable #-} -- implies DeriveFunctor and DeriveFoldable
|
||||
module Language.Scalie.Ast.Provenance (Provenance(..)) where
|
||||
import Data.Kind (Type)
|
||||
import Text.Show (Show)
|
||||
import Text.Read (Read)
|
||||
import Data.Functor (Functor)
|
||||
import Data.Foldable (Foldable)
|
||||
import Data.Bifunctor (Bifunctor (bimap))
|
||||
import Data.Traversable (Traversable)
|
||||
import Data.Bifoldable (Bifoldable (bifoldMap))
|
||||
import Data.Monoid (Monoid)
|
||||
import Data.Semigroup ((<>))
|
||||
import Data.Bitraversable (Bitraversable (bitraverse))
|
||||
import Control.Applicative (Applicative (liftA2))
|
||||
|
||||
type Provenance :: Type -> Type -> Type
|
||||
type role Provenance representational representational
|
||||
data Provenance source value = Provenance
|
||||
{ source :: source
|
||||
, value :: value
|
||||
}
|
||||
deriving stock (Show, Read, Functor, Foldable, Traversable)
|
||||
|
||||
instance Bifunctor Provenance where
|
||||
bimap :: (a -> b) -> (c -> d) -> Provenance a c -> Provenance b d
|
||||
bimap f g (Provenance a b) = Provenance (f a) (g b)
|
||||
|
||||
instance Bifoldable Provenance where
|
||||
bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> Provenance a b -> m
|
||||
bifoldMap f g (Provenance a b) = f a <> g b
|
||||
|
||||
instance Bitraversable Provenance where
|
||||
bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Provenance a b -> f (Provenance c d)
|
||||
bitraverse f g (Provenance a b) = liftA2 Provenance (f a) (g b)
|
||||
|
11
src/Language/Scalie/Ast/Provenance/SourceLocation.hs
Normal file
11
src/Language/Scalie/Ast/Provenance/SourceLocation.hs
Normal file
|
@ -0,0 +1,11 @@
|
|||
{-# LANGUAGE Safe #-}
|
||||
module Language.Scalie.Ast.Provenance.SourceLocation (SourceLocation(..)) where
|
||||
import Data.Kind (Type)
|
||||
import Text.Show (Show)
|
||||
import Text.Read (Read)
|
||||
import Data.Eq (Eq)
|
||||
|
||||
type SourceLocation :: Type
|
||||
data SourceLocation
|
||||
= Synthesized
|
||||
deriving stock (Show, Read, Eq)
|
11
src/Language/Scalie/Bytecode/Instruction.hs
Normal file
11
src/Language/Scalie/Bytecode/Instruction.hs
Normal file
|
@ -0,0 +1,11 @@
|
|||
{-# LANGUAGE Safe #-}
|
||||
{-# LANGUAGE EmptyDataDeriving #-} -- instruction doesn't have any cases yet
|
||||
module Language.Scalie.Bytecode.Instruction (Instruction(..)) where
|
||||
import Data.Kind (Type)
|
||||
import Text.Show (Show)
|
||||
import Text.Read (Read)
|
||||
import Data.Eq (Eq)
|
||||
|
||||
type Instruction :: Type
|
||||
data Instruction
|
||||
deriving stock (Show, Read, Eq)
|
21
src/Language/Scalie/Bytecode/Object.hs
Normal file
21
src/Language/Scalie/Bytecode/Object.hs
Normal file
|
@ -0,0 +1,21 @@
|
|||
{-# LANGUAGE Trustworthy #-} -- Trustworthy because it imports Vector but does not do unsafe things
|
||||
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
||||
|
||||
-- | This module describes a Bytecode Object, similar to a java classfile. It will hold source information, shared constants and
|
||||
|
||||
module Language.Scalie.Bytecode.Object (Object(..)) where
|
||||
import Data.Kind (Type)
|
||||
import Data.Vector (Vector)
|
||||
import Language.Scalie.Ast.Provenance (Provenance)
|
||||
import Language.Scalie.Bytecode.Instruction (Instruction)
|
||||
import Language.Scalie.Ast.Provenance.SourceLocation (SourceLocation)
|
||||
import Text.Show (Show)
|
||||
import Text.Read (Read)
|
||||
import Data.Semigroup (Semigroup)
|
||||
import Data.Monoid (Monoid)
|
||||
|
||||
type Object :: Type
|
||||
type role Object
|
||||
newtype Object = Object { instructions :: Vector (Provenance SourceLocation Instruction) }
|
||||
deriving stock (Show, Read)
|
||||
deriving newtype (Semigroup, Monoid)
|
28
src/Language/Scalie/Bytecode/Object/Builder.hs
Normal file
28
src/Language/Scalie/Bytecode/Object/Builder.hs
Normal file
|
@ -0,0 +1,28 @@
|
|||
{-# LANGUAGE Safe #-}
|
||||
{-# LANGUAGE DeriveFunctor #-}
|
||||
{-# LANGUAGE InstanceSigs #-}
|
||||
module Language.Scalie.Bytecode.Object.Builder (Builder, runBuilder) where
|
||||
import Data.Kind (Type)
|
||||
import Language.Scalie.Bytecode.Object qualified as Bytecode
|
||||
import Data.Functor (Functor)
|
||||
import Control.Applicative (Applicative (pure, (<*>)))
|
||||
import Control.Monad (Monad ((>>=)))
|
||||
|
||||
type Builder :: Type -> Type
|
||||
type role Builder representational
|
||||
newtype Builder a = Builder a
|
||||
deriving stock (Functor)
|
||||
|
||||
instance Applicative Builder where
|
||||
pure :: a -> Builder a
|
||||
pure = Builder
|
||||
(<*>) :: Builder (a -> b) -> Builder a -> Builder b
|
||||
(<*>) (Builder f) (Builder x) = Builder (f x)
|
||||
|
||||
instance Monad Builder where
|
||||
(>>=) :: Builder a -> (a -> Builder b) -> Builder b
|
||||
(>>=) (Builder x) f = f x
|
||||
|
||||
|
||||
runBuilder :: Builder a -> (Bytecode.Object, a)
|
||||
runBuilder = _
|
16
src/Language/Scalie/Compiler/Bytecode.hs
Normal file
16
src/Language/Scalie/Compiler/Bytecode.hs
Normal file
|
@ -0,0 +1,16 @@
|
|||
{-# LANGUAGE Safe #-}
|
||||
module Language.Scalie.Compiler.Bytecode (EntryPoint, compile) where
|
||||
import Language.Scalie.Ast.Module (Module)
|
||||
import Data.Text (Text)
|
||||
import Language.Scalie.Ast.Provenance (Provenance)
|
||||
import Language.Scalie.Ast.Provenance.SourceLocation (SourceLocation)
|
||||
import Language.Scalie.Bytecode.Object qualified as Bytecode
|
||||
import Data.Kind (Type)
|
||||
|
||||
-- | The name of the entrypoint function
|
||||
|
||||
type EntryPoint :: Type
|
||||
type EntryPoint = Text
|
||||
|
||||
compile :: Module (Provenance SourceLocation) -> EntryPoint -> Bytecode.Object
|
||||
compile = _
|
Loading…
Add table
Add a link
Reference in a new issue