1
1
mirror of https://github.com/github/semantic.git synced 2024-11-24 08:54:07 +03:00

Merge branch 'master' into charliesome/value-ref-address

This commit is contained in:
Charlie Somerville 2018-06-01 11:38:36 -07:00
commit 7478c4a6de
47 changed files with 1441 additions and 536 deletions

6
.gitmodules vendored
View File

@ -16,3 +16,9 @@
[submodule "vendor/fastsum"]
path = vendor/fastsum
url = git@github.com:patrickt/fastsum.git
[submodule "vendor/proto3-wire"]
path = vendor/proto3-wire
url = https://github.com/joshvera/proto3-wire
[submodule "vendor/proto3-suite"]
path = vendor/proto3-suite
url = https://github.com/joshvera/proto3-suite

View File

@ -208,6 +208,8 @@ library
, text >= 1.2.1.3
, these
, time
, proto3-suite
, proto3-wire
, unix
, unordered-containers
, haskell-tree-sitter

View File

@ -1,4 +1,5 @@
syntax = "proto3";
import "types.proto";
package semantic;
message HealthCheckRequest {
@ -33,12 +34,6 @@ message BlobPair {
Blob after = 2;
}
message Blob {
string source = 1;
string path = 2;
string language = 3;
}
message SummariesResponse {
repeated Summary changes = 1;
repeated Error errors = 2;
@ -61,13 +56,3 @@ message Error {
Span span = 2;
string language = 3;
}
message Span {
Pos start = 1;
Pos end = 2;
}
message Pos {
int32 line = 1;
int32 column = 2;
}

View File

@ -5,15 +5,12 @@ module Analysis.Abstract.Collecting
) where
import Control.Abstract
import Data.Abstract.Heap
import Data.Abstract.Live
import Data.Semilattice.Lower
import Prologue
-- | An analysis performing GC after every instruction.
collectingTerms :: ( Foldable (Cell address)
, Member (Reader (Live address)) effects
, Member (State (Heap address (Cell address) value)) effects
collectingTerms :: ( Member (Reader (Live address)) effects
, Member (Allocator address value) effects
, Ord address
, ValueRoots address value
)
@ -22,32 +19,7 @@ collectingTerms :: ( Foldable (Cell address)
collectingTerms recur term = do
roots <- TermEvaluator askRoots
v <- recur term
v <$ TermEvaluator (modifyHeap (gc (roots <> valueRoots v)))
-- | Collect any addresses in the heap not rooted in or reachable from the given 'Live' set.
gc :: ( Ord address
, Foldable (Cell address)
, ValueRoots address value
)
=> Live address -- ^ The set of addresses to consider rooted.
-> Heap address (Cell address) value -- ^ A heap to collect unreachable addresses within.
-> Heap address (Cell address) value -- ^ A garbage-collected heap.
gc roots heap = heapRestrict heap (reachable roots heap)
-- | Compute the set of addresses reachable from a given root set in a given heap.
reachable :: ( Ord address
, Foldable (Cell address)
, ValueRoots address value
)
=> Live address -- ^ The set of root addresses.
-> Heap address (Cell address) value -- ^ The heap to trace addresses through.
-> Live address -- ^ The set of addresses reachable from the root set.
reachable roots heap = go mempty roots
where go seen set = case liveSplit set of
Nothing -> seen
Just (a, as) -> go (liveInsert a seen) (case heapLookupAll a heap of
Just values -> liveDifference (foldr ((<>) . valueRoots) mempty values <> as) seen
_ -> seen)
v <$ TermEvaluator (gc (roots <> valueRoots v))
providingLiveSet :: Effectful (m address value) => m address value (Reader (Live address) ': effects) a -> m address value effects a

View File

@ -9,6 +9,7 @@ module Control.Abstract.Environment
, bindAll
, locally
, close
-- * Effects
, Env(..)
, runEnv
, EnvironmentError(..)
@ -56,6 +57,9 @@ locally a = do
close :: Member (Env address) effects => Set Name -> Evaluator address value effects (Environment address)
close = send . Close
-- Effects
data Env address return where
Lookup :: Name -> Env address (Maybe address)
Bind :: Name -> address -> Env address ()

View File

@ -1,9 +1,8 @@
{-# LANGUAGE GADTs, RankNTypes, ScopedTypeVariables, TypeFamilies, TypeOperators, UndecidableInstances #-}
{-# LANGUAGE GADTs, RankNTypes, TypeFamilies, TypeOperators, UndecidableInstances #-}
module Control.Abstract.Heap
( Heap
, getHeap
, putHeap
, modifyHeap
, box
, alloc
, deref
@ -12,6 +11,8 @@ module Control.Abstract.Heap
, letrec
, letrec'
, variable
-- * Garbage collection
, gc
-- * Effects
, Allocator(..)
, runAllocator
@ -23,8 +24,9 @@ module Control.Abstract.Heap
import Control.Abstract.Addressable
import Control.Abstract.Environment
import Control.Abstract.Evaluator
import Control.Monad.Effect.Internal
import Control.Abstract.Roots
import Data.Abstract.Heap
import Data.Abstract.Live
import Data.Abstract.Name
import Data.Semigroup.Reducer
import Prologue
@ -41,11 +43,7 @@ putHeap = put
modifyHeap :: Member (State (Heap address (Cell address) value)) effects => (Heap address (Cell address) value -> Heap address (Cell address) value) -> Evaluator address value effects ()
modifyHeap = modify'
box :: ( Member (Allocator address value) effects
, Member (State (Heap address (Cell address) value)) effects
, Ord address
, Reducer value (Cell address value)
)
box :: Member (Allocator address value) effects
=> value
-> Evaluator address value effects address
box val = do
@ -53,23 +51,20 @@ box val = do
assign addr val
pure addr
alloc :: forall address value effects . Member (Allocator address value) effects => Name -> Evaluator address value effects address
alloc = send . Alloc @address @value
alloc :: Member (Allocator address value) effects => Name -> Evaluator address value effects address
alloc = sendAllocator . Alloc
-- | Dereference the given address in the heap, or fail if the address is uninitialized.
deref :: Member (Allocator address value) effects => address -> Evaluator address value effects value
deref = send . Deref
-- | Write a value to the given address in the 'Store'.
assign :: ( Member (State (Heap address (Cell address) value)) effects
, Ord address
, Reducer value (Cell address value)
)
-- | Write a value to the given address in the 'Allocator'.
assign :: Member (Allocator address value) effects
=> address
-> value
-> Evaluator address value effects ()
assign address = modifyHeap . heapInsert address
assign address = send . Assign address
-- | Look up or allocate an address for a 'Name'.
@ -83,9 +78,6 @@ lookupOrAlloc name = lookupEnv name >>= maybeM (alloc name)
letrec :: ( Member (Allocator address value) effects
, Member (Env address) effects
, Member (State (Heap address (Cell address) value)) effects
, Ord address
, Reducer value (Cell address value)
)
=> Name
-> Evaluator address value effects value
@ -118,16 +110,55 @@ variable :: ( Member (Env address) effects
variable name = lookupEnv name >>= maybeM (freeVariableError name)
-- Garbage collection
-- | Collect any addresses in the heap not rooted in or reachable from the given 'Live' set.
gc :: Member (Allocator address value) effects
=> Live address -- ^ The set of addresses to consider rooted.
-> Evaluator address value effects ()
gc roots = sendAllocator (GC roots)
-- | Compute the set of addresses reachable from a given root set in a given heap.
reachable :: ( Ord address
, Foldable (Cell address)
, ValueRoots address value
)
=> Live address -- ^ The set of root addresses.
-> Heap address (Cell address) value -- ^ The heap to trace addresses through.
-> Live address -- ^ The set of addresses reachable from the root set.
reachable roots heap = go mempty roots
where go seen set = case liveSplit set of
Nothing -> seen
Just (a, as) -> go (liveInsert a seen) $ case heapLookupAll a heap of
Just values -> liveDifference (foldr ((<>) . valueRoots) mempty values <> as) seen
_ -> seen
-- Effects
data Allocator address value return where
Alloc :: Name -> Allocator address value address
Deref :: address -> Allocator address value value
sendAllocator :: Member (Allocator address value) effects => Allocator address value return -> Evaluator address value effects return
sendAllocator = send
runAllocator :: (Addressable address effects, Effectful (m address value), Member (Resumable (AddressError address value)) effects, Member (State (Heap address (Cell address) value)) effects) => m address value (Allocator address value ': effects) a -> m address value effects a
runAllocator = raiseHandler (interpret (\ eff -> case eff of
Alloc name -> lowerEff $ allocCell name
Deref addr -> lowerEff $ heapLookup addr <$> get >>= maybeM (throwResumable (UnallocatedAddress addr)) >>= derefCell addr >>= maybeM (throwResumable (UninitializedAddress addr))))
data Allocator address value return where
Alloc :: Name -> Allocator address value address
Deref :: address -> Allocator address value value
Assign :: address -> value -> Allocator address value ()
GC :: Live address -> Allocator address value ()
runAllocator :: ( Addressable address effects
, Foldable (Cell address)
, Member (Resumable (AddressError address value)) effects
, Member (State (Heap address (Cell address) value)) effects
, Reducer value (Cell address value)
, ValueRoots address value
)
=> Evaluator address value (Allocator address value ': effects) a
-> Evaluator address value effects a
runAllocator = interpret $ \ eff -> case eff of
Alloc name -> allocCell name
Deref addr -> heapLookup addr <$> get >>= maybeM (throwResumable (UnallocatedAddress addr)) >>= derefCell addr >>= maybeM (throwResumable (UninitializedAddress addr))
Assign addr value -> modifyHeap (heapInsert addr value)
GC roots -> modifyHeap (heapRestrict <*> reachable roots)
data AddressError address value resume where

View File

@ -1,6 +1,5 @@
module Control.Abstract.Primitive where
import Control.Abstract.Addressable
import Control.Abstract.Context
import Control.Abstract.Environment
import Control.Abstract.Evaluator
@ -8,7 +7,6 @@ import Control.Abstract.Heap
import Control.Abstract.Value
import Data.Abstract.Name
import Data.ByteString.Char8 (pack, unpack)
import Data.Semigroup.Reducer hiding (unit)
import Data.Semilattice.Lower
import Prologue
@ -17,9 +15,6 @@ builtin :: ( HasCallStack
, Member (Env address) effects
, Member (Reader ModuleInfo) effects
, Member (Reader Span) effects
, Member (State (Heap address (Cell address) value)) effects
, Ord address
, Reducer value (Cell address value)
)
=> String
-> Evaluator address value effects value
@ -45,10 +40,7 @@ defineBuiltins :: ( AbstractValue address value effects
, Member (Reader ModuleInfo) effects
, Member (Reader Span) effects
, Member (Resumable (EnvironmentError address)) effects
, Member (State (Heap address (Cell address) value)) effects
, Member Trace effects
, Ord address
, Reducer value (Cell address value)
)
=> Evaluator address value effects ()
defineBuiltins =

View File

@ -1,5 +1,6 @@
module Control.Abstract.Roots
( Live
( ValueRoots(..)
, Live
, askRoots
, extraRoots
) where
@ -8,6 +9,13 @@ import Control.Abstract.Evaluator
import Data.Abstract.Live
import Prologue
-- | Value types, e.g. closures, which can root a set of addresses.
class ValueRoots address value where
-- | Compute the set of addresses rooted by a given value.
valueRoots :: value -> Live address
-- | Retrieve the local 'Live' set.
askRoots :: Member (Reader (Live address)) effects => Evaluator address value effects (Live address)
askRoots = ask

View File

@ -15,20 +15,16 @@ module Control.Abstract.Value
, rvalBox
, subtermValue
, subtermAddress
, ValueRoots(..)
) where
import Control.Abstract.Addressable
import Control.Abstract.Environment
import Control.Abstract.Evaluator
import Control.Abstract.Heap
import Data.Abstract.Environment as Env
import Data.Abstract.Live (Live)
import Data.Abstract.Name
import Data.Abstract.Number as Number
import Data.Abstract.Ref
import Data.Scientific (Scientific)
import Data.Semigroup.Reducer hiding (unit)
import Data.Semilattice.Lower
import Prelude
import Prologue hiding (TypeError)
@ -191,9 +187,7 @@ doWhile body cond = loop $ \ continue -> body *> do
makeNamespace :: ( AbstractValue address value effects
, Member (Env address) effects
, Member (State (Heap address (Cell address) value)) effects
, Ord address
, Reducer value (Cell address value)
, Member (Allocator address value) effects
)
=> Name
-> address
@ -259,17 +253,7 @@ subtermAddress :: ( AbstractValue address value effects
-> Evaluator address value effects address
subtermAddress = address <=< subtermRef
rvalBox :: ( Member (Allocator address value) effects
, Member (State (Heap address (Cell address) value)) effects
, Ord address
, Reducer value (Cell address value)
)
rvalBox :: Member (Allocator address value) effects
=> value
-> Evaluator address value effects (ValueRef address value)
rvalBox val = Rval <$> (box val)
-- | Value types, e.g. closures, which can root a set of addresses.
class ValueRoots address value where
-- | Compute the set of addresses rooted by a given value.
valueRoots :: value -> Live address

View File

@ -41,21 +41,18 @@ import Prologue
-- | The 'Evaluatable' class defines the necessary interface for a term to be evaluated. While a default definition of 'eval' is given, instances with computational content must implement 'eval' to perform their small-step operational semantics.
class Evaluatable constr where
eval :: ( EvaluatableConstraints address term value effects
eval :: ( EvaluatableConstraints term address value effects
, Member Fail effects
)
=> SubtermAlgebra constr term (Evaluator address value effects (ValueRef address value))
default eval :: ( Member (Resumable (Unspecialized value)) effects
, Member (Allocator address value) effects
, Member (State (Heap address (Cell address) value)) effects
, Show1 constr
, Ord address
, Reducer value (Cell address value)
)
=> SubtermAlgebra constr term (Evaluator address value effects (ValueRef address value))
eval expr = rvalBox =<< throwResumable (Unspecialized ("Eval unspecialized for " ++ liftShowsPrec (const (const id)) (const id) 0 expr ""))
type EvaluatableConstraints address term value effects =
type EvaluatableConstraints term address value effects =
( AbstractValue address value effects
, Declarations term
, FreeVariables term
@ -71,10 +68,7 @@ type EvaluatableConstraints address term value effects =
, Member (Resumable ResolutionError) effects
, Member (Resumable (Unspecialized value)) effects
, Member (Return address value) effects
, Member (State (Heap address (Cell address) value)) effects
, Member Trace effects
, Ord address
, Reducer value (Cell address value)
)
@ -83,7 +77,8 @@ evaluatePackageWith :: forall address term value inner inner' inner'' outer
-- FIXME: Itd be nice if we didnt have to mention 'Addressable' here at all, but 'Located' locations require knowledge of 'currentModule' to run. Can we fix that?
. ( Addressable address inner'
, Evaluatable (Base term)
, EvaluatableConstraints address term value inner
, EvaluatableConstraints term address value inner
, Foldable (Cell address)
, Member Fail outer
, Member Fresh outer
, Member (Resumable (AddressError address value)) outer
@ -92,6 +87,8 @@ evaluatePackageWith :: forall address term value inner inner' inner'' outer
, Member (State (ModuleTable (Maybe (address, Environment address)))) outer
, Member Trace outer
, Recursive term
, Reducer value (Cell address value)
, ValueRoots address value
, inner ~ (LoopControl address value ': Return address value ': Env address ': Allocator address value ': inner')
, inner' ~ (Reader ModuleInfo ': inner'')
, inner'' ~ (Modules address value ': Reader Span ': Reader PackageInfo ': outer)

View File

@ -36,6 +36,10 @@ liveMember addr = Set.member addr . unLive
liveSplit :: Live address -> Maybe (address, Live address)
liveSplit = fmap (fmap Live) . Set.minView . unLive
-- | Map a function over the addresses in a 'Live' set.
liveMap :: Ord b => (a -> b) -> Live a -> Live b
liveMap f = Live . Set.map f . unLive
instance Show address => Show (Live address) where
showsPrec d = showsUnaryWith showsPrec "Live" d . Set.toList . unLive

View File

@ -10,7 +10,6 @@ module Data.Abstract.Type
import Control.Abstract
import Data.Abstract.Environment as Env
import Data.Semigroup.Foldable (foldMap1)
import Data.Semigroup.Reducer (Reducer)
import Prologue hiding (TypeError)
type TName = Int
@ -121,9 +120,6 @@ instance ( Member (Allocator address Type) effects
, Member Fresh effects
, Member (Resumable TypeError) effects
, Member (Return address Type) effects
, Member (State (Heap address (Cell address) Type)) effects
, Ord address
, Reducer Type (Cell address Type)
)
=> AbstractFunction address Type effects where
closure names _ body = do
@ -151,9 +147,6 @@ instance ( Member (Allocator address Type) effects
, Member NonDet effects
, Member (Resumable TypeError) effects
, Member (Return address Type) effects
, Member (State (Heap address (Cell address) Type)) effects
, Ord address
, Reducer Type (Cell address Type)
)
=> AbstractValue address Type effects where
array fields = do

View File

@ -10,7 +10,6 @@ import Data.Coerce
import Data.List (genericIndex, genericLength)
import Data.Scientific (Scientific)
import Data.Scientific.Exts
import Data.Semigroup.Reducer
import qualified Data.Set as Set
import Prologue
@ -62,9 +61,6 @@ instance ( Coercible body (Eff effects)
, Member (Reader PackageInfo) effects
, Member (Resumable (ValueError address body)) effects
, Member (Return address (Value address body)) effects
, Member (State (Heap address (Cell address) (Value address body))) effects
, Ord address
, Reducer (Value address body) (Cell address (Value address body))
, Show address
)
=> AbstractFunction address (Value address body) effects where
@ -114,9 +110,6 @@ instance ( Coercible body (Eff effects)
, Member (Reader PackageInfo) effects
, Member (Resumable (ValueError address body)) effects
, Member (Return address (Value address body)) effects
, Member (State (Heap address (Cell address) (Value address body))) effects
, Ord address
, Reducer (Value address body) (Cell address (Value address body))
, Show address
)
=> AbstractValue address (Value address body) effects where

View File

@ -1,3 +1,4 @@
{-# LANGUAGE DeriveAnyClass #-}
module Data.Blob
( Blob(..)
, nullBlob
@ -14,6 +15,7 @@ module Data.Blob
) where
import Prologue
import Proto3.Suite
import Data.Aeson
import Data.JSON.Fields
import Data.Language
@ -26,7 +28,7 @@ data Blob = Blob
, blobPath :: FilePath -- ^ The file path to the blob.
, blobLanguage :: Maybe Language -- ^ The language of this blob. Nothing denotes a langauge we don't support yet.
}
deriving (Show, Eq)
deriving (Show, Eq, Generic, Message, Named)
nullBlob :: Blob -> Bool
nullBlob Blob{..} = nullSource blobSource

View File

@ -3,6 +3,7 @@ module Data.Language where
import Prologue
import Data.Aeson
import Proto3.Suite
-- | A programming language.
data Language
@ -16,7 +17,7 @@ data Language
| Ruby
| TypeScript
| PHP
deriving (Eq, Generic, Ord, Read, Show, ToJSON)
deriving (Eq, Generic, Ord, Read, Show, ToJSON, Named, Enum, Finite, Message)
-- | Returns a Language based on the file extension (including the ".").
languageForType :: String -> Maybe Language

View File

@ -1,4 +1,4 @@
{-# LANGUAGE GeneralizedNewtypeDeriving, MultiParamTypeClasses #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Data.Source
( Source
, sourceBytes
@ -36,10 +36,11 @@ import Data.Span
import Data.String (IsString(..))
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import Proto3.Suite
-- | The contents of a source file, represented as a 'ByteString'.
newtype Source = Source { sourceBytes :: B.ByteString }
deriving (Eq, IsString, Show)
deriving (Eq, IsString, Show, Generic, MessageField)
fromBytes :: B.ByteString -> Source
fromBytes = Source

View File

@ -11,6 +11,9 @@ module Data.Span
) where
import Data.Aeson ((.=), (.:))
import Proto3.Suite
import Proto3.Wire.Decode as Decode
import Proto3.Wire.Encode as Encode
import qualified Data.Aeson as A
import Data.JSON.Fields
import Data.Semilattice.Lower
@ -22,7 +25,15 @@ data Pos = Pos
{ posLine :: !Int
, posColumn :: !Int
}
deriving (Show, Read, Eq, Ord, Generic, Hashable)
deriving (Show, Read, Eq, Ord, Generic, Hashable, Named, Message)
instance MessageField Pos where
encodeMessageField num = Encode.embedded num . encodeMessage (fieldNumber 1)
decodeMessageField = fromMaybe def <$> Decode.embedded (decodeMessage (fieldNumber 1))
protoType pr = messageField (Prim $ Named (Single (nameOf pr))) Nothing
instance HasDefault Pos where
def = Pos 1 1
instance A.ToJSON Pos where
toJSON Pos{..} =
@ -37,7 +48,7 @@ data Span = Span
{ spanStart :: Pos
, spanEnd :: Pos
}
deriving (Show, Read, Eq, Ord, Generic, Hashable)
deriving (Show, Read, Eq, Ord, Generic, Hashable, Named, Message)
spanFromSrcLoc :: SrcLoc -> Span
spanFromSrcLoc = Span . (Pos . srcLocStartLine <*> srcLocStartCol) <*> (Pos . srcLocEndLine <*> srcLocEndCol)

View File

@ -1,5 +1,5 @@
{-# LANGUAGE DeriveAnyClass, GADTs, TypeOperators, MultiParamTypeClasses, UndecidableInstances, ScopedTypeVariables #-}
{-# OPTIONS_GHC -Wno-redundant-constraints #-} -- For HasCallStack
{-# LANGUAGE AllowAmbiguousTypes, DeriveAnyClass, GADTs, TypeOperators, MultiParamTypeClasses, UndecidableInstances, ScopedTypeVariables, KindSignatures, RankNTypes, ConstraintKinds #-}
{-# OPTIONS_GHC -Wno-redundant-constraints -fno-warn-orphans #-} -- For HasCallStack
module Data.Syntax where
import Data.Abstract.Evaluatable
@ -16,7 +16,13 @@ import Prelude
import Prologue
import qualified Assigning.Assignment as Assignment
import qualified Data.Error as Error
import Proto3.Suite.Class
import Proto3.Wire.Decode
import Proto3.Wire.Types
import GHC.Types (Constraint)
import GHC.TypeLits
import qualified Proto3.Suite.DotProto as Proto
import Data.Char (toLower)
-- Combinators
-- | Lift syntax and an annotation into a term, injecting the syntax into a union & ensuring the annotation encompasses all children.
@ -97,12 +103,37 @@ infixContext :: (Context :< fs, Assignment.Parsing m, Semigroup a, HasCallStack,
-> m (Sum fs (Term (Sum fs) a))
infixContext context left right operators = uncurry (&) <$> postContextualizeThrough context left (asum operators) <*> postContextualize context right
instance (Apply Message1 fs, Generate Message1 fs fs, Generate Named1 fs fs) => Message1 (Sum fs) where
liftEncodeMessage encodeMessage num = apply @Message1 (liftEncodeMessage encodeMessage num)
liftDecodeMessage decodeMessage _ = oneof undefined listOfParsers
where
listOfParsers =
generate @Message1 @fs @fs (\ (_ :: proxy f) i -> let num = FieldNumber (fromInteger (succ i)) in [(num, fromJust <$> embedded (inject @f @fs <$> liftDecodeMessage decodeMessage num))])
liftDotProto _ =
[Proto.DotProtoMessageOneOf (Proto.Single "syntax") (generate @Named1 @fs @fs (\ (_ :: proxy f) i ->
let
num = FieldNumber (fromInteger (succ i))
fieldType = Proto.Prim (Proto.Named . Proto.Single $ nameOf1 (Proxy @f))
fieldName = Proto.Single (camelCase $ nameOf1 (Proxy @f))
camelCase (x : xs) = toLower x : xs
camelCase [] = []
in
[ Proto.DotProtoField num fieldType fieldName [] Nothing ]))]
class Generate (c :: (* -> *) -> Constraint) (all :: [* -> *]) (fs :: [* -> *]) where
generate :: Monoid b => (forall f proxy. (Element f all, c f) => proxy f -> Integer -> b) -> b
instance Generate c all '[] where
generate _ = mempty
instance (Element f all, c f, Generate c all fs) => Generate c all (f ': fs) where
generate each = each (Proxy @f) (natVal (Proxy @(ElemIndex f all))) `mappend` generate @c @all @fs each
-- Common
-- | An identifier of some other construct, whether a containing declaration (e.g. a class name) or a reference (e.g. a variable).
newtype Identifier a = Identifier { name :: Name }
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, ToJSONFields1)
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, Named1, ToJSONFields1)
instance Eq1 Identifier where liftEq = genericLiftEq
instance Ord1 Identifier where liftCompare = genericLiftCompare
@ -144,7 +175,7 @@ instance Evaluatable AccessibilityModifier
--
-- This can be used to represent an implicit no-op, e.g. the alternative in an 'if' statement without an 'else'.
data Empty a = Empty
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, Named1, Message1)
instance ToJSONFields1 Empty
@ -155,7 +186,6 @@ instance Show1 Empty where liftShowsPrec _ _ _ _ = showString "Empty"
instance Evaluatable Empty where
eval _ = rvalBox unit
-- | Syntax representing a parsing or assignment error.
data Error a = Error { errorCallStack :: ErrorStack, errorExpected :: [String], errorActual :: Maybe String, errorChildren :: [a] }
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)

View File

@ -218,7 +218,7 @@ instance Evaluatable Data.Syntax.Declaration.Datatype
-- | A single constructor in a datatype, or equally a 'struct' in C, Rust, or Swift.
data Constructor a = Constructor { constructorName :: !a, constructorFields :: ![a] }
data Constructor a = Constructor { constructorName :: !a, constructorFields :: !a }
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
instance Eq1 Data.Syntax.Declaration.Constructor where liftEq = genericLiftEq

View File

@ -1,20 +1,21 @@
{-# LANGUAGE DataKinds, DeriveAnyClass, DeriveGeneric, MultiParamTypeClasses, ViewPatterns #-}
{-# LANGUAGE DataKinds, DeriveAnyClass, DeriveGeneric, MultiParamTypeClasses, ViewPatterns, ScopedTypeVariables #-}
module Data.Syntax.Literal where
import Data.JSON.Fields
import Data.Abstract.Evaluatable
import Data.ByteString.Char8 (readInteger, unpack)
import Data.Abstract.Evaluatable
import Data.ByteString.Char8 (readInteger, unpack)
import qualified Data.ByteString.Char8 as B
import Data.Scientific.Exts
import Diffing.Algorithm
import Prelude hiding (Float, null)
import Prologue hiding (Set, hash, null)
import Text.Read (readMaybe)
import Data.JSON.Fields
import Data.Scientific.Exts
import Diffing.Algorithm
import Prelude hiding (Float, null)
import Prologue hiding (Set, hash, null)
import Proto3.Suite.Class
import Text.Read (readMaybe)
-- Boolean
newtype Boolean a = Boolean Bool
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
newtype Boolean a = Boolean { booleanContent :: Bool }
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, Named1, Message1)
true :: Boolean a
true = Boolean True
@ -57,7 +58,7 @@ instance ToJSONFields1 Data.Syntax.Literal.Integer where
-- | A literal float of unspecified width.
newtype Float a = Float { floatContent :: ByteString }
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, Named1, Message1)
instance Eq1 Data.Syntax.Literal.Float where liftEq = genericLiftEq
instance Ord1 Data.Syntax.Literal.Float where liftCompare = genericLiftCompare
@ -144,7 +145,7 @@ instance ToJSONFields1 InterpolationElement
-- | A sequence of textual contents within a string literal.
newtype TextElement a = TextElement { textElementContent :: ByteString }
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, Named1, Message1)
instance Eq1 TextElement where liftEq = genericLiftEq
instance Ord1 TextElement where liftCompare = genericLiftCompare
@ -157,7 +158,7 @@ instance Evaluatable TextElement where
eval (TextElement x) = rvalBox (string x)
data Null a = Null
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, Named1, Message1)
instance Eq1 Null where liftEq = genericLiftEq
instance Ord1 Null where liftCompare = genericLiftCompare
@ -199,7 +200,7 @@ instance Evaluatable Regex
-- Collections
newtype Array a = Array { arrayElements :: [a] }
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, Named1, Message1)
instance Eq1 Array where liftEq = genericLiftEq
instance Ord1 Array where liftCompare = genericLiftCompare
@ -211,7 +212,7 @@ instance Evaluatable Array where
eval (Array a) = rvalBox =<< (array =<< traverse subtermValue a)
newtype Hash a = Hash { hashElements :: [a] }
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, Named1, Message1)
instance Eq1 Hash where liftEq = genericLiftEq
instance Ord1 Hash where liftCompare = genericLiftCompare
@ -223,7 +224,7 @@ instance Evaluatable Hash where
eval t = rvalBox =<< (hash <$> traverse (subtermValue >=> asPair) (hashElements t))
data KeyValue a = KeyValue { key :: !a, value :: !a }
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, Named1, Message1)
instance Eq1 KeyValue where liftEq = genericLiftEq
instance Ord1 KeyValue where liftCompare = genericLiftCompare

View File

@ -6,7 +6,7 @@ import Data.JSON.Fields
import Diffing.Algorithm
import Prologue hiding (Map)
data Array a = Array { arraySize :: Maybe a, arrayElementType :: a }
data Array a = Array { arraySize :: !(Maybe a), arrayElementType :: !a }
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
instance Eq1 Array where liftEq = genericLiftEq
@ -34,7 +34,7 @@ instance Evaluatable Annotation where
eval Annotation{annotationSubject = Subterm _ action} = action
data Function a = Function { functionParameters :: [a], functionReturn :: a }
data Function a = Function { functionParameters :: ![a], functionReturn :: !a }
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
instance Eq1 Function where liftEq = genericLiftEq
@ -60,7 +60,7 @@ instance ToJSONFields1 Interface
instance Evaluatable Interface
data Map a = Map { mapKeyType :: a, mapElementType :: a }
data Map a = Map { mapKeyType :: !a, mapElementType :: !a }
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
instance Eq1 Map where liftEq = genericLiftEq

View File

@ -1,4 +1,4 @@
{-# LANGUAGE RankNTypes, TypeFamilies, TypeOperators #-}
{-# LANGUAGE RankNTypes, TypeFamilies, TypeOperators, ScopedTypeVariables #-}
module Data.Term
( Term(..)
, termIn
@ -16,6 +16,7 @@ import Data.Aeson
import Data.JSON.Fields
import Data.Record
import Text.Show
import Proto3.Suite.Class
-- | A Term with an abstract syntax tree and an annotation.
newtype Term syntax ann = Term { unTerm :: TermF syntax ann (Term syntax ann) }
@ -78,6 +79,14 @@ instance Show1 f => Show1 (Term f) where
instance (Show1 f, Show a) => Show (Term f a) where
showsPrec = showsPrec1
instance Message1 f => Message (Term f ()) where
encodeMessage num (Term (In _ f)) = liftEncodeMessage encodeMessage num f
decodeMessage num = termIn () <$> liftDecodeMessage decodeMessage num
dotProto _ = liftDotProto (Proxy @(f (Term f ())))
instance Named (Term f a) where
nameOf _ = "Term"
instance Ord1 f => Ord1 (Term f) where
liftCompare comp = go where go t1 t2 = liftCompare2 comp go (unTerm t1) (unTerm t2)

View File

@ -307,7 +307,7 @@ sliceType :: Assignment
sliceType = makeTerm <$> symbol SliceType <*> children (Type.Slice <$> expression)
structType :: Assignment
structType = makeTerm <$> symbol StructType <*> children (Declaration.Constructor <$> emptyTerm <*> manyTerm expression)
structType = makeTerm <$> symbol StructType <*> children (Declaration.Constructor <$> emptyTerm <*> expressions)
typeAlias :: Assignment
typeAlias = makeTerm <$> symbol TypeAlias <*> children (Declaration.TypeAlias [] <$> expression <*> expression)

View File

@ -10,7 +10,7 @@ import Assigning.Assignment hiding (Assignment, Error, count)
import Data.ByteString.Char8 (count)
import Data.Record
import Data.Sum
import Data.Syntax (emptyTerm, handleError, parseError, makeTerm, makeTerm'', contextualize, postContextualize)
import Data.Syntax (emptyTerm, handleError, parseError, makeTerm, makeTerm', makeTerm'', contextualize, postContextualize)
import Language.Haskell.Grammar as Grammar
import qualified Assigning.Assignment as Assignment
import qualified Data.Abstract.Name as Name
@ -25,6 +25,8 @@ import Prologue
type Syntax = '[
Comment.Comment
, Declaration.Constructor
, Declaration.Datatype
, Declaration.Function
, Literal.Array
, Literal.Character
@ -34,10 +36,15 @@ type Syntax = '[
, Syntax.Context
, Syntax.Empty
, Syntax.Error
, Syntax.Field
, Syntax.FunctionConstructor
, Syntax.Identifier
, Syntax.ListConstructor
, Syntax.Module
, Syntax.Pragma
, Syntax.RecordDataConstructor
, Syntax.StrictType
, Syntax.StrictTypeVariable
, Syntax.TupleConstructor
, Syntax.Type
, Syntax.TypeSynonym
@ -67,7 +74,8 @@ expression = term (handleError (choice expressionChoices))
expressionChoices :: [Assignment.Assignment [] Grammar Term]
expressionChoices = [
character
algebraicDatatypeDeclaration
, character
, comment
, constructorIdentifier
, float
@ -78,6 +86,7 @@ expressionChoices = [
, listExpression
, listType
, moduleIdentifier
, strictType
, string
, type'
, typeConstructorIdentifier
@ -90,14 +99,35 @@ expressionChoices = [
]
term :: Assignment -> Assignment
term term = contextualize comment (postContextualize comment term)
term term = contextualize (comment <|> pragma) (postContextualize (comment <|> pragma) term)
algebraicDatatypeDeclaration :: Assignment
algebraicDatatypeDeclaration = makeTerm
<$> symbol AlgebraicDatatypeDeclaration
<*> children (Declaration.Datatype
<$> (makeTerm <$> location <*> (Syntax.Type <$> typeConstructor <*> typeParameters))
<*> ((symbol Constructors *> children (many constructor))
<|> pure []))
comment :: Assignment
comment = makeTerm <$> symbol Comment <*> (Comment.Comment <$> source)
constructor :: Assignment
constructor = (makeTerm <$> symbol DataConstructor <*> children (Declaration.Constructor <$> typeConstructor <*> typeParameters))
<|> (makeTerm <$> symbol RecordDataConstructor <*> children (Syntax.RecordDataConstructor <$> constructorIdentifier <*> fields))
fields :: Assignment
fields = makeTerm <$> symbol Fields <*> children (many field)
field :: Assignment
field = makeTerm <$> symbol Field <*> children (Syntax.Field <$> variableIdentifiers <* token Annotation <*> term type')
variableIdentifier :: Assignment
variableIdentifier = makeTerm <$> symbol VariableIdentifier <*> (Syntax.Identifier . Name.name <$> source)
variableIdentifiers :: Assignment
variableIdentifiers = makeTerm <$> location <*> many variableIdentifier
constructorIdentifier :: Assignment
constructorIdentifier = makeTerm <$> symbol ConstructorIdentifier <*> (Syntax.Identifier . Name.name <$> source)
@ -134,6 +164,9 @@ integer = makeTerm <$> symbol Integer <*> (Literal.Integer <$> source)
listConstructor :: Assignment
listConstructor = makeTerm <$> token ListConstructor <*> pure Syntax.ListConstructor
pragma :: Assignment
pragma = makeTerm <$> symbol Pragma <*> (Syntax.Pragma <$> source)
unitConstructor :: Assignment
unitConstructor = makeTerm <$> token UnitConstructor <*> pure Syntax.UnitConstructor
@ -144,6 +177,10 @@ listExpression = makeTerm <$> symbol ListExpression <*> children (Literal.Array
listType :: Assignment
listType = makeTerm <$> symbol ListType <*> children (Literal.Array <$> many type')
strictType :: Assignment
strictType = makeTerm' <$> symbol StrictType <*> children ((inject <$> (Syntax.StrictType <$> typeConstructor <*> typeParameters))
<|> (inject <$> (Syntax.StrictTypeVariable <$> typeVariableIdentifier)))
tuplingConstructor :: Assignment
tuplingConstructor = makeTerm <$> symbol TuplingConstructor <*> (tupleWithArity <$> source)
-- a tuple (,) has arity two, but only one comma, so apply the successor to the count of commas for the correct arity.
@ -152,6 +189,8 @@ tuplingConstructor = makeTerm <$> symbol TuplingConstructor <*> (tupleWithArity
type' :: Assignment
type' = (makeTerm <$> symbol Type <*> children (Syntax.Type <$> typeConstructor <*> typeParameters))
<|> (makeTerm <$> symbol TypePattern <*> children (Syntax.Type <$> typeConstructor <*> typeParameters))
<|> strictType
<|> typeConstructor
typeParameters :: Assignment
typeParameters = makeTerm <$> location <*> (Type.TypeParameters <$> many expression)
@ -172,6 +211,7 @@ typeConstructor = typeConstructorIdentifier
<|> listType
<|> tuplingConstructor
<|> unitConstructor
<|> constructorIdentifier
typeSynonymDeclaration :: Assignment
typeSynonymDeclaration = makeTerm

View File

@ -21,6 +21,28 @@ instance ToJSONFields1 Module
instance Evaluatable Module
data StrictType a = StrictType { strictTypeIdentifier :: !a, strictTypeParameters :: !a }
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
instance Eq1 StrictType where liftEq = genericLiftEq
instance Ord1 StrictType where liftCompare = genericLiftCompare
instance Show1 StrictType where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 StrictType
instance Evaluatable StrictType
newtype StrictTypeVariable a = StrictTypeVariable { strictTypeVariableIdentifier :: a }
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
instance Eq1 StrictTypeVariable where liftEq = genericLiftEq
instance Ord1 StrictTypeVariable where liftCompare = genericLiftCompare
instance Show1 StrictTypeVariable where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 StrictTypeVariable
instance Evaluatable StrictTypeVariable
data Type a = Type { typeIdentifier :: !a, typeParameters :: !a }
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
@ -82,3 +104,33 @@ instance Show1 FunctionConstructor where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 FunctionConstructor
instance Evaluatable FunctionConstructor
data RecordDataConstructor a = RecordDataConstructor { recordDataConstructorName :: !a, recordDataConstructorFields :: !a } deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
instance Eq1 RecordDataConstructor where liftEq = genericLiftEq
instance Ord1 RecordDataConstructor where liftCompare = genericLiftCompare
instance Show1 RecordDataConstructor where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 RecordDataConstructor
instance Evaluatable RecordDataConstructor
data Field a = Field { fieldName :: !a, fieldBody :: !a } deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
instance Eq1 Field where liftEq = genericLiftEq
instance Ord1 Field where liftCompare = genericLiftCompare
instance Show1 Field where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Field
instance Evaluatable Field
newtype Pragma a = Pragma ByteString deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
instance Eq1 Pragma where liftEq = genericLiftEq
instance Ord1 Pragma where liftCompare = genericLiftCompare
instance Show1 Pragma where liftShowsPrec = genericLiftShowsPrec
instance ToJSONFields1 Pragma
instance Evaluatable Pragma

View File

@ -7,7 +7,6 @@ import Data.Abstract.Path
import qualified Data.ByteString.Char8 as BC
import Data.JSON.Fields
import qualified Data.Language as Language
import Data.Semigroup.Reducer (Reducer)
import Diffing.Algorithm
import Prelude hiding (fail)
import Prologue hiding (Text)
@ -59,10 +58,7 @@ include :: ( AbstractValue address value effects
, Member (Modules address value) effects
, Member (Resumable ResolutionError) effects
, Member (Resumable (EnvironmentError address)) effects
, Member (State (Heap address (Cell address) value)) effects
, Member Trace effects
, Ord address
, Reducer value (Cell address value)
)
=> Subterm term (Evaluator address value effects (ValueRef address value))
-> (ModulePath -> Evaluator address value effects (Maybe (address, Environment address)))

View File

@ -16,7 +16,6 @@ import System.FilePath.Posix
import qualified Data.ByteString.Char8 as BC
import qualified Data.Language as Language
import qualified Data.List.NonEmpty as NonEmpty
import qualified Data.Semigroup.Reducer as Reducer
data QualifiedName
= QualifiedName (NonEmpty FilePath)
@ -131,9 +130,6 @@ evalQualifiedImport :: ( AbstractValue address value effects
, Member (Allocator address value) effects
, Member (Env address) effects
, Member (Modules address value) effects
, Member (State (Heap address (Cell address) value)) effects
, Ord address
, Reducer.Reducer value (Cell address value)
)
=> Name -> ModulePath -> Evaluator address value effects value
evalQualifiedImport name path = letrec' name $ \addr -> do

View File

@ -12,7 +12,6 @@ import qualified Data.ByteString.Char8 as BC
import Data.JSON.Fields
import qualified Data.Language as Language
import qualified Data.Map as Map
import Data.Semigroup.Reducer (Reducer)
import Diffing.Algorithm
import Prelude
import Prologue
@ -137,9 +136,6 @@ evalRequire :: ( AbstractValue address value effects
, Member (Allocator address value) effects
, Member (Env address) effects
, Member (Modules address value) effects
, Member (State (Heap address (Cell address) value)) effects
, Ord address
, Reducer value (Cell address value)
)
=> M.ModulePath
-> Name

View File

@ -0,0 +1,18 @@
data N
data N a = N a
data N a = N !a
data N a b = N !a b
data B = A
| A0
| A9
| Aa
| A_
| Az'
data N = N { a :: Int }
data N = N { a, b :: Int }
data N = N { a :: !Int, b :: Int }
data N = N { a, b :: {-# UNPACK #-} !Int, c :: String }
data N = N { a :: Int } | O { b :: String }
data N = N { b :: Int } | O { c :: String }

View File

@ -0,0 +1,18 @@
data O
data O a = O a
data O a = O !a
data O a b = O !a b
data A = B
| B0
| B9
| Ba
| B_
| Bz'
data O = O { a :: Int }
data O = O { a, b :: Int }
data O = O { a :: !Int, b :: Int }
data O = O { a, b :: {-# UNPACK #-} !Int, c :: String }
data N = N { b :: Int } | O { c :: String }
data N = N { b :: Text } | O { c :: Bool }

View File

@ -0,0 +1,208 @@
(Module
(Empty)
(Statements
(Datatype
(Type
{ (Identifier)
->(Identifier) }
(TypeParameters)))
(Datatype
(Type
{ (Identifier)
->(Identifier) }
(TypeParameters
(Identifier)))
(Constructor
{ (Identifier)
->(Identifier) }
(TypeParameters
(Identifier))))
(Datatype
(Type
{ (Identifier)
->(Identifier) }
(TypeParameters
(Identifier)))
(Constructor
{ (Identifier)
->(Identifier) }
(TypeParameters
(StrictTypeVariable
(Identifier)))))
(Datatype
(Type
{ (Identifier)
->(Identifier) }
(TypeParameters
(Identifier)
(Identifier)))
(Constructor
{ (Identifier)
->(Identifier) }
(TypeParameters
(StrictTypeVariable
(Identifier))
(Identifier))))
(Datatype
(Type
{ (Identifier)
->(Identifier) }
(TypeParameters))
{+(Constructor
{+(Identifier)+}
{+(TypeParameters)+})+}
{+(Constructor
{+(Identifier)+}
{+(TypeParameters)+})+}
{+(Constructor
{+(Identifier)+}
{+(TypeParameters)+})+}
{+(Constructor
{+(Identifier)+}
{+(TypeParameters)+})+}
{+(Constructor
{+(Identifier)+}
{+(TypeParameters)+})+}
{+(Constructor
{+(Identifier)+}
{+(TypeParameters)+})+}
{-(Constructor
{-(Identifier)-}
{-(TypeParameters)-})-}
{-(Constructor
{-(Identifier)-}
{-(TypeParameters)-})-}
{-(Constructor
{-(Identifier)-}
{-(TypeParameters)-})-}
{-(Constructor
{-(Identifier)-}
{-(TypeParameters)-})-}
{-(Constructor
{-(Identifier)-}
{-(TypeParameters)-})-}
{-(Constructor
{-(Identifier)-}
{-(TypeParameters)-})-})
(Datatype
(Type
{ (Identifier)
->(Identifier) }
(TypeParameters))
(RecordDataConstructor
{ (Identifier)
->(Identifier) }
(Statements
(Field
(Statements
(Identifier))
(Identifier)))))
(Datatype
(Type
{ (Identifier)
->(Identifier) }
(TypeParameters))
(RecordDataConstructor
{ (Identifier)
->(Identifier) }
(Statements
(Field
(Statements
(Identifier)
(Identifier))
(Identifier)))))
(Datatype
(Type
{ (Identifier)
->(Identifier) }
(TypeParameters))
(RecordDataConstructor
{ (Identifier)
->(Identifier) }
(Statements
(Field
(Statements
(Identifier))
(StrictType
(Identifier)
(TypeParameters)))
(Field
(Statements
(Identifier))
(Identifier)))))
(Datatype
(Type
{ (Identifier)
->(Identifier) }
(TypeParameters))
(RecordDataConstructor
{ (Identifier)
->(Identifier) }
(Statements
(Field
(Statements
(Identifier)
(Identifier))
(Context
(Pragma)
(StrictType
(Identifier)
(TypeParameters))))
(Field
(Statements
(Identifier))
(Identifier)))))
{-(Datatype
{-(Type
{-(Identifier)-}
{-(TypeParameters)-})-}
{-(RecordDataConstructor
{-(Identifier)-}
{-(Statements
{-(Field
{-(Statements
{-(Identifier)-})-}
{-(Identifier)-})-})-})-}
{-(RecordDataConstructor
{-(Identifier)-}
{-(Statements
{-(Field
{-(Statements
{-(Identifier)-})-}
{-(Identifier)-})-})-})-})-}
(Datatype
(Type
(Identifier)
(TypeParameters))
(RecordDataConstructor
(Identifier)
(Statements
(Field
(Statements
(Identifier))
(Identifier))))
(RecordDataConstructor
(Identifier)
(Statements
(Field
(Statements
(Identifier))
(Identifier)))))
{+(Datatype
{+(Type
{+(Identifier)+}
{+(TypeParameters)+})+}
{+(RecordDataConstructor
{+(Identifier)+}
{+(Statements
{+(Field
{+(Statements
{+(Identifier)+})+}
{+(Identifier)+})+})+})+}
{+(RecordDataConstructor
{+(Identifier)+}
{+(Statements
{+(Field
{+(Statements
{+(Identifier)+})+}
{+(Identifier)+})+})+})+})+}))

View File

@ -0,0 +1,202 @@
(Module
(Empty)
(Statements
(Datatype
(Type
{ (Identifier)
->(Identifier) }
(TypeParameters)))
(Datatype
(Type
{ (Identifier)
->(Identifier) }
(TypeParameters
(Identifier)))
(Constructor
{ (Identifier)
->(Identifier) }
(TypeParameters
(Identifier))))
(Datatype
(Type
{ (Identifier)
->(Identifier) }
(TypeParameters
(Identifier)))
(Constructor
{ (Identifier)
->(Identifier) }
(TypeParameters
(StrictTypeVariable
(Identifier)))))
(Datatype
(Type
{ (Identifier)
->(Identifier) }
(TypeParameters
(Identifier)
(Identifier)))
(Constructor
{ (Identifier)
->(Identifier) }
(TypeParameters
(StrictTypeVariable
(Identifier))
(Identifier))))
(Datatype
(Type
{ (Identifier)
->(Identifier) }
(TypeParameters))
{+(Constructor
{+(Identifier)+}
{+(TypeParameters)+})+}
(Constructor
{ (Identifier)
->(Identifier) }
(TypeParameters))
{+(Constructor
{+(Identifier)+}
{+(TypeParameters)+})+}
{+(Constructor
{+(Identifier)+}
{+(TypeParameters)+})+}
(Constructor
{ (Identifier)
->(Identifier) }
(TypeParameters))
(Constructor
{ (Identifier)
->(Identifier) }
(TypeParameters))
{-(Constructor
{-(Identifier)-}
{-(TypeParameters)-})-}
{-(Constructor
{-(Identifier)-}
{-(TypeParameters)-})-}
{-(Constructor
{-(Identifier)-}
{-(TypeParameters)-})-})
(Datatype
(Type
{ (Identifier)
->(Identifier) }
(TypeParameters))
(RecordDataConstructor
{ (Identifier)
->(Identifier) }
(Statements
(Field
(Statements
(Identifier))
(Identifier)))))
(Datatype
(Type
{ (Identifier)
->(Identifier) }
(TypeParameters))
(RecordDataConstructor
{ (Identifier)
->(Identifier) }
(Statements
(Field
(Statements
(Identifier)
(Identifier))
(Identifier)))))
(Datatype
(Type
{ (Identifier)
->(Identifier) }
(TypeParameters))
(RecordDataConstructor
{ (Identifier)
->(Identifier) }
(Statements
(Field
(Statements
(Identifier))
(StrictType
(Identifier)
(TypeParameters)))
(Field
(Statements
(Identifier))
(Identifier)))))
(Datatype
(Type
{ (Identifier)
->(Identifier) }
(TypeParameters))
(RecordDataConstructor
{ (Identifier)
->(Identifier) }
(Statements
(Field
(Statements
(Identifier)
(Identifier))
(Context
(Pragma)
(StrictType
(Identifier)
(TypeParameters))))
(Field
(Statements
(Identifier))
(Identifier)))))
{+(Datatype
{+(Type
{+(Identifier)+}
{+(TypeParameters)+})+}
{+(RecordDataConstructor
{+(Identifier)+}
{+(Statements
{+(Field
{+(Statements
{+(Identifier)+})+}
{+(Identifier)+})+})+})+}
{+(RecordDataConstructor
{+(Identifier)+}
{+(Statements
{+(Field
{+(Statements
{+(Identifier)+})+}
{+(Identifier)+})+})+})+})+}
(Datatype
(Type
(Identifier)
(TypeParameters))
(RecordDataConstructor
(Identifier)
(Statements
(Field
(Statements
(Identifier))
(Identifier))))
(RecordDataConstructor
(Identifier)
(Statements
(Field
(Statements
(Identifier))
(Identifier)))))
{-(Datatype
{-(Type
{-(Identifier)-}
{-(TypeParameters)-})-}
{-(RecordDataConstructor
{-(Identifier)-}
{-(Statements
{-(Field
{-(Statements
{-(Identifier)-})-}
{-(Identifier)-})-})-})-}
{-(RecordDataConstructor
{-(Identifier)-}
{-(Statements
{-(Field
{-(Statements
{-(Identifier)-})-}
{-(Identifier)-})-})-})-})-}))

View File

@ -0,0 +1,156 @@
(Module
(Empty)
(Statements
(Datatype
(Type
(Identifier)
(TypeParameters)))
(Datatype
(Type
(Identifier)
(TypeParameters
(Identifier)))
(Constructor
(Identifier)
(TypeParameters
(Identifier))))
(Datatype
(Type
(Identifier)
(TypeParameters
(Identifier)))
(Constructor
(Identifier)
(TypeParameters
(StrictTypeVariable
(Identifier)))))
(Datatype
(Type
(Identifier)
(TypeParameters
(Identifier)
(Identifier)))
(Constructor
(Identifier)
(TypeParameters
(StrictTypeVariable
(Identifier))
(Identifier))))
(Datatype
(Type
(Identifier)
(TypeParameters))
(Constructor
(Identifier)
(TypeParameters))
(Constructor
(Identifier)
(TypeParameters))
(Constructor
(Identifier)
(TypeParameters))
(Constructor
(Identifier)
(TypeParameters))
(Constructor
(Identifier)
(TypeParameters))
(Constructor
(Identifier)
(TypeParameters)))
(Datatype
(Type
(Identifier)
(TypeParameters))
(RecordDataConstructor
(Identifier)
(Statements
(Field
(Statements
(Identifier))
(Identifier)))))
(Datatype
(Type
(Identifier)
(TypeParameters))
(RecordDataConstructor
(Identifier)
(Statements
(Field
(Statements
(Identifier)
(Identifier))
(Identifier)))))
(Datatype
(Type
(Identifier)
(TypeParameters))
(RecordDataConstructor
(Identifier)
(Statements
(Field
(Statements
(Identifier))
(StrictType
(Identifier)
(TypeParameters)))
(Field
(Statements
(Identifier))
(Identifier)))))
(Datatype
(Type
(Identifier)
(TypeParameters))
(RecordDataConstructor
(Identifier)
(Statements
(Field
(Statements
(Identifier)
(Identifier))
(Context
(Pragma)
(StrictType
(Identifier)
(TypeParameters))))
(Field
(Statements
(Identifier))
(Identifier)))))
(Datatype
(Type
(Identifier)
(TypeParameters))
(RecordDataConstructor
(Identifier)
(Statements
(Field
(Statements
(Identifier))
(Identifier))))
(RecordDataConstructor
(Identifier)
(Statements
(Field
(Statements
(Identifier))
(Identifier)))))
(Datatype
(Type
(Identifier)
(TypeParameters))
(RecordDataConstructor
(Identifier)
(Statements
(Field
(Statements
(Identifier))
(Identifier))))
(RecordDataConstructor
(Identifier)
(Statements
(Field
(Statements
(Identifier))
(Identifier)))))))

View File

@ -0,0 +1,156 @@
(Module
(Empty)
(Statements
(Datatype
(Type
(Identifier)
(TypeParameters)))
(Datatype
(Type
(Identifier)
(TypeParameters
(Identifier)))
(Constructor
(Identifier)
(TypeParameters
(Identifier))))
(Datatype
(Type
(Identifier)
(TypeParameters
(Identifier)))
(Constructor
(Identifier)
(TypeParameters
(StrictTypeVariable
(Identifier)))))
(Datatype
(Type
(Identifier)
(TypeParameters
(Identifier)
(Identifier)))
(Constructor
(Identifier)
(TypeParameters
(StrictTypeVariable
(Identifier))
(Identifier))))
(Datatype
(Type
(Identifier)
(TypeParameters))
(Constructor
(Identifier)
(TypeParameters))
(Constructor
(Identifier)
(TypeParameters))
(Constructor
(Identifier)
(TypeParameters))
(Constructor
(Identifier)
(TypeParameters))
(Constructor
(Identifier)
(TypeParameters))
(Constructor
(Identifier)
(TypeParameters)))
(Datatype
(Type
(Identifier)
(TypeParameters))
(RecordDataConstructor
(Identifier)
(Statements
(Field
(Statements
(Identifier))
(Identifier)))))
(Datatype
(Type
(Identifier)
(TypeParameters))
(RecordDataConstructor
(Identifier)
(Statements
(Field
(Statements
(Identifier)
(Identifier))
(Identifier)))))
(Datatype
(Type
(Identifier)
(TypeParameters))
(RecordDataConstructor
(Identifier)
(Statements
(Field
(Statements
(Identifier))
(StrictType
(Identifier)
(TypeParameters)))
(Field
(Statements
(Identifier))
(Identifier)))))
(Datatype
(Type
(Identifier)
(TypeParameters))
(RecordDataConstructor
(Identifier)
(Statements
(Field
(Statements
(Identifier)
(Identifier))
(Context
(Pragma)
(StrictType
(Identifier)
(TypeParameters))))
(Field
(Statements
(Identifier))
(Identifier)))))
(Datatype
(Type
(Identifier)
(TypeParameters))
(RecordDataConstructor
(Identifier)
(Statements
(Field
(Statements
(Identifier))
(Identifier))))
(RecordDataConstructor
(Identifier)
(Statements
(Field
(Statements
(Identifier))
(Identifier)))))
(Datatype
(Type
(Identifier)
(TypeParameters))
(RecordDataConstructor
(Identifier)
(Statements
(Field
(Statements
(Identifier))
(Identifier))))
(RecordDataConstructor
(Identifier)
(Statements
(Field
(Statements
(Identifier))
(Identifier)))))))

View File

@ -1,3 +1,3 @@
(Module
(Empty)
([]))
(Statements))

View File

@ -1,233 +1,234 @@
(Module
(Identifier)
(
(Statements
(Function
{ (Identifier)
->(Identifier) }
(Statements
(Integer)))
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Integer)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Integer)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Integer)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Integer)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Integer)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Integer)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Float)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Float)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Float)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Float)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Float)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Float)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Float)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Float)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Float)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Float)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Float)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Float)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Float)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Float)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Identifier)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Identifier)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Identifier)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Identifier)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Identifier)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Identifier)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Identifier)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Identifier)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Identifier)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Array
{+(TextElement)+}
{+(TextElement)+}
@ -265,231 +266,227 @@
{+(TextElement)+})+})+})+}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Integer)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Integer)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Integer)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Integer)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Integer)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Integer)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Float)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Float)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Float)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Float)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Float)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Float)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Float)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Float)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Float)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Float)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Float)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Float)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Float)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Float)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Identifier)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Identifier)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Identifier)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Identifier)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Identifier)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Identifier)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Identifier)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Identifier)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Identifier)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Array
{-(TextElement)-}
{-(TextElement)-}

View File

@ -1,235 +1,236 @@
(Module
(Identifier)
(
(Statements
(Function
{ (Identifier)
->(Identifier) }
(Statements
(Integer)))
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Integer)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Integer)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Integer)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Integer)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Integer)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Integer)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Float)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Float)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Float)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Float)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Float)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Float)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Float)+})+})+}
(Function
{ (Identifier)
->(Identifier) }
(
(Statements
{+(Float)+}
{-(Integer)-}))
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Float)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Float)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Float)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Float)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Float)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Float)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Identifier)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Identifier)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Identifier)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Identifier)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Identifier)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Identifier)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Identifier)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Identifier)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Identifier)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Character)+})+})+}
{+(Function
{+(Identifier)+}
{+(
{+(Statements
{+(Array
{+(TextElement)+}
{+(TextElement)+}
@ -267,227 +268,223 @@
{+(TextElement)+})+})+})+}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Integer)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Integer)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Integer)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Integer)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Integer)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Float)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Float)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Float)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Float)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Float)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Float)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Float)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Float)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Float)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Float)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Float)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Float)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Float)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Float)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Identifier)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Identifier)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Identifier)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Identifier)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Identifier)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Identifier)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Identifier)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Identifier)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Identifier)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Character)-})-})-}
{-(Function
{-(Identifier)-}
{-(
{-(Statements
{-(Array
{-(TextElement)-}
{-(TextElement)-}

View File

@ -1,233 +1,233 @@
(Module
(Identifier)
(
(Statements
(Function
(Identifier)
(
(Statements
(Integer)))
(Function
(Identifier)
(
(Statements
(Integer)))
(Function
(Identifier)
(
(Statements
(Integer)))
(Function
(Identifier)
(
(Statements
(Integer)))
(Function
(Identifier)
(
(Statements
(Integer)))
(Function
(Identifier)
(
(Statements
(Integer)))
(Function
(Identifier)
(
(Statements
(Float)))
(Function
(Identifier)
(
(Statements
(Float)))
(Function
(Identifier)
(
(Statements
(Float)))
(Function
(Identifier)
(
(Statements
(Float)))
(Function
(Identifier)
(
(Statements
(Float)))
(Function
(Identifier)
(
(Statements
(Float)))
(Function
(Identifier)
(
(Statements
(Float)))
(Function
(Identifier)
(
(Statements
(Float)))
(Function
(Identifier)
(
(Statements
(Float)))
(Function
(Identifier)
(
(Statements
(Float)))
(Function
(Identifier)
(
(Statements
(Float)))
(Function
(Identifier)
(
(Statements
(Float)))
(Function
(Identifier)
(
(Statements
(Float)))
(Function
(Identifier)
(
(Statements
(Float)))
(Function
(Identifier)
(
(Statements
(Identifier)))
(Function
(Identifier)
(
(Statements
(Identifier)))
(Function
(Identifier)
(
(Statements
(Identifier)))
(Function
(Identifier)
(
(Statements
(Identifier)))
(Function
(Identifier)
(
(Statements
(Identifier)))
(Function
(Identifier)
(
(Statements
(Identifier)))
(Function
(Identifier)
(
(Statements
(Identifier)))
(Function
(Identifier)
(
(Statements
(Identifier)))
(Function
(Identifier)
(
(Statements
(Identifier)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Array
(TextElement)
(TextElement)

View File

@ -1,233 +1,233 @@
(Module
(Identifier)
(
(Statements
(Function
(Identifier)
(
(Statements
(Integer)))
(Function
(Identifier)
(
(Statements
(Integer)))
(Function
(Identifier)
(
(Statements
(Integer)))
(Function
(Identifier)
(
(Statements
(Integer)))
(Function
(Identifier)
(
(Statements
(Integer)))
(Function
(Identifier)
(
(Statements
(Integer)))
(Function
(Identifier)
(
(Statements
(Float)))
(Function
(Identifier)
(
(Statements
(Float)))
(Function
(Identifier)
(
(Statements
(Float)))
(Function
(Identifier)
(
(Statements
(Float)))
(Function
(Identifier)
(
(Statements
(Float)))
(Function
(Identifier)
(
(Statements
(Float)))
(Function
(Identifier)
(
(Statements
(Float)))
(Function
(Identifier)
(
(Statements
(Float)))
(Function
(Identifier)
(
(Statements
(Float)))
(Function
(Identifier)
(
(Statements
(Float)))
(Function
(Identifier)
(
(Statements
(Float)))
(Function
(Identifier)
(
(Statements
(Float)))
(Function
(Identifier)
(
(Statements
(Float)))
(Function
(Identifier)
(
(Statements
(Float)))
(Function
(Identifier)
(
(Statements
(Identifier)))
(Function
(Identifier)
(
(Statements
(Identifier)))
(Function
(Identifier)
(
(Statements
(Identifier)))
(Function
(Identifier)
(
(Statements
(Identifier)))
(Function
(Identifier)
(
(Statements
(Identifier)))
(Function
(Identifier)
(
(Statements
(Identifier)))
(Function
(Identifier)
(
(Statements
(Identifier)))
(Function
(Identifier)
(
(Statements
(Identifier)))
(Function
(Identifier)
(
(Statements
(Identifier)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Character)))
(Function
(Identifier)
(
(Statements
(Array
(TextElement)
(TextElement)

View File

@ -1,6 +1,6 @@
(Module
(Empty)
(
(Statements
(TypeSynonym
(Type
{ (Identifier)

View File

@ -1,6 +1,6 @@
(Module
(Empty)
(
(Statements
(TypeSynonym
(Type
{ (Identifier)

View File

@ -1,6 +1,6 @@
(Module
(Empty)
(
(Statements
(TypeSynonym
(Type
(Identifier)

View File

@ -1,6 +1,6 @@
(Module
(Empty)
(
(Statements
(TypeSynonym
(Type
(Identifier)

45
types.proto Normal file
View File

@ -0,0 +1,45 @@
syntax = "proto3";
package semantic;
enum Language {Go = 0;
Haskell = 1;
JavaScript = 2;
JSON = 3;
JSX = 4;
Markdown = 5;
Python = 6;
Ruby = 7;
TypeScript = 8;
PHP = 9;}
message Blob { bytes blobSource = 1;
string blobPath = 2;
Language blobLanguage = 3;
}
message Pos { int64 posLine = 1;
int64 posColumn = 2;
}
message Span { Pos spanStart = 1;
Pos spanEnd = 2;
}
message Array { repeated Term arrayElements = 1;
}
message Boolean { bool booleanContent = 1;
}
message Hash { repeated Term hashElements = 1;
}
message Float { bytes floatContent = 1;
}
message KeyValue { Term key = 1;
Term value = 2;
}
message Null {
}
message TextElement { bytes textElementContent = 1;
}
message Term { oneof syntax {Array array = 1;
Boolean boolean = 2;
Hash hash = 3;
Float float = 4;
KeyValue keyValue = 5;
Null null = 6;
TextElement textElement = 7;}
}

2
vendor/fastsum vendored

@ -1 +1 @@
Subproject commit 2310af6de3d3c337d671cdf9fe3e007990fdb1e4
Subproject commit dbeff0af57fcea85bca07ff5a8149301dd3b084c

1
vendor/proto3-suite vendored Submodule

@ -0,0 +1 @@
Subproject commit c75b250e82481e23d2ff586b3e841834b5d93ff9

1
vendor/proto3-wire vendored Submodule

@ -0,0 +1 @@
Subproject commit c8792bc33154e849239b1c91ffe06af2e765d734