diff --git a/package.yaml b/package.yaml index 21401e8..336b741 100644 --- a/package.yaml +++ b/package.yaml @@ -19,6 +19,7 @@ extra-source-files: description: Please see the README on GitHub at default-extensions: + - DerivingStrategies - ImportQualifiedPost - NoImplicitPrelude - StandaloneKindSignatures diff --git a/scalie.cabal b/scalie.cabal index 0aa5f28..b67faef 100644 --- a/scalie.cabal +++ b/scalie.cabal @@ -19,11 +19,8 @@ extra-source-files: library exposed-modules: - Control.Ord.LexicographicallySorted Data.Map.Implicit - Language.Scalie.Ast Language.Scalie.Ast.Definition - Language.Scalie.Ast.Definition.Body Language.Scalie.Ast.Expression Language.Scalie.Ast.Module Language.Scalie.Ast.Pattern @@ -33,6 +30,7 @@ library hs-source-dirs: src default-extensions: + DerivingStrategies ImportQualifiedPost NoImplicitPrelude StandaloneKindSignatures @@ -52,6 +50,7 @@ executable scalie-exe hs-source-dirs: app default-extensions: + DerivingStrategies ImportQualifiedPost NoImplicitPrelude StandaloneKindSignatures @@ -73,6 +72,7 @@ test-suite scalie-test hs-source-dirs: test default-extensions: + DerivingStrategies ImportQualifiedPost NoImplicitPrelude StandaloneKindSignatures diff --git a/src/Data/Map/Implicit.hs b/src/Data/Map/Implicit.hs index f983432..ab2906e 100644 --- a/src/Data/Map/Implicit.hs +++ b/src/Data/Map/Implicit.hs @@ -1,17 +1,25 @@ {-# LANGUAGE Safe #-} {-# LANGUAGE TypeFamilies #-} --- +{-# LANGUAGE StandaloneDeriving #-} -- specify instance contexts +{-# LANGUAGE FlexibleContexts #-} -- use non type-variable argument in instance head +{-# LANGUAGE UndecidableInstances #-} -- use type family in instance head -- | A Map that derives the keys for the mapping from the items. module Data.Map.Implicit (ImplicitMap(), get, ImplicitKeyOf(..), empty) where import Data.Kind (Type, Constraint) import Data.Map (Map) import Data.Map qualified as Map +import Text.Show (Show) +import Text.Read (Read) +import Data.Ord (Ord) type ImplicitMap :: Type -> Type type role ImplicitMap nominal newtype ImplicitMap v = ImplicitMap { get :: Map (KeyType v) v } +deriving stock instance (Show (KeyType v), Show v) => Show (ImplicitMap v) +deriving stock instance (Read (KeyType v), Ord (KeyType v), Read v) => Read (ImplicitMap v) + type ImplicitKeyOf :: Type -> Constraint class ImplicitKeyOf v where diff --git a/src/Language/Scalie/Ast/Definition.hs b/src/Language/Scalie/Ast/Definition.hs index f7f092d..9e6d6f8 100644 --- a/src/Language/Scalie/Ast/Definition.hs +++ b/src/Language/Scalie/Ast/Definition.hs @@ -1,26 +1,51 @@ {-# LANGUAGE Safe #-} {-# LANGUAGE InstanceSigs #-} {-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE StandaloneDeriving #-} +{-# LANGUAGE UndecidableInstances #-} 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)) +import Language.Scalie.Domain.Type qualified as Scalie.Domain +import Language.Scalie.Ast.Expression (Expression) +import Text.Show (Show) +import Text.Read (Read) + +-- | 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.Ast.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 will be used to refer to this definition - , body :: f (DefinitionBody f) + -- ^ 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) + instance ImplicitKeyOf (Definition f) where type KeyType (Definition f) = f Text keyOf :: Definition f -> KeyType (Definition f) diff --git a/src/Language/Scalie/Ast/Definition/Body.hs b/src/Language/Scalie/Ast/Definition/Body.hs deleted file mode 100644 index 796c022..0000000 --- a/src/Language/Scalie/Ast/Definition/Body.hs +++ /dev/null @@ -1,15 +0,0 @@ -{-# 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 - } diff --git a/src/Language/Scalie/Ast/Expression.hs b/src/Language/Scalie/Ast/Expression.hs index 061c94e..09ef3b3 100644 --- a/src/Language/Scalie/Ast/Expression.hs +++ b/src/Language/Scalie/Ast/Expression.hs @@ -3,7 +3,10 @@ module Language.Scalie.Ast.Expression (Expression(..)) where import Prelude (Integer) import Data.Kind (Type) +import Text.Show (Show) +import Text.Read (Read) type Expression :: Type data Expression = RawInt Integer + deriving stock (Show, Read) diff --git a/src/Language/Scalie/Ast/Module.hs b/src/Language/Scalie/Ast/Module.hs index ca7587f..f90f9d1 100644 --- a/src/Language/Scalie/Ast/Module.hs +++ b/src/Language/Scalie/Ast/Module.hs @@ -1,13 +1,27 @@ {-# LANGUAGE Safe #-} -{-# LANGUAGE StandaloneKindSignatures #-} +{-# 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.Ast.Module (Module(..)) where import Data.Kind (Type) import Language.Scalie.Ast.Definition (Definition) import Data.Map.Implicit (ImplicitMap) +import Text.Show ( Show ) +import Text.Read (Read) +import Data.Text (Text) +import Language.Scalie.Ast.Expression (Expression) +import Language.Scalie.Domain.Type qualified as Scalie.Domain +import Data.Ord (Ord) + +-- | A module groups multiple related definitions. type Module :: (Type -> Type) -> Type type role Module nominal data Module f = Module { definitions :: ImplicitMap (Definition f) } + +deriving stock instance (Show (f Text), Show (f Expression), Show (f Scalie.Domain.Type)) => Show (Module f) +deriving stock instance (Read (f Text), Ord (f Text), Read (f Expression), Read (f Scalie.Domain.Type)) => Read (Module f) diff --git a/src/Language/Scalie/Ast/Pattern.hs b/src/Language/Scalie/Ast/Pattern.hs index 57e9ee6..9a07dc4 100644 --- a/src/Language/Scalie/Ast/Pattern.hs +++ b/src/Language/Scalie/Ast/Pattern.hs @@ -1,6 +1,28 @@ {-# LANGUAGE Safe #-} +{-# LANGUAGE DerivingStrategies #-} module Language.Scalie.Ast.Pattern (Pattern(..)) where import Prelude (Integer) +import Text.Show (Show) +import Text.Read (Read, readMaybe) +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) +-- >>> 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) + diff --git a/src/Language/Scalie/Domain/Type.hs b/src/Language/Scalie/Domain/Type.hs index 757d4d2..bf54b2d 100644 --- a/src/Language/Scalie/Domain/Type.hs +++ b/src/Language/Scalie/Domain/Type.hs @@ -2,7 +2,11 @@ module Language.Scalie.Domain.Type (Type(..)) where import Data.Kind qualified +import Text.Show (Show) +import Text.Read (Read) type Type :: Data.Kind.Type -data Type +data Type = RawInt + deriving stock (Show, Read) +