doc[core]
This commit is contained in:
parent
b7e579dc20
commit
3847e1e81e
6 changed files with 13 additions and 1 deletions
|
@ -60,6 +60,8 @@ deriving stock instance (Show (f (Expression f)), Show (f Scalie.Domain.Type), S
|
||||||
deriving stock instance (Read (f (Expression f)), Read (f Scalie.Domain.Type), Read (f Text)) => Read (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)
|
deriving stock instance (Eq (f (Expression f)), Eq (f Scalie.Domain.Type) , Eq (f Text)) => Eq (Definition f)
|
||||||
|
|
||||||
|
-- | Using custom instances allows extracting just the text whereever possible.
|
||||||
|
|
||||||
instance ImplicitKeyOf (Definition (Provenance a)) where
|
instance ImplicitKeyOf (Definition (Provenance a)) where
|
||||||
type KeyType (Definition (Provenance a)) = Text
|
type KeyType (Definition (Provenance a)) = Text
|
||||||
keyOf :: Definition (Provenance a) -> KeyType (Definition (Provenance a))
|
keyOf :: Definition (Provenance a) -> KeyType (Definition (Provenance a))
|
||||||
|
|
|
@ -24,6 +24,8 @@ import Test.QuickCheck.Gen (Gen)
|
||||||
import Test.QuickCheck qualified as Gen
|
import Test.QuickCheck qualified as Gen
|
||||||
|
|
||||||
|
|
||||||
|
-- | Desugared expression.
|
||||||
|
|
||||||
type Expression :: (Type -> Type) -> Type
|
type Expression :: (Type -> Type) -> Type
|
||||||
type role Expression nominal
|
type role Expression nominal
|
||||||
data Expression f
|
data Expression f
|
||||||
|
|
|
@ -9,7 +9,7 @@ import Data.Kind (Type)
|
||||||
import Language.Scalie.Core.Definition (Definition)
|
import Language.Scalie.Core.Definition (Definition)
|
||||||
import Data.Map.Implicit (ImplicitMap)
|
import Data.Map.Implicit (ImplicitMap)
|
||||||
|
|
||||||
-- | A module groups multiple related definitions.
|
-- | A module groups multiple related variable definitions.
|
||||||
--
|
--
|
||||||
-- >>> import Data.Functor.Identity (Identity(..))
|
-- >>> import Data.Functor.Identity (Identity(..))
|
||||||
-- >>> import Data.Map.Implicit qualified as ImplicitMap
|
-- >>> import Data.Map.Implicit qualified as ImplicitMap
|
||||||
|
|
|
@ -11,6 +11,8 @@ import Data.Bifunctor (Bifunctor (bimap))
|
||||||
import Data.Bifoldable (Bifoldable (bifoldMap))
|
import Data.Bifoldable (Bifoldable (bifoldMap))
|
||||||
import Data.Bitraversable (Bitraversable (bitraverse))
|
import Data.Bitraversable (Bitraversable (bitraverse))
|
||||||
|
|
||||||
|
-- | Provenance records where something comes from. E.g. file name, file line, other sources.
|
||||||
|
|
||||||
type Provenance :: Type -> Type -> Type
|
type Provenance :: Type -> Type -> Type
|
||||||
type role Provenance representational representational
|
type role Provenance representational representational
|
||||||
data Provenance source value = Provenance
|
data Provenance source value = Provenance
|
||||||
|
|
|
@ -2,6 +2,10 @@
|
||||||
module Language.Scalie.Core.Provenance.SourceLocation (SourceLocation(..)) where
|
module Language.Scalie.Core.Provenance.SourceLocation (SourceLocation(..)) where
|
||||||
import Data.Kind (Type)
|
import Data.Kind (Type)
|
||||||
|
|
||||||
|
-- | Location of anything in a user-provided source file.
|
||||||
|
--
|
||||||
|
-- TODO: Add more constructors
|
||||||
|
|
||||||
type SourceLocation :: Type
|
type SourceLocation :: Type
|
||||||
data SourceLocation
|
data SourceLocation
|
||||||
= Synthesized
|
= Synthesized
|
||||||
|
|
|
@ -12,6 +12,8 @@ data Type
|
||||||
= RawInt
|
= RawInt
|
||||||
deriving stock (Show, Read, Eq)
|
deriving stock (Show, Read, Eq)
|
||||||
|
|
||||||
|
-- add to the arbitrary instance when defining constructors
|
||||||
|
|
||||||
instance Arbitrary Type where
|
instance Arbitrary Type where
|
||||||
arbitrary :: Gen Type
|
arbitrary :: Gen Type
|
||||||
arbitrary = oneof [ pure RawInt ]
|
arbitrary = oneof [ pure RawInt ]
|
||||||
|
|
Loading…
Add table
Add a link
Reference in a new issue