feat[core]: Expressions and Patterns
This commit is contained in:
parent
45c02e7e54
commit
c02f1b292b
9 changed files with 192 additions and 15 deletions
|
@ -52,13 +52,13 @@ data Definition f = Definition
|
|||
-- ^ What is the type
|
||||
, name :: f Text
|
||||
-- ^ Which name can be used to refer to this definition
|
||||
, body :: f Expression
|
||||
, body :: f (Expression f)
|
||||
-- ^ What needs to be evaluated to get the value
|
||||
}
|
||||
|
||||
deriving stock instance (Show (f Expression), Show (f Scalie.Domain.Type), Show (f Text)) => Show (Definition f)
|
||||
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)
|
||||
deriving stock instance (Show (f (Expression f)), Show (f Scalie.Domain.Type), Show (f Text)) => Show (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)
|
||||
|
||||
instance ImplicitKeyOf (Definition (Provenance a)) where
|
||||
type KeyType (Definition (Provenance a)) = Text
|
||||
|
@ -75,7 +75,7 @@ instance ImplicitKeyOf (Definition Maybe) where
|
|||
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
|
||||
instance (Functor f, Arbitrary (f UnicodeString), Arbitrary (f Scalie.Domain.Type), Arbitrary (f (Expression f))) => Arbitrary (Definition f) where
|
||||
arbitrary :: Gen (Definition f)
|
||||
arbitrary = Definition
|
||||
<$> arbitrary
|
||||
|
|
|
@ -1,23 +1,54 @@
|
|||
{-# LANGUAGE Safe #-}
|
||||
{-# LANGUAGE StandaloneDeriving #-} -- to specify instance contexts
|
||||
{-# LANGUAGE UndecidableInstances #-} -- for the instance constraints containing the functor
|
||||
{-# LANGUAGE InstanceSigs #-}
|
||||
module Language.Scalie.Core.Expression (Expression(..)) where
|
||||
|
||||
import Prelude (Integer)
|
||||
import Prelude (Integer, Integral (div))
|
||||
import Data.Kind (Type)
|
||||
import Text.Show (Show)
|
||||
import Text.Read (Read)
|
||||
import Data.Eq (Eq)
|
||||
import Test.QuickCheck (Arbitrary (arbitrary), Gen, oneof)
|
||||
import Data.Functor ((<$>))
|
||||
import Data.Ratio (Rational)
|
||||
import Data.Text (Text)
|
||||
import Data.List.NonEmpty (NonEmpty)
|
||||
import Language.Scalie.Core.Expression.PatternMatchCase (PatternMatchCase)
|
||||
import Test.QuickCheck (Arbitrary (arbitrary), oneof, UnicodeString (getUnicodeString), NonEmptyList (getNonEmpty))
|
||||
import Test.QuickCheck.Gen (Gen)
|
||||
import Data.Functor ((<$>), Functor)
|
||||
import Control.Category ((.))
|
||||
import Data.Text qualified as Text
|
||||
import Language.Scalie.Core.Expression.VariableIdentifier (VariableIdentifier)
|
||||
import Control.Applicative ((<*>))
|
||||
import Data.List.NonEmpty qualified as NonEmpty
|
||||
import Test.QuickCheck qualified as Gen
|
||||
|
||||
type Expression :: Type
|
||||
data Expression
|
||||
= RawInt Integer
|
||||
deriving stock (Show, Read, Eq)
|
||||
type Expression :: (Type -> Type) -> Type
|
||||
type role Expression nominal
|
||||
data Expression f
|
||||
= RawInt (f Integer)
|
||||
| RawRational (f Rational)
|
||||
| RawString (f Text)
|
||||
| PatternMatch (f (NonEmpty (PatternMatchCase f)))
|
||||
| Lambda (f VariableIdentifier) (f (Expression f))
|
||||
|
||||
instance Arbitrary Expression where
|
||||
arbitrary :: Gen Expression
|
||||
-- to me, this looks incredibly dangerous, because of Show (f (Expression f)) => Show (Expression f)
|
||||
-- let's hope UndecidableInstances won't have the compiler diverge
|
||||
deriving stock instance (Show (f Integer), Show (f Rational), Show (f Text), Show (f (NonEmpty (PatternMatchCase f))), Show (f VariableIdentifier), Show (f (Expression f))) => Show (Expression f)
|
||||
deriving stock instance (Read (f Integer), Read (f Rational), Read (f Text), Read (f (NonEmpty (PatternMatchCase f))), Read (f VariableIdentifier), Read (f (Expression f))) => Read (Expression f)
|
||||
deriving stock instance (Eq (f Integer), Eq (f Rational), Eq (f Text), Eq (f (NonEmpty (PatternMatchCase f))), Eq (f VariableIdentifier), Eq (f (Expression f))) => Eq (Expression f)
|
||||
|
||||
instance (Arbitrary (f Integer), Arbitrary (f Rational), Arbitrary (f UnicodeString), Functor f, Arbitrary (f (Expression f)), Arbitrary (f VariableIdentifier), Arbitrary (f (NonEmptyList (PatternMatchCase f))) ) => Arbitrary (Expression f) where
|
||||
arbitrary :: Gen (Expression f)
|
||||
arbitrary = oneof
|
||||
[ RawInt <$> arbitrary
|
||||
, RawRational <$> arbitrary
|
||||
, RawString . (Text.pack . getUnicodeString <$>) <$> arbitrary
|
||||
, PatternMatch . (NonEmpty.fromList . getNonEmpty <$>) <$> Gen.scale (`div` 2) arbitrary -- scale the recursive case down
|
||||
, Lambda <$> arbitrary <*> Gen.scale (`div` 2) arbitrary -- scale the recursive case down
|
||||
]
|
||||
|
||||
-- >>> import Test.QuickCheck
|
||||
-- >>> import Data.Functor.Identity
|
||||
-- >>> sample (arbitrary :: Gen (Expression Identity))
|
||||
|
||||
|
|
8
src/Language/Scalie/Core/Expression.hs-boot
Normal file
8
src/Language/Scalie/Core/Expression.hs-boot
Normal file
|
@ -0,0 +1,8 @@
|
|||
{-# LANGUAGE Safe #-}
|
||||
module Language.Scalie.Core.Expression (Expression) where
|
||||
import Data.Kind (Type)
|
||||
|
||||
type Expression :: (Type -> Type) -> Type
|
||||
type role Expression nominal
|
||||
data Expression f
|
||||
|
27
src/Language/Scalie/Core/Expression/ConstructorIdentifier.hs
Normal file
27
src/Language/Scalie/Core/Expression/ConstructorIdentifier.hs
Normal file
|
@ -0,0 +1,27 @@
|
|||
{-# LANGUAGE Safe #-}
|
||||
{-# LANGUAGE InstanceSigs #-}
|
||||
|
||||
-- | Newtype synonym for type safety.
|
||||
|
||||
module Language.Scalie.Core.Expression.ConstructorIdentifier (ConstructorIdentifier(..)) where
|
||||
|
||||
import Data.Kind (Type)
|
||||
import Data.Text (Text)
|
||||
import Text.Show (Show)
|
||||
import Text.Read (Read)
|
||||
import Data.Eq (Eq)
|
||||
import Test.QuickCheck (Arbitrary (arbitrary), Gen, getUnicodeString)
|
||||
import Control.Category ((.))
|
||||
import Data.Text qualified as Text
|
||||
import Data.Functor ((<$>))
|
||||
|
||||
-- | Encodes the knowledge that the contained text is always a Constructor name.
|
||||
|
||||
type ConstructorIdentifier :: Type
|
||||
newtype ConstructorIdentifier = ConstructorIdentifier { get :: Text }
|
||||
deriving stock (Show, Read, Eq)
|
||||
|
||||
|
||||
instance Arbitrary ConstructorIdentifier where
|
||||
arbitrary :: Gen ConstructorIdentifier
|
||||
arbitrary = ConstructorIdentifier . Text.pack . getUnicodeString <$> arbitrary
|
43
src/Language/Scalie/Core/Expression/Pattern.hs
Normal file
43
src/Language/Scalie/Core/Expression/Pattern.hs
Normal file
|
@ -0,0 +1,43 @@
|
|||
{-# LANGUAGE Trustworthy #-} -- this module uses vectors
|
||||
{-# LANGUAGE StandaloneDeriving #-}
|
||||
{-# LANGUAGE UndecidableInstances #-}
|
||||
{-# LANGUAGE InstanceSigs #-}
|
||||
|
||||
-- | Pattern types for the core language. 'Pattern' enumerates all the possible ways to match on a value.
|
||||
|
||||
module Language.Scalie.Core.Expression.Pattern (Pattern(..)) where
|
||||
import Data.Kind (Type)
|
||||
import Language.Scalie.Core.Expression.VariableIdentifier (VariableIdentifier)
|
||||
import Language.Scalie.Core.Expression.ConstructorIdentifier (ConstructorIdentifier)
|
||||
import Data.Vector (Vector)
|
||||
import Text.Show (Show)
|
||||
import Text.Read (Read)
|
||||
import Data.Eq (Eq)
|
||||
import Test.QuickCheck (Arbitrary (arbitrary), Gen, oneof)
|
||||
import Data.Functor ((<$>), Functor)
|
||||
import Control.Applicative ((<*>))
|
||||
import Data.Vector qualified as Vector
|
||||
import Test.QuickCheck.Gen qualified as Gen
|
||||
import Prelude (div) -- seems to be the safe way to import div
|
||||
|
||||
-- | This is a single pattern. It may be used for a single argument.
|
||||
|
||||
type Pattern :: (Type -> Type) -> Type
|
||||
type role Pattern nominal
|
||||
data Pattern f
|
||||
= Variable (f VariableIdentifier) -- this is a catch-all, it matches anything
|
||||
| Record (f ConstructorIdentifier) (f (Vector (Pattern f))) -- match the constructor with the sub-patterns for the arguments
|
||||
|
||||
-- Remember to add cases to the arbitrary instance when adding data constructors
|
||||
|
||||
deriving stock instance (Show (f (Vector (Pattern f))), Show (f VariableIdentifier), Show (f ConstructorIdentifier)) => Show (Pattern f)
|
||||
deriving stock instance (Read (f (Vector (Pattern f))), Read (f VariableIdentifier), Read (f ConstructorIdentifier)) => Read (Pattern f)
|
||||
deriving stock instance (Eq (f (Vector (Pattern f))), Eq (f VariableIdentifier), Eq (f ConstructorIdentifier)) => Eq (Pattern f)
|
||||
|
||||
instance (Arbitrary (f VariableIdentifier), Arbitrary (f ConstructorIdentifier), Arbitrary (f [Pattern f]), Functor f) => Arbitrary (Pattern f) where
|
||||
arbitrary :: Gen (Pattern f)
|
||||
arbitrary = oneof
|
||||
[ Variable <$> arbitrary
|
||||
, Record <$> arbitrary <*> ((Vector.fromList <$>) <$> Gen.scale (`div` 2) arbitrary)
|
||||
]
|
||||
|
34
src/Language/Scalie/Core/Expression/PatternMatchCase.hs
Normal file
34
src/Language/Scalie/Core/Expression/PatternMatchCase.hs
Normal file
|
@ -0,0 +1,34 @@
|
|||
{-# LANGUAGE Safe #-}
|
||||
{-# LANGUAGE StandaloneDeriving #-}
|
||||
{-# LANGUAGE UndecidableInstances #-}
|
||||
{-# LANGUAGE InstanceSigs #-}
|
||||
module Language.Scalie.Core.Expression.PatternMatchCase (PatternMatchCase(..)) where
|
||||
import Data.Kind (Type)
|
||||
import {-# SOURCE #-} Language.Scalie.Core.Expression (Expression)
|
||||
import Language.Scalie.Core.Expression.Pattern (Pattern)
|
||||
import Text.Show (Show)
|
||||
import Text.Read (Read)
|
||||
import Data.Eq (Eq)
|
||||
import Test.QuickCheck (Arbitrary (arbitrary), Gen)
|
||||
import Data.Functor ((<$>))
|
||||
import Control.Applicative ((<*>))
|
||||
import Test.QuickCheck.Gen qualified as Gen
|
||||
import Prelude (div)
|
||||
|
||||
type PatternMatchCase :: (Type -> Type) -> Type
|
||||
type role PatternMatchCase nominal
|
||||
data PatternMatchCase f = PatternMatchCase
|
||||
{ pattern :: f (Pattern f)
|
||||
, body :: f (Expression f)
|
||||
}
|
||||
|
||||
deriving stock instance (Show (f (Pattern f)), Show (f (Expression f))) => Show (PatternMatchCase f)
|
||||
deriving stock instance (Read (f (Pattern f)), Read (f (Expression f))) => Read (PatternMatchCase f)
|
||||
deriving stock instance (Eq (f (Pattern f)), Eq (f (Expression f))) => Eq (PatternMatchCase f)
|
||||
|
||||
instance (Arbitrary (f (Pattern f)), Arbitrary (f (Expression f))) => Arbitrary (PatternMatchCase f) where
|
||||
arbitrary :: Gen (PatternMatchCase f)
|
||||
arbitrary = PatternMatchCase
|
||||
<$> arbitrary
|
||||
<*> Gen.scale (`div` 2) arbitrary
|
||||
|
27
src/Language/Scalie/Core/Expression/VariableIdentifier.hs
Normal file
27
src/Language/Scalie/Core/Expression/VariableIdentifier.hs
Normal file
|
@ -0,0 +1,27 @@
|
|||
{-# LANGUAGE Safe #-}
|
||||
{-# LANGUAGE InstanceSigs #-}
|
||||
|
||||
-- | Newtype synonym for type safety.
|
||||
|
||||
module Language.Scalie.Core.Expression.VariableIdentifier (VariableIdentifier(..)) where
|
||||
|
||||
import Data.Kind (Type)
|
||||
import Data.Text (Text)
|
||||
import Text.Show (Show)
|
||||
import Text.Read (Read)
|
||||
import Data.Eq (Eq)
|
||||
import Test.QuickCheck (Arbitrary (arbitrary), Gen, UnicodeString (getUnicodeString))
|
||||
import Control.Category ((.))
|
||||
import Data.Text qualified as Text
|
||||
import Data.Functor ((<$>))
|
||||
|
||||
-- | Encodes the knowledge that the contained text is always a variable name.
|
||||
|
||||
type VariableIdentifier :: Type
|
||||
newtype VariableIdentifier = VariableIdentifier { get :: Text }
|
||||
deriving stock (Show, Read, Eq)
|
||||
|
||||
instance Arbitrary VariableIdentifier where
|
||||
arbitrary :: Gen VariableIdentifier
|
||||
arbitrary = VariableIdentifier . Text.pack . getUnicodeString <$> arbitrary
|
||||
|
Loading…
Add table
Add a link
Reference in a new issue