feat: Ability to specify integer definitions
This commit is contained in:
parent
4bd766027f
commit
76970d7f9a
11 changed files with 143 additions and 11 deletions
28
src/Language/Scalie/Ast/Definition.hs
Normal file
28
src/Language/Scalie/Ast/Definition.hs
Normal file
|
@ -0,0 +1,28 @@
|
|||
{-# LANGUAGE Safe #-}
|
||||
{-# LANGUAGE InstanceSigs #-}
|
||||
{-# LANGUAGE TypeFamilies #-}
|
||||
module Language.Scalie.Ast.Definition (Definition(..)) where
|
||||
|
||||
import Data.Kind (Type)
|
||||
import Data.Text (Text)
|
||||
|
||||
import Language.Scalie.Domain.Type qualified as Scalie.Domain
|
||||
import Language.Scalie.Ast.Definition.Body (DefinitionBody)
|
||||
import Data.Map.Implicit (ImplicitKeyOf (KeyType, keyOf))
|
||||
|
||||
type Definition :: (Type -> Type) -> Type
|
||||
type role Definition nominal
|
||||
data Definition f = Definition
|
||||
{ signature :: f Scalie.Domain.Type
|
||||
-- ^ What is the type
|
||||
, name :: f Text
|
||||
-- ^ Which name will be used to refer to this definition
|
||||
, body :: f (DefinitionBody f)
|
||||
-- ^ What needs to be evaluated to get the value
|
||||
}
|
||||
|
||||
instance ImplicitKeyOf (Definition f) where
|
||||
type KeyType (Definition f) = f Text
|
||||
keyOf :: Definition f -> KeyType (Definition f)
|
||||
keyOf = name
|
||||
|
15
src/Language/Scalie/Ast/Definition/Body.hs
Normal file
15
src/Language/Scalie/Ast/Definition/Body.hs
Normal file
|
@ -0,0 +1,15 @@
|
|||
{-# LANGUAGE Trustworthy #-} -- I declare trustworthiness because I only use Vector, I do not call any unsafe functions.
|
||||
module Language.Scalie.Ast.Definition.Body (DefinitionBody(..)) where
|
||||
|
||||
import Data.Vector (Vector)
|
||||
|
||||
import Language.Scalie.Ast.Expression (Expression)
|
||||
import Language.Scalie.Ast.Pattern (Pattern)
|
||||
import Data.Kind (Type)
|
||||
|
||||
type DefinitionBody :: (Type -> Type) -> Type
|
||||
type role DefinitionBody representational
|
||||
data DefinitionBody f = DefinitionBody
|
||||
{ arguments :: f (Vector Pattern)
|
||||
, rhs :: f Expression
|
||||
}
|
9
src/Language/Scalie/Ast/Expression.hs
Normal file
9
src/Language/Scalie/Ast/Expression.hs
Normal file
|
@ -0,0 +1,9 @@
|
|||
{-# LANGUAGE Safe #-}
|
||||
module Language.Scalie.Ast.Expression (Expression(..)) where
|
||||
|
||||
import Prelude (Integer)
|
||||
import Data.Kind (Type)
|
||||
|
||||
type Expression :: Type
|
||||
data Expression
|
||||
= RawInt Integer
|
13
src/Language/Scalie/Ast/Module.hs
Normal file
13
src/Language/Scalie/Ast/Module.hs
Normal file
|
@ -0,0 +1,13 @@
|
|||
{-# LANGUAGE Safe #-}
|
||||
{-# LANGUAGE StandaloneKindSignatures #-}
|
||||
module Language.Scalie.Ast.Module (Module(..)) where
|
||||
|
||||
import Data.Kind (Type)
|
||||
import Language.Scalie.Ast.Definition (Definition)
|
||||
import Data.Map.Implicit (ImplicitMap)
|
||||
|
||||
type Module :: (Type -> Type) -> Type
|
||||
type role Module nominal
|
||||
data Module f = Module
|
||||
{ definitions :: ImplicitMap (Definition f)
|
||||
}
|
6
src/Language/Scalie/Ast/Pattern.hs
Normal file
6
src/Language/Scalie/Ast/Pattern.hs
Normal file
|
@ -0,0 +1,6 @@
|
|||
{-# LANGUAGE Safe #-}
|
||||
module Language.Scalie.Ast.Pattern (Pattern(..)) where
|
||||
import Prelude (Integer)
|
||||
|
||||
data Pattern
|
||||
= RawInt Integer
|
Loading…
Add table
Add a link
Reference in a new issue