Compare commits
2 commits
c02f1b292b
...
36ae4dd5e0
Author | SHA1 | Date | |
---|---|---|---|
36ae4dd5e0 | |||
390308e9d7 |
20 changed files with 106 additions and 172 deletions
|
@ -1,7 +1,5 @@
|
|||
{-# LANGUAGE Safe #-}
|
||||
module Main (main) where
|
||||
|
||||
import Control.Applicative (pure)
|
||||
import System.IO (IO)
|
||||
|
||||
main :: IO ()
|
||||
main = pure ()
|
||||
|
|
|
@ -21,7 +21,6 @@ description: Please see the README on GitHub at <https://github.com/gith
|
|||
default-extensions:
|
||||
- DerivingStrategies
|
||||
- ImportQualifiedPost
|
||||
- NoImplicitPrelude
|
||||
- OverloadedRecordDot
|
||||
- OverloadedStrings
|
||||
- StandaloneKindSignatures
|
||||
|
@ -37,6 +36,7 @@ dependencies:
|
|||
ghc-options:
|
||||
- -Weverything
|
||||
- -Wno-unsafe
|
||||
- -Wno-implicit-prelude # coding without prelude is no fun
|
||||
|
||||
library:
|
||||
source-dirs: src
|
||||
|
|
10
scalie.cabal
10
scalie.cabal
|
@ -31,7 +31,6 @@ 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
|
||||
|
@ -42,12 +41,11 @@ library
|
|||
default-extensions:
|
||||
DerivingStrategies
|
||||
ImportQualifiedPost
|
||||
NoImplicitPrelude
|
||||
OverloadedRecordDot
|
||||
OverloadedStrings
|
||||
StandaloneKindSignatures
|
||||
RoleAnnotations
|
||||
ghc-options: -Weverything -Wno-unsafe
|
||||
ghc-options: -Weverything -Wno-unsafe -Wno-implicit-prelude
|
||||
build-depends:
|
||||
QuickCheck
|
||||
, base
|
||||
|
@ -65,12 +63,11 @@ executable scalie-exe
|
|||
default-extensions:
|
||||
DerivingStrategies
|
||||
ImportQualifiedPost
|
||||
NoImplicitPrelude
|
||||
OverloadedRecordDot
|
||||
OverloadedStrings
|
||||
StandaloneKindSignatures
|
||||
RoleAnnotations
|
||||
ghc-options: -Weverything -Wno-unsafe -threaded -rtsopts -with-rtsopts=-N
|
||||
ghc-options: -Weverything -Wno-unsafe -Wno-implicit-prelude -threaded -rtsopts -with-rtsopts=-N
|
||||
build-depends:
|
||||
QuickCheck
|
||||
, base
|
||||
|
@ -92,12 +89,11 @@ test-suite scalie-test
|
|||
default-extensions:
|
||||
DerivingStrategies
|
||||
ImportQualifiedPost
|
||||
NoImplicitPrelude
|
||||
OverloadedRecordDot
|
||||
OverloadedStrings
|
||||
StandaloneKindSignatures
|
||||
RoleAnnotations
|
||||
ghc-options: -Weverything -Wno-unsafe -threaded -rtsopts -with-rtsopts=-N
|
||||
ghc-options: -Weverything -Wno-unsafe -Wno-implicit-prelude -threaded -rtsopts -with-rtsopts=-N
|
||||
build-depends:
|
||||
QuickCheck
|
||||
, base
|
||||
|
|
|
@ -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.
|
||||
|
||||
|
|
|
@ -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
|
||||
|
|
|
@ -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
|
||||
|
|
|
@ -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
|
||||
|
|
|
@ -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)
|
||||
]
|
||||
-}
|
||||
|
|
|
@ -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)
|
||||
--
|
||||
|
|
|
@ -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
|
||||
|
|
|
@ -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.
|
||||
|
||||
|
|
|
@ -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.
|
||||
|
||||
|
|
|
@ -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
|
||||
|
|
|
@ -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.
|
||||
|
||||
|
|
|
@ -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))
|
||||
}
|
||||
|
||||
|
|
|
@ -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)
|
||||
|
|
@ -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
|
||||
|
|
|
@ -1,8 +1,6 @@
|
|||
{-# 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"
|
||||
|
|
|
@ -3,19 +3,21 @@
|
|||
{-# 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 Test.QuickCheck.Roundtrip (roundtrips)
|
||||
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 Data.Map.Implicit (ImplicitMap)
|
||||
|
||||
import Language.Scalie.Core.Definition (Definition)
|
||||
|
||||
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.QuickCheck.Roundtrip (roundtrips)
|
||||
|
||||
import Test.Tasty (TestTree)
|
||||
import Test.Tasty.QuickCheck (QuickCheckMaxSize(QuickCheckMaxSize))
|
||||
|
||||
import Test.Tasty qualified as Tasty
|
||||
import Test.Tasty.QuickCheck qualified as Tasty.QuickCheck
|
||||
|
||||
-- | This is testworthy since I have somehow hand-hacked the read/show de/serialization of 'ImplicitMap'
|
||||
|
||||
|
@ -30,4 +32,5 @@ allTests :: [(String, Property)]
|
|||
allTests = $allProperties
|
||||
|
||||
testGroup :: TestTree
|
||||
testGroup = Tasty.QuickCheck.testProperties "Data.Map.Implicit" allTests
|
||||
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
|
||||
|
|
|
@ -1,7 +1,5 @@
|
|||
{-# 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)
|
||||
|
|
Loading…
Add table
Add a link
Reference in a new issue