feat[compiler]: Compile to bytecode
This commit is contained in:
parent
f9ea61d348
commit
13c3e4d007
7 changed files with 67 additions and 11 deletions
|
@ -1,16 +1,37 @@
|
|||
{-# LANGUAGE Safe #-}
|
||||
module Language.Scalie.Compiler.Bytecode (EntryPoint, compile) where
|
||||
import Language.Scalie.Ast.Module (Module)
|
||||
{-# LANGUAGE Trustworthy #-} -- uses vector operations
|
||||
{-# LANGUAGE OverloadedRecordDot #-}
|
||||
module Language.Scalie.Compiler.Bytecode (EntryPoint, compile, CompilationError(..)) where
|
||||
import Language.Scalie.Ast.Module (Module (definitions))
|
||||
import Data.Text (Text)
|
||||
import Language.Scalie.Ast.Provenance (Provenance)
|
||||
import Language.Scalie.Ast.Provenance (Provenance (value, Provenance, source))
|
||||
import Language.Scalie.Ast.Provenance.SourceLocation (SourceLocation)
|
||||
import Language.Scalie.Bytecode.Object qualified as Bytecode
|
||||
import Data.Kind (Type)
|
||||
import Data.Either (Either (Left, Right))
|
||||
import Data.Vector qualified as Vector
|
||||
import Control.Category ((.))
|
||||
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.Bytecode.Instruction qualified as Instruction
|
||||
|
||||
-- | The name of the entrypoint function
|
||||
|
||||
type EntryPoint :: Type
|
||||
type EntryPoint = Text
|
||||
|
||||
compile :: Module (Provenance SourceLocation) -> EntryPoint -> Bytecode.Object
|
||||
compile = _
|
||||
type CompilationError :: Type
|
||||
newtype CompilationError = NameNotFound Text
|
||||
|
||||
compile :: Module (Provenance SourceLocation) -> EntryPoint -> Either CompilationError Bytecode.Object
|
||||
compile mod entry = let
|
||||
topLevelDefinitions = mod.definitions.value
|
||||
in Bytecode.Object . Vector.fromList <$> case ImplicitMap.lookup entry topLevelDefinitions of
|
||||
Nothing -> Left $ NameNotFound entry
|
||||
Just def -> Right
|
||||
[ (\(RawInt i) -> Instruction.PushInteger i) <$> def.body
|
||||
, Provenance def.name.source (Instruction.ReturnValues 1)
|
||||
]
|
||||
|
|
Loading…
Add table
Add a link
Reference in a new issue