feat[core]: Function Property: Argument modification

This commit is contained in:
vegowotenks 2025-08-17 18:19:00 +02:00
parent a38a20a546
commit c78ed4ac90
12 changed files with 138 additions and 3 deletions

5
src/Data/Enum/Util.hs Normal file
View file

@ -0,0 +1,5 @@
{-# LANGUAGE Safe #-}
module Data.Enum.Util (enumerate) where
enumerate :: (Enum a, Bounded a) => [a]
enumerate = [minBound .. maxBound]

View file

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

View file

@ -0,0 +1,9 @@
{-# LANGUAGE Safe #-}
module Language.Scalie.Domain.Type (Type) where
import Data.Kind qualified
type Type :: Data.Kind.Type
data Type
instance Show Type
instance Read Type
instance Eq Type

View file

@ -0,0 +1,18 @@
{-# LANGUAGE Safe #-}
module Language.Scalie.Domain.Type.Function (Function(..)) where
-- meta
import Data.Kind qualified
-- scalie
import Language.Scalie.Domain.Type.Function.ArgumentModification (ArgumentModification)
import {-# SOURCE #-} Language.Scalie.Domain.Type qualified as Scalie.Domain
type Function :: Data.Kind.Type
data Function = Function
{ argument :: Scalie.Domain.Type
, result :: Scalie.Domain.Type
, argumentModification :: ArgumentModification
}
deriving stock (Show, Read, Eq)

View file

@ -0,0 +1,26 @@
{-# LANGUAGE Trustworthy #-} -- leancheck import somehow is not safe
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE InstanceSigs #-}
module Language.Scalie.Domain.Type.Function.ArgumentModification (ArgumentModification(..), toBool, fromBool) where
import Data.Kind qualified
import Test.LeanCheck (Listable (list))
import Data.Enum.Util (enumerate)
type ArgumentModification :: Data.Kind.Type
data ArgumentModification
= PureArguments
| LinearArguments
deriving stock (Show, Read, Eq, Ord, Enum, Bounded)
toBool :: ArgumentModification -> Bool
toBool = \case
PureArguments -> False
LinearArguments -> True
fromBool :: Bool -> ArgumentModification
fromBool = toEnum . fromEnum
instance Listable ArgumentModification where
list :: [ArgumentModification]
list = enumerate