Compare commits

...

5 commits

12 changed files with 109 additions and 28 deletions

View file

@ -24,6 +24,11 @@ library
Language.Scalie.Bytecode.Object Language.Scalie.Bytecode.Object
Language.Scalie.Bytecode.Object.Builder Language.Scalie.Bytecode.Object.Builder
Language.Scalie.Compiler.Bytecode Language.Scalie.Compiler.Bytecode
Language.Scalie.Core.AlgebraicDatatype
Language.Scalie.Core.AlgebraicDatatype.Constructor
Language.Scalie.Core.AlgebraicDatatype.Field
Language.Scalie.Core.AlgebraicDatatype.FieldIdentifier
Language.Scalie.Core.AlgebraicDatatype.TypeName
Language.Scalie.Core.Definition Language.Scalie.Core.Definition
Language.Scalie.Core.Expression Language.Scalie.Core.Expression
Language.Scalie.Core.Expression.ConstructorIdentifier Language.Scalie.Core.Expression.ConstructorIdentifier

View file

@ -0,0 +1,19 @@
{-# LANGUAGE Trustworthy #-}
module Language.Scalie.Core.AlgebraicDatatype (AlgebraicDatatype(..)) where
-- meta
import Data.Kind (Type)
-- data structures
import Data.Vector (Vector)
-- scalie
import Language.Scalie.Core.AlgebraicDatatype.TypeName (TypeName)
import Language.Scalie.Core.AlgebraicDatatype.Constructor (Constructor)
type AlgebraicDatatype :: (Type -> Type) -> Type
type role AlgebraicDatatype nominal
data AlgebraicDatatype f = AlgebraicDatatype
{ name :: f TypeName
, constructors :: f (Vector (Constructor f))
}

View file

@ -0,0 +1,13 @@
{-# LANGUAGE Trustworthy #-} -- uses vector operations
module Language.Scalie.Core.AlgebraicDatatype.Constructor (Constructor(..)) where
import Data.Kind (Type)
import Language.Scalie.Core.Expression.ConstructorIdentifier (ConstructorIdentifier)
import Data.Vector (Vector)
import Language.Scalie.Core.AlgebraicDatatype.Field (Field)
type Constructor :: (Type -> Type) -> Type
type role Constructor nominal
data Constructor f = Constructor
{ name :: f ConstructorIdentifier
, fields :: f (Vector (Field f))
}

View file

@ -0,0 +1,16 @@
{-# LANGUAGE Safe #-}
module Language.Scalie.Core.AlgebraicDatatype.Field (Field(..)) where
-- meta
import Data.Kind qualified
-- scalie
import Language.Scalie.Core.AlgebraicDatatype.FieldIdentifier (FieldIdentifier)
import Language.Scalie.Domain.Type qualified as Scalie.Domain
type Field :: (Data.Kind.Type -> Data.Kind.Type) -> Data.Kind.Type
type role Field nominal
data Field f = Field
{ name :: f FieldIdentifier
, typ :: f Scalie.Domain.Type
}

View file

@ -0,0 +1,8 @@
{-# LANGUAGE Safe #-}
module Language.Scalie.Core.AlgebraicDatatype.FieldIdentifier (FieldIdentifier(..)) where
import Data.Text (Text)
import Data.Kind (Type)
type FieldIdentifier :: Type
newtype FieldIdentifier = FieldIdentifier { get :: Text }
deriving stock (Show, Read, Eq)

View file

@ -0,0 +1,22 @@
{-# LANGUAGE Safe #-}
{-# LANGUAGE InstanceSigs #-}
module Language.Scalie.Core.AlgebraicDatatype.TypeName (TypeName(..)) where
-- meta
import Data.Kind (Type)
-- data structures
import Data.Text (Text)
import Data.Text qualified as Text
-- library: QuickCheck
import Test.QuickCheck (Arbitrary (arbitrary), Gen, UnicodeString (getUnicodeString))
type TypeName :: Type
newtype TypeName = TypeName { get :: Text }
deriving stock (Show, Read, Eq)
instance Arbitrary TypeName where
arbitrary :: Gen TypeName
arbitrary = TypeName . Text.pack . getUnicodeString <$> arbitrary

View file

@ -60,6 +60,8 @@ deriving stock instance (Show (f (Expression f)), Show (f Scalie.Domain.Type), S
deriving stock instance (Read (f (Expression f)), Read (f Scalie.Domain.Type), Read (f Text)) => Read (Definition f) deriving stock instance (Read (f (Expression f)), Read (f Scalie.Domain.Type), Read (f Text)) => Read (Definition f)
deriving stock instance (Eq (f (Expression f)), Eq (f Scalie.Domain.Type) , Eq (f Text)) => Eq (Definition f) deriving stock instance (Eq (f (Expression f)), Eq (f Scalie.Domain.Type) , Eq (f Text)) => Eq (Definition f)
-- | Using custom instances allows extracting just the text whereever possible.
instance ImplicitKeyOf (Definition (Provenance a)) where instance ImplicitKeyOf (Definition (Provenance a)) where
type KeyType (Definition (Provenance a)) = Text type KeyType (Definition (Provenance a)) = Text
keyOf :: Definition (Provenance a) -> KeyType (Definition (Provenance a)) keyOf :: Definition (Provenance a) -> KeyType (Definition (Provenance a))

View file

@ -24,6 +24,8 @@ import Test.QuickCheck.Gen (Gen)
import Test.QuickCheck qualified as Gen import Test.QuickCheck qualified as Gen
-- | Desugared expression.
type Expression :: (Type -> Type) -> Type type Expression :: (Type -> Type) -> Type
type role Expression nominal type role Expression nominal
data Expression f data Expression f

View file

@ -5,33 +5,24 @@
{-# LANGUAGE UndecidableInstances #-} -- instance head no smaller... {-# LANGUAGE UndecidableInstances #-} -- instance head no smaller...
module Language.Scalie.Core.Module (Module(..)) where module Language.Scalie.Core.Module (Module(..)) where
-- meta
import Data.Kind (Type) import Data.Kind (Type)
import Language.Scalie.Core.Definition (Definition)
-- data types
import Data.Map.Implicit (ImplicitMap) import Data.Map.Implicit (ImplicitMap)
-- | A module groups multiple related definitions. -- scalie
-- import Language.Scalie.Core.Definition (Definition)
-- >>> import Data.Functor.Identity (Identity(..)) import safe Language.Scalie.Core.AlgebraicDatatype ( AlgebraicDatatype )
-- >>> import Data.Map.Implicit qualified as ImplicitMap
-- >>> Module (Identity ImplicitMap.empty) -- | A module groups multiple related variable definitions.
-- Module {definitions = Identity ImplicitMapElems []}
--
-- >>> import Data.Maybe (Maybe(..))
-- >>> Module Nothing
-- Module {definitions = Nothing}
--
-- >>> import Text.Read (readMaybe)
-- >>> readMaybe "Module { definitions = Just (ImplicitMapElems []) }" :: Maybe (Module Maybe)
-- Just (Module {definitions = Just ImplicitMapElems []})
--
-- >>> readMaybe "Module { definitions = Just (ImplicitMapElems [Definition { signature = Nothing, name = Just \"x\", body = Nothing } ]) }" :: Maybe (Module Maybe)
-- Just (Module {definitions = Just ImplicitMapElems [Definition {signature = Nothing, name = Just "x", body = Nothing}]})
type Module :: (Type -> Type) -> Type type Module :: (Type -> Type) -> Type
type role Module nominal type role Module nominal
newtype Module f = Module data Module f = Module
{ definitions :: f (ImplicitMap (Definition f)) { definitions :: f (ImplicitMap (Definition f))
, datatypes :: f (ImplicitMap (AlgebraicDatatype f))
} }
deriving stock instance (Show (f (ImplicitMap (Definition f)))) => Show (Module f) deriving stock instance (Show (f (ImplicitMap (Definition f))), Show (f (ImplicitMap (AlgebraicDatatype f)))) => Show (Module f)
deriving stock instance (Read (f (ImplicitMap (Definition f)))) => Read (Module f) deriving stock instance (Read (f (ImplicitMap (Definition f))), Read (f (ImplicitMap (AlgebraicDatatype f)))) => Read (Module f)

View file

@ -11,6 +11,8 @@ import Data.Bifunctor (Bifunctor (bimap))
import Data.Bifoldable (Bifoldable (bifoldMap)) import Data.Bifoldable (Bifoldable (bifoldMap))
import Data.Bitraversable (Bitraversable (bitraverse)) import Data.Bitraversable (Bitraversable (bitraverse))
-- | Provenance records where something comes from. E.g. file name, file line, other sources.
type Provenance :: Type -> Type -> Type type Provenance :: Type -> Type -> Type
type role Provenance representational representational type role Provenance representational representational
data Provenance source value = Provenance data Provenance source value = Provenance

View file

@ -1,9 +1,10 @@
{-# LANGUAGE Safe #-} {-# LANGUAGE Safe #-}
module Language.Scalie.Core.Provenance.SourceLocation (SourceLocation(..)) where module Language.Scalie.Core.Provenance.SourceLocation (SourceLocation(..)) where
import Data.Kind (Type) import Data.Kind (Type)
import Text.Show (Show)
import Text.Read (Read) -- | Location of anything in a user-provided source file.
import Data.Eq (Eq) --
-- TODO: Add more constructors
type SourceLocation :: Type type SourceLocation :: Type
data SourceLocation data SourceLocation

View file

@ -3,17 +3,17 @@
module Language.Scalie.Domain.Type (Type(..)) where module Language.Scalie.Domain.Type (Type(..)) where
import Data.Kind qualified import Data.Kind qualified
import Text.Show (Show)
import Text.Read (Read)
import Data.Eq (Eq)
import Test.QuickCheck (Arbitrary (arbitrary), Gen, oneof) import Test.QuickCheck (Arbitrary (arbitrary), Gen, oneof)
import Control.Applicative (Applicative(pure))
-- | The type of an expression in Scalie, not to be confused with the 'Type' provided by GHC
type Type :: Data.Kind.Type type Type :: Data.Kind.Type
data Type data Type
= RawInt = RawInt
deriving stock (Show, Read, Eq) deriving stock (Show, Read, Eq)
-- add to the arbitrary instance when defining constructors
instance Arbitrary Type where instance Arbitrary Type where
arbitrary :: Gen Type arbitrary :: Gen Type
arbitrary = oneof [ pure RawInt ] arbitrary = oneof [ pure RawInt ]