feat[compiler]: Compile to bytecode

This commit is contained in:
vegowotenks 2025-08-14 14:44:23 +02:00
parent f9ea61d348
commit 13c3e4d007
7 changed files with 67 additions and 11 deletions

View file

@ -22,6 +22,7 @@ default-extensions:
- DerivingStrategies
- ImportQualifiedPost
- NoImplicitPrelude
- OverloadedRecordDot
- OverloadedStrings
- StandaloneKindSignatures
- RoleAnnotations

View file

@ -39,6 +39,7 @@ library
DerivingStrategies
ImportQualifiedPost
NoImplicitPrelude
OverloadedRecordDot
OverloadedStrings
StandaloneKindSignatures
RoleAnnotations
@ -61,6 +62,7 @@ executable scalie-exe
DerivingStrategies
ImportQualifiedPost
NoImplicitPrelude
OverloadedRecordDot
OverloadedStrings
StandaloneKindSignatures
RoleAnnotations
@ -87,6 +89,7 @@ test-suite scalie-test
DerivingStrategies
ImportQualifiedPost
NoImplicitPrelude
OverloadedRecordDot
OverloadedStrings
StandaloneKindSignatures
RoleAnnotations

View file

@ -6,7 +6,7 @@
{-# LANGUAGE StandaloneDeriving #-} -- derive Eq
-- | A Map that derives the keys for the mapping from the items.
module Data.Map.Implicit (ImplicitMap(), get, ImplicitKeyOf(..), empty, fromList) where
module Data.Map.Implicit (ImplicitMap(), get, ImplicitKeyOf(..), empty, fromList, lookup) where
import Data.Kind (Type, Constraint)
import Data.Map (Map)
import Text.Show (Show (show))
@ -21,6 +21,7 @@ import Data.Ord (Ord)
import Data.Eq (Eq)
import Test.QuickCheck.Arbitrary (Arbitrary (arbitrary))
import Test.QuickCheck.Gen (Gen)
import Data.Maybe (Maybe)
-- | This map will use the 'ImplicitKeyOf' class to compute the keys of the values.
@ -61,10 +62,20 @@ class ImplicitKeyOf v where
type KeyType v :: Type
keyOf :: v -> KeyType v
-- | The empty map
empty :: ImplicitMap v
empty = ImplicitMap Map.empty
-- | Build from a List of values, keys will be inferred using 'ImplicitKeyOf'.
-- If multiple values have the same key, the last one specified in the list will be used.
fromList :: (ImplicitKeyOf v, Ord (KeyType v)) => [v] -> ImplicitMap v
fromList = List.map (keyOf &&& id)
>>> Map.fromList
>>> ImplicitMap
-- | Retrieve the value associated with its implicit key from the map.
lookup :: Ord (KeyType a) => KeyType a -> ImplicitMap a -> Maybe a
lookup k m = Map.lookup k (get m)

View file

@ -3,6 +3,8 @@
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedRecordDot #-}
module Language.Scalie.Ast.Definition (Definition(..)) where
import Data.Kind (Type)
@ -22,6 +24,9 @@ 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 Data.Functor.Identity (Identity)
import Data.Maybe (Maybe)
-- | The definition of a value or a function (which is also a value)
--
@ -55,9 +60,19 @@ deriving stock instance (Show (f Expression), Show (f Scalie.Domain.Type), Show
deriving stock instance (Read (f Expression), Read (f Scalie.Domain.Type), Read (f Text)) => Read (Definition f)
deriving stock instance (Eq (f Expression) , Eq (f Scalie.Domain.Type) , Eq (f Text)) => Eq (Definition f)
instance ImplicitKeyOf (Definition f) where
type KeyType (Definition f) = f Text
keyOf :: Definition f -> KeyType (Definition f)
instance ImplicitKeyOf (Definition (Provenance a)) where
type KeyType (Definition (Provenance a)) = Text
keyOf :: Definition (Provenance a) -> KeyType (Definition (Provenance a))
keyOf = (.name.value)
instance ImplicitKeyOf (Definition Identity) where
type KeyType (Definition Identity) = Identity Text
keyOf :: Definition Identity -> KeyType (Definition Identity)
keyOf = name
instance ImplicitKeyOf (Definition Maybe) where
type KeyType (Definition Maybe) = Maybe Text
keyOf :: Definition Maybe -> KeyType (Definition Maybe)
keyOf = name
instance (Functor f, Arbitrary (f UnicodeString), Arbitrary (f Scalie.Domain.Type), Arbitrary (f Expression)) => Arbitrary (Definition f) where

View file

@ -5,7 +5,11 @@ import Data.Kind (Type)
import Text.Show (Show)
import Text.Read (Read)
import Data.Eq (Eq)
import Prelude (Integer) -- this is apparently the only safe way to import 'Integer'
import Data.Word (Word8)
type Instruction :: Type
data Instruction
= PushInteger Integer
| ReturnValues Word8
deriving stock (Show, Read, Eq)

View file

@ -7,6 +7,7 @@ import Language.Scalie.Bytecode.Object qualified as Bytecode
import Data.Functor (Functor)
import Control.Applicative (Applicative (pure, (<*>)))
import Control.Monad (Monad ((>>=)))
import Prelude (undefined)
type Builder :: Type -> Type
type role Builder representational
@ -25,4 +26,4 @@ instance Monad Builder where
runBuilder :: Builder a -> (Bytecode.Object, a)
runBuilder = _
runBuilder = undefined

View file

@ -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)
]