Compare commits

..

No commits in common. "36ae4dd5e0f5974e41a0ab15c28a280898139a1e" and "c02f1b292b4928c1cd9aff27b24d7140f549a1ee" have entirely different histories.

20 changed files with 170 additions and 104 deletions

View file

@ -1,5 +1,7 @@
{-# LANGUAGE Safe #-}
module Main (main) where
import Control.Applicative (pure)
import System.IO (IO)
main :: IO ()
main = pure ()

View file

@ -21,6 +21,7 @@ description: Please see the README on GitHub at <https://github.com/gith
default-extensions:
- DerivingStrategies
- ImportQualifiedPost
- NoImplicitPrelude
- OverloadedRecordDot
- OverloadedStrings
- StandaloneKindSignatures
@ -36,7 +37,6 @@ dependencies:
ghc-options:
- -Weverything
- -Wno-unsafe
- -Wno-implicit-prelude # coding without prelude is no fun
library:
source-dirs: src

View file

@ -31,6 +31,7 @@ library
Language.Scalie.Core.Expression.PatternMatchCase
Language.Scalie.Core.Expression.VariableIdentifier
Language.Scalie.Core.Module
Language.Scalie.Core.Pattern
Language.Scalie.Core.Provenance
Language.Scalie.Core.Provenance.SourceLocation
Language.Scalie.Domain.Type
@ -41,11 +42,12 @@ library
default-extensions:
DerivingStrategies
ImportQualifiedPost
NoImplicitPrelude
OverloadedRecordDot
OverloadedStrings
StandaloneKindSignatures
RoleAnnotations
ghc-options: -Weverything -Wno-unsafe -Wno-implicit-prelude
ghc-options: -Weverything -Wno-unsafe
build-depends:
QuickCheck
, base
@ -63,11 +65,12 @@ executable scalie-exe
default-extensions:
DerivingStrategies
ImportQualifiedPost
NoImplicitPrelude
OverloadedRecordDot
OverloadedStrings
StandaloneKindSignatures
RoleAnnotations
ghc-options: -Weverything -Wno-unsafe -Wno-implicit-prelude -threaded -rtsopts -with-rtsopts=-N
ghc-options: -Weverything -Wno-unsafe -threaded -rtsopts -with-rtsopts=-N
build-depends:
QuickCheck
, base
@ -89,11 +92,12 @@ test-suite scalie-test
default-extensions:
DerivingStrategies
ImportQualifiedPost
NoImplicitPrelude
OverloadedRecordDot
OverloadedStrings
StandaloneKindSignatures
RoleAnnotations
ghc-options: -Weverything -Wno-unsafe -Wno-implicit-prelude -threaded -rtsopts -with-rtsopts=-N
ghc-options: -Weverything -Wno-unsafe -threaded -rtsopts -with-rtsopts=-N
build-depends:
QuickCheck
, base

View file

@ -6,20 +6,22 @@
{-# 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, Data.Map.Implicit.lookup) where
import Control.Arrow (Arrow ((&&&)), (>>>))
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 Data.List qualified as List
import Text.Read (Read (readPrec), ReadPrec)
import Data.List qualified as List
import Control.Arrow (Arrow ((&&&)), (>>>))
import Data.Functor ((<$>))
import Data.Ord (Ord)
import Data.Eq (Eq)
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,9 +1,11 @@
{-# 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,17 +4,15 @@
-- | 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,10 +2,12 @@
{-# 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,11 +1,23 @@
{-# LANGUAGE Safe #-}
module Language.Scalie.Compiler.Bytecode (EntryPoint, CompilationError(..)) where
-- meta
import Data.Kind (Type)
-- data structures
{-# 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
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)
-- | The name of the entrypoint function
@ -14,3 +26,15 @@ 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)
-- data structures
import Data.Text (Text)
import Data.Functor.Identity (Identity)
import Data.Map.Implicit (ImplicitKeyOf (KeyType, keyOf))
import Data.Text qualified as Text
-- scalie
import Language.Scalie.Core.Expression (Expression)
import Language.Scalie.Core.Provenance (Provenance (value))
import Language.Scalie.Domain.Type qualified as Scalie.Domain
-- library: QuickCheck
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)
--

View file

@ -4,26 +4,25 @@
{-# LANGUAGE InstanceSigs #-}
module Language.Scalie.Core.Expression (Expression(..)) where
-- meta
import Prelude (Integer, Integral (div))
import Data.Kind (Type)
-- data structures
import Text.Show (Show)
import Text.Read (Read)
import Data.Eq (Eq)
import Data.Ratio (Rational)
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,16 +5,15 @@
module Language.Scalie.Core.Expression.ConstructorIdentifier (ConstructorIdentifier(..)) where
-- meta
import Data.Kind (Type)
-- data structures
import Data.Text (Text)
import Data.Text qualified as Text
-- library: QuickCheck
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 ((<$>))
-- | Encodes the knowledge that the contained text is always a Constructor name.

View file

@ -6,22 +6,19 @@
-- | 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)
-- library: QuickCheck
import Data.Vector (Vector)
import Text.Show (Show)
import Text.Read (Read)
import Data.Eq (Eq)
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)
-- library: QuickCheck
import Text.Show (Show)
import Text.Read (Read)
import Data.Eq (Eq)
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 Data.Text qualified as Text
-- library: QuickCheck
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 ((<$>))
-- | Encodes the knowledge that the contained text is always a variable name.

View file

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

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

View file

@ -1,6 +1,8 @@
{-# LANGUAGE Unsafe #-} -- unsafe: Uses functions imported from unsafe modules
import System.IO (IO)
import Test.Data.Map.Implicit qualified
import Test.Tasty qualified as Tasty
import Data.Function (($))
main :: IO ()
main = Tasty.defaultMain $ Tasty.testGroup "all"

View file

@ -3,21 +3,19 @@
{-# OPTIONS_GHC -Wno-all-missed-specialisations #-} -- a lot of warnings for unspecialized 'read' and 'show', which I cannot specialize
-- I wouldn't know how at least, they're not my datatypes, I cannot use the hint and add an 'INLINABLE' pragma
module Test.Data.Map.Implicit (testGroup) where
import Data.Functor.Identity (Identity)
import Data.Map.Implicit (ImplicitMap)
import Language.Scalie.Core.Definition (Definition)
import Test.QuickCheck (Property, allProperties)
import Test.QuickCheck.Roundtrip (roundtrips)
import Test.Tasty (TestTree)
import Test.Tasty.QuickCheck (QuickCheckMaxSize(QuickCheckMaxSize))
import Test.Tasty qualified as Tasty
import Text.Show (show)
import Text.Read (read)
import Data.Map.Implicit (ImplicitMap)
import Data.Bool (Bool)
import Language.Scalie.Core.Definition (Definition)
import Data.Functor.Identity (Identity)
import Test.QuickCheck (Property, allProperties)
import Data.String (String)
import Control.Applicative (pure)
import Data.Maybe (Maybe)
import Test.Tasty.QuickCheck qualified as Tasty.QuickCheck
import Test.Tasty (TestTree)
-- | This is testworthy since I have somehow hand-hacked the read/show de/serialization of 'ImplicitMap'
@ -32,5 +30,4 @@ allTests :: [(String, Property)]
allTests = $allProperties
testGroup :: TestTree
testGroup = Tasty.localOption (QuickCheckMaxSize 25) -- it is necessary to restrain the size because the generated core would get veeeeeery big otherwise
$ Tasty.QuickCheck.testProperties "Data.Map.Implicit" allTests
testGroup = Tasty.QuickCheck.testProperties "Data.Map.Implicit" allTests

View file

@ -1,5 +1,7 @@
{-# LANGUAGE Safe #-}
module Test.QuickCheck.Roundtrip (roundtrips) where
import Data.Eq ((==), Eq)
import Data.Bool (Bool)
roundtrips :: Eq t1 => (t2 -> t1) -> (t1 -> t2) -> t1 -> Bool
roundtrips back forth x = x == back (forth x)