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,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)