refactor[core]: Ast module is now Core

This commit is contained in:
vegowotenks 2025-08-15 08:42:28 +02:00
parent 13c3e4d007
commit 45c02e7e54
10 changed files with 24 additions and 24 deletions

View file

@ -0,0 +1,84 @@
{-# LANGUAGE Safe #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedRecordDot #-}
module Language.Scalie.Core.Definition (Definition(..)) where
import Data.Kind (Type)
import Data.Text (Text)
import Data.Map.Implicit (ImplicitKeyOf (KeyType, keyOf))
import Language.Scalie.Domain.Type qualified as Scalie.Domain
import Language.Scalie.Core.Expression (Expression)
import Text.Show (Show)
import Text.Read (Read)
import Data.Eq (Eq)
import Test.QuickCheck.Arbitrary (Arbitrary (arbitrary))
import Test.QuickCheck.Gen (Gen)
import Control.Applicative (Applicative((<*>)), (<$>))
import Data.Text qualified as Text
import Control.Category (Category((.)))
import Test.QuickCheck.Modifiers (UnicodeString(getUnicodeString))
import Data.Functor (Functor)
import Language.Scalie.Core.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)
--
-- >>> import Data.Functor.Identity (Identity(Identity))
-- >>> import Data.Function (($))
-- >>> :set -XOverloadedStrings
-- >>> import Language.Scalie.Core.Expression qualified as Expression
-- >>> Definition (Identity Scalie.Domain.RawInt) (Identity "x") (Identity (Expression.RawInt 5))
-- Definition {signature = Identity RawInt, name = Identity "x", body = Identity (RawInt 5)}
--
-- >>> import Data.Maybe (Maybe(..))
-- >>> Definition Nothing (Just "x") (Just (Expression.RawInt 5))
-- Definition {signature = Nothing, name = Just "x", body = Just (RawInt 5)}
--
-- >>> import Text.Read (readMaybe)
-- >>> readMaybe "Definition {signature = Just RawInt, name = Nothing, body = Nothing}" :: Maybe (Definition Maybe)
-- Just (Definition {signature = Just RawInt, name = Nothing, body = Nothing})
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 can be used to refer to this definition
, body :: f Expression
-- ^ 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)
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
arbitrary :: Gen (Definition f)
arbitrary = Definition
<$> arbitrary
<*> ((Text.pack . getUnicodeString <$>) <$> arbitrary)
<*> arbitrary

View file

@ -0,0 +1,23 @@
{-# LANGUAGE Safe #-}
{-# LANGUAGE InstanceSigs #-}
module Language.Scalie.Core.Expression (Expression(..)) where
import Prelude (Integer)
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 ((<$>))
type Expression :: Type
data Expression
= RawInt Integer
deriving stock (Show, Read, Eq)
instance Arbitrary Expression where
arbitrary :: Gen Expression
arbitrary = oneof
[ RawInt <$> arbitrary
]

View file

@ -0,0 +1,39 @@
{-# LANGUAGE Safe #-}
{-# LANGUAGE StandaloneKindSignatures #-} -- because of -Weverything
{-# LANGUAGE StandaloneDeriving #-} -- to specify contexts
{-# LANGUAGE FlexibleContexts #-} -- 'non type-variable argument'
{-# LANGUAGE UndecidableInstances #-} -- instance head no smaller...
module Language.Scalie.Core.Module (Module(..)) where
import Data.Kind (Type)
import Language.Scalie.Core.Definition (Definition)
import Data.Map.Implicit (ImplicitMap)
import Text.Show (Show)
import Text.Read (Read)
-- | A module groups multiple related definitions.
--
-- >>> import Data.Functor.Identity (Identity(..))
-- >>> import Data.Map.Implicit qualified as ImplicitMap
-- >>> Module (Identity ImplicitMap.empty)
-- 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 role Module nominal
data Module f = Module
{ definitions :: f (ImplicitMap (Definition f))
}
deriving stock instance (Show (f (ImplicitMap (Definition f)))) => Show (Module f)
deriving stock instance (Read (f (ImplicitMap (Definition f)))) => Read (Module f)

View file

@ -0,0 +1,30 @@
{-# LANGUAGE Safe #-}
{-# LANGUAGE DerivingStrategies #-}
module Language.Scalie.Core.Pattern (Pattern(..)) where
import Prelude (Integer)
import Text.Show (Show)
import Text.Read (Read)
import Data.Kind qualified
-- | A pattern in scalie. Used to select branches to jump to, with pattern matching.
--
-- >>> RawInt 15
-- RawInt 15
--
-- >>> import Data.Maybe (Maybe)
-- >>> import Text.Read (readMaybe)
-- >>> readMaybe "RawInt (-5)" :: Maybe Pattern
-- Just (RawInt (-5))
--
-- >>> readMaybe "RawInt (+5)" :: Maybe Pattern
-- Nothing
--
-- >>> readMaybe "RawInt (5)" :: Maybe Pattern
-- Just (RawInt 5)
type Pattern :: Data.Kind.Type
data Pattern
= RawInt Integer
deriving stock (Show, Read)

View file

@ -0,0 +1,37 @@
{-# LANGUAGE Safe #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE DeriveTraversable #-} -- implies DeriveFunctor and DeriveFoldable
module Language.Scalie.Core.Provenance (Provenance(..)) where
import Data.Kind (Type)
import Text.Show (Show)
import Text.Read (Read)
import Data.Functor (Functor)
import Data.Foldable (Foldable)
import Data.Bifunctor (Bifunctor (bimap))
import Data.Traversable (Traversable)
import Data.Bifoldable (Bifoldable (bifoldMap))
import Data.Monoid (Monoid)
import Data.Semigroup ((<>))
import Data.Bitraversable (Bitraversable (bitraverse))
import Control.Applicative (Applicative (liftA2))
type Provenance :: Type -> Type -> Type
type role Provenance representational representational
data Provenance source value = Provenance
{ source :: source
, value :: value
}
deriving stock (Show, Read, Functor, Foldable, Traversable)
instance Bifunctor Provenance where
bimap :: (a -> b) -> (c -> d) -> Provenance a c -> Provenance b d
bimap f g (Provenance a b) = Provenance (f a) (g b)
instance Bifoldable Provenance where
bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> Provenance a b -> m
bifoldMap f g (Provenance a b) = f a <> g b
instance Bitraversable Provenance where
bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Provenance a b -> f (Provenance c d)
bitraverse f g (Provenance a b) = liftA2 Provenance (f a) (g b)

View file

@ -0,0 +1,11 @@
{-# LANGUAGE Safe #-}
module Language.Scalie.Core.Provenance.SourceLocation (SourceLocation(..)) where
import Data.Kind (Type)
import Text.Show (Show)
import Text.Read (Read)
import Data.Eq (Eq)
type SourceLocation :: Type
data SourceLocation
= Synthesized
deriving stock (Show, Read, Eq)