feat[dev]: import Prelude

This commit is contained in:
vegowotenks 2025-08-15 10:28:13 +02:00
parent 390308e9d7
commit 36ae4dd5e0
20 changed files with 102 additions and 172 deletions

View file

@ -6,22 +6,20 @@
{-# LANGUAGE StandaloneDeriving #-} -- derive Eq
-- | A Map that derives the keys for the mapping from the items.
module Data.Map.Implicit (ImplicitMap(), get, ImplicitKeyOf(..), empty, fromList, lookup) where
import Data.Kind (Type, Constraint)
import Data.Map (Map)
import Text.Show (Show (show))
import Data.String (String)
import Control.Category ((.), Category (id))
import Data.Map qualified as Map
import Text.Read (Read (readPrec), ReadPrec)
import Data.List qualified as List
module Data.Map.Implicit (ImplicitMap(), get, ImplicitKeyOf(..), empty, fromList, Data.Map.Implicit.lookup) where
import Control.Arrow (Arrow ((&&&)), (>>>))
import Data.Functor ((<$>))
import Data.Ord (Ord)
import Data.Eq (Eq)
import Data.Kind (Type, Constraint)
import Data.Map (Map)
import Data.Map qualified as Map
import Data.List qualified as List
import Text.Read (Read (readPrec), ReadPrec)
import Test.QuickCheck.Arbitrary (Arbitrary (arbitrary))
import Test.QuickCheck.Gen (Gen)
import Data.Maybe (Maybe)
-- | This map will use the 'ImplicitKeyOf' class to compute the keys of the values.

View file

@ -1,11 +1,9 @@
{-# LANGUAGE Safe #-}
{-# LANGUAGE EmptyDataDeriving #-} -- instruction doesn't have any cases yet
module Language.Scalie.Bytecode.Instruction (Instruction(..)) where
import Data.Kind (Type)
import Text.Show (Show)
import Text.Read (Read)
import Data.Eq (Eq)
import Prelude (Integer) -- this is apparently the only safe way to import 'Integer'
import Data.Word (Word8)
type Instruction :: Type

View file

@ -4,15 +4,17 @@
-- | This module describes a Bytecode Object, similar to a java classfile. It will hold source information, shared constants and
module Language.Scalie.Bytecode.Object (Object(..)) where
-- meta
import Data.Kind (Type)
-- data structures
import Data.Vector (Vector)
-- Scalie
import Language.Scalie.Core.Provenance (Provenance)
import Language.Scalie.Bytecode.Instruction (Instruction)
import Language.Scalie.Core.Provenance.SourceLocation (SourceLocation)
import Text.Show (Show)
import Text.Read (Read)
import Data.Semigroup (Semigroup)
import Data.Monoid (Monoid)
type Object :: Type
type role Object

View file

@ -2,12 +2,10 @@
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE InstanceSigs #-}
module Language.Scalie.Bytecode.Object.Builder (Builder, runBuilder) where
import Data.Kind (Type)
import Language.Scalie.Bytecode.Object qualified as Bytecode
import Data.Functor (Functor)
import Control.Applicative (Applicative (pure, (<*>)))
import Control.Monad (Monad ((>>=)))
import Prelude (undefined)
type Builder :: Type -> Type
type role Builder representational

View file

@ -1,23 +1,11 @@
{-# LANGUAGE Trustworthy #-} -- uses vector operations
{-# LANGUAGE OverloadedRecordDot #-}
module Language.Scalie.Compiler.Bytecode (EntryPoint, compile, CompilationError(..)) where
import Language.Scalie.Core.Module (Module (definitions))
import Data.Text (Text)
import Language.Scalie.Core.Provenance (Provenance (value, Provenance, source))
import Language.Scalie.Core.Provenance.SourceLocation (SourceLocation)
import Language.Scalie.Bytecode.Object qualified as Bytecode
{-# LANGUAGE Safe #-}
module Language.Scalie.Compiler.Bytecode (EntryPoint, CompilationError(..)) where
-- meta
import Data.Kind (Type)
import Data.Either (Either (Left, Right))
import Data.Vector qualified as Vector
import Control.Category ((.))
import Data.Function (($))
import Data.Functor ((<$>))
import Data.Map.Implicit qualified as ImplicitMap
import Data.Maybe (Maybe(Nothing, Just))
import Language.Scalie.Core.Definition (Definition(body, name))
import Language.Scalie.Core.Expression (Expression(RawInt))
import Language.Scalie.Bytecode.Instruction qualified as Instruction
import Prelude (undefined)
-- data structures
import Data.Text (Text)
-- | The name of the entrypoint function
@ -26,15 +14,3 @@ type EntryPoint = Text
type CompilationError :: Type
newtype CompilationError = NameNotFound Text
compile :: Module (Provenance SourceLocation) -> EntryPoint -> Either CompilationError Bytecode.Object
compile mod entry = undefined
{- let
topLevelDefinitions = mod.definitions.value
in Bytecode.Object . Vector.fromList <$> case ImplicitMap.lookup entry topLevelDefinitions of
Nothing -> Left $ NameNotFound entry
Just def -> Right
[ (\(RawInt i) -> Instruction.PushInteger i) <$> def.body
, Provenance def.name.source (Instruction.ReturnValues 1)
]
-}

View file

@ -7,26 +7,26 @@
{-# LANGUAGE OverloadedRecordDot #-}
module Language.Scalie.Core.Definition (Definition(..)) where
-- meta
import Data.Kind (Type)
import Data.Text (Text)
-- data structures
import Data.Text (Text)
import Data.Functor.Identity (Identity)
import Data.Map.Implicit (ImplicitKeyOf (KeyType, keyOf))
import Language.Scalie.Domain.Type qualified as Scalie.Domain
import Data.Text qualified as Text
-- scalie
import Language.Scalie.Core.Expression (Expression)
import Text.Show (Show)
import Text.Read (Read)
import Data.Eq (Eq)
import Language.Scalie.Core.Provenance (Provenance (value))
import Language.Scalie.Domain.Type qualified as Scalie.Domain
-- library: QuickCheck
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)
--

View file

@ -4,25 +4,26 @@
{-# LANGUAGE InstanceSigs #-}
module Language.Scalie.Core.Expression (Expression(..)) where
import Prelude (Integer, Integral (div))
-- meta
import Data.Kind (Type)
import Text.Show (Show)
import Text.Read (Read)
import Data.Eq (Eq)
import Data.Ratio (Rational)
-- data structures
import Data.Text (Text)
import Data.List.NonEmpty (NonEmpty)
import Data.Text qualified as Text
import Data.List.NonEmpty qualified as NonEmpty
-- scalie
import Language.Scalie.Core.Expression.PatternMatchCase (PatternMatchCase)
import Language.Scalie.Core.Expression.VariableIdentifier (VariableIdentifier)
-- library: QuickCheck
import Test.QuickCheck (Arbitrary (arbitrary), oneof, UnicodeString (getUnicodeString), NonEmptyList (getNonEmpty))
import Test.QuickCheck.Gen (Gen)
import Data.Functor ((<$>), Functor)
import Control.Category ((.))
import Data.Text qualified as Text
import Language.Scalie.Core.Expression.VariableIdentifier (VariableIdentifier)
import Control.Applicative ((<*>))
import Data.List.NonEmpty qualified as NonEmpty
import Test.QuickCheck qualified as Gen
type Expression :: (Type -> Type) -> Type
type role Expression nominal
data Expression f

View file

@ -5,15 +5,16 @@
module Language.Scalie.Core.Expression.ConstructorIdentifier (ConstructorIdentifier(..)) where
-- meta
import Data.Kind (Type)
-- data structures
import Data.Text (Text)
import Text.Show (Show)
import Text.Read (Read)
import Data.Eq (Eq)
import Test.QuickCheck (Arbitrary (arbitrary), Gen, getUnicodeString)
import Control.Category ((.))
import Data.Text qualified as Text
import Data.Functor ((<$>))
-- library: QuickCheck
import Test.QuickCheck (Arbitrary (arbitrary), Gen, getUnicodeString)
-- | Encodes the knowledge that the contained text is always a Constructor name.

View file

@ -6,19 +6,22 @@
-- | Pattern types for the core language. 'Pattern' enumerates all the possible ways to match on a value.
module Language.Scalie.Core.Expression.Pattern (Pattern(..)) where
-- meta
import Data.Kind (Type)
-- data structures
import Data.Vector (Vector)
import Data.Vector qualified as Vector
-- Scalie
import Language.Scalie.Core.Expression.VariableIdentifier (VariableIdentifier)
import Language.Scalie.Core.Expression.ConstructorIdentifier (ConstructorIdentifier)
import Data.Vector (Vector)
import Text.Show (Show)
import Text.Read (Read)
import Data.Eq (Eq)
-- library: QuickCheck
import Test.QuickCheck (Arbitrary (arbitrary), Gen, oneof)
import Data.Functor ((<$>), Functor)
import Control.Applicative ((<*>))
import Data.Vector qualified as Vector
import Test.QuickCheck.Gen qualified as Gen
import Prelude (div) -- seems to be the safe way to import div
-- | This is a single pattern. It may be used for a single argument.

View file

@ -3,17 +3,17 @@
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE InstanceSigs #-}
module Language.Scalie.Core.Expression.PatternMatchCase (PatternMatchCase(..)) where
-- meta
import Data.Kind (Type)
-- scalie
import {-# SOURCE #-} Language.Scalie.Core.Expression (Expression)
import Language.Scalie.Core.Expression.Pattern (Pattern)
import Text.Show (Show)
import Text.Read (Read)
import Data.Eq (Eq)
-- library: QuickCheck
import Test.QuickCheck (Arbitrary (arbitrary), Gen)
import Data.Functor ((<$>))
import Control.Applicative ((<*>))
import Test.QuickCheck.Gen qualified as Gen
import Prelude (div)
type PatternMatchCase :: (Type -> Type) -> Type
type role PatternMatchCase nominal

View file

@ -5,15 +5,15 @@
module Language.Scalie.Core.Expression.VariableIdentifier (VariableIdentifier(..)) where
-- meta
import Data.Kind (Type)
-- data structures
import Data.Text (Text)
import Text.Show (Show)
import Text.Read (Read)
import Data.Eq (Eq)
import Test.QuickCheck (Arbitrary (arbitrary), Gen, UnicodeString (getUnicodeString))
import Control.Category ((.))
import Data.Text qualified as Text
import Data.Functor ((<$>))
-- library: QuickCheck
import Test.QuickCheck (Arbitrary (arbitrary), Gen, UnicodeString (getUnicodeString))
-- | Encodes the knowledge that the contained text is always a variable name.

View file

@ -8,8 +8,6 @@ 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.
--
@ -31,7 +29,7 @@ import Text.Read (Read)
type Module :: (Type -> Type) -> Type
type role Module nominal
data Module f = Module
newtype Module f = Module
{ definitions :: f (ImplicitMap (Definition f))
}

View file

@ -1,30 +0,0 @@
{-# 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

@ -2,18 +2,14 @@
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE DeriveTraversable #-} -- implies DeriveFunctor and DeriveFoldable
module Language.Scalie.Core.Provenance (Provenance(..)) where
-- meta
import Data.Kind (Type)
import Text.Show (Show)
import Text.Read (Read)
import Data.Functor (Functor)
import Data.Foldable (Foldable)
-- classes
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