1
1
mirror of https://github.com/github/semantic.git synced 2024-12-29 18:06:14 +03:00

Merge remote-tracking branch 'origin/master' into add-python

This commit is contained in:
joshvera 2018-07-23 18:21:01 -04:00
commit 322db1dd89
95 changed files with 2191 additions and 1531 deletions

View File

@ -82,8 +82,6 @@ library
, Data.JSON.Fields
, Data.Language
, Data.Map.Monoidal
, Data.Mergeable
, Data.Options
, Data.Patch
, Data.Project
, Data.Range
@ -126,7 +124,11 @@ library
, Language.Ruby.Syntax
, Language.TypeScript.Assignment
, Language.TypeScript.Grammar
, Language.TypeScript.Resolution
, Language.TypeScript.Syntax
, Language.TypeScript.Syntax.JavaScript
, Language.TypeScript.Syntax.JSX
, Language.TypeScript.Syntax.TypeScript
, Language.PHP.Assignment
, Language.PHP.Grammar
, Language.PHP.Syntax
@ -249,9 +251,9 @@ library
, StrictData
, TypeApplications
if flag(release)
ghc-options: -Wall -Werror -Wcompat -Wincomplete-record-updates -Wincomplete-uni-patterns -Wredundant-constraints -fno-warn-name-shadowing -O1 -j
ghc-options: -Wall -Werror -Wmissing-export-lists -Wcompat -Wincomplete-record-updates -Wincomplete-uni-patterns -Wredundant-constraints -fno-warn-name-shadowing -O1 -j
else
ghc-options: -Wall -Wcompat -Wincomplete-record-updates -Wincomplete-uni-patterns -Wredundant-constraints -fno-warn-name-shadowing -O0 -j
ghc-options: -Wall -Wmissing-export-lists -Wcompat -Wincomplete-record-updates -Wincomplete-uni-patterns -Wredundant-constraints -fno-warn-name-shadowing -O0 -j
ghc-prof-options: -fprof-auto
executable semantic
@ -279,10 +281,11 @@ test-suite test
, Analysis.TypeScript.Spec
, Assigning.Assignment.Spec
, Control.Abstract.Evaluator.Spec
, Data.Diff.Spec
, Data.Abstract.Path.Spec
, Data.Diff.Spec
, Data.Functor.Classes.Generic.Spec
, Data.Functor.Listable
, Data.Mergeable
, Data.Scientific.Spec
, Data.Source.Spec
, Data.Term.Spec

View File

@ -18,14 +18,13 @@ module Analysis.Abstract.Graph
import Algebra.Graph.Export.Dot hiding (vertexName)
import Control.Abstract
import Data.Abstract.Address
import Data.Abstract.Module (Module(moduleInfo), ModuleInfo(..))
import Data.Abstract.Name
import Data.Abstract.Package (PackageInfo(..))
import Data.Abstract.Declarations
import Data.Abstract.Module (Module (moduleInfo), ModuleInfo (..))
import Data.Abstract.Package (PackageInfo (..))
import Data.ByteString.Builder
import Data.Graph
import Data.Graph.Vertex
import Data.Sum
import qualified Data.Syntax as Syntax
import Data.Record
import Data.Term
import qualified Data.Text.Encoding as T
import Prologue hiding (project)
@ -35,39 +34,62 @@ style = (defaultStyle (T.encodeUtf8Builder . vertexName))
{ vertexAttributes = vertexAttributes
, edgeAttributes = edgeAttributes
}
where vertexAttributes Package{} = [ "style" := "dashed", "shape" := "box" ]
vertexAttributes Module{} = [ "style" := "dotted, rounded", "shape" := "box" ]
vertexAttributes Variable{} = []
edgeAttributes Package{} Module{} = [ "style" := "dashed" ]
edgeAttributes Module{} Variable{} = [ "style" := "dotted" ]
edgeAttributes Variable{} Module{} = [ "color" := "blue" ]
where vertexAttributes Package{} = [ "style" := "dashed", "shape" := "box" ]
vertexAttributes Module{} = [ "style" := "dotted, rounded", "shape" := "box" ]
vertexAttributes Variable{..} = [ "tooltip" := T.encodeUtf8Builder (showSpan variableSpan), "style" := "rounded", "shape" := "box" ]
vertexAttributes Method{..} = [ "tooltip" := T.encodeUtf8Builder (showSpan methodSpan) , "style" := "rounded", "shape" := "box" ]
vertexAttributes Function{..} = [ "tooltip" := T.encodeUtf8Builder (showSpan functionSpan), "style" := "rounded", "shape" := "box" ]
edgeAttributes Package{} Module{} = [ "len" := "5.0", "style" := "dashed" ]
edgeAttributes Module{} Module{} = [ "len" := "5.0", "label" := "imports" ]
edgeAttributes Variable{} Module{} = [ "len" := "5.0", "color" := "blue", "label" := "refers to symbol defined in" ]
edgeAttributes _ Module{} = [ "len" := "5.0", "color" := "blue", "label" := "defined in" ]
edgeAttributes Method{} Variable{} = [ "len" := "2.0", "color" := "green", "label" := "calls" ]
edgeAttributes Function{} Variable{} = [ "len" := "2.0", "color" := "green", "label" := "calls" ]
edgeAttributes Module{} Function{} = [ "len" := "2.0", "color" := "red", "label" := "defines" ]
edgeAttributes Module{} Method{} = [ "len" := "2.0", "color" := "red", "label" := "defines" ]
edgeAttributes Module{} _ = [ "len" := "2.0", "color" := "green", "label" := "calls" ]
edgeAttributes _ _ = []
-- | Add vertices to the graph for evaluated identifiers.
graphingTerms :: ( Element Syntax.Identifier syntax
, Member (Reader ModuleInfo) effects
graphingTerms :: ( Member (Reader ModuleInfo) effects
, Member (Env (Hole context (Located address))) effects
, Member (State (Graph Vertex)) effects
, Base term ~ TermF (Sum syntax) ann
, Member (Reader Vertex) effects
, HasField fields Span
, VertexDeclaration syntax
, Declarations1 syntax
, Foldable syntax
, Functor syntax
, term ~ Term syntax (Record fields)
)
=> SubtermAlgebra (Base term) term (TermEvaluator term (Hole context (Located address)) value effects a)
-> SubtermAlgebra (Base term) term (TermEvaluator term (Hole context (Located address)) value effects a)
graphingTerms recur term@(In _ syntax) = do
case project syntax of
Just (Syntax.Identifier name) -> do
moduleInclusion (Variable (formatName name))
variableDefinition name
_ -> pure ()
recur term
graphingTerms recur term@(In a syntax) = do
definedInModule <- currentModule
case toVertex a definedInModule (subterm <$> syntax) of
Just (v@Function{}, _) -> recurWithContext v
Just (v@Method{}, _) -> recurWithContext v
Just (Variable{..}, name) -> do
definedInModuleInfo <- maybe (ModuleInfo "unknown") (maybe (ModuleInfo "hole") addressModule . toMaybe) <$> TermEvaluator (lookupEnv name)
variableDefinition (variableVertex variableName definedInModuleInfo variableSpan)
recur term
_ -> recur term
where
recurWithContext v = do
variableDefinition v
moduleInclusion v
local (const v) (recur term)
-- | Add vertices to the graph for evaluated modules and the packages containing them.
graphingPackages :: ( Member (Reader PackageInfo) effects
, Member (State (Graph Vertex)) effects
, Member (Reader Vertex) effects
)
=> SubtermAlgebra Module term (TermEvaluator term address value effects a)
-> SubtermAlgebra Module term (TermEvaluator term address value effects a)
graphingPackages recur m = packageInclusion (moduleVertex (moduleInfo m)) *> recur m
graphingPackages recur m =
let v = moduleVertex (moduleInfo m) in packageInclusion v *> local (const v) (recur m)
-- | Add vertices to the graph for imported modules.
graphingModules :: forall term address value effects a
@ -75,16 +97,20 @@ graphingModules :: forall term address value effects a
, Member (Modules address) effects
, Member (Reader ModuleInfo) effects
, Member (State (Graph Vertex)) effects
, Member (Reader Vertex) effects
)
=> SubtermAlgebra Module term (TermEvaluator term address value effects a)
-> SubtermAlgebra Module term (TermEvaluator term address value effects a)
graphingModules recur m = do
appendGraph (vertex (moduleVertex (moduleInfo m)))
eavesdrop @(Modules address) (\ m -> case m of
Load path -> moduleInclusion (moduleVertex (ModuleInfo path))
Lookup path -> moduleInclusion (moduleVertex (ModuleInfo path))
_ -> pure ())
(recur m)
let v = moduleVertex (moduleInfo m)
appendGraph (vertex v)
local (const v) $
eavesdrop @(Modules address) (\ m -> case m of
-- NB: path is null for Languages like Ruby that have module imports that require concrete value semantics.
Load path | not (Prologue.null path) -> moduleInclusion (moduleVertex (ModuleInfo path))
Lookup path | not (Prologue.null path) -> moduleInclusion (moduleVertex (ModuleInfo path))
_ -> pure ())
(recur m)
-- | Add vertices to the graph for imported modules.
graphingModuleInfo :: forall term address value effects a
@ -98,7 +124,7 @@ graphingModuleInfo :: forall term address value effects a
graphingModuleInfo recur m = do
appendGraph (vertex (moduleInfo m))
eavesdrop @(Modules address) (\ eff -> case eff of
Load path -> currentModule >>= appendGraph . (`connect` vertex (ModuleInfo path)) . vertex
Load path -> currentModule >>= appendGraph . (`connect` vertex (ModuleInfo path)) . vertex
Lookup path -> currentModule >>= appendGraph . (`connect` vertex (ModuleInfo path)) . vertex
_ -> pure ())
(recur m)
@ -127,15 +153,15 @@ moduleInclusion v = do
m <- currentModule
appendGraph (vertex (moduleVertex m) `connect` vertex v)
-- | Add an edge from the passed variable name to the module it originated within.
variableDefinition :: ( Member (Env (Hole context (Located address))) effects
, Member (State (Graph Vertex)) effects
-- | Add an edge from the passed variable name to the context it originated within.
variableDefinition :: ( Member (State (Graph Vertex)) effects
, Member (Reader Vertex) effects
)
=> Name
=> Vertex
-> TermEvaluator term (Hole context (Located address)) value effects ()
variableDefinition name = do
graph <- maybe lowerBound (maybe lowerBound (vertex . moduleVertex . addressModule) . toMaybe) <$> TermEvaluator (lookupEnv name)
appendGraph (vertex (Variable (formatName name)) `connect` graph)
variableDefinition var = do
context <- ask
appendGraph $ vertex context `connect` vertex var
appendGraph :: (Effectful m, Member (State (Graph v)) effects) => Graph v -> m effects ()
appendGraph = modify' . (<>)

View File

@ -1,4 +1,8 @@
module Control.Abstract.Hole where
module Control.Abstract.Hole
( AbstractHole (..)
, Hole (..)
, toMaybe
) where
import Prologue

View File

@ -1,4 +1,11 @@
module Control.Abstract.Primitive where
module Control.Abstract.Primitive
( define
, defineClass
, defineNamespace
, builtInPrint
, builtInExport
, lambda
) where
import Control.Abstract.Context
import Control.Abstract.Environment

View File

@ -124,6 +124,9 @@ class (AbstractFunction address value effects, AbstractIntro value) => AbstractV
-- | Eliminate boolean values. TODO: s/boolean/truthy
ifthenelse :: value -> Evaluator address value effects a -> Evaluator address value effects a -> Evaluator address value effects a
-- | Compute the disjunction (boolean or) of two computed values. This should have short-circuiting semantics where applicable.
disjunction :: Evaluator address value effects value -> Evaluator address value effects value -> Evaluator address value effects value
-- | @index x i@ computes @x[i]@, with zero-indexing.
index :: value -> value -> Evaluator address value effects address

View File

@ -1,5 +1,10 @@
{-# LANGUAGE DataKinds #-}
module Data.AST where
module Data.AST
( Node (..)
, AST
, Location
, nodeLocation
) where
import Data.Range
import Data.Record

View File

@ -1,5 +1,11 @@
{-# LANGUAGE GeneralizedNewtypeDeriving, TypeFamilies #-}
module Data.Abstract.Address where
module Data.Abstract.Address
( Precise (..)
, Located (..)
, Latest (..)
, All (..)
, Monovariant (..)
) where
import Data.Abstract.Module (ModuleInfo)
import Data.Abstract.Name

View File

@ -1,5 +1,13 @@
{-# LANGUAGE ConstraintKinds, GeneralizedNewtypeDeriving, TypeFamilies #-}
module Data.Abstract.Cache where
module Data.Abstract.Cache
( Cache
, Cached (..)
, Cacheable
, cacheLookup
, cacheSet
, cacheInsert
, cacheKeys
) where
import Data.Abstract.Configuration
import Data.Abstract.Heap

View File

@ -1,4 +1,4 @@
module Data.Abstract.Configuration where
module Data.Abstract.Configuration ( Configuration (..) ) where
import Data.Abstract.Environment
import Data.Abstract.Heap

View File

@ -1,5 +1,8 @@
{-# LANGUAGE GeneralizedNewtypeDeriving, UndecidableInstances #-}
module Data.Abstract.Declarations where
module Data.Abstract.Declarations
( Declarations (..)
, Declarations1 (..)
) where
import Data.Abstract.Name
import Data.Sum

View File

@ -1,5 +1,8 @@
{-# LANGUAGE DefaultSignatures, GeneralizedNewtypeDeriving, UndecidableInstances #-}
module Data.Abstract.FreeVariables where
module Data.Abstract.FreeVariables
( FreeVariables (..)
, FreeVariables1 (..)
) where
import Data.Abstract.Name
import Data.Sum

View File

@ -1,5 +1,13 @@
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Data.Abstract.Heap where
module Data.Abstract.Heap
( Heap
, heapLookup
, heapLookupAll
, heapInsert
, heapInit
, heapSize
, heapRestrict
) where
import Data.Abstract.Live
import qualified Data.Map.Monoidal as Monoidal

View File

@ -1,5 +1,15 @@
{-# LANGUAGE DataKinds, GeneralizedNewtypeDeriving, TypeFamilies, TypeOperators #-}
module Data.Abstract.Live where
module Data.Abstract.Live
( Live (..)
, fromAddresses
, liveSingleton
, liveInsert
, liveDelete
, liveDifference
, liveMember
, liveSplit
, liveMap
) where
import Data.Set as Set
import Prologue

View File

@ -1,4 +1,9 @@
module Data.Abstract.Package where
module Data.Abstract.Package
( Package (..)
, PackageInfo (..)
, PackageName
, Data.Abstract.Package.fromModules
) where
import Data.Abstract.Module
import Data.Abstract.ModuleTable as ModuleTable

View File

@ -1,4 +1,8 @@
module Data.Abstract.Path where
module Data.Abstract.Path
( dropRelativePrefix
, joinPaths
, stripQuotes
) where
import Prologue
import qualified Data.Text as T

View File

@ -1,5 +1,8 @@
{-# LANGUAGE GADTs #-}
module Data.Abstract.Ref where
module Data.Abstract.Ref
( ValueRef (..)
, Ref (..)
) where
import Data.Abstract.Name

View File

@ -1,5 +1,5 @@
{-# LANGUAGE GADTs, UndecidableInstances #-}
module Data.Abstract.Value.Abstract where
module Data.Abstract.Value.Abstract ( Abstract (..) ) where
import Control.Abstract
import Data.Abstract.Environment as Env
@ -67,6 +67,7 @@ instance ( Member (Allocator address Abstract) effects
index _ _ = box Abstract
ifthenelse _ if' else' = if' <|> else'
disjunction = (<|>)
liftNumeric _ _ = pure Abstract
liftNumeric2 _ _ _ = pure Abstract

View File

@ -1,5 +1,12 @@
{-# LANGUAGE GADTs, RankNTypes, TypeOperators, UndecidableInstances, LambdaCase #-}
module Data.Abstract.Value.Concrete where
module Data.Abstract.Value.Concrete
( Value (..)
, ValueError (..)
, ClosureBody (..)
, runValueError
, runValueErrorWith
, throwValueError
) where
import Control.Abstract
import Data.Abstract.Environment (Environment, Bindings)
@ -145,6 +152,11 @@ instance ( Coercible body (Eff effects)
bool <- case cond of { Boolean b -> pure b ; _ -> throwValueError (BoolError cond) }
if bool then if' else else'
disjunction a b = do
a' <- a
ifthenelse a' (pure a') b
index = go where
tryIdx list ii
| ii > genericLength list = box =<< throwValueError (BoundsError list ii)

View File

@ -293,6 +293,9 @@ instance ( Member (Allocator address Type) effects
box (Var field)
ifthenelse cond if' else' = unify cond Bool *> (if' <|> else')
disjunction a b = do
a' <- a
unify a' Bool *> (pure a' <|> b)
liftNumeric _ = unify (Int :+ Float :+ Rational)
liftNumeric2 _ left right = case (left, right) of

View File

@ -12,21 +12,16 @@ module Data.Diff
, mergeF
, merging
, diffPatches
, beforeTerm
, afterTerm
, stripDiff
) where
import Control.Applicative ((<|>))
import Data.Aeson
import Data.Bifoldable
import Data.Bifunctor
import Data.Bitraversable
import Data.Foldable (asum)
import Data.Functor.Classes
import Data.Functor.Foldable
import Data.JSON.Fields
import Data.Mergeable (Mergeable(sequenceAlt))
import Data.Patch
import Data.Record
import Data.Term
@ -93,19 +88,6 @@ diffPatches = para $ \ diff -> case diff of
Merge merge -> foldMap snd merge
-- | Recover the before state of a diff.
beforeTerm :: (Foldable syntax, Mergeable syntax) => Diff syntax ann1 ann2 -> Maybe (Term syntax ann1)
beforeTerm = cata $ \ diff -> case diff of
Patch patch -> (before patch >>= \ (In a l) -> termIn a <$> sequenceAlt l) <|> (after patch >>= asum)
Merge (In (a, _) l) -> termIn a <$> sequenceAlt l
-- | Recover the after state of a diff.
afterTerm :: (Foldable syntax, Mergeable syntax) => Diff syntax ann1 ann2 -> Maybe (Term syntax ann2)
afterTerm = cata $ \ diff -> case diff of
Patch patch -> (after patch >>= \ (In b r) -> termIn b <$> sequenceAlt r) <|> (before patch >>= asum)
Merge (In (_, b) r) -> termIn b <$> sequenceAlt r
-- | Strips the head annotation off a diff annotated with non-empty records.
stripDiff :: Functor syntax
=> Diff syntax (Record (h1 ': t1)) (Record (h2 ': t2))

View File

@ -29,6 +29,7 @@ import Data.Map (Map)
import qualified Data.Map as Map
import Data.Set (Set)
import qualified Data.Set as Set
import Data.Span
import qualified Data.Vector as Vec
import Data.Word
import GHC.Exts (fromList)
@ -42,6 +43,8 @@ data VertexType
= PACKAGE
| MODULE
| VARIABLE
| METHOD
| FUNCTION
deriving (Eq, Ord, Show, Enum, Bounded, Generic, ToJSON, FromJSON, PB.Named, PB.Finite, PB.MessageField)
-- | Defaults to 'PACKAGE'.
@ -117,6 +120,8 @@ taggedGraphToAdjacencyList = accumToAdj . adjMapToAccum . adjacencyMap . toGraph
V.Package{} -> PACKAGE
V.Module{} -> MODULE
V.Variable{} -> VARIABLE
V.Method{} -> METHOD
V.Function{} -> FUNCTION
-- Annotate all vertices of a 'Graph' with a 'Tag', starting from 1.
-- Two vertices @a@ and @b@ will share a 'Tag' iff @a == b@.
@ -158,7 +163,9 @@ importGraphToGraph (AdjacencyList vs es) = simplify built
pbToVertex (Vertex t c _) = case t of
MODULE -> V.Module c
PACKAGE -> V.Package c
VARIABLE -> V.Variable c
VARIABLE -> V.Variable c "unknown" emptySpan
METHOD -> V.Method c "unknown" emptySpan
FUNCTION -> V.Function c "unknown" emptySpan
-- | For debugging: returns True if all edges reference a valid vertex tag.

View File

@ -1,37 +1,139 @@
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveAnyClass, ScopedTypeVariables, TypeFamilies, TypeOperators, UndecidableInstances #-}
module Data.Graph.Vertex
( Vertex (..)
, moduleVertex
, packageVertex
, vertexToType
) where
import Prologue hiding (packageName)
( Vertex (..)
, packageVertex
, moduleVertex
, variableVertex
, methodVertex
, functionVertex
, vertexName
, showSpan
, VertexDeclaration (..)
, VertexDeclaration' (..)
, VertexDeclarationStrategy
, VertexDeclarationWithStrategy
) where
import Data.Abstract.Declarations
import Data.Abstract.Module (ModuleInfo (..))
import Data.Abstract.Name
import Data.Abstract.Package (PackageInfo (..))
import Data.Aeson
import Data.Record
import Data.Span
import qualified Data.Syntax as Syntax
import qualified Data.Syntax.Declaration as Declaration
import qualified Data.Syntax.Expression as Expression
import Data.Term
import qualified Data.Text as T
import Data.Abstract.Module (ModuleInfo (..))
import Data.Abstract.Name
import Data.Abstract.Package (PackageInfo (..))
import Prologue hiding (packageName)
-- | A vertex of some specific type.
data Vertex
= Package { vertexName :: Text }
| Module { vertexName :: Text }
| Variable { vertexName :: Text }
= Package { packageName :: Text }
| Module { moduleName :: Text }
| Variable { variableName :: Text, variableModuleName :: Text, variableSpan :: Span }
| Method { methodName :: Text, methodModuleName :: Text, methodSpan :: Span }
| Function { functionName :: Text, functionModuleName :: Text, functionSpan :: Span }
deriving (Eq, Ord, Show, Generic, Hashable)
packageVertex :: PackageInfo -> Vertex
packageVertex = Package . formatName . packageName
packageVertex (PackageInfo name _) = Package (formatName name)
moduleVertex :: ModuleInfo -> Vertex
moduleVertex = Module . T.pack . modulePath
variableVertex :: Text -> ModuleInfo -> Span -> Vertex
variableVertex name ModuleInfo{..} = Variable name (T.pack modulePath)
methodVertex :: Text -> ModuleInfo -> Span -> Vertex
methodVertex name ModuleInfo{..} = Method name (T.pack modulePath)
functionVertex :: Text -> ModuleInfo -> Span -> Vertex
functionVertex name ModuleInfo{..} = Function name (T.pack modulePath)
instance ToJSON Vertex where
toJSON v = object [ "name" .= vertexName v, "type" .= vertexToType v ]
vertexName :: Vertex -> Text
vertexName Package{..} = packageName <> " (Package)"
vertexName Module{..} = moduleName <> " (Module)"
vertexName Variable{..} = variableModuleName <> "::" <> variableName <> " (Variable)"
vertexName Method{..} = methodModuleName <> "::" <> methodName <> " (Method)"
vertexName Function{..} = functionModuleName <> "::" <> functionName <> " (Function)"
showSpan :: Span -> Text
showSpan (Span (Pos a b) (Pos c d)) = T.pack $
"[" <> show a <> ", " <> show b <> "]"
<> " - "
<> "[" <> show c <> ", " <> show d <> "]"
vertexToType :: Vertex -> Text
vertexToType Package{} = "package"
vertexToType Module{} = "module"
vertexToType Variable{} = "variable"
vertexToType Method{} = "method"
vertexToType Function{} = "function"
instance Lower Vertex where
lowerBound = Package ""
class VertexDeclaration syntax where
toVertex :: (Declarations1 syntax, Foldable syntax, HasField fields Span)
=> Record fields
-> ModuleInfo
-> syntax (Term syntax (Record fields))
-> Maybe (Vertex, Name)
instance (VertexDeclaration' syntax syntax) => VertexDeclaration syntax where
toVertex = toVertex'
class VertexDeclaration' whole syntax where
toVertex' :: (Declarations1 whole, Foldable whole, HasField fields Span)
=> Record fields
-> ModuleInfo
-> syntax (Term whole (Record fields))
-> Maybe (Vertex, Name)
instance (VertexDeclarationStrategy syntax ~ strategy, VertexDeclarationWithStrategy strategy whole syntax) => VertexDeclaration' whole syntax where
toVertex' = toVertexWithStrategy (Proxy :: Proxy strategy)
data Strategy = Default | Custom
type family VertexDeclarationStrategy syntax where
VertexDeclarationStrategy Syntax.Identifier = 'Custom
VertexDeclarationStrategy Declaration.Function = 'Custom
VertexDeclarationStrategy Declaration.Method = 'Custom
VertexDeclarationStrategy Expression.MemberAccess = 'Custom
VertexDeclarationStrategy (Sum _) = 'Custom
VertexDeclarationStrategy syntax = 'Default
class VertexDeclarationWithStrategy (strategy :: Strategy) whole syntax where
toVertexWithStrategy :: (Declarations1 whole, Foldable whole, HasField fields Span)
=> proxy strategy
-> Record fields
-> ModuleInfo
-> syntax (Term whole (Record fields))
-> Maybe (Vertex, Name)
-- | The 'Default' strategy produces 'Nothing'.
instance VertexDeclarationWithStrategy 'Default whole syntax where
toVertexWithStrategy _ _ _ _ = Nothing
instance Apply (VertexDeclaration' whole) fs => VertexDeclarationWithStrategy 'Custom whole (Sum fs) where
toVertexWithStrategy _ ann info = apply @(VertexDeclaration' whole) (toVertex' ann info)
instance VertexDeclarationWithStrategy 'Custom whole Syntax.Identifier where
toVertexWithStrategy _ ann info (Syntax.Identifier name) = Just (variableVertex (formatName name) info (getField ann), name)
instance VertexDeclarationWithStrategy 'Custom whole Declaration.Function where
toVertexWithStrategy _ ann info term@Declaration.Function{} = (\n -> (functionVertex (formatName n) info (getField ann), n)) <$> liftDeclaredName declaredName term
instance VertexDeclarationWithStrategy 'Custom whole Declaration.Method where
toVertexWithStrategy _ ann info term@Declaration.Method{} = (\n -> (methodVertex (formatName n) info (getField ann), n)) <$> liftDeclaredName declaredName term
instance VertexDeclarationWithStrategy 'Custom whole whole => VertexDeclarationWithStrategy 'Custom whole Expression.MemberAccess where
toVertexWithStrategy proxy ann info (Expression.MemberAccess (Term (In lhsAnn lhs)) name) =
case toVertexWithStrategy proxy lhsAnn info lhs of
Just (Variable n _ _, _) -> Just (variableVertex (n <> "." <> formatName name) info (getField ann), name)
_ -> Just (variableVertex (formatName name) info (getField ann), name)

View File

@ -1,5 +1,12 @@
{-# LANGUAGE DeriveAnyClass, DeriveGeneric, LambdaCase #-}
module Data.Language where
module Data.Language
( Language (..)
, ensureLanguage
, extensionsForLanguage
, knownLanguage
, languageForFilePath
, languageForType
) where
import Data.Aeson
import Data.Char (toUpper)

View File

@ -1 +0,0 @@
module Data.Options where

View File

@ -1,5 +1,10 @@
{-# LANGUAGE ConstraintKinds, DataKinds, GADTs, KindSignatures, MultiParamTypeClasses, TypeFamilies, TypeOperators, UndecidableInstances #-}
module Data.Record where
module Data.Record
( Record (..)
, HasField (..)
, rhead
, rtail
) where
import Data.Aeson
import Data.JSON.Fields

View File

@ -1,4 +1,7 @@
module Data.SplitDiff where
module Data.SplitDiff
( SplitPatch (..)
, getRange
) where
import Control.Monad.Free
import Data.Range
@ -20,6 +23,3 @@ getRange diff = getField $ case diff of
-- | A diff with only one sides annotations.
type SplitDiff syntax ann = Free (TermF syntax ann) (SplitPatch (Term syntax ann))
unSplit :: Functor syntax => SplitDiff syntax ann -> Term syntax ann
unSplit = iter Term . fmap splitTerm

View File

@ -1,5 +1,5 @@
{-# LANGUAGE AllowAmbiguousTypes, DeriveAnyClass, GADTs, TypeOperators, MultiParamTypeClasses, UndecidableInstances, ScopedTypeVariables, KindSignatures, RankNTypes, ConstraintKinds, GeneralizedNewtypeDeriving, DerivingStrategies #-}
{-# OPTIONS_GHC -Wno-redundant-constraints -fno-warn-orphans #-} -- For HasCallStack
{-# OPTIONS_GHC -Wno-missing-export-lists -Wno-redundant-constraints -fno-warn-orphans #-} -- For HasCallStack
module Data.Syntax where
import Data.Abstract.Evaluatable
@ -65,7 +65,6 @@ handleError = flip Assignment.catchError (\ err -> makeTerm <$> Assignment.locat
parseError :: (HasCallStack, Error :< syntaxes, Bounded grammar, Enum grammar, Ix grammar, Apply Foldable syntaxes) => Assignment.Assignment ast grammar (Term (Sum syntaxes) (Record Location))
parseError = makeTerm <$> Assignment.token maxBound <*> pure (Error (ErrorStack $ errorSite <$> getCallStack (freezeCallStack callStack)) [] (Just "ParseError") [])
-- | Match context terms before a subject term, wrapping both up in a Context term if any context terms matched, or otherwise returning the subject term.
contextualize :: (HasCallStack, Context :< syntaxes, Alternative m, Semigroup ann, Apply Foldable syntaxes)
=> m (Term (Sum syntaxes) ann)
@ -157,7 +156,7 @@ instance Message1 [] where
newtype Identifier a = Identifier { name :: Name }
deriving newtype (Eq, Ord, Show)
deriving stock (Foldable, Functor, Generic1, Traversable)
deriving anyclass (Diffable, Hashable1, Mergeable, Message1, Named1, ToJSONFields1)
deriving anyclass (Diffable, Hashable1, Message1, Named1, ToJSONFields1)
instance Eq1 Identifier where liftEq = genericLiftEq
instance Ord1 Identifier where liftCompare = genericLiftCompare
@ -176,7 +175,7 @@ instance Declarations1 Identifier where
newtype AccessibilityModifier a = AccessibilityModifier { contents :: Text }
deriving newtype (Eq, Ord, Show)
deriving stock (Foldable, Functor, Generic1, Traversable)
deriving anyclass (Declarations1, Diffable, FreeVariables1, Hashable1, Mergeable, Message1, Named1, ToJSONFields1)
deriving anyclass (Declarations1, Diffable, FreeVariables1, Hashable1, Message1, Named1, ToJSONFields1)
instance Eq1 AccessibilityModifier where liftEq = genericLiftEq
instance Ord1 AccessibilityModifier where liftCompare = genericLiftCompare
@ -189,7 +188,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 (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
instance Eq1 Empty where liftEq _ _ _ = True
instance Ord1 Empty where liftCompare _ _ _ = EQ
@ -200,7 +199,7 @@ instance Evaluatable Empty where
-- | Syntax representing a parsing or assignment error.
data Error a = Error { errorCallStack :: ErrorStack, errorExpected :: [String], errorActual :: Maybe String, errorChildren :: [a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Error where liftEq = genericLiftEq
instance Ord1 Error where liftCompare = genericLiftCompare
@ -281,7 +280,7 @@ instance Ord ErrorStack where
data Context a = Context { contextTerms :: NonEmpty a, contextSubject :: a }
deriving (Declarations1, Eq, Foldable, FreeVariables1, Functor, Generic1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Eq, Foldable, FreeVariables1, Functor, Generic1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Diffable Context where
subalgorithmFor blur focus (Context n s) = Context <$> traverse blur n <*> focus s

View File

@ -1,4 +1,5 @@
{-# LANGUAGE DeriveAnyClass, MultiParamTypeClasses #-}
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
module Data.Syntax.Comment where
import Data.Abstract.Evaluatable
@ -9,7 +10,7 @@ import Proto3.Suite.Class
-- | An unnested comment (line or block).
newtype Comment a = Comment { commentContent :: Text }
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
instance Eq1 Comment where liftEq = genericLiftEq
instance Ord1 Comment where liftCompare = genericLiftCompare
@ -25,7 +26,7 @@ instance Evaluatable Comment where
-- | HashBang line (e.g. `#!/usr/bin/env node`)
newtype HashBang a = HashBang { value :: Text }
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
instance Eq1 HashBang where liftEq = genericLiftEq
instance Ord1 HashBang where liftCompare = genericLiftCompare

View File

@ -1,4 +1,5 @@
{-# LANGUAGE DeriveAnyClass, MultiParamTypeClasses, ScopedTypeVariables, UndecidableInstances #-}
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
module Data.Syntax.Declaration where
import qualified Data.Abstract.Environment as Env
@ -10,7 +11,7 @@ import Prologue
import Proto3.Suite.Class
data Function a = Function { functionContext :: ![a], functionName :: !a, functionParameters :: ![a], functionBody :: !a }
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Mergeable, ToJSONFields1, Named1, Message1)
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, ToJSONFields1, Named1, Message1)
instance Diffable Function where
equivalentBySubterm = Just . functionName
@ -38,7 +39,7 @@ instance FreeVariables1 Function where
data Method a = Method { methodContext :: ![a], methodReceiver :: !a, methodName :: !a, methodParameters :: ![a], methodBody :: !a }
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Mergeable, ToJSONFields1, Named1, Message1)
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, ToJSONFields1, Named1, Message1)
instance Eq1 Method where liftEq = genericLiftEq
instance Ord1 Method where liftCompare = genericLiftCompare
@ -66,7 +67,7 @@ instance FreeVariables1 Method where
-- | A method signature in TypeScript or a method spec in Go.
data MethodSignature a = MethodSignature { methodSignatureContext :: ![a], methodSignatureName :: !a, methodSignatureParameters :: ![a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 MethodSignature where liftEq = genericLiftEq
instance Ord1 MethodSignature where liftCompare = genericLiftCompare
@ -77,7 +78,7 @@ instance Evaluatable MethodSignature
newtype RequiredParameter a = RequiredParameter { requiredParameter :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 RequiredParameter where liftEq = genericLiftEq
instance Ord1 RequiredParameter where liftCompare = genericLiftCompare
@ -88,7 +89,7 @@ instance Evaluatable RequiredParameter
newtype OptionalParameter a = OptionalParameter { optionalParameter :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 OptionalParameter where liftEq = genericLiftEq
instance Ord1 OptionalParameter where liftCompare = genericLiftCompare
@ -103,7 +104,7 @@ instance Evaluatable OptionalParameter
-- TODO: It would be really nice to have a more meaningful type contained in here than [a]
-- | A declaration of possibly many variables such as var foo = 5, bar = 6 in JavaScript.
newtype VariableDeclaration a = VariableDeclaration { variableDeclarations :: [a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 VariableDeclaration where liftEq = genericLiftEq
instance Ord1 VariableDeclaration where liftCompare = genericLiftCompare
@ -120,8 +121,9 @@ instance Declarations a => Declarations (VariableDeclaration a) where
-- | A TypeScript/Java style interface declaration to implement.
data InterfaceDeclaration a = InterfaceDeclaration { interfaceDeclarationContext :: ![a], interfaceDeclarationIdentifier :: !a, interfaceDeclarationBody :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
data InterfaceDeclaration a = InterfaceDeclaration { interfaceDeclarationContext :: ![a], interfaceDeclarationIdentifier :: !a, interfaceDeclarationSuperInterfaces :: ![a], interfaceDeclarationBody :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 InterfaceDeclaration where liftEq = genericLiftEq
instance Ord1 InterfaceDeclaration where liftCompare = genericLiftCompare
@ -136,7 +138,7 @@ instance Declarations a => Declarations (InterfaceDeclaration a) where
-- | A public field definition such as a field definition in a JavaScript class.
data PublicFieldDefinition a = PublicFieldDefinition { publicFieldContext :: ![a], publicFieldPropertyName :: !a, publicFieldValue :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 PublicFieldDefinition where liftEq = genericLiftEq
instance Ord1 PublicFieldDefinition where liftCompare = genericLiftCompare
@ -147,7 +149,7 @@ instance Evaluatable PublicFieldDefinition
data Variable a = Variable { variableName :: !a, variableType :: !a, variableValue :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Variable where liftEq = genericLiftEq
instance Ord1 Variable where liftCompare = genericLiftCompare
@ -157,7 +159,7 @@ instance Show1 Variable where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Variable
data Class a = Class { classContext :: ![a], classIdentifier :: !a, classSuperclasses :: ![a], classBody :: !a }
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Mergeable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
instance Declarations a => Declarations (Class a) where
declaredName (Class _ name _ _) = declaredName name
@ -182,7 +184,7 @@ instance Evaluatable Class where
-- | A decorator in Python
data Decorator a = Decorator { decoratorIdentifier :: !a, decoratorParamaters :: ![a], decoratorBody :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Decorator where liftEq = genericLiftEq
instance Ord1 Decorator where liftCompare = genericLiftCompare
@ -196,7 +198,7 @@ instance Evaluatable Decorator
-- | An ADT, i.e. a disjoint sum of products, like 'data' in Haskell, or 'enum' in Rust or Swift.
data Datatype a = Datatype { datatypeContext :: a, datatypeName :: a, datatypeConstructors :: [a], datatypeDeriving :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Data.Syntax.Declaration.Datatype where liftEq = genericLiftEq
instance Ord1 Data.Syntax.Declaration.Datatype where liftCompare = genericLiftCompare
@ -208,7 +210,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 { constructorContext :: [a], constructorName :: a, constructorFields :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Data.Syntax.Declaration.Constructor where liftEq = genericLiftEq
instance Ord1 Data.Syntax.Declaration.Constructor where liftCompare = genericLiftCompare
@ -220,7 +222,7 @@ instance Evaluatable Data.Syntax.Declaration.Constructor
-- | Comprehension (e.g. ((a for b in c if a()) in Python)
data Comprehension a = Comprehension { comprehensionValue :: !a, comprehensionBody :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Comprehension where liftEq = genericLiftEq
instance Ord1 Comprehension where liftCompare = genericLiftCompare
@ -232,7 +234,7 @@ instance Evaluatable Comprehension
-- | A declared type (e.g. `a []int` in Go).
data Type a = Type { typeName :: !a, typeKind :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Type where liftEq = genericLiftEq
instance Ord1 Type where liftCompare = genericLiftCompare
@ -244,7 +246,7 @@ instance Evaluatable Type
-- | Type alias declarations in Javascript/Haskell, etc.
data TypeAlias a = TypeAlias { typeAliasContext :: ![a], typeAliasIdentifier :: !a, typeAliasKind :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 TypeAlias where liftEq = genericLiftEq
instance Ord1 TypeAlias where liftCompare = genericLiftCompare

View File

@ -1,4 +1,5 @@
{-# LANGUAGE DeriveAnyClass, MultiParamTypeClasses, ScopedTypeVariables, UndecidableInstances #-}
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
module Data.Syntax.Directive where
import Data.Abstract.Evaluatable
@ -12,7 +13,7 @@ import Proto3.Suite.Class
-- A file directive like the Ruby constant `__FILE__`.
data File a = File
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 File where liftEq = genericLiftEq
instance Ord1 File where liftCompare = genericLiftCompare
@ -24,7 +25,7 @@ instance Evaluatable File where
-- A line directive like the Ruby constant `__LINE__`.
data Line a = Line
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Line where liftEq = genericLiftEq
instance Ord1 Line where liftCompare = genericLiftCompare

View File

@ -1,4 +1,5 @@
{-# LANGUAGE DeriveAnyClass, MultiParamTypeClasses, ScopedTypeVariables, UndecidableInstances, DuplicateRecordFields #-}
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
module Data.Syntax.Expression where
import Data.Abstract.Evaluatable hiding (Member)
@ -11,7 +12,7 @@ import Proto3.Suite.Class
-- | Typical prefix function application, like `f(x)` in many languages, or `f x` in Haskell.
data Call a = Call { callContext :: ![a], callFunction :: !a, callParams :: ![a], callBlock :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Call where liftEq = genericLiftEq
instance Ord1 Call where liftCompare = genericLiftCompare
@ -23,7 +24,7 @@ instance Evaluatable Call where
Rval <$> call op (map subtermAddress callParams)
data LessThan a = LessThan { lhs :: a, rhs :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 LessThan where liftEq = genericLiftEq
instance Ord1 LessThan where liftCompare = genericLiftCompare
@ -35,7 +36,7 @@ instance Evaluatable LessThan where
(LessThan a b) -> liftComparison (Concrete (<)) a b
data LessThanEqual a = LessThanEqual { lhs :: a, rhs :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 LessThanEqual where liftEq = genericLiftEq
instance Ord1 LessThanEqual where liftCompare = genericLiftCompare
@ -47,7 +48,7 @@ instance Evaluatable LessThanEqual where
(LessThanEqual a b) -> liftComparison (Concrete (<=)) a b
data GreaterThan a = GreaterThan { lhs :: a, rhs :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 GreaterThan where liftEq = genericLiftEq
instance Ord1 GreaterThan where liftCompare = genericLiftCompare
@ -59,7 +60,7 @@ instance Evaluatable GreaterThan where
(GreaterThan a b) -> liftComparison (Concrete (>)) a b
data GreaterThanEqual a = GreaterThanEqual { lhs :: a, rhs :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 GreaterThanEqual where liftEq = genericLiftEq
instance Ord1 GreaterThanEqual where liftCompare = genericLiftCompare
@ -71,7 +72,7 @@ instance Evaluatable GreaterThanEqual where
(GreaterThanEqual a b) -> liftComparison (Concrete (>=)) a b
data Equal a = Equal { lhs :: a, rhs :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Equal where liftEq = genericLiftEq
instance Ord1 Equal where liftCompare = genericLiftCompare
@ -85,7 +86,7 @@ instance Evaluatable Equal where
(Equal a b) -> liftComparison (Concrete (==)) a b
data StrictEqual a = StrictEqual { lhs :: a, rhs :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 StrictEqual where liftEq = genericLiftEq
instance Ord1 StrictEqual where liftCompare = genericLiftCompare
@ -99,7 +100,7 @@ instance Evaluatable StrictEqual where
(StrictEqual a b) -> liftComparison (Concrete (==)) a b
data Comparison a = Comparison { lhs :: a, rhs :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Comparison where liftEq = genericLiftEq
instance Ord1 Comparison where liftCompare = genericLiftCompare
@ -111,7 +112,7 @@ instance Evaluatable Comparison where
(Comparison a b) -> liftComparison (Concrete (==)) a b
data Plus a = Plus { lhs :: a, rhs :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Plus where liftEq = genericLiftEq
instance Ord1 Plus where liftCompare = genericLiftCompare
@ -122,7 +123,7 @@ instance Evaluatable Plus where
go (Plus a b) = liftNumeric2 add a b where add = liftReal (+)
data Minus a = Minus { lhs :: a, rhs :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Minus where liftEq = genericLiftEq
instance Ord1 Minus where liftCompare = genericLiftCompare
@ -133,7 +134,7 @@ instance Evaluatable Minus where
go (Minus a b) = liftNumeric2 sub a b where sub = liftReal (-)
data Times a = Times { lhs :: a, rhs :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Times where liftEq = genericLiftEq
instance Ord1 Times where liftCompare = genericLiftCompare
@ -144,7 +145,7 @@ instance Evaluatable Times where
go (Times a b) = liftNumeric2 mul a b where mul = liftReal (*)
data DividedBy a = DividedBy { lhs :: a, rhs :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 DividedBy where liftEq = genericLiftEq
instance Ord1 DividedBy where liftCompare = genericLiftCompare
@ -155,7 +156,7 @@ instance Evaluatable DividedBy where
go (DividedBy a b) = liftNumeric2 div' a b where div' = liftIntegralFrac div (/)
data Modulo a = Modulo { lhs :: a, rhs :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Modulo where liftEq = genericLiftEq
instance Ord1 Modulo where liftCompare = genericLiftCompare
@ -166,7 +167,7 @@ instance Evaluatable Modulo where
go (Modulo a b) = liftNumeric2 mod'' a b where mod'' = liftIntegralFrac mod mod'
data Power a = Power { lhs :: a, rhs :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Power where liftEq = genericLiftEq
instance Ord1 Power where liftCompare = genericLiftCompare
@ -176,8 +177,8 @@ instance Evaluatable Power where
eval t = rvalBox =<< (traverse subtermValue t >>= go) where
go (Power a b) = liftNumeric2 liftedExponent a b
newtype Negate a = Negate { term :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
newtype Negate a = Negate { value :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Negate where liftEq = genericLiftEq
instance Ord1 Negate where liftCompare = genericLiftCompare
@ -188,7 +189,7 @@ instance Evaluatable Negate where
go (Negate a) = liftNumeric negate a
data FloorDivision a = FloorDivision { lhs :: a, rhs :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 FloorDivision where liftEq = genericLiftEq
instance Ord1 FloorDivision where liftCompare = genericLiftCompare
@ -200,7 +201,7 @@ instance Evaluatable FloorDivision where
-- | Regex matching operators (Ruby's =~ and ~!)
data Matches a = Matches { lhs :: a, rhs :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Matches where liftEq = genericLiftEq
instance Ord1 Matches where liftCompare = genericLiftCompare
@ -208,7 +209,7 @@ instance Show1 Matches where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Matches
data NotMatches a = NotMatches { lhs :: a, rhs :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 NotMatches where liftEq = genericLiftEq
instance Ord1 NotMatches where liftCompare = genericLiftCompare
@ -216,20 +217,17 @@ instance Show1 NotMatches where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable NotMatches
data Or a = Or { lhs :: a, rhs :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Or where liftEq = genericLiftEq
instance Ord1 Or where liftCompare = genericLiftCompare
instance Show1 Or where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Or where
eval t = rvalBox =<< go (fmap subtermValue t) where
go (Or a b) = do
cond <- a
ifthenelse cond (pure cond) b
eval (Or a b) = disjunction (subtermValue a) (subtermValue b) >>= rvalBox
data And a = And { lhs :: a, rhs :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 And where liftEq = genericLiftEq
instance Ord1 And where liftCompare = genericLiftCompare
@ -240,8 +238,8 @@ instance Evaluatable And where
cond <- a
ifthenelse cond b (pure cond)
newtype Not a = Not { term :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
newtype Not a = Not { value :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Not where liftEq = genericLiftEq
instance Ord1 Not where liftCompare = genericLiftCompare
@ -252,7 +250,7 @@ instance Evaluatable Not where
go (Not a) = a >>= fmap (boolean . not) . asBool
data XOr a = XOr { lhs :: a, rhs :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 XOr where liftEq = genericLiftEq
instance Ord1 XOr where liftCompare = genericLiftCompare
@ -265,7 +263,7 @@ instance Evaluatable XOr where
-- | Javascript delete operator
newtype Delete a = Delete { value :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Delete where liftEq = genericLiftEq
instance Ord1 Delete where liftCompare = genericLiftCompare
@ -277,7 +275,7 @@ instance Evaluatable Delete
-- | A sequence expression such as Javascript or C's comma operator.
data SequenceExpression a = SequenceExpression { firstExpression :: !a, secondExpression :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 SequenceExpression where liftEq = genericLiftEq
instance Ord1 SequenceExpression where liftCompare = genericLiftCompare
@ -289,7 +287,7 @@ instance Evaluatable SequenceExpression
-- | Javascript void operator
newtype Void a = Void { value :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Void where liftEq = genericLiftEq
instance Ord1 Void where liftCompare = genericLiftCompare
@ -301,7 +299,7 @@ instance Evaluatable Void
-- | Javascript typeof operator
newtype Typeof a = Typeof { value :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Typeof where liftEq = genericLiftEq
instance Ord1 Typeof where liftCompare = genericLiftCompare
@ -312,7 +310,7 @@ instance Evaluatable Typeof
-- | Bitwise operators.
data BOr a = BOr { left :: a, right :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 BOr where liftEq = genericLiftEq
instance Ord1 BOr where liftCompare = genericLiftCompare
@ -320,7 +318,7 @@ instance Show1 BOr where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable BOr where
data BAnd a = BAnd { left :: a, right :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 BAnd where liftEq = genericLiftEq
instance Ord1 BAnd where liftCompare = genericLiftCompare
@ -328,7 +326,7 @@ instance Show1 BAnd where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable BAnd where
data BXOr a = BXOr { left :: a, right :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 BXOr where liftEq = genericLiftEq
instance Ord1 BXOr where liftCompare = genericLiftCompare
@ -336,7 +334,7 @@ instance Show1 BXOr where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable BXOr where
data LShift a = LShift { left :: a, right :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 LShift where liftEq = genericLiftEq
instance Ord1 LShift where liftCompare = genericLiftCompare
@ -344,7 +342,7 @@ instance Show1 LShift where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable LShift where
data RShift a = RShift { left :: a, right :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 RShift where liftEq = genericLiftEq
instance Ord1 RShift where liftCompare = genericLiftCompare
@ -352,7 +350,7 @@ instance Show1 RShift where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable RShift where
data UnsignedRShift a = UnsignedRShift { left :: a, right :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 UnsignedRShift where liftEq = genericLiftEq
instance Ord1 UnsignedRShift where liftCompare = genericLiftCompare
@ -360,7 +358,7 @@ instance Show1 UnsignedRShift where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable UnsignedRShift where
newtype Complement a = Complement { value :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Complement where liftEq = genericLiftEq
instance Ord1 Complement where liftCompare = genericLiftCompare
@ -370,7 +368,7 @@ instance Evaluatable Complement where
-- | Member Access (e.g. a.b)
data MemberAccess a = MemberAccess { lhs :: a, rhs :: Name }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 MemberAccess where liftEq = genericLiftEq
instance Ord1 MemberAccess where liftCompare = genericLiftCompare
@ -383,7 +381,7 @@ instance Evaluatable MemberAccess where
-- | Subscript (e.g a[1])
data Subscript a = Subscript { lhs :: a, rhs :: [a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Subscript where liftEq = genericLiftEq
instance Ord1 Subscript where liftCompare = genericLiftCompare
@ -396,7 +394,7 @@ instance Evaluatable Subscript where
eval (Subscript _ _) = rvalBox =<< throwResumable (Unspecialized "Eval unspecialized for subscript with slices")
data Member a = Member { lhs :: a, rhs :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Member where liftEq = genericLiftEq
instance Ord1 Member where liftCompare = genericLiftCompare
@ -406,7 +404,7 @@ instance Evaluatable Member where
-- | Enumeration (e.g. a[1:10:1] in Python (start at index 1, stop at index 10, step 1 element from start to stop))
data Enumeration a = Enumeration { enumerationStart :: !a, enumerationEnd :: !a, enumerationStep :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Enumeration where liftEq = genericLiftEq
instance Ord1 Enumeration where liftCompare = genericLiftCompare
@ -418,7 +416,7 @@ instance Evaluatable Enumeration
-- | InstanceOf (e.g. a instanceof b in JavaScript
data InstanceOf a = InstanceOf { instanceOfSubject :: !a, instanceOfObject :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 InstanceOf where liftEq = genericLiftEq
instance Ord1 InstanceOf where liftCompare = genericLiftCompare
@ -430,7 +428,7 @@ instance Evaluatable InstanceOf
-- | ScopeResolution (e.g. import a.b in Python or a::b in C++)
newtype ScopeResolution a = ScopeResolution { scopes :: NonEmpty a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Hashable1 ScopeResolution where liftHashWithSalt = foldl
instance Eq1 ScopeResolution where liftEq = genericLiftEq
@ -444,7 +442,7 @@ instance Evaluatable ScopeResolution where
-- | A non-null expression such as Typescript or Swift's ! expression.
newtype NonNullExpression a = NonNullExpression { nonNullExpression :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 NonNullExpression where liftEq = genericLiftEq
instance Ord1 NonNullExpression where liftCompare = genericLiftCompare
@ -456,7 +454,7 @@ instance Evaluatable NonNullExpression
-- | An await expression in Javascript or C#.
newtype Await a = Await { awaitSubject :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Await where liftEq = genericLiftEq
instance Ord1 Await where liftCompare = genericLiftCompare
@ -468,7 +466,7 @@ instance Evaluatable Await
-- | An object constructor call in Javascript, Java, etc.
newtype New a = New { newSubject :: [a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 New where liftEq = genericLiftEq
instance Ord1 New where liftCompare = genericLiftCompare
@ -479,7 +477,7 @@ instance Evaluatable New
-- | A cast expression to a specified type.
data Cast a = Cast { castSubject :: !a, castType :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Cast where liftEq = genericLiftEq
instance Ord1 Cast where liftCompare = genericLiftCompare
@ -489,7 +487,7 @@ instance Show1 Cast where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Cast
data Super a = Super
deriving (Diffable, Eq, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1)
deriving (Diffable, Eq, Foldable, Functor, Generic1, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1)
instance Eq1 Super where liftEq = genericLiftEq
instance Ord1 Super where liftCompare = genericLiftCompare
@ -497,7 +495,7 @@ instance Show1 Super where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Super
data This a = This
deriving (Diffable, Eq, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1)
deriving (Diffable, Eq, Foldable, Functor, Generic1, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1)
instance Eq1 This where liftEq = genericLiftEq
instance Ord1 This where liftCompare = genericLiftCompare

View File

@ -1,4 +1,5 @@
{-# LANGUAGE DeriveAnyClass, ViewPatterns, ScopedTypeVariables, DuplicateRecordFields #-}
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
module Data.Syntax.Literal where
import Data.Abstract.Evaluatable
@ -15,7 +16,7 @@ import Text.Read (readMaybe)
-- Boolean
newtype Boolean a = Boolean { booleanContent :: Bool }
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
true :: Boolean a
true = Boolean True
@ -34,7 +35,7 @@ instance Evaluatable Boolean where
-- | A literal integer of unspecified width. No particular base is implied.
newtype Integer a = Integer { integerContent :: Text }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Data.Syntax.Literal.Integer where liftEq = genericLiftEq
instance Ord1 Data.Syntax.Literal.Integer where liftCompare = genericLiftCompare
@ -48,7 +49,7 @@ instance Evaluatable Data.Syntax.Literal.Integer where
-- | A literal float of unspecified width.
newtype Float a = Float { floatContent :: Text }
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
instance Eq1 Data.Syntax.Literal.Float where liftEq = genericLiftEq
instance Ord1 Data.Syntax.Literal.Float where liftCompare = genericLiftCompare
@ -60,7 +61,7 @@ instance Evaluatable Data.Syntax.Literal.Float where
-- Rational literals e.g. `2/3r`
newtype Rational a = Rational { value :: Text }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Data.Syntax.Literal.Rational where liftEq = genericLiftEq
instance Ord1 Data.Syntax.Literal.Rational where liftCompare = genericLiftCompare
@ -75,7 +76,7 @@ instance Evaluatable Data.Syntax.Literal.Rational where
-- Complex literals e.g. `3 + 2i`
newtype Complex a = Complex { value :: Text }
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
instance Eq1 Data.Syntax.Literal.Complex where liftEq = genericLiftEq
instance Ord1 Data.Syntax.Literal.Complex where liftCompare = genericLiftCompare
@ -87,7 +88,7 @@ instance Evaluatable Complex
-- Strings, symbols
newtype String a = String { stringElements :: [a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Data.Syntax.Literal.String where liftEq = genericLiftEq
instance Ord1 Data.Syntax.Literal.String where liftCompare = genericLiftCompare
@ -99,7 +100,7 @@ instance Show1 Data.Syntax.Literal.String where liftShowsPrec = genericLiftShows
instance Evaluatable Data.Syntax.Literal.String
newtype Character a = Character { characterContent :: Text }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Data.Syntax.Literal.Character where liftEq = genericLiftEq
instance Ord1 Data.Syntax.Literal.Character where liftCompare = genericLiftCompare
@ -109,7 +110,7 @@ instance Evaluatable Data.Syntax.Literal.Character
-- | An interpolation element within a string literal.
newtype InterpolationElement a = InterpolationElement { interpolationBody :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 InterpolationElement where liftEq = genericLiftEq
instance Ord1 InterpolationElement where liftCompare = genericLiftCompare
@ -120,7 +121,7 @@ instance Evaluatable InterpolationElement
-- | A sequence of textual contents within a string literal.
newtype TextElement a = TextElement { textElementContent :: Text }
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
instance Eq1 TextElement where liftEq = genericLiftEq
instance Ord1 TextElement where liftCompare = genericLiftCompare
@ -130,7 +131,7 @@ instance Evaluatable TextElement where
eval (TextElement x) = rvalBox (string x)
data Null a = Null
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
instance Eq1 Null where liftEq = genericLiftEq
instance Ord1 Null where liftCompare = genericLiftCompare
@ -139,7 +140,7 @@ instance Show1 Null where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Null where eval _ = rvalBox null
newtype Symbol a = Symbol { symbolContent :: Text }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Symbol where liftEq = genericLiftEq
instance Ord1 Symbol where liftCompare = genericLiftCompare
@ -149,7 +150,7 @@ instance Evaluatable Symbol where
eval (Symbol s) = rvalBox (symbol s)
newtype Regex a = Regex { regexContent :: Text }
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
instance Eq1 Regex where liftEq = genericLiftEq
instance Ord1 Regex where liftCompare = genericLiftCompare
@ -163,7 +164,7 @@ instance Evaluatable Regex
-- Collections
newtype Array a = Array { arrayElements :: [a] }
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
instance Eq1 Array where liftEq = genericLiftEq
instance Ord1 Array where liftCompare = genericLiftCompare
@ -173,7 +174,7 @@ instance Evaluatable Array where
eval (Array a) = rvalBox =<< array =<< traverse subtermAddress a
newtype Hash a = Hash { hashElements :: [a] }
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
instance Eq1 Hash where liftEq = genericLiftEq
instance Ord1 Hash where liftCompare = genericLiftCompare
@ -183,7 +184,7 @@ instance Evaluatable Hash where
eval t = rvalBox =<< (hash <$> traverse (subtermValue >=> asPair) (hashElements t))
data KeyValue a = KeyValue { key :: !a, value :: !a }
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
instance Eq1 KeyValue where liftEq = genericLiftEq
instance Ord1 KeyValue where liftCompare = genericLiftCompare
@ -194,7 +195,7 @@ instance Evaluatable KeyValue where
rvalBox =<< (kvPair <$> key <*> value)
newtype Tuple a = Tuple { tupleContents :: [a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Tuple where liftEq = genericLiftEq
instance Ord1 Tuple where liftCompare = genericLiftCompare
@ -204,7 +205,7 @@ instance Evaluatable Tuple where
eval (Tuple cs) = rvalBox =<< tuple =<< traverse subtermAddress cs
newtype Set a = Set { setElements :: [a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Set where liftEq = genericLiftEq
instance Ord1 Set where liftCompare = genericLiftCompare
@ -218,7 +219,7 @@ instance Evaluatable Set
-- | A declared pointer (e.g. var pointer *int in Go)
newtype Pointer a = Pointer a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Pointer where liftEq = genericLiftEq
instance Ord1 Pointer where liftCompare = genericLiftCompare
@ -230,7 +231,7 @@ instance Evaluatable Pointer
-- | A reference to a pointer's address (e.g. &pointer in Go)
newtype Reference a = Reference a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Reference where liftEq = genericLiftEq
instance Ord1 Reference where liftCompare = genericLiftCompare

View File

@ -1,4 +1,5 @@
{-# LANGUAGE DeriveAnyClass, ScopedTypeVariables, UndecidableInstances, ViewPatterns, DuplicateRecordFields #-}
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
module Data.Syntax.Statement where
import Data.Abstract.Evaluatable
@ -17,7 +18,7 @@ import Proto3.Suite.Class
-- 2. Each statement can affect the environment of later statements (e.g. by 'modify'-ing the environment); and
-- 3. Only the last statements return value is returned.
newtype Statements a = Statements { statements :: [a] }
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
instance Eq1 Statements where liftEq = genericLiftEq
instance Ord1 Statements where liftCompare = genericLiftCompare
@ -29,7 +30,7 @@ instance Evaluatable Statements where
-- | Conditional. This must have an else block, which can be filled with some default value when omitted in the source, e.g. 'pure ()' for C-style if-without-else or 'pure Nothing' for Ruby-style, in both cases assuming some appropriate Applicative context into which the If will be lifted.
data If a = If { ifCondition :: !a, ifThenBody :: !a, ifElseBody :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 If where liftEq = genericLiftEq
instance Ord1 If where liftCompare = genericLiftCompare
@ -42,7 +43,7 @@ instance Evaluatable If where
-- | Else statement. The else condition is any term, that upon successful completion, continues evaluation to the elseBody, e.g. `for ... else` in Python.
data Else a = Else { elseCondition :: !a, elseBody :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Else where liftEq = genericLiftEq
instance Ord1 Else where liftCompare = genericLiftCompare
@ -55,7 +56,7 @@ instance Evaluatable Else
-- | Goto statement (e.g. `goto a` in Go).
newtype Goto a = Goto { gotoLocation :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Goto where liftEq = genericLiftEq
instance Ord1 Goto where liftCompare = genericLiftCompare
@ -67,7 +68,7 @@ instance Evaluatable Goto
-- | A pattern-matching or computed jump control-flow statement, like 'switch' in C or JavaScript, or 'case' in Ruby or Haskell.
data Match a = Match { matchSubject :: !a, matchPatterns :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Match where liftEq = genericLiftEq
instance Ord1 Match where liftCompare = genericLiftCompare
@ -79,7 +80,7 @@ instance Evaluatable Match
-- | A pattern in a pattern-matching or computed jump control-flow statement, like 'case' in C or JavaScript, 'when' in Ruby, or the left-hand side of '->' in the body of Haskell 'case' expressions.
data Pattern a = Pattern { value :: !a, patternBody :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Pattern where liftEq = genericLiftEq
instance Ord1 Pattern where liftCompare = genericLiftCompare
@ -91,7 +92,7 @@ instance Evaluatable Pattern
-- | A let statement or local binding, like 'a as b' or 'let a = b'.
data Let a = Let { letVariable :: !a, letValue :: !a, letBody :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Let where liftEq = genericLiftEq
instance Ord1 Let where liftCompare = genericLiftCompare
@ -108,7 +109,7 @@ instance Evaluatable Let where
-- | Assignment to a variable or other lvalue.
data Assignment a = Assignment { assignmentContext :: ![a], assignmentTarget :: !a, assignmentValue :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Assignment where liftEq = genericLiftEq
instance Ord1 Assignment where liftCompare = genericLiftCompare
@ -135,7 +136,7 @@ instance Evaluatable Assignment where
-- | Post increment operator (e.g. 1++ in Go, or i++ in C).
newtype PostIncrement a = PostIncrement a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 PostIncrement where liftEq = genericLiftEq
instance Ord1 PostIncrement where liftCompare = genericLiftCompare
@ -147,7 +148,7 @@ instance Evaluatable PostIncrement
-- | Post decrement operator (e.g. 1-- in Go, or i-- in C).
newtype PostDecrement a = PostDecrement a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 PostDecrement where liftEq = genericLiftEq
instance Ord1 PostDecrement where liftCompare = genericLiftCompare
@ -158,7 +159,7 @@ instance Evaluatable PostDecrement
-- | Pre increment operator (e.g. ++1 in C or Java).
newtype PreIncrement a = PreIncrement a
deriving (Diffable, Eq, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1)
deriving (Diffable, Eq, Foldable, Functor, Generic1, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1)
instance Eq1 PreIncrement where liftEq = genericLiftEq
instance Ord1 PreIncrement where liftCompare = genericLiftCompare
@ -170,7 +171,7 @@ instance Evaluatable PreIncrement
-- | Pre decrement operator (e.g. --1 in C or Java).
newtype PreDecrement a = PreDecrement a
deriving (Diffable, Eq, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1)
deriving (Diffable, Eq, Foldable, Functor, Generic1, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1)
instance Eq1 PreDecrement where liftEq = genericLiftEq
instance Ord1 PreDecrement where liftCompare = genericLiftCompare
@ -182,8 +183,8 @@ instance Evaluatable PreDecrement
-- Returns
newtype Return a = Return { term :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
newtype Return a = Return { value :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Return where liftEq = genericLiftEq
instance Ord1 Return where liftCompare = genericLiftCompare
@ -192,8 +193,8 @@ instance Show1 Return where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Return where
eval (Return x) = Rval <$> (subtermAddress x >>= earlyReturn)
newtype Yield a = Yield { term :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
newtype Yield a = Yield { value :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Yield where liftEq = genericLiftEq
instance Ord1 Yield where liftCompare = genericLiftCompare
@ -203,8 +204,8 @@ instance Show1 Yield where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Yield
newtype Break a = Break { term :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
newtype Break a = Break { value :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Break where liftEq = genericLiftEq
instance Ord1 Break where liftCompare = genericLiftCompare
@ -213,8 +214,8 @@ instance Show1 Break where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Break where
eval (Break x) = Rval <$> (subtermAddress x >>= throwBreak)
newtype Continue a = Continue { term :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
newtype Continue a = Continue { value :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Continue where liftEq = genericLiftEq
instance Ord1 Continue where liftCompare = genericLiftCompare
@ -223,8 +224,8 @@ instance Show1 Continue where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Continue where
eval (Continue x) = Rval <$> (subtermAddress x >>= throwContinue)
newtype Retry a = Retry { term :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
newtype Retry a = Retry { value :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Retry where liftEq = genericLiftEq
instance Ord1 Retry where liftCompare = genericLiftCompare
@ -235,7 +236,7 @@ instance Evaluatable Retry
newtype NoOp a = NoOp { value :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 NoOp where liftEq = genericLiftEq
instance Ord1 NoOp where liftCompare = genericLiftCompare
@ -247,7 +248,7 @@ instance Evaluatable NoOp where
-- Loops
data For a = For { forBefore :: !a, forCondition :: !a, forStep :: !a, forBody :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 For where liftEq = genericLiftEq
instance Ord1 For where liftCompare = genericLiftCompare
@ -258,7 +259,7 @@ instance Evaluatable For where
data ForEach a = ForEach { forEachBinding :: !a, forEachSubject :: !a, forEachBody :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 ForEach where liftEq = genericLiftEq
instance Ord1 ForEach where liftCompare = genericLiftCompare
@ -269,7 +270,7 @@ instance Evaluatable ForEach
data While a = While { whileCondition :: !a, whileBody :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 While where liftEq = genericLiftEq
instance Ord1 While where liftCompare = genericLiftCompare
@ -279,7 +280,7 @@ instance Evaluatable While where
eval While{..} = rvalBox =<< while (subtermValue whileCondition) (subtermValue whileBody)
data DoWhile a = DoWhile { doWhileCondition :: !a, doWhileBody :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 DoWhile where liftEq = genericLiftEq
instance Ord1 DoWhile where liftCompare = genericLiftCompare
@ -291,7 +292,7 @@ instance Evaluatable DoWhile where
-- Exception handling
newtype Throw a = Throw { value :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Throw where liftEq = genericLiftEq
instance Ord1 Throw where liftCompare = genericLiftCompare
@ -302,7 +303,7 @@ instance Evaluatable Throw
data Try a = Try { tryBody :: !a, tryCatch :: ![a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Try where liftEq = genericLiftEq
instance Ord1 Try where liftCompare = genericLiftCompare
@ -313,7 +314,7 @@ instance Evaluatable Try
data Catch a = Catch { catchException :: !a, catchBody :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Catch where liftEq = genericLiftEq
instance Ord1 Catch where liftCompare = genericLiftCompare
@ -323,8 +324,8 @@ instance Show1 Catch where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Catch
newtype Finally a = Finally { term :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
newtype Finally a = Finally { value :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Finally where liftEq = genericLiftEq
instance Ord1 Finally where liftCompare = genericLiftCompare
@ -338,7 +339,7 @@ instance Evaluatable Finally
-- | ScopeEntry (e.g. `BEGIN {}` block in Ruby or Perl).
newtype ScopeEntry a = ScopeEntry { terms :: [a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 ScopeEntry where liftEq = genericLiftEq
instance Ord1 ScopeEntry where liftCompare = genericLiftCompare
@ -350,7 +351,7 @@ instance Evaluatable ScopeEntry
-- | ScopeExit (e.g. `END {}` block in Ruby or Perl).
newtype ScopeExit a = ScopeExit { terms :: [a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 ScopeExit where liftEq = genericLiftEq
instance Ord1 ScopeExit where liftCompare = genericLiftCompare

View File

@ -1,4 +1,5 @@
{-# LANGUAGE DataKinds, DeriveAnyClass, DeriveGeneric, MultiParamTypeClasses, UndecidableInstances #-}
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
module Data.Syntax.Type where
import Data.Abstract.Evaluatable
@ -9,7 +10,7 @@ import Prologue hiding (Map)
import Proto3.Suite.Class
data Array a = Array { arraySize :: !(Maybe a), arrayElementType :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Array where liftEq = genericLiftEq
instance Ord1 Array where liftCompare = genericLiftCompare
@ -21,7 +22,7 @@ instance Evaluatable Array
-- TODO: What about type variables? re: FreeVariables1
data Annotation a = Annotation { annotationSubject :: !a, annotationType :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Annotation where liftEq = genericLiftEq
instance Ord1 Annotation where liftCompare = genericLiftCompare
@ -33,7 +34,7 @@ instance Evaluatable Annotation where
data Function a = Function { functionParameters :: ![a], functionReturn :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Function where liftEq = genericLiftEq
instance Ord1 Function where liftCompare = genericLiftCompare
@ -44,7 +45,7 @@ instance Evaluatable Function
newtype Interface a = Interface [a]
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Interface where liftEq = genericLiftEq
instance Ord1 Interface where liftCompare = genericLiftCompare
@ -55,7 +56,7 @@ instance Evaluatable Interface
data Map a = Map { mapKeyType :: !a, mapElementType :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Map where liftEq = genericLiftEq
instance Ord1 Map where liftCompare = genericLiftCompare
@ -66,7 +67,7 @@ instance Evaluatable Map
newtype Parenthesized a = Parenthesized a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Parenthesized where liftEq = genericLiftEq
instance Ord1 Parenthesized where liftCompare = genericLiftCompare
@ -77,7 +78,7 @@ instance Evaluatable Parenthesized
newtype Pointer a = Pointer a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Pointer where liftEq = genericLiftEq
instance Ord1 Pointer where liftCompare = genericLiftCompare
@ -88,7 +89,7 @@ instance Evaluatable Pointer
newtype Product a = Product [a]
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Product where liftEq = genericLiftEq
instance Ord1 Product where liftCompare = genericLiftCompare
@ -99,7 +100,7 @@ instance Evaluatable Product
data Readonly a = Readonly
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Readonly where liftEq = genericLiftEq
instance Ord1 Readonly where liftCompare = genericLiftCompare
@ -110,7 +111,7 @@ instance Evaluatable Readonly
newtype Slice a = Slice { value :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Slice where liftEq = genericLiftEq
instance Ord1 Slice where liftCompare = genericLiftCompare
@ -121,7 +122,7 @@ instance Evaluatable Slice
newtype TypeParameters a = TypeParameters { terms :: [a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 TypeParameters where liftEq = genericLiftEq
instance Ord1 TypeParameters where liftCompare = genericLiftCompare
@ -132,7 +133,7 @@ instance Evaluatable TypeParameters
-- data instead of newtype because no payload
data Void a = Void
deriving (Diffable, Eq, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1)
deriving (Diffable, Eq, Foldable, Functor, Generic1, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1)
instance Eq1 Void where liftEq = genericLiftEq
instance Ord1 Void where liftCompare = genericLiftCompare
@ -143,7 +144,7 @@ instance Evaluatable Void
-- data instead of newtype because no payload
data Int a = Int
deriving (Diffable, Eq, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1)
deriving (Diffable, Eq, Foldable, Functor, Generic1, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1)
instance Eq1 Int where liftEq = genericLiftEq
instance Ord1 Int where liftCompare = genericLiftCompare
@ -153,7 +154,7 @@ instance Show1 Int where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Int
data Float a = Float
deriving (Diffable, Eq, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1)
deriving (Diffable, Eq, Foldable, Functor, Generic1, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1)
instance Eq1 Float where liftEq = genericLiftEq
instance Ord1 Float where liftCompare = genericLiftCompare
@ -163,7 +164,7 @@ instance Show1 Float where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Float
data Double a = Double
deriving (Diffable, Eq, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1)
deriving (Diffable, Eq, Foldable, Functor, Generic1, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1)
instance Eq1 Double where liftEq = genericLiftEq
instance Ord1 Double where liftCompare = genericLiftCompare
@ -173,7 +174,7 @@ instance Show1 Double where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Double
data Bool a = Bool
deriving (Diffable, Eq, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1)
deriving (Diffable, Eq, Foldable, Functor, Generic1, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1)
instance Eq1 Bool where liftEq = genericLiftEq
instance Ord1 Bool where liftCompare = genericLiftCompare

View File

@ -1,5 +1,18 @@
{-# LANGUAGE DefaultSignatures, GADTs, TypeOperators, UndecidableInstances #-}
module Diffing.Algorithm where
module Diffing.Algorithm
( AlgorithmF (..)
, Algorithm
, Diffable (..)
, Equivalence (..)
, diff
, diffThese
, diffMaybe
, linearly
, byReplacing
, comparableTerms
, equivalentTerms
, algorithmForTerms
) where
import Control.Monad.Free.Freer
import Data.Diff

View File

@ -1,4 +1,5 @@
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
module Language.Go.Grammar where
import Language.Haskell.TH

View File

@ -1,4 +1,5 @@
{-# LANGUAGE DeriveAnyClass #-}
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
module Language.Go.Syntax where
import Data.Abstract.Evaluatable
@ -55,7 +56,7 @@ resolveGoImport (ImportPath path NonRelative) = do
--
-- If the list of symbols is empty copy everything to the calling environment.
data Import a = Import { importFrom :: ImportPath, importWildcardToken :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Import where liftEq = genericLiftEq
instance Ord1 Import where liftCompare = genericLiftCompare
@ -75,7 +76,7 @@ instance Evaluatable Import where
--
-- If the list of symbols is empty copy and qualify everything to the calling environment.
data QualifiedImport a = QualifiedImport { qualifiedImportFrom :: !ImportPath, qualifiedImportAlias :: !a}
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 QualifiedImport where liftEq = genericLiftEq
instance Ord1 QualifiedImport where liftCompare = genericLiftCompare
@ -95,7 +96,7 @@ instance Evaluatable QualifiedImport where
-- | Side effect only imports (no symbols made available to the calling environment).
data SideEffectImport a = SideEffectImport { sideEffectImportFrom :: !ImportPath, sideEffectImportToken :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 SideEffectImport where liftEq = genericLiftEq
instance Ord1 SideEffectImport where liftCompare = genericLiftCompare
@ -110,7 +111,7 @@ instance Evaluatable SideEffectImport where
-- A composite literal in Go
data Composite a = Composite { compositeType :: !a, compositeElement :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Composite where liftEq = genericLiftEq
instance Ord1 Composite where liftCompare = genericLiftCompare
@ -121,7 +122,7 @@ instance Evaluatable Composite
-- | A default pattern in a Go select or switch statement (e.g. `switch { default: s() }`).
newtype DefaultPattern a = DefaultPattern { defaultPatternBody :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 DefaultPattern where liftEq = genericLiftEq
instance Ord1 DefaultPattern where liftCompare = genericLiftCompare
@ -132,7 +133,7 @@ instance Evaluatable DefaultPattern
-- | A defer statement in Go (e.g. `defer x()`).
newtype Defer a = Defer { deferBody :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Defer where liftEq = genericLiftEq
instance Ord1 Defer where liftCompare = genericLiftCompare
@ -143,7 +144,7 @@ instance Evaluatable Defer
-- | A go statement (i.e. go routine) in Go (e.g. `go x()`).
newtype Go a = Go { goBody :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Go where liftEq = genericLiftEq
instance Ord1 Go where liftCompare = genericLiftCompare
@ -154,7 +155,7 @@ instance Evaluatable Go
-- | A label statement in Go (e.g. `label:continue`).
data Label a = Label { _labelName :: !a, labelStatement :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Label where liftEq = genericLiftEq
instance Ord1 Label where liftCompare = genericLiftCompare
@ -165,7 +166,7 @@ instance Evaluatable Label
-- | A rune literal in Go (e.g. `'⌘'`).
newtype Rune a = Rune { _runeLiteral :: Text }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
-- TODO: Implement Eval instance for Rune
instance Evaluatable Rune
@ -176,7 +177,7 @@ instance Show1 Rune where liftShowsPrec = genericLiftShowsPrec
-- | A select statement in Go (e.g. `select { case x := <-c: x() }` where each case is a send or receive operation on channels).
newtype Select a = Select { selectCases :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
-- TODO: Implement Eval instance for Select
instance Evaluatable Select
@ -187,7 +188,7 @@ instance Show1 Select where liftShowsPrec = genericLiftShowsPrec
-- | A send statement in Go (e.g. `channel <- value`).
data Send a = Send { sendReceiver :: !a, sendValue :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Send where liftEq = genericLiftEq
instance Ord1 Send where liftCompare = genericLiftCompare
@ -198,7 +199,7 @@ instance Evaluatable Send
-- | A slice expression in Go (e.g. `a[1:4:3]` where a is a list, 1 is the low bound, 4 is the high bound, and 3 is the max capacity).
data Slice a = Slice { sliceName :: !a, sliceLow :: !a, sliceHigh :: !a, sliceCapacity :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Slice where liftEq = genericLiftEq
instance Ord1 Slice where liftCompare = genericLiftCompare
@ -209,7 +210,7 @@ instance Evaluatable Slice
-- | A type switch statement in Go (e.g. `switch x.(type) { // cases }`).
data TypeSwitch a = TypeSwitch { typeSwitchSubject :: !a, typeSwitchCases :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 TypeSwitch where liftEq = genericLiftEq
instance Ord1 TypeSwitch where liftCompare = genericLiftCompare
@ -220,7 +221,7 @@ instance Evaluatable TypeSwitch
-- | A type switch guard statement in a Go type switch statement (e.g. `switch i := x.(type) { // cases}`).
newtype TypeSwitchGuard a = TypeSwitchGuard { typeSwitchGuardSubject :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 TypeSwitchGuard where liftEq = genericLiftEq
instance Ord1 TypeSwitchGuard where liftCompare = genericLiftCompare
@ -231,7 +232,7 @@ instance Evaluatable TypeSwitchGuard
-- | A receive statement in a Go select statement (e.g. `case value := <-channel` )
data Receive a = Receive { receiveSubject :: !a, receiveExpression :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Receive where liftEq = genericLiftEq
instance Ord1 Receive where liftCompare = genericLiftCompare
@ -242,7 +243,7 @@ instance Evaluatable Receive
-- | A receive operator unary expression in Go (e.g. `<-channel` )
newtype ReceiveOperator a = ReceiveOperator a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ReceiveOperator where liftEq = genericLiftEq
instance Ord1 ReceiveOperator where liftCompare = genericLiftCompare
@ -253,7 +254,7 @@ instance Evaluatable ReceiveOperator
-- | A field declaration in a Go struct type declaration.
data Field a = Field { fieldContext :: ![a], fieldName :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Field where liftEq = genericLiftEq
instance Ord1 Field where liftCompare = genericLiftCompare
@ -264,7 +265,7 @@ instance Evaluatable Field
data Package a = Package { packageName :: !a, packageContents :: ![a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Package where liftEq = genericLiftEq
instance Ord1 Package where liftCompare = genericLiftCompare
@ -276,7 +277,7 @@ instance Evaluatable Package where
-- | A type assertion in Go (e.g. `x.(T)` where the value of `x` is not nil and is of type `T`).
data TypeAssertion a = TypeAssertion { typeAssertionSubject :: !a, typeAssertionType :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 TypeAssertion where liftEq = genericLiftEq
instance Ord1 TypeAssertion where liftCompare = genericLiftCompare
@ -287,7 +288,7 @@ instance Evaluatable TypeAssertion
-- | A type conversion expression in Go (e.g. `T(x)` where `T` is a type and `x` is an expression that can be converted to type `T`).
data TypeConversion a = TypeConversion { typeConversionType :: !a, typeConversionSubject :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 TypeConversion where liftEq = genericLiftEq
instance Ord1 TypeConversion where liftCompare = genericLiftCompare
@ -298,7 +299,7 @@ instance Evaluatable TypeConversion
-- | Variadic arguments and parameters in Go (e.g. parameter: `param ...Type`, argument: `Type...`).
data Variadic a = Variadic { variadicContext :: [a], variadicIdentifier :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Variadic where liftEq = genericLiftEq
instance Ord1 Variadic where liftCompare = genericLiftCompare

View File

@ -1,4 +1,5 @@
{-# LANGUAGE DeriveAnyClass #-}
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
module Language.Go.Type where
import Prologue
@ -8,7 +9,7 @@ import Diffing.Algorithm
-- | A Bidirectional channel in Go (e.g. `chan`).
newtype BidirectionalChannel a = BidirectionalChannel a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 BidirectionalChannel where liftEq = genericLiftEq
instance Ord1 BidirectionalChannel where liftCompare = genericLiftCompare
@ -19,7 +20,7 @@ instance Evaluatable BidirectionalChannel
-- | A Receive channel in Go (e.g. `<-chan`).
newtype ReceiveChannel a = ReceiveChannel a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ReceiveChannel where liftEq = genericLiftEq
instance Ord1 ReceiveChannel where liftCompare = genericLiftCompare
@ -30,7 +31,7 @@ instance Evaluatable ReceiveChannel
-- | A Send channel in Go (e.g. `chan<-`).
newtype SendChannel a = SendChannel a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 SendChannel where liftEq = genericLiftEq
instance Ord1 SendChannel where liftCompare = genericLiftCompare

View File

@ -1,4 +1,5 @@
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
module Language.Haskell.Grammar where
import Language.Haskell.TH

View File

@ -1,4 +1,5 @@
{-# LANGUAGE DeriveAnyClass #-}
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
module Language.Haskell.Syntax where
import Data.Abstract.Evaluatable
@ -12,7 +13,7 @@ data Module a = Module { moduleContext :: [a]
, moduleExports :: [a]
, moduleStatements :: a
}
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Module where liftEq = genericLiftEq
instance Ord1 Module where liftCompare = genericLiftCompare
@ -21,7 +22,7 @@ instance Show1 Module where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Module
newtype StrictPattern a = StrictPattern a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 StrictPattern where liftEq = genericLiftEq
instance Ord1 StrictPattern where liftCompare = genericLiftCompare
@ -30,7 +31,7 @@ instance Show1 StrictPattern where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable StrictPattern
data StrictType a = StrictType { strictTypeIdentifier :: a, strictTypeParameters :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 StrictType where liftEq = genericLiftEq
instance Ord1 StrictType where liftCompare = genericLiftCompare
@ -39,7 +40,7 @@ instance Show1 StrictType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable StrictType
newtype StrictTypeVariable a = StrictTypeVariable a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 StrictTypeVariable where liftEq = genericLiftEq
instance Ord1 StrictTypeVariable where liftCompare = genericLiftCompare
@ -48,7 +49,7 @@ instance Show1 StrictTypeVariable where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable StrictTypeVariable
data Type a = Type { typeIdentifier :: a, typeParameters :: a, typeKindSignature :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Type where liftEq = genericLiftEq
instance Ord1 Type where liftCompare = genericLiftCompare
@ -57,7 +58,7 @@ instance Show1 Type where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Type
data TypeSynonym a = TypeSynonym { typeSynonymLeft :: a, typeSynonymContext :: [a], typeSynonymRight :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 TypeSynonym where liftEq = genericLiftEq
instance Ord1 TypeSynonym where liftCompare = genericLiftCompare
@ -66,7 +67,7 @@ instance Show1 TypeSynonym where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable TypeSynonym
data UnitConstructor a = UnitConstructor
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 UnitConstructor where liftEq = genericLiftEq
instance Ord1 UnitConstructor where liftCompare = genericLiftCompare
@ -75,7 +76,7 @@ instance Show1 UnitConstructor where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable UnitConstructor
newtype TupleConstructor a = TupleConstructor { tupleConstructorArity :: Int }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 TupleConstructor where liftEq = genericLiftEq
instance Ord1 TupleConstructor where liftCompare = genericLiftCompare
@ -84,7 +85,7 @@ instance Show1 TupleConstructor where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable TupleConstructor
data ListConstructor a = ListConstructor
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ListConstructor where liftEq = genericLiftEq
instance Ord1 ListConstructor where liftCompare = genericLiftCompare
@ -93,7 +94,7 @@ instance Show1 ListConstructor where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ListConstructor
data FunctionConstructor a = FunctionConstructor
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 FunctionConstructor where liftEq = genericLiftEq
instance Ord1 FunctionConstructor where liftCompare = genericLiftCompare
@ -102,7 +103,7 @@ instance Show1 FunctionConstructor where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable FunctionConstructor
data RecordDataConstructor a = RecordDataConstructor { recordDataConstructorContext :: [a], recordDataConstructorName :: !a, recordDataConstructorFields :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 RecordDataConstructor where liftEq = genericLiftEq
instance Ord1 RecordDataConstructor where liftCompare = genericLiftCompare
@ -111,7 +112,7 @@ instance Show1 RecordDataConstructor where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable RecordDataConstructor
data Field a = Field { fieldName :: !a, fieldBody :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Field where liftEq = genericLiftEq
instance Ord1 Field where liftCompare = genericLiftCompare
@ -120,7 +121,7 @@ instance Show1 Field where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Field
newtype Pragma a = Pragma Text
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Pragma where liftEq = genericLiftEq
instance Ord1 Pragma where liftCompare = genericLiftCompare
@ -129,7 +130,7 @@ instance Show1 Pragma where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Pragma
newtype Deriving a = Deriving [a]
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Deriving where liftEq = genericLiftEq
instance Ord1 Deriving where liftCompare = genericLiftCompare
@ -137,7 +138,7 @@ instance Show1 Deriving where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Deriving
newtype Context' a = Context' a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Context' where liftEq = genericLiftEq
instance Ord1 Context' where liftCompare = genericLiftCompare
@ -146,7 +147,7 @@ instance Show1 Context' where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Context'
newtype Class a = Class { classContent :: [a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Class where liftEq = genericLiftEq
instance Ord1 Class where liftCompare = genericLiftCompare
@ -155,7 +156,7 @@ instance Show1 Class where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Class
data GADT a = GADT { gadtContext :: a, gadtName :: a, gadtConstructors :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 GADT where liftEq = genericLiftEq
instance Ord1 GADT where liftCompare = genericLiftCompare
@ -164,7 +165,7 @@ instance Show1 GADT where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable GADT
data GADTConstructor a = GADTConstructor { gadtConstructorContext :: a, gadtConstructorName :: a, gadtConstructorTypeSignature :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 GADTConstructor where liftEq = genericLiftEq
instance Ord1 GADTConstructor where liftCompare = genericLiftCompare
@ -173,7 +174,7 @@ instance Show1 GADTConstructor where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable GADTConstructor
data FunctionType a = FunctionType { functionTypeLeft :: a, functionTypeRight :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 FunctionType where liftEq = genericLiftEq
instance Ord1 FunctionType where liftCompare = genericLiftCompare
@ -182,7 +183,7 @@ instance Show1 FunctionType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable FunctionType
data TypeSignature a = TypeSignature { typeSignatureName :: [a], typeSignatureContext :: [a], typeSignatureContent :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 TypeSignature where liftEq = genericLiftEq
instance Ord1 TypeSignature where liftCompare = genericLiftCompare
@ -191,7 +192,7 @@ instance Show1 TypeSignature where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable TypeSignature
data ExpressionTypeSignature a = ExpressionTypeSignature { expressionTypeSignatureName :: [a], expressionTypeSignatureContext :: [a], expressionTypeSignatureContent :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ExpressionTypeSignature where liftEq = genericLiftEq
instance Ord1 ExpressionTypeSignature where liftCompare = genericLiftCompare
@ -200,7 +201,7 @@ instance Show1 ExpressionTypeSignature where liftShowsPrec = genericLiftShowsPre
instance Evaluatable ExpressionTypeSignature
newtype KindSignature a = KindSignature { kindSignatureContent :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 KindSignature where liftEq = genericLiftEq
instance Ord1 KindSignature where liftCompare = genericLiftCompare
@ -209,7 +210,7 @@ instance Show1 KindSignature where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable KindSignature
data KindFunctionType a = KindFunctionType { kindFunctionTypeLeft :: a, kindFunctionTypeRight :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 KindFunctionType where liftEq = genericLiftEq
instance Ord1 KindFunctionType where liftCompare = genericLiftCompare
@ -218,7 +219,7 @@ instance Show1 KindFunctionType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable KindFunctionType
newtype Kind a = Kind { kindKind :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Kind where liftEq = genericLiftEq
instance Ord1 Kind where liftCompare = genericLiftCompare
@ -227,7 +228,7 @@ instance Show1 Kind where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Kind
newtype KindListType a = KindListType { kindListTypeKind :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 KindListType where liftEq = genericLiftEq
instance Ord1 KindListType where liftCompare = genericLiftCompare
@ -236,7 +237,7 @@ instance Show1 KindListType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable KindListType
data Star a = Star
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Star where liftEq = genericLiftEq
instance Ord1 Star where liftCompare = genericLiftCompare
@ -245,7 +246,7 @@ instance Show1 Star where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Star
newtype QualifiedTypeClassIdentifier a = QualifiedTypeClassIdentifier (NonEmpty a)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 QualifiedTypeClassIdentifier where liftEq = genericLiftEq
instance Ord1 QualifiedTypeClassIdentifier where liftCompare = genericLiftCompare
@ -255,7 +256,7 @@ instance Hashable1 QualifiedTypeClassIdentifier where liftHashWithSalt = foldl
instance Evaluatable QualifiedTypeClassIdentifier
newtype QualifiedTypeConstructorIdentifier a = QualifiedTypeConstructorIdentifier (NonEmpty a)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 QualifiedTypeConstructorIdentifier where liftEq = genericLiftEq
instance Ord1 QualifiedTypeConstructorIdentifier where liftCompare = genericLiftCompare
@ -265,7 +266,7 @@ instance Hashable1 QualifiedTypeConstructorIdentifier where liftHashWithSalt = f
instance Evaluatable QualifiedTypeConstructorIdentifier
newtype QualifiedConstructorIdentifier a = QualifiedConstructorIdentifier (NonEmpty a)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 QualifiedConstructorIdentifier where liftEq = genericLiftEq
instance Ord1 QualifiedConstructorIdentifier where liftCompare = genericLiftCompare
@ -275,7 +276,7 @@ instance Hashable1 QualifiedConstructorIdentifier where liftHashWithSalt = foldl
instance Evaluatable QualifiedConstructorIdentifier
newtype QualifiedInfixVariableIdentifier a = QualifiedInfixVariableIdentifier (NonEmpty a)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 QualifiedInfixVariableIdentifier where liftEq = genericLiftEq
instance Ord1 QualifiedInfixVariableIdentifier where liftCompare = genericLiftCompare
@ -285,7 +286,7 @@ instance Hashable1 QualifiedInfixVariableIdentifier where liftHashWithSalt = fol
instance Evaluatable QualifiedInfixVariableIdentifier
newtype QualifiedModuleIdentifier a = QualifiedModuleIdentifier (NonEmpty a)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 QualifiedModuleIdentifier where liftEq = genericLiftEq
instance Ord1 QualifiedModuleIdentifier where liftCompare = genericLiftCompare
@ -295,7 +296,7 @@ instance Hashable1 QualifiedModuleIdentifier where liftHashWithSalt = foldl
instance Evaluatable QualifiedModuleIdentifier
newtype QualifiedVariableIdentifier a = QualifiedVariableIdentifier (NonEmpty a)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 QualifiedVariableIdentifier where liftEq = genericLiftEq
instance Ord1 QualifiedVariableIdentifier where liftCompare = genericLiftCompare
@ -305,7 +306,7 @@ instance Hashable1 QualifiedVariableIdentifier where liftHashWithSalt = foldl
instance Evaluatable QualifiedVariableIdentifier
data AnnotatedTypeVariable a = AnnotatedTypeVariable { annotatedTypeVariableIdentifier :: a, annotatedTypeVariableannotation :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 AnnotatedTypeVariable where liftEq = genericLiftEq
instance Ord1 AnnotatedTypeVariable where liftCompare = genericLiftCompare
@ -314,7 +315,7 @@ instance Show1 AnnotatedTypeVariable where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable AnnotatedTypeVariable
newtype Export a = Export { exportContent :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Export where liftEq = genericLiftEq
instance Ord1 Export where liftCompare = genericLiftCompare
@ -323,7 +324,7 @@ instance Show1 Export where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Export
newtype ModuleExport a = ModuleExport { moduleExportContent :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ModuleExport where liftEq = genericLiftEq
instance Ord1 ModuleExport where liftCompare = genericLiftCompare
@ -332,7 +333,7 @@ instance Show1 ModuleExport where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ModuleExport
newtype TypeConstructorExport a = TypeConstructorExport { typeConstructorExportContent :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 TypeConstructorExport where liftEq = genericLiftEq
instance Ord1 TypeConstructorExport where liftCompare = genericLiftCompare
@ -341,7 +342,7 @@ instance Show1 TypeConstructorExport where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable TypeConstructorExport
data AllConstructors a = AllConstructors
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 AllConstructors where liftEq = genericLiftEq
instance Ord1 AllConstructors where liftCompare = genericLiftCompare
@ -350,7 +351,7 @@ instance Show1 AllConstructors where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable AllConstructors
data InfixOperatorPattern a = InfixOperatorPattern { infixOperatorPatternLeft :: a, infixOperatorPatternOperator :: a, infixOperatorPatternRight :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 InfixOperatorPattern where liftEq = genericLiftEq
instance Ord1 InfixOperatorPattern where liftCompare = genericLiftCompare
@ -359,7 +360,7 @@ instance Show1 InfixOperatorPattern where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable InfixOperatorPattern
newtype QuotedName a = QuotedName { quotedNameContent :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 QuotedName where liftEq = genericLiftEq
instance Ord1 QuotedName where liftCompare = genericLiftCompare
@ -368,7 +369,7 @@ instance Show1 QuotedName where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable QuotedName
newtype TypePattern a = TypePattern { typePatternContent :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 TypePattern where liftEq = genericLiftEq
instance Ord1 TypePattern where liftCompare = genericLiftCompare
@ -377,7 +378,7 @@ instance Show1 TypePattern where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable TypePattern
newtype ScopedTypeVariables a = ScopedTypeVariables { scopedTypeVariablesContent :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ScopedTypeVariables where liftEq = genericLiftEq
instance Ord1 ScopedTypeVariables where liftCompare = genericLiftCompare
@ -386,7 +387,7 @@ instance Show1 ScopedTypeVariables where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ScopedTypeVariables
data NewType a = NewType { newTypeContext :: [a], newTypeLeft :: a, newTypeRight :: a, newTypeDeriving :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 NewType where liftEq = genericLiftEq
instance Ord1 NewType where liftCompare = genericLiftCompare
@ -395,7 +396,7 @@ instance Show1 NewType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable NewType
newtype DefaultDeclaration a = DefaultDeclaration { defaultDeclarationContent :: [a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 DefaultDeclaration where liftEq = genericLiftEq
instance Ord1 DefaultDeclaration where liftCompare = genericLiftCompare
@ -404,7 +405,7 @@ instance Show1 DefaultDeclaration where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable DefaultDeclaration
data EqualityConstraint a = EqualityConstraint { equalityConstraintLeft :: a, equalityConstraintRight :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 EqualityConstraint where liftEq = genericLiftEq
instance Ord1 EqualityConstraint where liftCompare = genericLiftCompare
@ -413,7 +414,7 @@ instance Show1 EqualityConstraint where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable EqualityConstraint
newtype TypeVariableIdentifier a = TypeVariableIdentifier Name
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 TypeVariableIdentifier where liftEq = genericLiftEq
instance Ord1 TypeVariableIdentifier where liftCompare = genericLiftCompare
@ -422,7 +423,7 @@ instance Show1 TypeVariableIdentifier where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable TypeVariableIdentifier
newtype TypeConstructorIdentifier a = TypeConstructorIdentifier Name
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 TypeConstructorIdentifier where liftEq = genericLiftEq
instance Ord1 TypeConstructorIdentifier where liftCompare = genericLiftCompare
@ -431,7 +432,7 @@ instance Show1 TypeConstructorIdentifier where liftShowsPrec = genericLiftShowsP
instance Evaluatable TypeConstructorIdentifier
newtype ModuleIdentifier a = ModuleIdentifier Name
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ModuleIdentifier where liftEq = genericLiftEq
instance Ord1 ModuleIdentifier where liftCompare = genericLiftCompare
@ -440,7 +441,7 @@ instance Show1 ModuleIdentifier where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ModuleIdentifier
newtype ConstructorIdentifier a = ConstructorIdentifier Name
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ConstructorIdentifier where liftEq = genericLiftEq
instance Ord1 ConstructorIdentifier where liftCompare = genericLiftCompare
@ -449,7 +450,7 @@ instance Show1 ConstructorIdentifier where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ConstructorIdentifier
newtype ImplicitParameterIdentifier a = ImplicitParameterIdentifier Name
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ImplicitParameterIdentifier where liftEq = genericLiftEq
instance Ord1 ImplicitParameterIdentifier where liftCompare = genericLiftCompare
@ -458,7 +459,7 @@ instance Show1 ImplicitParameterIdentifier where liftShowsPrec = genericLiftShow
instance Evaluatable ImplicitParameterIdentifier
newtype InfixConstructorIdentifier a = InfixConstructorIdentifier Name
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 InfixConstructorIdentifier where liftEq = genericLiftEq
instance Ord1 InfixConstructorIdentifier where liftCompare = genericLiftCompare
@ -467,7 +468,7 @@ instance Show1 InfixConstructorIdentifier where liftShowsPrec = genericLiftShows
instance Evaluatable InfixConstructorIdentifier
newtype InfixVariableIdentifier a = InfixVariableIdentifier Name
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 InfixVariableIdentifier where liftEq = genericLiftEq
instance Ord1 InfixVariableIdentifier where liftCompare = genericLiftCompare
@ -476,7 +477,7 @@ instance Show1 InfixVariableIdentifier where liftShowsPrec = genericLiftShowsPre
instance Evaluatable InfixVariableIdentifier
newtype TypeClassIdentifier a = TypeClassIdentifier Name
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 TypeClassIdentifier where liftEq = genericLiftEq
instance Ord1 TypeClassIdentifier where liftCompare = genericLiftCompare
@ -485,7 +486,7 @@ instance Show1 TypeClassIdentifier where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable TypeClassIdentifier
newtype VariableIdentifier a = VariableIdentifier Name
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 VariableIdentifier where liftEq = genericLiftEq
instance Ord1 VariableIdentifier where liftCompare = genericLiftCompare
@ -494,7 +495,7 @@ instance Show1 VariableIdentifier where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable VariableIdentifier
newtype PrimitiveConstructorIdentifier a = PrimitiveConstructorIdentifier Name
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 PrimitiveConstructorIdentifier where liftEq = genericLiftEq
instance Ord1 PrimitiveConstructorIdentifier where liftCompare = genericLiftCompare
@ -503,7 +504,7 @@ instance Show1 PrimitiveConstructorIdentifier where liftShowsPrec = genericLiftS
instance Evaluatable PrimitiveConstructorIdentifier
newtype PrimitiveVariableIdentifier a = PrimitiveVariableIdentifier Name
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 PrimitiveVariableIdentifier where liftEq = genericLiftEq
instance Ord1 PrimitiveVariableIdentifier where liftCompare = genericLiftCompare
@ -512,7 +513,7 @@ instance Show1 PrimitiveVariableIdentifier where liftShowsPrec = genericLiftShow
instance Evaluatable PrimitiveVariableIdentifier
newtype VariableOperator a = VariableOperator a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 VariableOperator where liftEq = genericLiftEq
instance Ord1 VariableOperator where liftCompare = genericLiftCompare
@ -521,7 +522,7 @@ instance Show1 VariableOperator where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable VariableOperator
newtype ConstructorOperator a = ConstructorOperator a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ConstructorOperator where liftEq = genericLiftEq
instance Ord1 ConstructorOperator where liftCompare = genericLiftCompare
@ -530,7 +531,7 @@ instance Show1 ConstructorOperator where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ConstructorOperator
newtype TypeOperator a = TypeOperator Name
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 TypeOperator where liftEq = genericLiftEq
instance Ord1 TypeOperator where liftCompare = genericLiftCompare
@ -539,7 +540,7 @@ instance Show1 TypeOperator where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable TypeOperator
newtype PromotedTypeOperator a = PromotedTypeOperator a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 PromotedTypeOperator where liftEq = genericLiftEq
instance Ord1 PromotedTypeOperator where liftCompare = genericLiftCompare
@ -548,7 +549,7 @@ instance Show1 PromotedTypeOperator where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable PromotedTypeOperator
newtype ConstructorSymbol a = ConstructorSymbol { constructorSymbolName :: Name }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ConstructorSymbol where liftEq = genericLiftEq
instance Ord1 ConstructorSymbol where liftCompare = genericLiftCompare
@ -557,7 +558,7 @@ instance Show1 ConstructorSymbol where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ConstructorSymbol
newtype VariableSymbol a = VariableSymbol { variableSymbolName :: Name }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 VariableSymbol where liftEq = genericLiftEq
instance Ord1 VariableSymbol where liftCompare = genericLiftCompare
@ -566,7 +567,7 @@ instance Show1 VariableSymbol where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable VariableSymbol
data StandaloneDerivingInstance a = StandaloneDerivingInstance { standaloneDerivingInstanceContext :: [a], standaloneDerivingInstanceClass :: a, standaloneDerivingInstanceInstance :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 StandaloneDerivingInstance where liftEq = genericLiftEq
instance Ord1 StandaloneDerivingInstance where liftCompare = genericLiftCompare
@ -575,7 +576,7 @@ instance Show1 StandaloneDerivingInstance where liftShowsPrec = genericLiftShows
instance Evaluatable StandaloneDerivingInstance
data ImportDeclaration a = ImportDeclaration { importPackageQualifiedContent :: a, importModule :: a, importSpec :: [a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ImportDeclaration where liftEq = genericLiftEq
instance Ord1 ImportDeclaration where liftCompare = genericLiftCompare
@ -584,7 +585,7 @@ instance Show1 ImportDeclaration where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ImportDeclaration
data QualifiedImportDeclaration a = QualifiedImportDeclaration { qualifiedImportPackageQualifiedContent :: a, qualifiedImportModule :: a, qualifiedImportSpec :: [a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 QualifiedImportDeclaration where liftEq = genericLiftEq
instance Ord1 QualifiedImportDeclaration where liftCompare = genericLiftCompare
@ -593,7 +594,7 @@ instance Show1 QualifiedImportDeclaration where liftShowsPrec = genericLiftShows
instance Evaluatable QualifiedImportDeclaration
newtype Import a = Import { importContent :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Import where liftEq = genericLiftEq
instance Ord1 Import where liftCompare = genericLiftCompare
@ -602,7 +603,7 @@ instance Show1 Import where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Import
newtype HiddenImport a = HiddenImport { hiddenimportContent :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 HiddenImport where liftEq = genericLiftEq
instance Ord1 HiddenImport where liftCompare = genericLiftCompare
@ -611,7 +612,7 @@ instance Show1 HiddenImport where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable HiddenImport
data ImportAlias a = ImportAlias { importAliasSource :: a, importAliasName :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ImportAlias where liftEq = genericLiftEq
instance Ord1 ImportAlias where liftCompare = genericLiftCompare
@ -620,7 +621,7 @@ instance Show1 ImportAlias where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ImportAlias
data App a = App { appLeft :: a, appLeftTypeApp :: a, appRight :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 App where liftEq = genericLiftEq
instance Ord1 App where liftCompare = genericLiftCompare
@ -629,7 +630,7 @@ instance Show1 App where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable App
data InfixOperatorApp a = InfixOperatorApp { infixOperatorAppLeft :: a, infixOperatorAppLeftTypeApp :: a, infixOperatorAppOperator :: a, infixOperatorAppRight :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 InfixOperatorApp where liftEq = genericLiftEq
instance Ord1 InfixOperatorApp where liftCompare = genericLiftCompare
@ -638,7 +639,7 @@ instance Show1 InfixOperatorApp where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable InfixOperatorApp
newtype TypeApp a = TypeApp { typeAppType :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 TypeApp where liftEq = genericLiftEq
instance Ord1 TypeApp where liftCompare = genericLiftCompare
@ -647,7 +648,7 @@ instance Show1 TypeApp where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable TypeApp
data ListComprehension a = ListComprehension { comprehensionValue :: a, comprehensionSource :: [a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ListComprehension where liftEq = genericLiftEq
instance Ord1 ListComprehension where liftCompare = genericLiftCompare
@ -656,7 +657,7 @@ instance Show1 ListComprehension where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ListComprehension
data Generator a = Generator { generatorValue :: a, generatorSource :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Generator where liftEq = genericLiftEq
instance Ord1 Generator where liftCompare = genericLiftCompare
@ -665,7 +666,7 @@ instance Show1 Generator where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Generator
newtype Tuple a = Tuple [a]
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Tuple where liftEq = genericLiftEq
instance Ord1 Tuple where liftCompare = genericLiftCompare
@ -674,7 +675,7 @@ instance Show1 Tuple where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Tuple
newtype TuplePattern a = TuplePattern [a]
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 TuplePattern where liftEq = genericLiftEq
instance Ord1 TuplePattern where liftCompare = genericLiftCompare
@ -684,7 +685,7 @@ instance Evaluatable TuplePattern
-- e.g. [1..], [1,2..], [1,2..10]
data ArithmeticSequence a = ArithmeticSequence { from :: a, next :: Maybe a, to :: Maybe a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ArithmeticSequence where liftEq = genericLiftEq
instance Ord1 ArithmeticSequence where liftCompare = genericLiftCompare
@ -693,7 +694,7 @@ instance Show1 ArithmeticSequence where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ArithmeticSequence
data RightOperatorSection a = RightOperatorSection a a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 RightOperatorSection where liftEq = genericLiftEq
instance Ord1 RightOperatorSection where liftCompare = genericLiftCompare
@ -702,7 +703,7 @@ instance Show1 RightOperatorSection where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable RightOperatorSection
data LeftOperatorSection a = LeftOperatorSection a a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 LeftOperatorSection where liftEq = genericLiftEq
instance Ord1 LeftOperatorSection where liftCompare = genericLiftCompare
@ -711,7 +712,7 @@ instance Show1 LeftOperatorSection where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable LeftOperatorSection
newtype ConstructorPattern a = ConstructorPattern a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ConstructorPattern where liftEq = genericLiftEq
instance Ord1 ConstructorPattern where liftCompare = genericLiftCompare
@ -721,7 +722,7 @@ instance Evaluatable ConstructorPattern
-- e.g. `a <- b` in a Haskell do block.
data BindPattern a = BindPattern { bindPatternLeft :: [a], bindPatternRight :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 BindPattern where liftEq = genericLiftEq
instance Ord1 BindPattern where liftCompare = genericLiftCompare
@ -730,7 +731,7 @@ instance Show1 BindPattern where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable BindPattern
newtype Do a = Do [a]
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Do where liftEq = genericLiftEq
instance Ord1 Do where liftCompare = genericLiftCompare
@ -739,7 +740,7 @@ instance Show1 Do where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Do
data Lambda a = Lambda { lambdaHead :: a, lambdaBody :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Lambda where liftEq = genericLiftEq
instance Ord1 Lambda where liftCompare = genericLiftCompare
@ -749,7 +750,7 @@ instance Evaluatable Lambda
-- e.g. -1 or (-a) as an expression and not `-` as a variable operator.
newtype PrefixNegation a = PrefixNegation a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 PrefixNegation where liftEq = genericLiftEq
instance Ord1 PrefixNegation where liftCompare = genericLiftCompare
@ -758,7 +759,7 @@ instance Show1 PrefixNegation where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable PrefixNegation
newtype CPPDirective a = CPPDirective Text
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 CPPDirective where liftEq = genericLiftEq
instance Ord1 CPPDirective where liftCompare = genericLiftCompare
@ -767,7 +768,7 @@ instance Show1 CPPDirective where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable CPPDirective
data QuasiQuotation a = QuasiQuotation { quasiQuotationHead :: a, quasiQuotationBody :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 QuasiQuotation where liftEq = genericLiftEq
instance Ord1 QuasiQuotation where liftCompare = genericLiftCompare
@ -776,7 +777,7 @@ instance Show1 QuasiQuotation where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable QuasiQuotation
newtype QuasiQuotationExpressionBody a = QuasiQuotationExpressionBody Name
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 QuasiQuotationExpressionBody where liftEq = genericLiftEq
instance Ord1 QuasiQuotationExpressionBody where liftCompare = genericLiftCompare
@ -785,7 +786,7 @@ instance Show1 QuasiQuotationExpressionBody where liftShowsPrec = genericLiftSho
instance Evaluatable QuasiQuotationExpressionBody
data QuasiQuotationPattern a = QuasiQuotationPattern
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 QuasiQuotationPattern where liftEq = genericLiftEq
instance Ord1 QuasiQuotationPattern where liftCompare = genericLiftCompare
@ -794,7 +795,7 @@ instance Show1 QuasiQuotationPattern where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable QuasiQuotationPattern
data QuasiQuotationType a = QuasiQuotationType
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 QuasiQuotationType where liftEq = genericLiftEq
instance Ord1 QuasiQuotationType where liftCompare = genericLiftCompare
@ -803,7 +804,7 @@ instance Show1 QuasiQuotationType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable QuasiQuotationType
data QuasiQuotationDeclaration a = QuasiQuotationDeclaration
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 QuasiQuotationDeclaration where liftEq = genericLiftEq
instance Ord1 QuasiQuotationDeclaration where liftCompare = genericLiftCompare
@ -812,7 +813,7 @@ instance Show1 QuasiQuotationDeclaration where liftShowsPrec = genericLiftShowsP
instance Evaluatable QuasiQuotationDeclaration
newtype QuasiQuotationQuoter a = QuasiQuotationQuoter Name
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 QuasiQuotationQuoter where liftEq = genericLiftEq
instance Ord1 QuasiQuotationQuoter where liftCompare = genericLiftCompare
@ -821,7 +822,7 @@ instance Show1 QuasiQuotationQuoter where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable QuasiQuotationQuoter
data QuasiQuotationExpression a = QuasiQuotationExpression
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 QuasiQuotationExpression where liftEq = genericLiftEq
instance Ord1 QuasiQuotationExpression where liftCompare = genericLiftCompare
@ -830,7 +831,7 @@ instance Show1 QuasiQuotationExpression where liftShowsPrec = genericLiftShowsPr
instance Evaluatable QuasiQuotationExpression
newtype Splice a = Splice a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Splice where liftEq = genericLiftEq
instance Ord1 Splice where liftCompare = genericLiftCompare
@ -839,7 +840,7 @@ instance Show1 Splice where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Splice
data TypeClass a = TypeClass { typeClassContext :: a, typeClassIdentifier :: a, typeClassParameters :: [a], typeClassBody :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 TypeClass where liftEq = genericLiftEq
instance Ord1 TypeClass where liftCompare = genericLiftCompare
@ -848,7 +849,7 @@ instance Show1 TypeClass where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable TypeClass
data Fixity' a = Fixity' { fixityPrecedence :: a, fixityIdentifier :: [a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Fixity' where liftEq = genericLiftEq
instance Ord1 Fixity' where liftCompare = genericLiftCompare
@ -858,7 +859,7 @@ instance Evaluatable Fixity'
-- The default signature of a type class. The default signature has the same shape as a TypeSignature Assignment.
data DefaultSignature a = DefaultSignature { defaultSignatureName :: [a], defaultSignatureContext :: [a], defaultSignatureContent :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 DefaultSignature where liftEq = genericLiftEq
instance Ord1 DefaultSignature where liftCompare = genericLiftCompare
@ -867,7 +868,7 @@ instance Show1 DefaultSignature where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable DefaultSignature
data TypeFamily a = TypeFamily { typeFamilyIdentifier :: a, typeFamilyParameters :: [a], typeFamilySignature :: a, typeFamilyBody :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 TypeFamily where liftEq = genericLiftEq
instance Ord1 TypeFamily where liftCompare = genericLiftCompare
@ -876,7 +877,7 @@ instance Show1 TypeFamily where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable TypeFamily
newtype FunctionalDependency a = FunctionalDependency { functionalDependencyContent :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 FunctionalDependency where liftEq = genericLiftEq
instance Ord1 FunctionalDependency where liftCompare = genericLiftCompare
@ -885,7 +886,7 @@ instance Show1 FunctionalDependency where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable FunctionalDependency
data TypeClassInstance a = TypeClassInstance { typeClassInstanceContext :: [a], typeClassInstanceIdentifier :: a, typeClassInstanceInstance :: a, typeClassInstanceBody :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 TypeClassInstance where liftEq = genericLiftEq
instance Ord1 TypeClassInstance where liftCompare = genericLiftCompare
@ -894,7 +895,7 @@ instance Show1 TypeClassInstance where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable TypeClassInstance
newtype Instance a = Instance a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Instance where liftEq = genericLiftEq
instance Ord1 Instance where liftCompare = genericLiftCompare
@ -904,7 +905,7 @@ instance Evaluatable Instance
-- e.g. The `Bar{..}` in `foo Bar{..} = baz`.
newtype LabeledPattern a = LabeledPattern a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 LabeledPattern where liftEq = genericLiftEq
instance Ord1 LabeledPattern where liftCompare = genericLiftCompare
@ -914,7 +915,7 @@ instance Evaluatable LabeledPattern
-- e.g. The `{..}` in `foo Bar{..} = baz`
data RecordWildCards a = RecordWildCards
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 RecordWildCards where liftEq = genericLiftEq
instance Ord1 RecordWildCards where liftCompare = genericLiftCompare
@ -924,7 +925,7 @@ instance Evaluatable RecordWildCards
-- e.g. `type instance F [Int] = Int` where `F` is an open type family.
data TypeInstance a = TypeInstance { typeInstanceType :: a, typeInstanceBody :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 TypeInstance where liftEq = genericLiftEq
instance Ord1 TypeInstance where liftCompare = genericLiftCompare
@ -933,7 +934,7 @@ instance Show1 TypeInstance where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable TypeInstance
newtype KindParenthesizedConstructor a = KindParenthesizedConstructor { kindParenthesizedConstructorContent :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 KindParenthesizedConstructor where liftEq = genericLiftEq
instance Ord1 KindParenthesizedConstructor where liftCompare = genericLiftCompare
@ -942,7 +943,7 @@ instance Show1 KindParenthesizedConstructor where liftShowsPrec = genericLiftSho
instance Evaluatable KindParenthesizedConstructor
newtype KindTupleType a = KindTupleType { kindTupleType :: [a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 KindTupleType where liftEq = genericLiftEq
instance Ord1 KindTupleType where liftCompare = genericLiftCompare
@ -951,7 +952,7 @@ instance Show1 KindTupleType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable KindTupleType
data Wildcard a = Wildcard
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Wildcard where liftEq = genericLiftEq
instance Ord1 Wildcard where liftCompare = genericLiftCompare
@ -960,7 +961,7 @@ instance Show1 Wildcard where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Wildcard
data Let a = Let { letStatements :: [a], letInClause :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Let where liftEq = genericLiftEq
instance Ord1 Let where liftCompare = genericLiftCompare
@ -969,7 +970,7 @@ instance Show1 Let where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Let
newtype ListPattern a = ListPattern a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ListPattern where liftEq = genericLiftEq
instance Ord1 ListPattern where liftCompare = genericLiftCompare
@ -979,7 +980,7 @@ instance Evaluatable ListPattern
-- e.g. The `n@num1` in `f n@num1 x@num2 = x`
data AsPattern a = AsPattern { asPatternLeft :: a, asPatternRight :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 AsPattern where liftEq = genericLiftEq
instance Ord1 AsPattern where liftCompare = genericLiftCompare
@ -989,7 +990,7 @@ instance Evaluatable AsPattern
-- e.g. The `a = 1` in `foo Bar{ a = 1 } = baz`.
data FieldPattern a = FieldPattern { fieldPatternLeft :: a, fieldPatternRight :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 FieldPattern where liftEq = genericLiftEq
instance Ord1 FieldPattern where liftCompare = genericLiftCompare
@ -999,7 +1000,7 @@ instance Evaluatable FieldPattern
-- e.g. The `start` or `end` in `f Blob{start, end} = [start, end]`.
newtype NamedFieldPun a = NamedFieldPun a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 NamedFieldPun where liftEq = genericLiftEq
instance Ord1 NamedFieldPun where liftCompare = genericLiftCompare
@ -1009,7 +1010,7 @@ instance Evaluatable NamedFieldPun
-- e.g. The `-(1)` in `f (-(1)) = 1`.
newtype NegativeLiteral a = NegativeLiteral a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 NegativeLiteral where liftEq = genericLiftEq
instance Ord1 NegativeLiteral where liftCompare = genericLiftCompare
@ -1019,7 +1020,7 @@ instance Evaluatable NegativeLiteral
-- e.g. The `~a` in `f ~a = 1`
newtype IrrefutablePattern a = IrrefutablePattern a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 IrrefutablePattern where liftEq = genericLiftEq
instance Ord1 IrrefutablePattern where liftCompare = genericLiftCompare
@ -1029,7 +1030,7 @@ instance Evaluatable IrrefutablePattern
-- For handling guards in case alternative expressions.
newtype CaseGuardPattern a = CaseGuardPattern [a]
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 CaseGuardPattern where liftEq = genericLiftEq
instance Ord1 CaseGuardPattern where liftCompare = genericLiftCompare
@ -1038,7 +1039,7 @@ instance Show1 CaseGuardPattern where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable CaseGuardPattern
newtype Guard a = Guard a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Guard where liftEq = genericLiftEq
instance Ord1 Guard where liftCompare = genericLiftCompare
@ -1047,7 +1048,7 @@ instance Show1 Guard where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Guard
newtype LambdaCase a = LambdaCase [a]
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 LambdaCase where liftEq = genericLiftEq
instance Ord1 LambdaCase where liftCompare = genericLiftCompare
@ -1057,7 +1058,7 @@ instance Evaluatable LambdaCase
-- For handling guards in function declarations.
newtype FunctionGuardPattern a = FunctionGuardPattern [a]
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 FunctionGuardPattern where liftEq = genericLiftEq
instance Ord1 FunctionGuardPattern where liftCompare = genericLiftCompare
@ -1067,7 +1068,7 @@ instance Evaluatable FunctionGuardPattern
-- The `y { a = 1, b = 2} in `f y@Example = y { a = 1, b = 2 }`.
newtype LabeledUpdate a = LabeledUpdate [a]
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 LabeledUpdate where liftEq = genericLiftEq
instance Ord1 LabeledUpdate where liftCompare = genericLiftCompare
@ -1077,7 +1078,7 @@ instance Evaluatable LabeledUpdate
-- The `a = 1` in `f y@Example = y { a = 1, b = 2 }`.
data FieldBind a = FieldBind { fieldBindLeft :: a, fieldBindRight :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 FieldBind where liftEq = genericLiftEq
instance Ord1 FieldBind where liftCompare = genericLiftCompare
@ -1086,7 +1087,7 @@ instance Show1 FieldBind where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable FieldBind
data ViewPattern a = ViewPattern { viewPatternLeft :: a, viewPatternRight :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ViewPattern where liftEq = genericLiftEq
instance Ord1 ViewPattern where liftCompare = genericLiftCompare
@ -1096,7 +1097,7 @@ instance Evaluatable ViewPattern
-- The `a <- b` in `f a | a <- b = c` of a function declaration.
data PatternGuard a = PatternGuard { patternGuardPattern :: a, patternGuardExpression :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 PatternGuard where liftEq = genericLiftEq
instance Ord1 PatternGuard where liftCompare = genericLiftCompare
@ -1105,7 +1106,7 @@ instance Show1 PatternGuard where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable PatternGuard
data LabeledConstruction a = LabeledConstruction { labeledConstructionConstructor :: a, labeledConstructionFields :: [a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 LabeledConstruction where liftEq = genericLiftEq
instance Ord1 LabeledConstruction where liftCompare = genericLiftCompare
@ -1114,7 +1115,7 @@ instance Show1 LabeledConstruction where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable LabeledConstruction
data InfixDataConstructor a = InfixDataConstructor { infixDataConstructorContext :: [a], infixDataConstructorLeft :: a, infixDataConstructorOperator :: a, infixDataConstructorRight :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 InfixDataConstructor where liftEq = genericLiftEq
instance Ord1 InfixDataConstructor where liftCompare = genericLiftCompare

View File

@ -1,4 +1,5 @@
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
module Language.JSON.Grammar where
import Language.Haskell.TH

View File

@ -14,7 +14,7 @@ import Data.Record
import Data.Syntax (contextualize, emptyTerm, handleError, infixContext, makeTerm, makeTerm', makeTerm'', makeTerm1, parseError, postContextualize)
import Data.Sum
import Language.Java.Grammar as Grammar
import Language.Java.Syntax as Java.Syntax
import qualified Language.Java.Syntax as Java.Syntax
import qualified Assigning.Assignment as Assignment
import qualified Data.Syntax as Syntax
import qualified Data.Syntax.Comment as Comment
@ -25,7 +25,7 @@ import qualified Data.Syntax.Statement as Statement
import qualified Data.Syntax.Type as Type
import qualified Data.Term as Term
import Prelude hiding (break)
import Prologue hiding (for, try, This)
import Prologue hiding (for, try, This, catches, finally)
type Syntax =
'[ Comment.Comment
@ -66,18 +66,33 @@ type Syntax =
, Expression.Member
, Expression.Super
, Expression.This
, Java.Syntax.AnnotatedType
, Java.Syntax.Annotation
, Java.Syntax.AnnotationField
, Java.Syntax.AnnotationTypeElement
, Java.Syntax.ArrayCreationExpression
, Java.Syntax.AssertStatement
, Java.Syntax.Asterisk
, Java.Syntax.CatchType
, Java.Syntax.Constructor
, Java.Syntax.ClassBody
, Java.Syntax.ClassLiteral
, Java.Syntax.DefaultValue
, Java.Syntax.DimsExpr
, Java.Syntax.EnumDeclaration
, Java.Syntax.GenericType
, Java.Syntax.Import
, Java.Syntax.Lambda
, Java.Syntax.LambdaBody
, Java.Syntax.MethodReference
, Java.Syntax.Module
, Java.Syntax.New
, Java.Syntax.NewKeyword
, Java.Syntax.Package
, Java.Syntax.SpreadParameter
, Java.Syntax.StaticInitializer
, Java.Syntax.Synchronized
, Java.Syntax.TryWithResources
, Java.Syntax.TypeParameter
, Java.Syntax.TypeWithModifiers
, Java.Syntax.Variable
@ -125,41 +140,43 @@ type Syntax =
]
type Term = Term.Term (Sum Syntax) (Record Location)
type Assignment = Assignment.Assignment [] Grammar Term
type Assignment = Assignment.Assignment [] Grammar
-- | Assignment from AST in Java's grammar onto a program in Java's syntax.
assignment :: Assignment
assignment :: Assignment Term
assignment = handleError $ makeTerm <$> symbol Grammar.Program <*> children (Statement.Statements <$> manyTerm expression) <|> parseError
-- | Match a term optionally preceded by comment(s), or a sequence of comments if the term is not present.
manyTerm :: Assignment -> Assignment.Assignment [] Grammar [Term]
manyTerm :: Assignment Term -> Assignment [Term]
manyTerm term = many (contextualize comment term <|> makeTerm1 <$> (Syntax.Context <$> some1 comment <*> emptyTerm))
-- | Match a series of terms or comments until a delimiter is matched.
manyTermsTill :: Assignment.Assignment [] Grammar Term
-> Assignment.Assignment [] Grammar b
-> Assignment.Assignment [] Grammar [Term]
manyTermsTill :: Assignment Term
-> Assignment b
-> Assignment [Term]
manyTermsTill step = manyTill (step <|> comment)
someTerm :: Assignment -> Assignment.Assignment [] Grammar [Term]
someTerm :: Assignment Term -> Assignment [Term]
someTerm term = some (contextualize comment term <|> makeTerm1 <$> (Syntax.Context <$> some1 comment <*> emptyTerm))
-- | Match comments before and after the node.
term :: Assignment -> Assignment
term :: Assignment Term -> Assignment Term
term term = contextualize comment (postContextualize comment term)
-- | Match
expression :: Assignment
expression :: Assignment Term
expression = handleError (choice expressionChoices)
expressions :: Assignment
expressions :: Assignment Term
expressions = makeTerm'' <$> location <*> many expression
expressionChoices :: [Assignment.Assignment [] Grammar Term]
expressionChoices :: [Assignment Term]
expressionChoices =
[
arrayInitializer
, arrayAccess
arrayAccess
, arrayCreationExpression
, arrayInitializer
, assert
, assignment'
, block
, binary
@ -168,11 +185,13 @@ expressionChoices =
, castExpression
, char
, class'
, classBody
, classInstance
, classLiteral
, continue
, constructorDeclaration
, dimsExpr
, explicitConstructorInvocation
-- , TODO: constantDeclaration
, doWhile
, fieldAccess
, fieldDeclaration
@ -184,8 +203,10 @@ expressionChoices =
, identifier
, import'
, integer
, lambda
, method
, methodInvocation
, methodReference
, module'
, null'
, package
@ -194,6 +215,7 @@ expressionChoices =
, string
, super
, switch
, staticInitializer
, synchronized
, ternary
, this
@ -206,22 +228,22 @@ expressionChoices =
, while
]
modifier :: Assignment
modifier :: Assignment Term
modifier = make <$> symbol Modifier <*> children(Left <$> annotation <|> Right . Syntax.AccessibilityModifier <$> source)
where
make loc (Right modifier) = makeTerm loc modifier
make _ (Left annotation) = annotation
arrayInitializer :: Assignment
arrayInitializer :: Assignment Term
arrayInitializer = makeTerm <$> symbol ArrayInitializer <*> (Literal.Array <$> many expression)
comment :: Assignment
comment :: Assignment Term
comment = makeTerm <$> symbol Comment <*> (Comment.Comment <$> source)
localVariableDeclaration :: Assignment
localVariableDeclaration :: Assignment Term
localVariableDeclaration = makeTerm <$> symbol LocalVariableDeclaration <*> children ((,) <$> manyTerm modifier <*> type' <**> variableDeclaratorList)
variableDeclaratorList :: Assignment.Assignment [] Grammar (([Term], Term) -> [Term])
variableDeclaratorList :: Assignment (([Term], Term) -> [Term])
variableDeclaratorList = symbol VariableDeclaratorList *> children (makeDecl <$> some variableDeclarator)
where
variableDeclarator = symbol VariableDeclarator *> children ((,) <$> variableDeclaratorId <*> optional expression)
@ -229,200 +251,243 @@ variableDeclaratorList = symbol VariableDeclaratorList *> children (makeDecl <$>
makeSingleDecl modifiers type' (target, Nothing) = makeTerm1 (Java.Syntax.Variable modifiers type' target)
makeSingleDecl modifiers type' (target, Just value) = makeTerm1 (Statement.Assignment [] (makeTerm1 (Java.Syntax.Variable modifiers type' target)) value)
localVariableDeclarationStatement :: Assignment
arrayCreationExpression :: Assignment Term
arrayCreationExpression = makeTerm <$> symbol Grammar.ArrayCreationExpression <*> children (Java.Syntax.ArrayCreationExpression <$> (new *> type') <*> many dimsExpr)
where new = token AnonNew $> Java.Syntax.NewKeyword
localVariableDeclarationStatement :: Assignment Term
localVariableDeclarationStatement = symbol LocalVariableDeclarationStatement *> children localVariableDeclaration
variableDeclaratorId :: Assignment
variableDeclaratorId :: Assignment Term
variableDeclaratorId = symbol VariableDeclaratorId *> children identifier
-- Literals
boolean :: Assignment
boolean = toTerm (branchNode BooleanLiteral
( leafNode Grammar.True $> Literal.true
<|> leafNode Grammar.False $> Literal.false))
boolean :: Assignment Term
boolean = makeTerm <$> symbol BooleanLiteral <*> children
(token Grammar.True $> Literal.true
<|> token Grammar.False $> Literal.false)
null' :: Assignment
null' :: Assignment Term
null' = makeTerm <$> symbol NullLiteral <*> (Literal.Null <$ source)
-- Integer supports all integer and floating point literals (hex, octal, binary)
integer :: Assignment
integer :: Assignment Term
integer = makeTerm <$> symbol IntegerLiteral <*> children (Literal.Integer <$> source)
float :: Assignment
float :: Assignment Term
float = makeTerm <$> symbol FloatingPointLiteral <*> children (Literal.Float <$> source)
string :: Assignment
string :: Assignment Term
string = makeTerm <$> symbol StringLiteral <*> (Literal.TextElement <$> source)
char :: Assignment
char :: Assignment Term
char = makeTerm <$> symbol CharacterLiteral <*> (Literal.TextElement <$> source)
-- Identifiers
identifier :: Assignment
identifier = makeTerm <$> (symbol Identifier <|> symbol TypeIdentifier) <*> (Syntax.Identifier . name <$> source)
identifier :: Assignment Term
identifier = makeTerm <$> symbol Identifier <*> (Syntax.Identifier . name <$> source)
identifier' :: Assignment.Assignment [] Grammar Name
identifier' = (symbol Identifier <|> symbol TypeIdentifier) *> (name <$> source)
typeIdentifier :: Assignment Term
typeIdentifier = makeTerm <$> symbol TypeIdentifier <*> (Syntax.Identifier . name <$> source)
scopedIdentifier :: Assignment
identifier' :: Assignment Name
identifier' = (symbol Identifier <|> symbol TypeIdentifier <|> symbol Identifier') *> (name <$> source)
scopedIdentifier :: Assignment Term
scopedIdentifier = makeTerm <$> symbol ScopedIdentifier <*> children (Expression.MemberAccess <$> term expression <*> identifier')
superInterfaces :: Assignment.Assignment [] Grammar [Term]
superInterfaces :: Assignment [Term]
superInterfaces = symbol SuperInterfaces *> children (symbol InterfaceTypeList *> children(manyTerm type'))
-- Declarations
class' :: Assignment
class' :: Assignment Term
class' = makeTerm <$> symbol ClassDeclaration <*> children (makeClass <$> many modifier <*> term identifier <*> (typeParameters <|> pure []) <*> optional superClass <*> (superInterfaces <|> pure []) <*> classBody)
where
makeClass modifiers identifier typeParams superClass superInterfaces = Declaration.Class (modifiers <> typeParams) identifier (maybeToList superClass <> superInterfaces) -- not doing an assignment, just straight up function
classBody = makeTerm <$> symbol ClassBody <*> children (manyTerm expression)
makeClass modifiers identifier typeParams superClass superInterfaces = Declaration.Class (modifiers <> typeParams) identifier (maybeToList superClass <> superInterfaces)
superClass = symbol Superclass *> children type'
-- TODO: superclass
-- need to match the superclass node when it exists (which will be a rule, similar to how the type params rule matches the typeparams node when it exists)
-- optional, when we have a single term
-- superInterfaces is also optional but since it produces a list, lists already have an empty value so we don't need to wrap it up in a maybe to get an empty value
fieldDeclaration :: Assignment
classBody :: Assignment Term
classBody = makeTerm <$> symbol Grammar.ClassBody <*> children (manyTerm expression)
staticInitializer :: Assignment Term
staticInitializer = makeTerm <$> symbol Grammar.StaticInitializer <*> children (Java.Syntax.StaticInitializer <$> block)
fieldDeclaration :: Assignment Term
fieldDeclaration = makeTerm <$> symbol FieldDeclaration <*> children ((,) <$> manyTerm modifier <*> type' <**> variableDeclaratorList)
method :: Assignment
method :: Assignment Term
method = makeTerm <$> symbol MethodDeclaration <*> children (makeMethod <$> many modifier <*> emptyTerm <*> methodHeader <*> methodBody)
where
methodBody = symbol MethodBody *> children (term expression <|> emptyTerm)
methodDeclarator = symbol MethodDeclarator *> children ( (,) <$> identifier <*> formalParameters)
methodHeader = symbol MethodHeader *> children ((,,,,) <$> (typeParameters <|> pure []) <*> manyTerm annotation <*> type' <*> methodDeclarator <*> (throws <|> pure []))
makeMethod modifiers receiver (typeParams, annotations, returnType, (name, params), throws) = Declaration.Method (returnType : modifiers <> typeParams <> annotations <> throws) receiver name params
-- methodHeader needs to include typeParameters (it does)
generic :: Assignment
generic :: Assignment Term
generic = makeTerm <$> symbol Grammar.GenericType <*> children(Java.Syntax.GenericType <$> term type' <*> manyTerm type')
methodInvocation :: Assignment
methodInvocation = makeTerm <$> symbol MethodInvocation <*> children (uncurry Expression.Call <$> (callFunction <$> expression <*> optional ((,) <$ token AnonDot <*> manyTerm typeArgument <*> identifier')) <*> (argumentList <|> pure []) <*> emptyTerm)
methodInvocation :: Assignment Term
methodInvocation = makeTerm <$> symbol MethodInvocation <*> children (uncurry Expression.Call <$> (callFunction <$> expression <*> optional ((,) <$ optional (token AnonRParen) <* token AnonDot <*> manyTerm typeArgument <*> identifier')) <*> (argumentList <|> pure []) <*> emptyTerm)
where
callFunction a (Just (typeArguments, b)) = (typeArguments, makeTerm1 (Expression.MemberAccess a b))
callFunction a Nothing = ([], a)
explicitConstructorInvocation :: Assignment
explicitConstructorInvocation = makeTerm <$> symbol ExplicitConstructorInvocation <*> children (uncurry Expression.Call <$> (callFunction <$> term expression <*> optional ((,) <$ token AnonDot <*> manyTerm type' <*> identifier')) <*> argumentList <*> emptyTerm)
methodReference :: Assignment Term
methodReference = makeTerm <$> symbol Grammar.MethodReference <*> children (Java.Syntax.MethodReference <$> term type' <*> manyTerm typeArgument <*> (new <|> term identifier))
where new = makeTerm <$> token AnonNew <*> pure Java.Syntax.NewKeyword
explicitConstructorInvocation :: Assignment Term
explicitConstructorInvocation = makeTerm <$> symbol ExplicitConstructorInvocation <*> children (uncurry Expression.Call <$> (callFunction <$> term expression <*> optional ((,) <$ optional (token AnonRParen) <* token AnonDot <*> manyTerm type' <*> identifier')) <*> argumentList <*> emptyTerm)
where
callFunction a (Just (typeArguments, b)) = (typeArguments, makeTerm1 (Expression.MemberAccess a b))
callFunction a Nothing = ([], a)
module' :: Assignment
module' = toTerm (branchNode ModuleDeclaration (Java.Syntax.Module <$> expression <*> many expression))
module' :: Assignment Term
module' = makeTerm <$> symbol ModuleDeclaration <*> children (Java.Syntax.Module <$> expression <*> many expression)
import' :: Assignment
import' :: Assignment Term
import' = makeTerm <$> symbol ImportDeclaration <*> children (Java.Syntax.Import <$> someTerm (expression <|> asterisk))
where asterisk = makeTerm <$> token Grammar.Asterisk <*> pure Java.Syntax.Asterisk
interface :: Assignment
interface :: Assignment Term
interface = makeTerm <$> symbol InterfaceDeclaration <*> children (normal <|> annotationType)
where
interfaceBody = makeTerm <$> symbol InterfaceBody <*> children (manyTerm interfaceMemberDeclaration)
normal = symbol NormalInterfaceDeclaration *> children (makeInterface <$> manyTerm modifier <*> identifier <*> (typeParameters <|> pure []) <*> interfaceBody)
normal = symbol NormalInterfaceDeclaration *> children (makeInterface <$> manyTerm modifier <*> identifier <*> (typeParameters <|> pure []) <*> (extends <|> pure []) <*> interfaceBody)
makeInterface modifiers identifier typeParams = Declaration.InterfaceDeclaration (modifiers <> typeParams) identifier
annotationType = symbol AnnotationTypeDeclaration *> children (Declaration.InterfaceDeclaration [] <$> identifier <*> annotationTypeBody)
annotationTypeBody = makeTerm <$> symbol AnnotationTypeBody <*> children (many expression)
interfaceMemberDeclaration = symbol InterfaceMemberDeclaration *> children (term expression)
annotationType = symbol AnnotationTypeDeclaration *> children (Declaration.InterfaceDeclaration [] <$> identifier <*> pure [] <*> annotationTypeBody)
annotationTypeBody = makeTerm <$> symbol AnnotationTypeBody <*> children (manyTerm annotationTypeMember)
annotationTypeMember = symbol AnnotationTypeMemberDeclaration *> children (class' <|> interface <|> constant <|> annotationTypeElement)
annotationTypeElement = makeTerm <$> symbol AnnotationTypeElementDeclaration <*> children (Java.Syntax.AnnotationTypeElement <$> many modifier <*> type' <*> identifier <*> (dims <|> pure []) <*> (defaultValue <|> emptyTerm))
defaultValue = makeTerm <$> symbol DefaultValue <*> children (Java.Syntax.DefaultValue <$> elementValue)
elementValue = symbol ElementValue *> children (term expression)
interfaceMemberDeclaration = symbol InterfaceMemberDeclaration *> children (constant <|> method <|> class' <|> interface)
extends = symbol ExtendsInterfaces *> children (symbol InterfaceTypeList *> children (manyTerm type'))
package :: Assignment
constant :: Assignment Term
constant = makeTerm <$> symbol ConstantDeclaration <*> children ((,) [] <$> type' <**> variableDeclaratorList)
package :: Assignment Term
package = makeTerm <$> symbol PackageDeclaration <*> children (Java.Syntax.Package <$> someTerm expression)
enum :: Assignment
enum :: Assignment Term
enum = makeTerm <$> symbol Grammar.EnumDeclaration <*> children (Java.Syntax.EnumDeclaration <$> manyTerm modifier <*> term identifier <*> (superInterfaces <|> pure []) <*> manyTerm enumConstant <*> (enumBodyDeclarations <|> pure []))
where
enumConstant = symbol EnumConstant *> children (term identifier)
enumBodyDeclarations = symbol EnumBodyDeclarations *> children (manyTerm expression)
return' :: Assignment
return' :: Assignment Term
return' = makeTerm <$> symbol ReturnStatement <*> (Statement.Return <$> children (expression <|> emptyTerm))
-- method expressions
dims :: Assignment.Assignment [] Grammar [Term]
dims :: Assignment [Term]
dims = symbol Dims *> children (many (emptyTerm <* token AnonLBracket <* token AnonRBracket))
type' :: Assignment
dimsExpr :: Assignment Term
dimsExpr = makeTerm <$> symbol Grammar.DimsExpr <*> children (Java.Syntax.DimsExpr <$> manyTerm annotation <*> manyTerm expression)
type' :: Assignment Term
type' = choice [
makeTerm <$> token VoidType <*> pure Type.Void
, makeTerm <$> token IntegralType <*> pure Type.Int
, makeTerm <$> token FloatingPointType <*> pure Type.Float
, makeTerm <$> token BooleanType <*> pure Type.Bool
makeTerm <$> symbol VoidType <*> children (pure Type.Void)
, makeTerm <$> symbol IntegralType <*> children (pure Type.Int)
, makeTerm <$> symbol FloatingPointType <*> children (pure Type.Float)
, makeTerm <$> symbol BooleanType <*> children (pure Type.Bool)
, symbol ArrayType *> children (array <$> type' <*> dims) -- type rule recurs into itself
, symbol CatchType *> children (term type')
, symbol ExceptionType *> children (term type')
, makeTerm <$> symbol ScopedTypeIdentifier <*> children (Expression.MemberAccess <$> term type' <*> identifier')
, wildcard
, identifier
, typeIdentifier
, generic
, typeArgument
, annotatedType
]
where array = foldl (\into each -> makeTerm1 (Type.Array (Just each) into))
typeArgument :: Assignment
annotatedType :: Assignment Term
annotatedType = makeTerm <$> symbol AnnotatedType <*> children (Java.Syntax.AnnotatedType <$> many annotation <*> type')
typeArgument :: Assignment Term
typeArgument = symbol TypeArgument *> children (term type')
wildcard :: Assignment
wildcard :: Assignment Term
wildcard = makeTerm <$> symbol Grammar.Wildcard <*> children (Java.Syntax.Wildcard <$> manyTerm annotation <*> optional (super <|> extends))
where
super = makeTerm <$> token Super <*> (Java.Syntax.WildcardBoundSuper <$> type')
extends = makeTerm1 <$> (Java.Syntax.WildcardBoundExtends <$> type')
if' :: Assignment
if' :: Assignment Term
if' = makeTerm <$> symbol IfThenElseStatement <*> children (Statement.If <$> term expression <*> term expression <*> (term expression <|> emptyTerm))
block :: Assignment
block :: Assignment Term
block = makeTerm <$> symbol Block <*> children (manyTerm expression)
while :: Assignment
while :: Assignment Term
while = makeTerm <$> symbol WhileStatement <*> children (Statement.While <$> term expression <*> term expression)
doWhile :: Assignment
doWhile :: Assignment Term
doWhile = makeTerm <$> symbol DoStatement <*> children (flip Statement.DoWhile <$> term expression <*> term expression)
switch :: Assignment
switch :: Assignment Term
switch = makeTerm <$> symbol SwitchStatement <*> children (Statement.Match <$> term expression <*> switchBlock)
where
switchBlock = makeTerm <$> symbol SwitchBlock <*> children (manyTerm switchLabel)
switchLabel = makeTerm <$> symbol SwitchLabel <*> (Statement.Pattern <$> children (term expression <|> emptyTerm) <*> expressions)
break :: Assignment
break :: Assignment Term
break = makeTerm <$> symbol BreakStatement <*> children (Statement.Break <$> (term expression <|> emptyTerm))
continue :: Assignment
continue :: Assignment Term
continue = makeTerm <$> symbol ContinueStatement <*> children (Statement.Continue <$> (term expression <|> emptyTerm))
throw :: Assignment
throw :: Assignment Term
throw = makeTerm <$> symbol ThrowStatement <*> children (Statement.Throw <$> term expression)
try :: Assignment
try = makeTerm <$> symbol TryStatement <*> children (Statement.Try <$> term expression <*> (append <$> optional catches <*> optional finally))
where
catches = symbol Catches *> children (manyTerm catch)
catch = makeTerm <$> symbol CatchClause <*> children (Statement.Catch <$> catchFormalParameter <*> term expression)
catchFormalParameter = makeTerm <$> symbol CatchFormalParameter <*> children (flip Type.Annotation <$> type' <* symbol VariableDeclaratorId <*> children identifier)
finally = makeTerm <$> symbol Finally <*> children (Statement.Finally <$> term expression)
-- append catches finally =
append Nothing Nothing = []
append Nothing (Just a) = [a]
append (Just a) Nothing = a
append (Just a) (Just b) = a <> [b]
try :: Assignment Term
try = symbol TryStatement *> children tryWithResources <|> makeTerm <$> symbol TryStatement <*> children (Statement.Try <$> term expression <*> (append <$> optional catches <*> optional finally))
for :: Assignment
catches :: Assignment [Term]
catches = symbol Catches *> children (manyTerm catch)
where
catch = makeTerm <$> symbol CatchClause <*> children (Statement.Catch <$> catchFormalParameter <*> term expression)
catchFormalParameter = makeTerm <$> symbol CatchFormalParameter <*> children (flip Type.Annotation <$> catchType <* symbol VariableDeclaratorId <*> children identifier)
catchType :: Assignment Term
catchType = makeTerm <$> symbol CatchType <*> (Java.Syntax.CatchType <$> many type')
finally :: Assignment Term
finally = makeTerm <$> symbol Finally <*> children (Statement.Finally <$> term expression)
append :: Maybe [a] -> Maybe a -> [a]
append Nothing Nothing = []
append Nothing (Just a) = [a]
append (Just a) Nothing = a
append (Just a) (Just b) = a <> [b]
tryWithResources :: Assignment Term
tryWithResources = makeTerm <$> symbol TryWithResourcesStatement <*> children (Java.Syntax.TryWithResources <$> resourceSpecification <*> block <*> (append <$> optional catches <*> optional finally))
where
resourceSpecification = symbol ResourceSpecification *> children (manyTerm resource)
resource = symbol Resource *> children variableAccess <|> makeTerm <$> symbol Resource <*> children (makeSingleDecl <$> many modifier <*> type' <*> variableDeclaratorId <*> term expression)
variableAccess = symbol VariableAccess *> children (identifier <|> fieldAccess)
makeSingleDecl modifiers type' target = Statement.Assignment [] (makeTerm1 (Java.Syntax.Variable modifiers type' target))
for :: Assignment Term
for = symbol ForStatement *> children (basicFor <|> enhancedFor)
basicFor :: Assignment
basicFor :: Assignment Term
basicFor = makeTerm <$> symbol BasicForStatement <*> children (Statement.For <$ token AnonFor <* token AnonLParen <*> (token AnonSemicolon *> emptyTerm <|> forInit <* token AnonSemicolon) <*> (token AnonSemicolon *> emptyTerm <|> term expression <* token AnonSemicolon) <*> forStep <*> term expression)
where
forInit = symbol ForInit *> children (term expression)
forStep = makeTerm <$> location <*> manyTermsTill expression (token AnonRParen)
enhancedFor :: Assignment
enhancedFor :: Assignment Term
enhancedFor = makeTerm <$> symbol EnhancedForStatement <*> children (Statement.ForEach <$> (variable <$> manyTerm modifier <*> type' <*> variableDeclaratorId) <*> term expression <*> term expression)
where variable modifiers type' variableDeclaratorId = makeTerm1 (Java.Syntax.Variable modifiers type' variableDeclaratorId)
-- TODO: instanceOf
binary :: Assignment
binary = makeTerm' <$> symbol BinaryExpression <*> children (infixTerm expression expression
assert :: Assignment Term
assert = makeTerm <$> symbol Grammar.AssertStatement <*> children (Java.Syntax.AssertStatement <$> term expression <*> optional (term expression))
binary :: Assignment Term
binary = makeTerm' <$> symbol BinaryExpression <*> children (infixTerm expressionAndParens expressionAndParens
[ (inject .) . Expression.LessThan <$ symbol AnonLAngle
, (inject .) . Expression.GreaterThan <$ symbol AnonRAngle
, (inject .) . Expression.Equal <$ symbol AnonEqualEqual
@ -444,16 +509,20 @@ binary = makeTerm' <$> symbol BinaryExpression <*> children (infixTerm expressio
, (inject .) . Expression.DividedBy <$ symbol AnonSlash
, (inject .) . Expression.InstanceOf <$ symbol AnonInstanceof
])
where invert cons a b = Expression.Not (makeTerm1 (cons a b))
where
invert cons a b = Expression.Not (makeTerm1 (cons a b))
expressionAndParens = token AnonLParen *> expressionAndParens <* token AnonRParen <|> expression
-- TODO: expressionAndParens is a hack that accommodates Java's nested parens
-- but altering the TreeSitter Java grammar is a better longer term goal.
-- | Match infix terms separated by any of a list of operators, assigning any comments following each operand.
infixTerm :: Assignment
-> Assignment
-> [Assignment.Assignment [] Grammar (Term -> Term -> Sum Syntax Term)]
-> Assignment.Assignment [] Grammar (Sum Syntax Term)
infixTerm :: Assignment Term
-> Assignment Term
-> [Assignment (Term -> Term -> Sum Syntax Term)]
-> Assignment (Sum Syntax Term)
infixTerm = infixContext comment
assignment' :: Assignment
assignment' :: Assignment Term
assignment' = makeTerm' <$> symbol AssignmentExpression <*> children (infixTerm lhs expression
[ (inject .) . Statement.Assignment [] <$ symbol AnonEqual
, assign Expression.Plus <$ symbol AnonPlusEqual
@ -479,7 +548,7 @@ data UnaryType
| UBang
| UTilde
unary :: Assignment
unary :: Assignment Term
unary = make <$> symbol UnaryExpression <*> children ((,) <$> operator <*> term expression)
where
make _ (UPlus, operand) = operand
@ -491,36 +560,37 @@ unary = make <$> symbol UnaryExpression <*> children ((,) <$> operator <*> term
<|> token AnonBang $> UBang
<|> token AnonTilde $> UTilde
update :: Assignment
update :: Assignment Term
update = makeTerm' <$> symbol UpdateExpression <*> children (
inject . Statement.PreIncrement <$ token AnonPlusPlus <*> term expression
<|> inject . Statement.PreDecrement <$ token AnonMinusMinus <*> term expression
<|> inject . Statement.PostIncrement <$> term expression <* token AnonPlusPlus
<|> inject . Statement.PostDecrement <$> term expression <* token AnonMinusMinus)
ternary :: Assignment
ternary :: Assignment Term
ternary = makeTerm <$> symbol TernaryExpression <*> children (Statement.If <$> term expression <*> term expression <*> term expression)
synchronized :: Assignment
synchronized :: Assignment Term
synchronized = makeTerm <$> symbol SynchronizedStatement <*> children (Java.Syntax.Synchronized <$> term expression <*> term expression)
classInstance :: Assignment
classInstance :: Assignment Term
classInstance = makeTerm <$> symbol ClassInstanceCreationExpression <*> children unqualified
where
unqualified = symbol UnqualifiedClassInstanceCreationExpression *> children (Java.Syntax.New <$> type' <*> (argumentList <|> pure []))
unqualified = symbol UnqualifiedClassInstanceCreationExpression *> children (Java.Syntax.New <$> type' <*> (argumentList <|> pure []) <*> optional classBody)
argumentList :: Assignment.Assignment [] Grammar [Term]
classLiteral :: Assignment Term
classLiteral = makeTerm <$> symbol Grammar.ClassLiteral <*> children (Java.Syntax.ClassLiteral <$> type')
argumentList :: Assignment [Term]
argumentList = symbol ArgumentList *> children (manyTerm expression)
super :: Assignment
super :: Assignment Term
super = makeTerm <$> token Super <*> pure Expression.Super
-- INCORRECT: super = makeTerm <$> token Super $> Expression.Super
-- Take partially applied function and replace it instead of applying
this :: Assignment
this :: Assignment Term
this = makeTerm <$> token This <*> pure Expression.This
constructorDeclaration :: Assignment
constructorDeclaration :: Assignment Term
constructorDeclaration = makeTerm <$> symbol ConstructorDeclaration <*> children (
constructor <$> manyTerm modifier <*> constructorDeclarator <*> (throws <|> pure []) <*> constructorBody)
where
@ -528,13 +598,14 @@ constructorDeclaration = makeTerm <$> symbol ConstructorDeclaration <*> children
constructorBody = makeTerm <$> symbol ConstructorBody <*> children (manyTerm expression) -- wrapping list of terms up in single node
constructor modifiers (typeParameters, identifier, formalParameters) = Java.Syntax.Constructor modifiers typeParameters identifier formalParameters -- let partial application do its thing
typeParameters :: Assignment.Assignment [] Grammar [Term]
typeParameters :: Assignment [Term]
typeParameters = symbol TypeParameters *> children (manyTerm typeParam)
where
typeParam = makeTerm <$> symbol Grammar.TypeParameter <*> children (Java.Syntax.TypeParameter <$> manyTerm annotation <*> term identifier <*> (typeBound <|> pure []))
typeBound = symbol TypeBound *> children (manyTerm type')
annotation :: Assignment
annotation :: Assignment Term
annotation = makeTerm <$> symbol NormalAnnotation <*> children (Java.Syntax.Annotation <$> term expression <*> (elementValuePairList <|> pure []))
<|> makeTerm <$> symbol MarkerAnnotation <*> children (Java.Syntax.Annotation <$> term expression <*> pure [])
<|> makeTerm <$> symbol SingleElementAnnotation <*> children (Java.Syntax.Annotation <$> term expression <*> (pure <$> term elementValue))
@ -543,28 +614,33 @@ annotation = makeTerm <$> symbol NormalAnnotation <*> children (Java.Syntax.Anno
elementValuePair = makeTerm <$> symbol ElementValuePair <*> children (Java.Syntax.AnnotationField <$> term expression <*> term elementValue)
elementValue = symbol ElementValue *> children (term expression)
throws :: Assignment.Assignment [] Grammar [Term]
throws = symbol Throws *> children (symbol ExceptionTypeList *> children(manyTerm type'))
throws :: Assignment [Term]
throws = symbol Throws *> children (symbol ExceptionTypeList *> children (manyTerm type'))
formalParameters :: Assignment.Assignment [] Grammar [Term]
formalParameters :: Assignment [Term]
formalParameters = manyTerm (parameter <|> spreadParameter)
where
parameter = makeTerm <$> symbol FormalParameter <*> children (makeAnnotation <$> manyTerm modifier <*> type' <* symbol VariableDeclaratorId <*> children identifier)
makeAnnotation [] type' variableName = Type.Annotation variableName type'
makeAnnotation modifiers type' variableName = Type.Annotation variableName (makeTerm1 (Java.Syntax.TypeWithModifiers modifiers type'))
castExpression :: Assignment
castExpression :: Assignment Term
castExpression = makeTerm <$> symbol CastExpression <*> children (flip Type.Annotation <$> type' <*> term expression)
fieldAccess :: Assignment
fieldAccess :: Assignment Term
fieldAccess = makeTerm <$> symbol FieldAccess <*> children (Expression.MemberAccess <$> term expression <*> identifier')
spreadParameter :: Assignment
spreadParameter :: Assignment Term
spreadParameter = makeTerm <$> symbol Grammar.SpreadParameter <*> children (Java.Syntax.SpreadParameter <$> (makeSingleDecl <$> manyTerm modifier <*> type' <*> variableDeclarator))
where
variableDeclarator = symbol VariableDeclarator *> children ((,) <$> variableDeclaratorId <*> optional expression)
makeSingleDecl modifiers type' (target, Nothing) = makeTerm1 (Java.Syntax.Variable modifiers type' target)
makeSingleDecl modifiers type' (target, Just value) = makeTerm1 (Statement.Assignment [] (makeTerm1 (Java.Syntax.Variable modifiers type' target)) value)
arrayAccess :: Assignment
arrayAccess :: Assignment Term
arrayAccess = makeTerm <$> symbol ArrayAccess <*> children (Expression.Subscript <$> term expression <*> manyTerm expression)
lambda :: Assignment Term
lambda = makeTerm <$> symbol LambdaExpression <*> children (Java.Syntax.Lambda <$> manyTerm expression <*> lambdaBody)
where
lambdaBody = makeTerm <$> symbol Grammar.LambdaBody <*> children (Java.Syntax.LambdaBody <$> manyTerm expression)

View File

@ -1,4 +1,5 @@
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
module Language.Java.Grammar where
import Language.Haskell.TH

View File

@ -1,4 +1,5 @@
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveAnyClass, DuplicateRecordFields #-}
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
module Language.Java.Syntax where
import Data.Abstract.Evaluatable
@ -7,7 +8,7 @@ import Prologue hiding (Constructor)
import Data.JSON.Fields
newtype Import a = Import [a]
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Import where liftEq = genericLiftEq
@ -18,7 +19,7 @@ instance Show1 Import where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Import
data Module a = Module { moduleIdentifier :: !a, moduleStatements :: ![a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Module where liftEq = genericLiftEq
@ -28,7 +29,7 @@ instance Show1 Module where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Module
newtype Package a = Package [a]
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Package where liftEq = genericLiftEq
@ -39,7 +40,7 @@ instance Show1 Package where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Package
data EnumDeclaration a = EnumDeclaration { enumDeclarationModifier :: ![a], enumDeclarationIdentifier :: !a, enumDeclarationSuperInterfaces :: ![a], enumDeclarationConstant :: ![a], enumDeclarationBody :: ![a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 EnumDeclaration where liftEq = genericLiftEq
instance Ord1 EnumDeclaration where liftCompare = genericLiftCompare
@ -48,7 +49,7 @@ instance Evaluatable EnumDeclaration
data Variable a = Variable { variableModifiers :: ![a], variableType :: !a, variableName :: !a}
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Variable where liftEq = genericLiftEq
instance Ord1 Variable where liftCompare = genericLiftCompare
@ -58,7 +59,7 @@ instance Show1 Variable where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Variable
data Synchronized a = Synchronized { synchronizedSubject :: !a, synchronizedBody :: !a}
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Synchronized where liftEq = genericLiftEq
instance Ord1 Synchronized where liftCompare = genericLiftCompare
@ -67,8 +68,8 @@ instance Show1 Synchronized where liftShowsPrec = genericLiftShowsPrec
-- TODO: Implement Eval instance for Synchronized
instance Evaluatable Synchronized
data New a = New { newType :: !a, newArgs :: ![a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
data New a = New { newType :: !a, newArgs :: ![a], newClassBody :: Maybe a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 New where liftEq = genericLiftEq
instance Ord1 New where liftCompare = genericLiftCompare
@ -78,7 +79,7 @@ instance Show1 New where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable New
data Asterisk a = Asterisk
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Asterisk where liftEq = genericLiftEq
instance Ord1 Asterisk where liftCompare = genericLiftCompare
@ -89,7 +90,7 @@ instance Evaluatable Asterisk
data Constructor a = Constructor { constructorModifiers :: ![a], constructorTypeParams :: ![a], constructorIdentifier :: !a, constructorParams :: ![a], constructorThrows :: ![a], constructorBody :: a}
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Constructor where liftEq = genericLiftEq
instance Ord1 Constructor where liftCompare = genericLiftCompare
@ -99,7 +100,7 @@ instance Show1 Constructor where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Constructor
data TypeParameter a = TypeParameter { typeParamAnnotation :: ![a], typeParamIdentifier :: !a, typeParamTypeBound :: ![a]}
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 TypeParameter where liftEq = genericLiftEq
instance Ord1 TypeParameter where liftCompare = genericLiftCompare
@ -109,7 +110,7 @@ instance Show1 TypeParameter where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable TypeParameter
data Annotation a = Annotation { annotationName :: !a, annotationField :: [a]}
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Annotation where liftEq = genericLiftEq
instance Ord1 Annotation where liftCompare = genericLiftCompare
@ -119,7 +120,7 @@ instance Show1 Annotation where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Annotation
data AnnotationField a = AnnotationField { annotationFieldName :: a, annotationFieldValue :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 AnnotationField where liftEq = genericLiftEq
instance Ord1 AnnotationField where liftCompare = genericLiftCompare
@ -129,7 +130,7 @@ instance Show1 AnnotationField where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable AnnotationField
data GenericType a = GenericType { genericTypeIdentifier :: a, genericTypeArguments :: [a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 GenericType where liftEq = genericLiftEq
instance Ord1 GenericType where liftCompare = genericLiftCompare
@ -138,8 +139,28 @@ instance Show1 GenericType where liftShowsPrec = genericLiftShowsPrec
-- TODO: Implement Eval instance for GenericType
instance Evaluatable GenericType
data AnnotatedType a = AnnotatedType { annotationes :: [a], annotatedType :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 AnnotatedType where liftEq = genericLiftEq
instance Ord1 AnnotatedType where liftCompare = genericLiftCompare
instance Show1 AnnotatedType where liftShowsPrec = genericLiftShowsPrec
-- TODO: Implement Eval instance for AnnotatedType
instance Evaluatable AnnotatedType
newtype CatchType a = CatchType { types :: [a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 CatchType where liftEq = genericLiftEq
instance Ord1 CatchType where liftCompare = genericLiftCompare
instance Show1 CatchType where liftShowsPrec = genericLiftShowsPrec
-- TODO: Implement Eval instance for CatchType
instance Evaluatable CatchType
data TypeWithModifiers a = TypeWithModifiers [a] a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 TypeWithModifiers where liftEq = genericLiftEq
instance Ord1 TypeWithModifiers where liftCompare = genericLiftCompare
@ -149,7 +170,7 @@ instance Show1 TypeWithModifiers where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable TypeWithModifiers
data Wildcard a = Wildcard { wildcardAnnotation :: [a], wildcardBounds :: Maybe a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Wildcard where liftEq = genericLiftEq
instance Ord1 Wildcard where liftCompare = genericLiftCompare
@ -159,7 +180,7 @@ instance Show1 Wildcard where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Wildcard
data WildcardBounds a = WildcardBoundExtends { wildcardBoundType :: a} | WildcardBoundSuper { wildcardBoundType :: a}
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 WildcardBounds where liftEq = genericLiftEq
instance Ord1 WildcardBounds where liftCompare = genericLiftCompare
@ -169,7 +190,7 @@ instance Show1 WildcardBounds where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable WildcardBounds
newtype SpreadParameter a = SpreadParameter { spreadParameterVariableDeclarator :: a}
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 SpreadParameter where liftEq = genericLiftEq
instance Ord1 SpreadParameter where liftCompare = genericLiftCompare
@ -177,3 +198,126 @@ instance Show1 SpreadParameter where liftShowsPrec = genericLiftShowsPrec
-- TODO: Implement Eval instance for SpreadParameter
instance Evaluatable SpreadParameter
newtype StaticInitializer a = StaticInitializer { staticInitializerBlock :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 StaticInitializer where liftEq = genericLiftEq
instance Ord1 StaticInitializer where liftCompare = genericLiftCompare
instance Show1 StaticInitializer where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable StaticInitializer
data MethodReference a = MethodReference { methodReferenceType :: !a, methodReferenceTypeArgs :: ![a], methodReferenceIdentifier :: !a}
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 MethodReference where liftEq = genericLiftEq
instance Ord1 MethodReference where liftCompare = genericLiftCompare
instance Show1 MethodReference where liftShowsPrec = genericLiftShowsPrec
-- TODO: Implement Eval instance for TypeWithModifiers
instance Evaluatable MethodReference
data NewKeyword a = NewKeyword
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 NewKeyword where liftEq = genericLiftEq
instance Ord1 NewKeyword where liftCompare = genericLiftCompare
instance Show1 NewKeyword where liftShowsPrec = genericLiftShowsPrec
-- TODO: Implement Eval instance for TypeWithModifiers
instance Evaluatable NewKeyword
data Lambda a = Lambda { lambdaParams :: ![a], lambdaBody :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Lambda where liftEq = genericLiftEq
instance Ord1 Lambda where liftCompare = genericLiftCompare
instance Show1 Lambda where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Lambda
newtype LambdaBody a = LambdaBody { lambdaBodyExpression :: [a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 LambdaBody where liftEq = genericLiftEq
instance Ord1 LambdaBody where liftCompare = genericLiftCompare
instance Show1 LambdaBody where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable LambdaBody
data ArrayCreationExpression a = ArrayCreationExpression { arrayCreationExpressionType :: !a, arrayCreationExpressionDims :: ![a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ArrayCreationExpression where liftEq = genericLiftEq
instance Ord1 ArrayCreationExpression where liftCompare = genericLiftCompare
instance Show1 ArrayCreationExpression where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ArrayCreationExpression
data DimsExpr a = DimsExpr { dimsExprAnnotation :: ![a], dimsExprExpression :: ![a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 DimsExpr where liftEq = genericLiftEq
instance Ord1 DimsExpr where liftCompare = genericLiftCompare
instance Show1 DimsExpr where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable DimsExpr
newtype ClassBody a = ClassBody { classBodyExpression :: [a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ClassBody where liftEq = genericLiftEq
instance Ord1 ClassBody where liftCompare = genericLiftCompare
instance Show1 ClassBody where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ClassBody
newtype ClassLiteral a = ClassLiteral { classLiteralType :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ClassLiteral where liftEq = genericLiftEq
instance Ord1 ClassLiteral where liftCompare = genericLiftCompare
instance Show1 ClassLiteral where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ClassLiteral
data TryWithResources a = TryWithResources { tryResources :: ![a], tryBody :: !a, tryCatch :: ![a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 TryWithResources where liftEq = genericLiftEq
instance Ord1 TryWithResources where liftCompare = genericLiftCompare
instance Show1 TryWithResources where liftShowsPrec = genericLiftShowsPrec
-- TODO: Implement Eval instance for TryWithResources
instance Evaluatable TryWithResources
data AssertStatement a = AssertStatement { assertLHS :: !a, assertRHS :: !(Maybe a) }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 AssertStatement where liftEq = genericLiftEq
instance Ord1 AssertStatement where liftCompare = genericLiftCompare
instance Show1 AssertStatement where liftShowsPrec = genericLiftShowsPrec
-- TODO: Implement Eval instance for AssertStatement
instance Evaluatable AssertStatement
newtype DefaultValue a = DefaultValue { defaultValueElement :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 DefaultValue where liftEq = genericLiftEq
instance Ord1 DefaultValue where liftCompare = genericLiftCompare
instance Show1 DefaultValue where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable DefaultValue
data AnnotationTypeElement a = AnnotationTypeElement { modifiers :: ![a], annotationType :: a, identifier :: !a, dims :: ![a], defaultValue :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 AnnotationTypeElement where liftEq = genericLiftEq
instance Ord1 AnnotationTypeElement where liftCompare = genericLiftCompare
instance Show1 AnnotationTypeElement where liftShowsPrec = genericLiftShowsPrec
-- TODO: Implement Eval instance for AnnotationTypeElement
instance Evaluatable AnnotationTypeElement

View File

@ -1,4 +1,5 @@
{-# LANGUAGE DeriveAnyClass #-}
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
module Language.Markdown.Syntax where
import Prologue hiding (Text)
@ -7,7 +8,7 @@ import qualified Data.Text as T
import Diffing.Algorithm
newtype Document a = Document [a]
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1)
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1)
instance Eq1 Document where liftEq = genericLiftEq
instance Ord1 Document where liftCompare = genericLiftCompare
@ -17,70 +18,70 @@ instance Show1 Document where liftShowsPrec = genericLiftShowsPrec
-- Block elements
newtype Paragraph a = Paragraph [a]
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1)
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1)
instance Eq1 Paragraph where liftEq = genericLiftEq
instance Ord1 Paragraph where liftCompare = genericLiftCompare
instance Show1 Paragraph where liftShowsPrec = genericLiftShowsPrec
data Heading a = Heading { headingLevel :: Int, headingContent :: [a], sectionContent :: [a] }
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1)
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1)
instance Eq1 Heading where liftEq = genericLiftEq
instance Ord1 Heading where liftCompare = genericLiftCompare
instance Show1 Heading where liftShowsPrec = genericLiftShowsPrec
newtype UnorderedList a = UnorderedList [a]
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1)
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1)
instance Eq1 UnorderedList where liftEq = genericLiftEq
instance Ord1 UnorderedList where liftCompare = genericLiftCompare
instance Show1 UnorderedList where liftShowsPrec = genericLiftShowsPrec
newtype OrderedList a = OrderedList [a]
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1)
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1)
instance Eq1 OrderedList where liftEq = genericLiftEq
instance Ord1 OrderedList where liftCompare = genericLiftCompare
instance Show1 OrderedList where liftShowsPrec = genericLiftShowsPrec
newtype BlockQuote a = BlockQuote [a]
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1)
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1)
instance Eq1 BlockQuote where liftEq = genericLiftEq
instance Ord1 BlockQuote where liftCompare = genericLiftCompare
instance Show1 BlockQuote where liftShowsPrec = genericLiftShowsPrec
data ThematicBreak a = ThematicBreak
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1)
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1)
instance Eq1 ThematicBreak where liftEq = genericLiftEq
instance Ord1 ThematicBreak where liftCompare = genericLiftCompare
instance Show1 ThematicBreak where liftShowsPrec = genericLiftShowsPrec
newtype HTMLBlock a = HTMLBlock T.Text
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1)
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1)
instance Eq1 HTMLBlock where liftEq = genericLiftEq
instance Ord1 HTMLBlock where liftCompare = genericLiftCompare
instance Show1 HTMLBlock where liftShowsPrec = genericLiftShowsPrec
newtype Table a = Table [a]
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1)
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1)
instance Eq1 Table where liftEq = genericLiftEq
instance Ord1 Table where liftCompare = genericLiftCompare
instance Show1 Table where liftShowsPrec = genericLiftShowsPrec
newtype TableRow a = TableRow [a]
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1)
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1)
instance Eq1 TableRow where liftEq = genericLiftEq
instance Ord1 TableRow where liftCompare = genericLiftCompare
instance Show1 TableRow where liftShowsPrec = genericLiftShowsPrec
newtype TableCell a = TableCell [a]
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1)
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1)
instance Eq1 TableCell where liftEq = genericLiftEq
instance Ord1 TableCell where liftCompare = genericLiftCompare
@ -90,56 +91,56 @@ instance Show1 TableCell where liftShowsPrec = genericLiftShowsPrec
-- Inline elements
newtype Strong a = Strong [a]
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1)
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1)
instance Eq1 Strong where liftEq = genericLiftEq
instance Ord1 Strong where liftCompare = genericLiftCompare
instance Show1 Strong where liftShowsPrec = genericLiftShowsPrec
newtype Emphasis a = Emphasis [a]
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1)
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1)
instance Eq1 Emphasis where liftEq = genericLiftEq
instance Ord1 Emphasis where liftCompare = genericLiftCompare
instance Show1 Emphasis where liftShowsPrec = genericLiftShowsPrec
newtype Text a = Text T.Text
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1)
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1)
instance Eq1 Text where liftEq = genericLiftEq
instance Ord1 Text where liftCompare = genericLiftCompare
instance Show1 Text where liftShowsPrec = genericLiftShowsPrec
data Link a = Link { linkURL :: T.Text, linkTitle :: Maybe T.Text }
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1)
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1)
instance Eq1 Link where liftEq = genericLiftEq
instance Ord1 Link where liftCompare = genericLiftCompare
instance Show1 Link where liftShowsPrec = genericLiftShowsPrec
data Image a = Image { imageURL :: T.Text, imageTitle :: Maybe T.Text }
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1)
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1)
instance Eq1 Image where liftEq = genericLiftEq
instance Ord1 Image where liftCompare = genericLiftCompare
instance Show1 Image where liftShowsPrec = genericLiftShowsPrec
data Code a = Code { codeLanguage :: Maybe T.Text, codeContent :: T.Text }
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1)
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1)
instance Eq1 Code where liftEq = genericLiftEq
instance Ord1 Code where liftCompare = genericLiftCompare
instance Show1 Code where liftShowsPrec = genericLiftShowsPrec
data LineBreak a = LineBreak
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1)
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1)
instance Eq1 LineBreak where liftEq = genericLiftEq
instance Ord1 LineBreak where liftCompare = genericLiftCompare
instance Show1 LineBreak where liftShowsPrec = genericLiftShowsPrec
newtype Strikethrough a = Strikethrough [a]
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1)
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1)
instance Eq1 Strikethrough where liftEq = genericLiftEq
instance Ord1 Strikethrough where liftCompare = genericLiftCompare

View File

@ -1,4 +1,5 @@
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
module Language.PHP.Grammar where
import Language.Haskell.TH

View File

@ -1,4 +1,5 @@
{-# LANGUAGE DeriveAnyClass #-}
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
module Language.PHP.Syntax where
import Data.Abstract.Evaluatable
@ -11,7 +12,7 @@ import Diffing.Algorithm
import Prologue hiding (Text)
newtype Text a = Text T.Text
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Text where liftEq = genericLiftEq
instance Ord1 Text where liftCompare = genericLiftCompare
@ -20,7 +21,7 @@ instance Evaluatable Text
newtype VariableName a = VariableName a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 VariableName where liftEq = genericLiftEq
instance Ord1 VariableName where liftCompare = genericLiftCompare
@ -66,7 +67,7 @@ include pathTerm f = do
pure (Rval v)
newtype Require a = Require a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Require where liftEq = genericLiftEq
instance Ord1 Require where liftCompare = genericLiftCompare
@ -77,7 +78,7 @@ instance Evaluatable Require where
newtype RequireOnce a = RequireOnce a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 RequireOnce where liftEq = genericLiftEq
instance Ord1 RequireOnce where liftCompare = genericLiftCompare
@ -88,7 +89,7 @@ instance Evaluatable RequireOnce where
newtype Include a = Include a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Include where liftEq = genericLiftEq
instance Ord1 Include where liftCompare = genericLiftCompare
@ -99,7 +100,7 @@ instance Evaluatable Include where
newtype IncludeOnce a = IncludeOnce a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 IncludeOnce where liftEq = genericLiftEq
instance Ord1 IncludeOnce where liftCompare = genericLiftCompare
@ -110,7 +111,7 @@ instance Evaluatable IncludeOnce where
newtype ArrayElement a = ArrayElement a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ArrayElement where liftEq = genericLiftEq
instance Ord1 ArrayElement where liftCompare = genericLiftCompare
@ -118,7 +119,7 @@ instance Show1 ArrayElement where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ArrayElement
newtype GlobalDeclaration a = GlobalDeclaration [a]
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 GlobalDeclaration where liftEq = genericLiftEq
instance Ord1 GlobalDeclaration where liftCompare = genericLiftCompare
@ -126,7 +127,7 @@ instance Show1 GlobalDeclaration where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable GlobalDeclaration
newtype SimpleVariable a = SimpleVariable a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 SimpleVariable where liftEq = genericLiftEq
instance Ord1 SimpleVariable where liftCompare = genericLiftCompare
@ -136,7 +137,7 @@ instance Evaluatable SimpleVariable
-- | TODO: Unify with TypeScript's PredefinedType
newtype CastType a = CastType { _castType :: T.Text }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 CastType where liftEq = genericLiftEq
instance Ord1 CastType where liftCompare = genericLiftCompare
@ -144,7 +145,7 @@ instance Show1 CastType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable CastType
newtype ErrorControl a = ErrorControl a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ErrorControl where liftEq = genericLiftEq
instance Ord1 ErrorControl where liftCompare = genericLiftCompare
@ -152,7 +153,7 @@ instance Show1 ErrorControl where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ErrorControl
newtype Clone a = Clone a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Clone where liftEq = genericLiftEq
instance Ord1 Clone where liftCompare = genericLiftCompare
@ -160,7 +161,7 @@ instance Show1 Clone where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Clone
newtype ShellCommand a = ShellCommand T.Text
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ShellCommand where liftEq = genericLiftEq
instance Ord1 ShellCommand where liftCompare = genericLiftCompare
@ -169,7 +170,7 @@ instance Evaluatable ShellCommand
-- | TODO: Combine with TypeScript update expression.
newtype Update a = Update { _updateSubject :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Update where liftEq = genericLiftEq
instance Ord1 Update where liftCompare = genericLiftCompare
@ -177,7 +178,7 @@ instance Show1 Update where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Update
newtype NewVariable a = NewVariable [a]
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 NewVariable where liftEq = genericLiftEq
instance Ord1 NewVariable where liftCompare = genericLiftCompare
@ -185,7 +186,7 @@ instance Show1 NewVariable where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable NewVariable
newtype RelativeScope a = RelativeScope T.Text
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 RelativeScope where liftEq = genericLiftEq
instance Ord1 RelativeScope where liftCompare = genericLiftCompare
@ -193,7 +194,7 @@ instance Show1 RelativeScope where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable RelativeScope
data QualifiedName a = QualifiedName !a !a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 QualifiedName where liftEq = genericLiftEq
instance Ord1 QualifiedName where liftCompare = genericLiftCompare
@ -205,7 +206,7 @@ instance Evaluatable QualifiedName where
Rval <$> evaluateInScopedEnv namePtr (subtermAddress iden)
newtype NamespaceName a = NamespaceName (NonEmpty a)
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1)
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Diffable, FreeVariables1, Declarations1, ToJSONFields1)
instance Hashable1 NamespaceName where liftHashWithSalt = foldl
instance Eq1 NamespaceName where liftEq = genericLiftEq
@ -217,7 +218,7 @@ instance Evaluatable NamespaceName where
where f ns id = ns >>= flip evaluateInScopedEnv id
newtype ConstDeclaration a = ConstDeclaration [a]
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ConstDeclaration where liftEq = genericLiftEq
instance Ord1 ConstDeclaration where liftCompare = genericLiftCompare
@ -225,7 +226,7 @@ instance Show1 ConstDeclaration where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ConstDeclaration
data ClassConstDeclaration a = ClassConstDeclaration a [a]
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ClassConstDeclaration where liftEq = genericLiftEq
instance Ord1 ClassConstDeclaration where liftCompare = genericLiftCompare
@ -233,7 +234,7 @@ instance Show1 ClassConstDeclaration where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ClassConstDeclaration
newtype ClassInterfaceClause a = ClassInterfaceClause [a]
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ClassInterfaceClause where liftEq = genericLiftEq
instance Ord1 ClassInterfaceClause where liftCompare = genericLiftCompare
@ -241,7 +242,7 @@ instance Show1 ClassInterfaceClause where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ClassInterfaceClause
newtype ClassBaseClause a = ClassBaseClause a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ClassBaseClause where liftEq = genericLiftEq
instance Ord1 ClassBaseClause where liftCompare = genericLiftCompare
@ -250,7 +251,7 @@ instance Evaluatable ClassBaseClause
newtype UseClause a = UseClause [a]
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 UseClause where liftEq = genericLiftEq
instance Ord1 UseClause where liftCompare = genericLiftCompare
@ -258,7 +259,7 @@ instance Show1 UseClause where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable UseClause
newtype ReturnType a = ReturnType a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ReturnType where liftEq = genericLiftEq
instance Ord1 ReturnType where liftCompare = genericLiftCompare
@ -266,7 +267,7 @@ instance Show1 ReturnType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ReturnType
newtype TypeDeclaration a = TypeDeclaration a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 TypeDeclaration where liftEq = genericLiftEq
instance Ord1 TypeDeclaration where liftCompare = genericLiftCompare
@ -274,7 +275,7 @@ instance Show1 TypeDeclaration where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable TypeDeclaration
newtype BaseTypeDeclaration a = BaseTypeDeclaration a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 BaseTypeDeclaration where liftEq = genericLiftEq
instance Ord1 BaseTypeDeclaration where liftCompare = genericLiftCompare
@ -282,7 +283,7 @@ instance Show1 BaseTypeDeclaration where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable BaseTypeDeclaration
newtype ScalarType a = ScalarType T.Text
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ScalarType where liftEq = genericLiftEq
instance Ord1 ScalarType where liftCompare = genericLiftCompare
@ -290,7 +291,7 @@ instance Show1 ScalarType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ScalarType
newtype EmptyIntrinsic a = EmptyIntrinsic a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 EmptyIntrinsic where liftEq = genericLiftEq
instance Ord1 EmptyIntrinsic where liftCompare = genericLiftCompare
@ -298,7 +299,7 @@ instance Show1 EmptyIntrinsic where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable EmptyIntrinsic
newtype ExitIntrinsic a = ExitIntrinsic a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ExitIntrinsic where liftEq = genericLiftEq
instance Ord1 ExitIntrinsic where liftCompare = genericLiftCompare
@ -306,7 +307,7 @@ instance Show1 ExitIntrinsic where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ExitIntrinsic
newtype IssetIntrinsic a = IssetIntrinsic a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 IssetIntrinsic where liftEq = genericLiftEq
instance Ord1 IssetIntrinsic where liftCompare = genericLiftCompare
@ -314,7 +315,7 @@ instance Show1 IssetIntrinsic where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable IssetIntrinsic
newtype EvalIntrinsic a = EvalIntrinsic a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 EvalIntrinsic where liftEq = genericLiftEq
instance Ord1 EvalIntrinsic where liftCompare = genericLiftCompare
@ -322,7 +323,7 @@ instance Show1 EvalIntrinsic where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable EvalIntrinsic
newtype PrintIntrinsic a = PrintIntrinsic a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 PrintIntrinsic where liftEq = genericLiftEq
instance Ord1 PrintIntrinsic where liftCompare = genericLiftCompare
@ -330,7 +331,7 @@ instance Show1 PrintIntrinsic where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable PrintIntrinsic
newtype NamespaceAliasingClause a = NamespaceAliasingClause a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 NamespaceAliasingClause where liftEq = genericLiftEq
instance Ord1 NamespaceAliasingClause where liftCompare = genericLiftCompare
@ -338,7 +339,7 @@ instance Show1 NamespaceAliasingClause where liftShowsPrec = genericLiftShowsPre
instance Evaluatable NamespaceAliasingClause
newtype NamespaceUseDeclaration a = NamespaceUseDeclaration [a]
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 NamespaceUseDeclaration where liftEq = genericLiftEq
instance Ord1 NamespaceUseDeclaration where liftCompare = genericLiftCompare
@ -346,7 +347,7 @@ instance Show1 NamespaceUseDeclaration where liftShowsPrec = genericLiftShowsPre
instance Evaluatable NamespaceUseDeclaration
newtype NamespaceUseClause a = NamespaceUseClause [a]
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 NamespaceUseClause where liftEq = genericLiftEq
instance Ord1 NamespaceUseClause where liftCompare = genericLiftCompare
@ -354,7 +355,7 @@ instance Show1 NamespaceUseClause where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable NamespaceUseClause
newtype NamespaceUseGroupClause a = NamespaceUseGroupClause [a]
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 NamespaceUseGroupClause where liftEq = genericLiftEq
instance Ord1 NamespaceUseGroupClause where liftCompare = genericLiftCompare
@ -362,7 +363,7 @@ instance Show1 NamespaceUseGroupClause where liftShowsPrec = genericLiftShowsPre
instance Evaluatable NamespaceUseGroupClause
data Namespace a = Namespace { namespaceName :: [a], namespaceBody :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Namespace where liftEq = genericLiftEq
instance Ord1 Namespace where liftCompare = genericLiftCompare
@ -385,7 +386,7 @@ instance Evaluatable Namespace where
go [] = subtermValue namespaceBody
data TraitDeclaration a = TraitDeclaration { traitName :: a, traitStatements :: [a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 TraitDeclaration where liftEq = genericLiftEq
instance Ord1 TraitDeclaration where liftCompare = genericLiftCompare
@ -393,7 +394,7 @@ instance Show1 TraitDeclaration where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable TraitDeclaration
data AliasAs a = AliasAs { aliasAsName :: a, aliasAsModifier :: a, aliasAsClause :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 AliasAs where liftEq = genericLiftEq
instance Ord1 AliasAs where liftCompare = genericLiftCompare
@ -401,7 +402,7 @@ instance Show1 AliasAs where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable AliasAs
data InsteadOf a = InsteadOf a a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 InsteadOf where liftEq = genericLiftEq
instance Ord1 InsteadOf where liftCompare = genericLiftCompare
@ -409,7 +410,7 @@ instance Show1 InsteadOf where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable InsteadOf
newtype TraitUseSpecification a = TraitUseSpecification [a]
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 TraitUseSpecification where liftEq = genericLiftEq
instance Ord1 TraitUseSpecification where liftCompare = genericLiftCompare
@ -417,7 +418,7 @@ instance Show1 TraitUseSpecification where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable TraitUseSpecification
data TraitUseClause a = TraitUseClause [a] a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 TraitUseClause where liftEq = genericLiftEq
instance Ord1 TraitUseClause where liftCompare = genericLiftCompare
@ -425,7 +426,7 @@ instance Show1 TraitUseClause where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable TraitUseClause
data DestructorDeclaration a = DestructorDeclaration [a] a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 DestructorDeclaration where liftEq = genericLiftEq
instance Ord1 DestructorDeclaration where liftCompare = genericLiftCompare
@ -433,7 +434,7 @@ instance Show1 DestructorDeclaration where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable DestructorDeclaration
newtype Static a = Static T.Text
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Static where liftEq = genericLiftEq
instance Ord1 Static where liftCompare = genericLiftCompare
@ -441,7 +442,7 @@ instance Show1 Static where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Static
newtype ClassModifier a = ClassModifier T.Text
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ClassModifier where liftEq = genericLiftEq
instance Ord1 ClassModifier where liftCompare = genericLiftCompare
@ -449,7 +450,7 @@ instance Show1 ClassModifier where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ClassModifier
data ConstructorDeclaration a = ConstructorDeclaration [a] [a] a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ConstructorDeclaration where liftEq = genericLiftEq
instance Ord1 ConstructorDeclaration where liftCompare = genericLiftCompare
@ -457,7 +458,7 @@ instance Show1 ConstructorDeclaration where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ConstructorDeclaration
data PropertyDeclaration a = PropertyDeclaration a [a]
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 PropertyDeclaration where liftEq = genericLiftEq
instance Ord1 PropertyDeclaration where liftCompare = genericLiftCompare
@ -465,7 +466,7 @@ instance Show1 PropertyDeclaration where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable PropertyDeclaration
data PropertyModifier a = PropertyModifier a a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 PropertyModifier where liftEq = genericLiftEq
instance Ord1 PropertyModifier where liftCompare = genericLiftCompare
@ -473,7 +474,7 @@ instance Show1 PropertyModifier where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable PropertyModifier
data InterfaceDeclaration a = InterfaceDeclaration a a [a]
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 InterfaceDeclaration where liftEq = genericLiftEq
instance Ord1 InterfaceDeclaration where liftCompare = genericLiftCompare
@ -481,7 +482,7 @@ instance Show1 InterfaceDeclaration where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable InterfaceDeclaration
newtype InterfaceBaseClause a = InterfaceBaseClause [a]
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 InterfaceBaseClause where liftEq = genericLiftEq
instance Ord1 InterfaceBaseClause where liftCompare = genericLiftCompare
@ -489,7 +490,7 @@ instance Show1 InterfaceBaseClause where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable InterfaceBaseClause
newtype Echo a = Echo a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Echo where liftEq = genericLiftEq
instance Ord1 Echo where liftCompare = genericLiftCompare
@ -497,7 +498,7 @@ instance Show1 Echo where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Echo
newtype Unset a = Unset a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Unset where liftEq = genericLiftEq
instance Ord1 Unset where liftCompare = genericLiftCompare
@ -505,7 +506,7 @@ instance Show1 Unset where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Unset
data Declare a = Declare a a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Declare where liftEq = genericLiftEq
instance Ord1 Declare where liftCompare = genericLiftCompare
@ -513,7 +514,7 @@ instance Show1 Declare where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Declare
newtype DeclareDirective a = DeclareDirective a
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 DeclareDirective where liftEq = genericLiftEq
instance Ord1 DeclareDirective where liftCompare = genericLiftCompare
@ -521,7 +522,7 @@ instance Show1 DeclareDirective where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable DeclareDirective
newtype LabeledStatement a = LabeledStatement { _labeledStatementIdentifier :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 LabeledStatement where liftEq = genericLiftEq
instance Ord1 LabeledStatement where liftCompare = genericLiftCompare

View File

@ -1,4 +1,5 @@
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
module Language.Python.Grammar where
import Language.Haskell.TH

View File

@ -1,4 +1,5 @@
{-# LANGUAGE DeriveAnyClass #-}
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
module Language.Python.Syntax where
import Data.Abstract.Environment as Env
@ -9,7 +10,6 @@ import Data.Functor.Classes.Generic
import Data.JSON.Fields
import qualified Data.Language as Language
import qualified Data.List.NonEmpty as NonEmpty
import Data.Mergeable
import qualified Data.Text as T
import Diffing.Algorithm
import GHC.Generics
@ -101,7 +101,7 @@ resolvePythonModules q = do
--
-- If the list of symbols is empty copy everything to the calling environment.
data Import a = Import { importFrom :: QualifiedName, importSymbols :: ![Alias] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Import where liftEq = genericLiftEq
instance Ord1 Import where liftCompare = genericLiftCompare
@ -156,7 +156,7 @@ evalQualifiedImport name path = letrec' name $ \addr -> do
unit <$ makeNamespace name addr Nothing
newtype QualifiedImport a = QualifiedImport { qualifiedImportFrom :: NonEmpty FilePath }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Named1, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Message1 QualifiedImport where
liftEncodeMessage _ _ QualifiedImport{..} = encodeMessageField 1 qualifiedImportFrom
@ -189,7 +189,7 @@ instance Evaluatable QualifiedImport where
makeNamespace name addr Nothing
data QualifiedAliasedImport a = QualifiedAliasedImport { qualifiedAliasedImportFrom :: QualifiedName, qualifiedAliasedImportAlias :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 QualifiedAliasedImport where liftEq = genericLiftEq
instance Ord1 QualifiedAliasedImport where liftCompare = genericLiftCompare
@ -213,7 +213,7 @@ instance Evaluatable QualifiedAliasedImport where
-- | Ellipsis (used in splice expressions and alternatively can be used as a fill in expression, like `undefined` in Haskell)
data Ellipsis a = Ellipsis
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Ellipsis where liftEq = genericLiftEq
instance Ord1 Ellipsis where liftCompare = genericLiftCompare
@ -224,7 +224,7 @@ instance Evaluatable Ellipsis
data Redirect a = Redirect { lhs :: a, rhs :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Redirect where liftEq = genericLiftEq
instance Ord1 Redirect where liftCompare = genericLiftCompare

View File

@ -1,4 +1,5 @@
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
module Language.Ruby.Grammar where
import Language.Haskell.TH

View File

@ -1,4 +1,5 @@
{-# LANGUAGE DeriveAnyClass, DuplicateRecordFields, TupleSections #-}
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
module Language.Ruby.Syntax where
import Control.Monad (unless)
@ -43,7 +44,7 @@ cleanNameOrPath :: Text -> String
cleanNameOrPath = T.unpack . dropRelativePrefix . stripQuotes
data Send a = Send { sendReceiver :: Maybe a, sendSelector :: Maybe a, sendArgs :: [a], sendBlock :: Maybe a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Send where liftEq = genericLiftEq
instance Ord1 Send where liftCompare = genericLiftCompare
@ -58,7 +59,7 @@ instance Evaluatable Send where
Rval <$> call func (map subtermAddress sendArgs) -- TODO pass through sendBlock
data Require a = Require { requireRelative :: Bool, requirePath :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Require where liftEq = genericLiftEq
instance Ord1 Require where liftCompare = genericLiftCompare
@ -86,7 +87,7 @@ doRequire path = do
data Load a = Load { loadPath :: a, loadWrap :: Maybe a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Load where liftEq = genericLiftEq
instance Ord1 Load where liftCompare = genericLiftCompare
@ -120,7 +121,7 @@ doLoad path shouldWrap = do
-- TODO: autoload
data Class a = Class { classIdentifier :: !a, classSuperClass :: !(Maybe a), classBody :: !a }
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Mergeable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
instance Diffable Class where
equivalentBySubterm = Just . classIdentifier
@ -137,7 +138,7 @@ instance Evaluatable Class where
subtermValue classBody <* makeNamespace name addr super)
data Module a = Module { moduleIdentifier :: !a, moduleStatements :: ![a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Eq1 Module where liftEq = genericLiftEq
instance Ord1 Module where liftCompare = genericLiftCompare
@ -150,7 +151,7 @@ instance Evaluatable Module where
value =<< (eval xs <* makeNamespace name addr Nothing))
data LowPrecedenceAnd a = LowPrecedenceAnd { lhs :: a, rhs :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Evaluatable LowPrecedenceAnd where
-- N.B. we have to use Monad rather than Applicative/Traversable on 'And' and 'Or' so that we don't evaluate both operands
@ -164,7 +165,7 @@ instance Ord1 LowPrecedenceAnd where liftCompare = genericLiftCompare
instance Show1 LowPrecedenceAnd where liftShowsPrec = genericLiftShowsPrec
data LowPrecedenceOr a = LowPrecedenceOr { lhs :: a, rhs :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
instance Evaluatable LowPrecedenceOr where
-- N.B. we have to use Monad rather than Applicative/Traversable on 'And' and 'Or' so that we don't evaluate both operands

View File

@ -35,6 +35,7 @@ import qualified Data.Term as Term
import qualified Data.Diff as Diff
import Language.TypeScript.Grammar as Grammar
import qualified Language.TypeScript.Syntax as TypeScript.Syntax
import qualified Language.TypeScript.Resolution as TypeScript.Resolution
import Prologue
import Proto3.Suite (Named1(..), Named(..))
@ -714,7 +715,7 @@ importStatement = makeImportTerm <$> symbol Grammar.ImportStatement <*> childr
makeNameAliasPair from Nothing = (from, from)
-- TODO: Need to validate that inline comments are still handled with this change in assigning to Path and not a Term.
fromClause = symbol Grammar.String *> (TypeScript.Syntax.importPath <$> source)
fromClause = symbol Grammar.String *> (TypeScript.Resolution.importPath <$> source)
debuggerStatement :: Assignment Term
debuggerStatement = makeTerm <$> symbol Grammar.DebuggerStatement <*> (TypeScript.Syntax.Debugger <$ rawSource)
@ -752,8 +753,8 @@ enumAssignment :: Assignment Term
enumAssignment = makeTerm <$> symbol Grammar.EnumAssignment <*> children (Statement.Assignment [] <$> term propertyName <*> term expression)
interfaceDeclaration :: Assignment Term
interfaceDeclaration = makeInterfaceDecl <$> symbol Grammar.InterfaceDeclaration <*> children ((,,,) <$> term identifier <*> (term typeParameters <|> emptyTerm) <*> (term extendsClause <|> emptyTerm) <*> term objectType)
where makeInterfaceDecl loc (identifier, typeParams, clause, objectType) = makeTerm loc (Declaration.InterfaceDeclaration [typeParams, clause] identifier objectType)
interfaceDeclaration = makeInterfaceDecl <$> symbol Grammar.InterfaceDeclaration <*> children ((,,,) <$> term identifier <*> (term typeParameters <|> emptyTerm) <*> optional (term extendsClause) <*> term objectType)
where makeInterfaceDecl loc (identifier, typeParams, clause, objectType) = makeTerm loc (Declaration.InterfaceDeclaration [typeParams] identifier (toList clause) objectType)
ambientDeclaration :: Assignment Term
ambientDeclaration = makeTerm <$> symbol Grammar.AmbientDeclaration <*> children (TypeScript.Syntax.AmbientDeclaration <$> term (choice [declaration, statementBlock]))
@ -770,7 +771,7 @@ exportStatement = makeTerm <$> symbol Grammar.ExportStatement <*> children (flip
makeNameAliasPair from Nothing = TypeScript.Syntax.Alias from from
rawIdentifier = (symbol Identifier <|> symbol Identifier') *> (name <$> source)
-- TODO: Need to validate that inline comments are still handled with this change in assigning to Path and not a Term.
fromClause = symbol Grammar.String *> (TypeScript.Syntax.importPath <$> source)
fromClause = symbol Grammar.String *> (TypeScript.Resolution.importPath <$> source)
propertySignature :: Assignment Term
propertySignature = makePropertySignature <$> symbol Grammar.PropertySignature <*> children ((,,,) <$> (term accessibilityModifier' <|> emptyTerm) <*> (term readonly' <|> emptyTerm) <*> term propertyName <*> (term typeAnnotation' <|> emptyTerm))
@ -839,7 +840,7 @@ variableDeclarator =
requireCall = symbol CallExpression *> children ((symbol Identifier <|> symbol Identifier') *> do
s <- source
guard (s == "require")
symbol Arguments *> children (symbol Grammar.String *> (TypeScript.Syntax.importPath <$> source))
symbol Arguments *> children (symbol Grammar.String *> (TypeScript.Resolution.importPath <$> source))
)

View File

@ -1,4 +1,5 @@
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
module Language.TypeScript.Grammar where
import Language.Haskell.TH

View File

@ -0,0 +1,173 @@
{-# LANGUAGE DeriveAnyClass #-}
module Language.TypeScript.Resolution
( ImportPath (..)
, IsRelative (..)
, importPath
, toName
, resolveWithNodejsStrategy
, resolveModule
, resolveNonRelativePath
, javascriptExtensions
, evalRequire
, typescriptExtensions
) where
import Prologue
import Data.Aeson
import qualified Data.Map as Map
import qualified Data.Text as T
import Proto3.Suite
import qualified Proto3.Wire.Decode as Decode
import qualified Proto3.Wire.Encode as Encode
import System.FilePath.Posix
import Data.Abstract.Evaluatable
import qualified Data.Abstract.Module as M
import Data.Abstract.Package
import Data.Abstract.Path
import qualified Data.Language as Language
data IsRelative = Unknown | Relative | NonRelative
deriving (Bounded, Enum, Finite, MessageField, Named, Eq, Generic, Hashable, Ord, Show, ToJSON)
instance Primitive IsRelative where
encodePrimitive = Encode.enum
decodePrimitive = either (const def) id <$> Decode.enum
primType _ = Named (Single (nameOf (Proxy @IsRelative)))
instance HasDefault IsRelative where
def = Unknown
data ImportPath = ImportPath { unPath :: FilePath, pathIsRelative :: IsRelative }
deriving (Eq, Generic, Hashable, Message, Named, Ord, Show, ToJSON)
instance MessageField ImportPath where
encodeMessageField num = Encode.embedded num . encodeMessage (fieldNumber 1)
decodeMessageField = fromMaybe def <$> Decode.embedded (decodeMessage (fieldNumber 1))
protoType _ = messageField (Prim $ Named (Single (nameOf (Proxy @ImportPath)))) Nothing
instance HasDefault ImportPath where
def = ImportPath mempty Relative
-- TODO: fix the duplication present in this and Python
importPath :: Text -> ImportPath
importPath str = let path = stripQuotes str in ImportPath (T.unpack path) (pathType path)
where
pathType xs | not (T.null xs), T.head xs == '.' = Relative -- TODO: fix partiality
| otherwise = NonRelative
toName :: ImportPath -> Name
toName = name . T.pack . unPath
-- Node.js resolution algorithm: https://nodejs.org/api/modules.html#modules_all_together
--
-- NB: TypeScript has a couple of different strategies, but the main one (and the
-- only one we support) mimics Node.js.
resolveWithNodejsStrategy :: ( Member (Modules address) effects
, Member (Reader M.ModuleInfo) effects
, Member (Reader PackageInfo) effects
, Member (Resumable ResolutionError) effects
, Member Trace effects
)
=> ImportPath
-> [String]
-> Evaluator address value effects M.ModulePath
resolveWithNodejsStrategy (ImportPath path NonRelative) exts = resolveNonRelativePath path exts
resolveWithNodejsStrategy (ImportPath path _) exts = resolveRelativePath path exts
-- | Resolve a relative TypeScript import to a known 'ModuleName' or fail.
--
-- import { b } from "./moduleB" in /root/src/moduleA.ts
--
-- /root/src/moduleB.ts
-- /root/src/moduleB/package.json (if it specifies a "types" property)
-- /root/src/moduleB/index.ts
resolveRelativePath :: ( Member (Modules address) effects
, Member (Reader M.ModuleInfo) effects
, Member (Reader PackageInfo) effects
, Member (Resumable ResolutionError) effects
, Member Trace effects
)
=> FilePath
-> [String]
-> Evaluator address value effects M.ModulePath
resolveRelativePath relImportPath exts = do
M.ModuleInfo{..} <- currentModule
let relRootDir = takeDirectory modulePath
let path = joinPaths relRootDir relImportPath
trace ("attempting to resolve (relative) require/import " <> show relImportPath)
resolveModule path exts >>= either notFound (\x -> x <$ traceResolve relImportPath path)
where
notFound xs = throwResumable $ NotFoundError relImportPath xs Language.TypeScript
-- | Resolve a non-relative TypeScript import to a known 'ModuleName' or fail.
--
-- import { b } from "moduleB" in source file /root/src/moduleA.ts
--
-- /root/src/node_modules/moduleB.ts
-- /root/src/node_modules/moduleB/package.json (if it specifies a "types" property)
-- /root/src/node_modules/moduleB/index.ts
--
-- /root/node_modules/moduleB.ts, etc
-- /node_modules/moduleB.ts, etc
resolveNonRelativePath :: ( Member (Modules address) effects
, Member (Reader M.ModuleInfo) effects
, Member (Reader PackageInfo) effects
, Member (Resumable ResolutionError) effects
, Member Trace effects
)
=> FilePath
-> [String]
-> Evaluator address value effects M.ModulePath
resolveNonRelativePath name exts = do
M.ModuleInfo{..} <- currentModule
go "." modulePath mempty
where
nodeModulesPath dir = takeDirectory dir </> "node_modules" </> name
-- Recursively search in a 'node_modules' directory, stepping up a directory each time.
go root path searched = do
trace ("attempting to resolve (non-relative) require/import " <> show name)
res <- resolveModule (nodeModulesPath path) exts
case res of
Left xs | parentDir <- takeDirectory path , root /= parentDir -> go root parentDir (searched <> xs)
| otherwise -> notFound (searched <> xs)
Right m -> m <$ traceResolve name m
notFound xs = throwResumable $ NotFoundError name xs Language.TypeScript
-- | Resolve a module name to a ModulePath.
resolveModule :: ( Member (Modules address) effects
, Member (Reader PackageInfo) effects
, Member Trace effects
)
=> FilePath -- ^ Module path used as directory to search in
-> [String] -- ^ File extensions to look for
-> Evaluator address value effects (Either [FilePath] M.ModulePath)
resolveModule path' exts = do
let path = makeRelative "." path'
PackageInfo{..} <- currentPackage
let packageDotJSON = Map.lookup (path </> "package.json") packageResolutions
let searchPaths = ((path <.>) <$> exts)
<> maybe mempty (:[]) packageDotJSON
<> (((path </> "index") <.>) <$> exts)
trace ("searching in " <> show searchPaths)
maybe (Left searchPaths) Right <$> resolve searchPaths
typescriptExtensions :: [String]
typescriptExtensions = ["ts", "tsx", "d.ts"]
javascriptExtensions :: [String]
javascriptExtensions = ["js"]
evalRequire :: ( AbstractValue address value effects
, Member (Allocator address value) effects
, Member (Env address) effects
, Member (Modules address) effects
)
=> M.ModulePath
-> Name
-> Evaluator address value effects value
evalRequire modulePath alias = letrec' alias $ \addr -> do
importedEnv <- fst <$> require modulePath
bindAll importedEnv
unit <$ makeNamespace alias addr Nothing

View File

@ -1,855 +1,5 @@
{-# LANGUAGE DeriveAnyClass, DuplicateRecordFields #-}
module Language.TypeScript.Syntax where
module Language.TypeScript.Syntax ( module X ) where
import qualified Data.Abstract.Environment as Env
import Data.Abstract.Evaluatable
import qualified Data.Abstract.Module as M
import Data.Abstract.Package
import Data.Abstract.Path
import Data.Aeson
import Data.JSON.Fields
import qualified Data.Language as Language
import qualified Data.Map as Map
import qualified Data.Text as T
import Diffing.Algorithm
import Prologue
import System.FilePath.Posix
import Proto3.Suite
import qualified Proto3.Wire.Encode as Encode
import qualified Proto3.Wire.Decode as Decode
data IsRelative = Unknown | Relative | NonRelative
deriving (Bounded, Enum, Finite, MessageField, Named, Eq, Generic, Hashable, Ord, Show, ToJSON)
instance Primitive IsRelative where
encodePrimitive = Encode.enum
decodePrimitive = either (const def) id <$> Decode.enum
primType _ = Named (Single (nameOf (Proxy @IsRelative)))
instance HasDefault IsRelative where
def = Unknown
data ImportPath = ImportPath { unPath :: FilePath, pathIsRelative :: IsRelative }
deriving (Eq, Generic, Hashable, Message, Named, Ord, Show, ToJSON)
instance MessageField ImportPath where
encodeMessageField num = Encode.embedded num . encodeMessage (fieldNumber 1)
decodeMessageField = fromMaybe def <$> Decode.embedded (decodeMessage (fieldNumber 1))
protoType _ = messageField (Prim $ Named (Single (nameOf (Proxy @ImportPath)))) Nothing
instance HasDefault ImportPath where
def = ImportPath mempty Relative
-- TODO: fix the duplication present in this and Python
importPath :: Text -> ImportPath
importPath str = let path = stripQuotes str in ImportPath (T.unpack path) (pathType path)
where
pathType xs | not (T.null xs), T.head xs == '.' = Relative -- TODO: fix partiality
| otherwise = NonRelative
toName :: ImportPath -> Name
toName = name . T.pack . unPath
-- Node.js resolution algorithm: https://nodejs.org/api/modules.html#modules_all_together
--
-- NB: TypeScript has a couple of different strategies, but the main one (and the
-- only one we support) mimics Node.js.
resolveWithNodejsStrategy :: ( Member (Modules address) effects
, Member (Reader M.ModuleInfo) effects
, Member (Reader PackageInfo) effects
, Member (Resumable ResolutionError) effects
, Member Trace effects
)
=> ImportPath
-> [String]
-> Evaluator address value effects M.ModulePath
resolveWithNodejsStrategy (ImportPath path NonRelative) exts = resolveNonRelativePath path exts
resolveWithNodejsStrategy (ImportPath path _) exts = resolveRelativePath path exts
-- | Resolve a relative TypeScript import to a known 'ModuleName' or fail.
--
-- import { b } from "./moduleB" in /root/src/moduleA.ts
--
-- /root/src/moduleB.ts
-- /root/src/moduleB/package.json (if it specifies a "types" property)
-- /root/src/moduleB/index.ts
resolveRelativePath :: ( Member (Modules address) effects
, Member (Reader M.ModuleInfo) effects
, Member (Reader PackageInfo) effects
, Member (Resumable ResolutionError) effects
, Member Trace effects
)
=> FilePath
-> [String]
-> Evaluator address value effects M.ModulePath
resolveRelativePath relImportPath exts = do
M.ModuleInfo{..} <- currentModule
let relRootDir = takeDirectory modulePath
let path = joinPaths relRootDir relImportPath
trace ("attempting to resolve (relative) require/import " <> show relImportPath)
resolveModule path exts >>= either notFound (\x -> x <$ traceResolve relImportPath path)
where
notFound xs = throwResumable $ NotFoundError relImportPath xs Language.TypeScript
-- | Resolve a non-relative TypeScript import to a known 'ModuleName' or fail.
--
-- import { b } from "moduleB" in source file /root/src/moduleA.ts
--
-- /root/src/node_modules/moduleB.ts
-- /root/src/node_modules/moduleB/package.json (if it specifies a "types" property)
-- /root/src/node_modules/moduleB/index.ts
--
-- /root/node_modules/moduleB.ts, etc
-- /node_modules/moduleB.ts, etc
resolveNonRelativePath :: ( Member (Modules address) effects
, Member (Reader M.ModuleInfo) effects
, Member (Reader PackageInfo) effects
, Member (Resumable ResolutionError) effects
, Member Trace effects
)
=> FilePath
-> [String]
-> Evaluator address value effects M.ModulePath
resolveNonRelativePath name exts = do
M.ModuleInfo{..} <- currentModule
go "." modulePath mempty
where
nodeModulesPath dir = takeDirectory dir </> "node_modules" </> name
-- Recursively search in a 'node_modules' directory, stepping up a directory each time.
go root path searched = do
trace ("attempting to resolve (non-relative) require/import " <> show name)
res <- resolveModule (nodeModulesPath path) exts
case res of
Left xs | parentDir <- takeDirectory path , root /= parentDir -> go root parentDir (searched <> xs)
| otherwise -> notFound (searched <> xs)
Right m -> m <$ traceResolve name m
notFound xs = throwResumable $ NotFoundError name xs Language.TypeScript
-- | Resolve a module name to a ModulePath.
resolveModule :: ( Member (Modules address) effects
, Member (Reader PackageInfo) effects
, Member Trace effects
)
=> FilePath -- ^ Module path used as directory to search in
-> [String] -- ^ File extensions to look for
-> Evaluator address value effects (Either [FilePath] M.ModulePath)
resolveModule path' exts = do
let path = makeRelative "." path'
PackageInfo{..} <- currentPackage
let packageDotJSON = Map.lookup (path </> "package.json") packageResolutions
let searchPaths = ((path <.>) <$> exts)
<> maybe mempty (:[]) packageDotJSON
<> (((path </> "index") <.>) <$> exts)
trace ("searching in " <> show searchPaths)
maybe (Left searchPaths) Right <$> resolve searchPaths
typescriptExtensions :: [String]
typescriptExtensions = ["ts", "tsx", "d.ts"]
javascriptExtensions :: [String]
javascriptExtensions = ["js"]
evalRequire :: ( AbstractValue address value effects
, Member (Allocator address value) effects
, Member (Env address) effects
, Member (Modules address) effects
)
=> M.ModulePath
-> Name
-> Evaluator address value effects value
evalRequire modulePath alias = letrec' alias $ \addr -> do
importedEnv <- fst <$> require modulePath
bindAll importedEnv
unit <$ makeNamespace alias addr Nothing
data Import a = Import { importSymbols :: ![Alias], importFrom :: ImportPath }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Import where liftEq = genericLiftEq
instance Ord1 Import where liftCompare = genericLiftCompare
instance Show1 Import where liftShowsPrec = genericLiftShowsPrec
-- http://www.typescriptlang.org/docs/handbook/module-resolution.html
instance Evaluatable Import where
eval (Import symbols importPath) = do
modulePath <- resolveWithNodejsStrategy importPath typescriptExtensions
importedEnv <- fst <$> require modulePath
bindAll (renamed importedEnv)
rvalBox unit
where
renamed importedEnv
| Prologue.null symbols = importedEnv
| otherwise = Env.overwrite (toTuple <$> symbols) importedEnv
data JavaScriptRequire a = JavaScriptRequire { javascriptRequireIden :: !a, javascriptRequireFrom :: ImportPath }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 JavaScriptRequire where liftEq = genericLiftEq
instance Ord1 JavaScriptRequire where liftCompare = genericLiftCompare
instance Show1 JavaScriptRequire where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable JavaScriptRequire where
eval (JavaScriptRequire aliasTerm importPath) = do
modulePath <- resolveWithNodejsStrategy importPath javascriptExtensions
alias <- maybeM (throwEvalError NoNameError) (declaredName (subterm aliasTerm))
rvalBox =<< evalRequire modulePath alias
data QualifiedAliasedImport a = QualifiedAliasedImport { qualifiedAliasedImportAlias :: !a, qualifiedAliasedImportFrom :: ImportPath }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 QualifiedAliasedImport where liftEq = genericLiftEq
instance Ord1 QualifiedAliasedImport where liftCompare = genericLiftCompare
instance Show1 QualifiedAliasedImport where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable QualifiedAliasedImport where
eval (QualifiedAliasedImport aliasTerm importPath) = do
modulePath <- resolveWithNodejsStrategy importPath typescriptExtensions
alias <- maybeM (throwEvalError NoNameError) (declaredName (subterm aliasTerm))
rvalBox =<< evalRequire modulePath alias
newtype SideEffectImport a = SideEffectImport { sideEffectImportFrom :: ImportPath }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 SideEffectImport where liftEq = genericLiftEq
instance Ord1 SideEffectImport where liftCompare = genericLiftCompare
instance Show1 SideEffectImport where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable SideEffectImport where
eval (SideEffectImport importPath) = do
modulePath <- resolveWithNodejsStrategy importPath typescriptExtensions
void $ require modulePath
rvalBox unit
-- | Qualified Export declarations
newtype QualifiedExport a = QualifiedExport { qualifiedExportSymbols :: [Alias] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 QualifiedExport where liftEq = genericLiftEq
instance Ord1 QualifiedExport where liftCompare = genericLiftCompare
instance Show1 QualifiedExport where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable QualifiedExport where
eval (QualifiedExport exportSymbols) = do
-- Insert the aliases with no addresses.
for_ exportSymbols $ \Alias{..} ->
export aliasValue aliasName Nothing
rvalBox unit
data Alias = Alias { aliasValue :: Name, aliasName :: Name }
deriving (Eq, Generic, Hashable, Ord, Show, Message, Named, ToJSON)
toTuple :: Alias -> (Name, Name)
toTuple Alias{..} = (aliasValue, aliasName)
-- | Qualified Export declarations that export from another module.
data QualifiedExportFrom a = QualifiedExportFrom { qualifiedExportFrom :: ImportPath, qualifiedExportFromSymbols :: ![Alias]}
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 QualifiedExportFrom where liftEq = genericLiftEq
instance Ord1 QualifiedExportFrom where liftCompare = genericLiftCompare
instance Show1 QualifiedExportFrom where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable QualifiedExportFrom where
eval (QualifiedExportFrom importPath exportSymbols) = do
modulePath <- resolveWithNodejsStrategy importPath typescriptExtensions
importedEnv <- fst <$> require modulePath
-- Look up addresses in importedEnv and insert the aliases with addresses into the exports.
for_ exportSymbols $ \Alias{..} -> do
let address = Env.lookup aliasValue importedEnv
maybe (throwEvalError $ ExportError modulePath aliasValue) (export aliasValue aliasName . Just) address
rvalBox unit
newtype DefaultExport a = DefaultExport { defaultExport :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 DefaultExport where liftEq = genericLiftEq
instance Ord1 DefaultExport where liftCompare = genericLiftCompare
instance Show1 DefaultExport where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable DefaultExport where
eval (DefaultExport term) = do
case declaredName term of
Just name -> do
addr <- lookupOrAlloc name
v <- subtermValue term
assign addr v
export name name Nothing
bind name addr
Nothing -> throwEvalError DefaultExportError
rvalBox unit
-- | Lookup type for a type-level key in a typescript map.
data LookupType a = LookupType { lookupTypeIdentifier :: a, lookupTypeKey :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 LookupType where liftEq = genericLiftEq
instance Ord1 LookupType where liftCompare = genericLiftCompare
instance Show1 LookupType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable LookupType
-- | ShorthandPropertyIdentifier used in object patterns such as var baz = { foo } to mean var baz = { foo: foo }
newtype ShorthandPropertyIdentifier a = ShorthandPropertyIdentifier { contents :: T.Text }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ShorthandPropertyIdentifier where liftEq = genericLiftEq
instance Ord1 ShorthandPropertyIdentifier where liftCompare = genericLiftCompare
instance Show1 ShorthandPropertyIdentifier where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ShorthandPropertyIdentifier
data Union a = Union { unionLeft :: !a, unionRight :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Language.TypeScript.Syntax.Union where liftEq = genericLiftEq
instance Ord1 Language.TypeScript.Syntax.Union where liftCompare = genericLiftCompare
instance Show1 Language.TypeScript.Syntax.Union where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Language.TypeScript.Syntax.Union
data Intersection a = Intersection { intersectionLeft :: !a, intersectionRight :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Intersection where liftEq = genericLiftEq
instance Ord1 Intersection where liftCompare = genericLiftCompare
instance Show1 Intersection where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Intersection
data FunctionType a = FunctionType { functionTypeParameters :: !a, functionFormalParameters :: ![a], functionType :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 FunctionType where liftEq = genericLiftEq
instance Ord1 FunctionType where liftCompare = genericLiftCompare
instance Show1 FunctionType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable FunctionType
data AmbientFunction a = AmbientFunction { ambientFunctionContext :: ![a], ambientFunctionIdentifier :: !a, ambientFunctionParameters :: ![a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 AmbientFunction where liftEq = genericLiftEq
instance Ord1 AmbientFunction where liftCompare = genericLiftCompare
instance Show1 AmbientFunction where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable AmbientFunction
data ImportRequireClause a = ImportRequireClause { importRequireIdentifier :: !a, importRequireSubject :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ImportRequireClause where liftEq = genericLiftEq
instance Ord1 ImportRequireClause where liftCompare = genericLiftCompare
instance Show1 ImportRequireClause where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ImportRequireClause
newtype ImportClause a = ImportClause { importClauseElements :: [a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ImportClause where liftEq = genericLiftEq
instance Ord1 ImportClause where liftCompare = genericLiftCompare
instance Show1 ImportClause where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ImportClause
newtype Tuple a = Tuple { tupleElements :: [a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Tuple where liftEq = genericLiftEq
instance Ord1 Tuple where liftCompare = genericLiftCompare
instance Show1 Tuple where liftShowsPrec = genericLiftShowsPrec
-- This is a tuple type, not a tuple value, so we can't lean on the shared Tuple value
instance Evaluatable Tuple
data Constructor a = Constructor { constructorTypeParameters :: !a, constructorFormalParameters :: ![a], constructorType :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Language.TypeScript.Syntax.Constructor where liftEq = genericLiftEq
instance Ord1 Language.TypeScript.Syntax.Constructor where liftCompare = genericLiftCompare
instance Show1 Language.TypeScript.Syntax.Constructor where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Language.TypeScript.Syntax.Constructor
data TypeParameter a = TypeParameter { typeParameter :: !a, typeParameterConstraint :: !a, typeParameterDefaultType :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 TypeParameter where liftEq = genericLiftEq
instance Ord1 TypeParameter where liftCompare = genericLiftCompare
instance Show1 TypeParameter where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable TypeParameter
data TypeAssertion a = TypeAssertion { typeAssertionParameters :: !a, typeAssertionExpression :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 TypeAssertion where liftEq = genericLiftEq
instance Ord1 TypeAssertion where liftCompare = genericLiftCompare
instance Show1 TypeAssertion where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable TypeAssertion
newtype Annotation a = Annotation { annotationType :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Annotation where liftEq = genericLiftEq
instance Ord1 Annotation where liftCompare = genericLiftCompare
instance Show1 Annotation where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Annotation
newtype Decorator a = Decorator { decoratorTerm :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Decorator where liftEq = genericLiftEq
instance Ord1 Decorator where liftCompare = genericLiftCompare
instance Show1 Decorator where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Decorator
newtype ComputedPropertyName a = ComputedPropertyName { propertyName :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ComputedPropertyName where liftEq = genericLiftEq
instance Ord1 ComputedPropertyName where liftCompare = genericLiftCompare
instance Show1 ComputedPropertyName where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ComputedPropertyName
newtype Constraint a = Constraint { constraintType :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Constraint where liftEq = genericLiftEq
instance Ord1 Constraint where liftCompare = genericLiftCompare
instance Show1 Constraint where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Constraint
newtype DefaultType a = DefaultType { defaultType :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 DefaultType where liftEq = genericLiftEq
instance Ord1 DefaultType where liftCompare = genericLiftCompare
instance Show1 DefaultType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable DefaultType
newtype ParenthesizedType a = ParenthesizedType { parenthesizedType :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ParenthesizedType where liftEq = genericLiftEq
instance Ord1 ParenthesizedType where liftCompare = genericLiftCompare
instance Show1 ParenthesizedType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ParenthesizedType
newtype PredefinedType a = PredefinedType { predefinedType :: T.Text }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 PredefinedType where liftEq = genericLiftEq
instance Ord1 PredefinedType where liftCompare = genericLiftCompare
instance Show1 PredefinedType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable PredefinedType
newtype TypeIdentifier a = TypeIdentifier { contents :: T.Text }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 TypeIdentifier where liftEq = genericLiftEq
instance Ord1 TypeIdentifier where liftCompare = genericLiftCompare
instance Show1 TypeIdentifier where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable TypeIdentifier
data NestedIdentifier a = NestedIdentifier { left :: !a, right :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 NestedIdentifier where liftEq = genericLiftEq
instance Ord1 NestedIdentifier where liftCompare = genericLiftCompare
instance Show1 NestedIdentifier where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable NestedIdentifier
data NestedTypeIdentifier a = NestedTypeIdentifier { left :: !a, right :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 NestedTypeIdentifier where liftEq = genericLiftEq
instance Ord1 NestedTypeIdentifier where liftCompare = genericLiftCompare
instance Show1 NestedTypeIdentifier where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable NestedTypeIdentifier
data GenericType a = GenericType { genericTypeIdentifier :: !a, genericTypeArguments :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 GenericType where liftEq = genericLiftEq
instance Ord1 GenericType where liftCompare = genericLiftCompare
instance Show1 GenericType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable GenericType
data TypePredicate a = TypePredicate { typePredicateIdentifier :: !a, typePredicateType :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 TypePredicate where liftEq = genericLiftEq
instance Ord1 TypePredicate where liftCompare = genericLiftCompare
instance Show1 TypePredicate where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable TypePredicate
newtype ObjectType a = ObjectType { objectTypeElements :: [a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ObjectType where liftEq = genericLiftEq
instance Ord1 ObjectType where liftCompare = genericLiftCompare
instance Show1 ObjectType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ObjectType
data With a = With { withExpression :: !a, withBody :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 With where liftEq = genericLiftEq
instance Ord1 With where liftCompare = genericLiftCompare
instance Show1 With where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable With
newtype AmbientDeclaration a = AmbientDeclaration { ambientDeclarationBody :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 AmbientDeclaration where liftEq = genericLiftEq
instance Ord1 AmbientDeclaration where liftCompare = genericLiftCompare
instance Show1 AmbientDeclaration where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable AmbientDeclaration where
eval (AmbientDeclaration body) = subtermRef body
data EnumDeclaration a = EnumDeclaration { enumDeclarationIdentifier :: !a, enumDeclarationBody :: ![a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 EnumDeclaration where liftEq = genericLiftEq
instance Ord1 EnumDeclaration where liftCompare = genericLiftCompare
instance Show1 EnumDeclaration where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable EnumDeclaration
instance Declarations a => Declarations (EnumDeclaration a) where
declaredName EnumDeclaration{..} = declaredName enumDeclarationIdentifier
newtype ExtendsClause a = ExtendsClause { extendsClauses :: [a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ExtendsClause where liftEq = genericLiftEq
instance Ord1 ExtendsClause where liftCompare = genericLiftCompare
instance Show1 ExtendsClause where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ExtendsClause
newtype ArrayType a = ArrayType { arrayType :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ArrayType where liftEq = genericLiftEq
instance Ord1 ArrayType where liftCompare = genericLiftCompare
instance Show1 ArrayType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ArrayType
newtype FlowMaybeType a = FlowMaybeType { flowMaybeType :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 FlowMaybeType where liftEq = genericLiftEq
instance Ord1 FlowMaybeType where liftCompare = genericLiftCompare
instance Show1 FlowMaybeType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable FlowMaybeType
newtype TypeQuery a = TypeQuery { typeQuerySubject :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 TypeQuery where liftEq = genericLiftEq
instance Ord1 TypeQuery where liftCompare = genericLiftCompare
instance Show1 TypeQuery where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable TypeQuery
newtype IndexTypeQuery a = IndexTypeQuery { indexTypeQuerySubject :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 IndexTypeQuery where liftEq = genericLiftEq
instance Ord1 IndexTypeQuery where liftCompare = genericLiftCompare
instance Show1 IndexTypeQuery where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable IndexTypeQuery
newtype TypeArguments a = TypeArguments { typeArguments :: [a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 TypeArguments where liftEq = genericLiftEq
instance Ord1 TypeArguments where liftCompare = genericLiftCompare
instance Show1 TypeArguments where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable TypeArguments
newtype ThisType a = ThisType { contents :: T.Text }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ThisType where liftEq = genericLiftEq
instance Ord1 ThisType where liftCompare = genericLiftCompare
instance Show1 ThisType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ThisType
newtype ExistentialType a = ExistentialType { contents :: T.Text }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ExistentialType where liftEq = genericLiftEq
instance Ord1 ExistentialType where liftCompare = genericLiftCompare
instance Show1 ExistentialType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ExistentialType
newtype LiteralType a = LiteralType { literalTypeSubject :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 LiteralType where liftEq = genericLiftEq
instance Ord1 LiteralType where liftCompare = genericLiftCompare
instance Show1 LiteralType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable LiteralType
data PropertySignature a = PropertySignature { modifiers :: ![a], propertySignaturePropertyName :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 PropertySignature where liftEq = genericLiftEq
instance Ord1 PropertySignature where liftCompare = genericLiftCompare
instance Show1 PropertySignature where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable PropertySignature
data CallSignature a = CallSignature { callSignatureTypeParameters :: !a, callSignatureParameters :: ![a], callSignatureType :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 CallSignature where liftEq = genericLiftEq
instance Ord1 CallSignature where liftCompare = genericLiftCompare
instance Show1 CallSignature where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable CallSignature
-- | Todo: Move type params and type to context
data ConstructSignature a = ConstructSignature { constructSignatureTypeParameters :: !a, constructSignatureParameters :: ![a], constructSignatureType :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ConstructSignature where liftEq = genericLiftEq
instance Ord1 ConstructSignature where liftCompare = genericLiftCompare
instance Show1 ConstructSignature where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ConstructSignature
data IndexSignature a = IndexSignature { indexSignatureSubject :: a, indexSignatureType :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 IndexSignature where liftEq = genericLiftEq
instance Ord1 IndexSignature where liftCompare = genericLiftCompare
instance Show1 IndexSignature where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable IndexSignature
data AbstractMethodSignature a = AbstractMethodSignature { abstractMethodSignatureContext :: ![a], abstractMethodSignatureName :: !a, abstractMethodSignatureParameters :: ![a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 AbstractMethodSignature where liftEq = genericLiftEq
instance Ord1 AbstractMethodSignature where liftCompare = genericLiftCompare
instance Show1 AbstractMethodSignature where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable AbstractMethodSignature
data Debugger a = Debugger
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Debugger where liftEq = genericLiftEq
instance Ord1 Debugger where liftCompare = genericLiftCompare
instance Show1 Debugger where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Debugger
data ForOf a = ForOf { forOfBinding :: !a, forOfSubject :: !a, forOfBody :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ForOf where liftEq = genericLiftEq
instance Ord1 ForOf where liftCompare = genericLiftCompare
instance Show1 ForOf where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ForOf
data This a = This
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 This where liftEq = genericLiftEq
instance Ord1 This where liftCompare = genericLiftCompare
instance Show1 This where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable This
data LabeledStatement a = LabeledStatement { labeledStatementIdentifier :: !a, labeledStatementSubject :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 LabeledStatement where liftEq = genericLiftEq
instance Ord1 LabeledStatement where liftCompare = genericLiftCompare
instance Show1 LabeledStatement where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable LabeledStatement
newtype Update a = Update { updateSubject :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Update where liftEq = genericLiftEq
instance Ord1 Update where liftCompare = genericLiftCompare
instance Show1 Update where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Update
data Module a = Module { moduleIdentifier :: !a, moduleStatements :: ![a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Module where liftEq = genericLiftEq
instance Ord1 Module where liftCompare = genericLiftCompare
instance Show1 Module where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Module where
eval (Module iden xs) = do
name <- maybeM (throwEvalError NoNameError) (declaredName (subterm iden))
rvalBox =<< letrec' name (\addr ->
value =<< (eval xs <* makeNamespace name addr Nothing))
data InternalModule a = InternalModule { internalModuleIdentifier :: !a, internalModuleStatements :: ![a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 InternalModule where liftEq = genericLiftEq
instance Ord1 InternalModule where liftCompare = genericLiftCompare
instance Show1 InternalModule where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable InternalModule where
eval (InternalModule iden xs) = do
name <- maybeM (throwEvalError NoNameError) (declaredName (subterm iden))
rvalBox =<< letrec' name (\addr ->
value =<< (eval xs <* makeNamespace name addr Nothing))
instance Declarations a => Declarations (InternalModule a) where
declaredName InternalModule{..} = declaredName internalModuleIdentifier
data ImportAlias a = ImportAlias { importAliasSubject :: !a, importAlias :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ImportAlias where liftEq = genericLiftEq
instance Ord1 ImportAlias where liftCompare = genericLiftCompare
instance Show1 ImportAlias where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ImportAlias
data Super a = Super
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Super where liftEq = genericLiftEq
instance Ord1 Super where liftCompare = genericLiftCompare
instance Show1 Super where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Super
data Undefined a = Undefined
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Undefined where liftEq = genericLiftEq
instance Ord1 Undefined where liftCompare = genericLiftCompare
instance Show1 Undefined where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Undefined
data ClassHeritage a = ClassHeritage { classHeritageExtendsClause :: !a, implementsClause :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ClassHeritage where liftEq = genericLiftEq
instance Ord1 ClassHeritage where liftCompare = genericLiftCompare
instance Show1 ClassHeritage where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ClassHeritage
data AbstractClass a = AbstractClass { abstractClassIdentifier :: !a, abstractClassTypeParameters :: !a, classHeritage :: ![a], classBody :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 AbstractClass where liftEq = genericLiftEq
instance Ord1 AbstractClass where liftCompare = genericLiftCompare
instance Show1 AbstractClass where liftShowsPrec = genericLiftShowsPrec
instance Declarations a => Declarations (AbstractClass a) where
declaredName AbstractClass{..} = declaredName abstractClassIdentifier
instance Evaluatable AbstractClass where
eval AbstractClass{..} = do
name <- maybeM (throwEvalError NoNameError) (declaredName (subterm abstractClassIdentifier))
supers <- traverse subtermAddress classHeritage
(v, addr) <- letrec name $ do
void $ subtermValue classBody
classBinds <- Env.head <$> getEnv
klass name supers classBinds
rvalBox =<< (v <$ bind name addr)
data JsxElement a = JsxElement { jsxOpeningElement :: !a, jsxElements :: ![a], jsxClosingElement :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 JsxElement where liftEq = genericLiftEq
instance Ord1 JsxElement where liftCompare = genericLiftCompare
instance Show1 JsxElement where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable JsxElement
newtype JsxText a = JsxText { contents :: T.Text }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 JsxText where liftEq = genericLiftEq
instance Ord1 JsxText where liftCompare = genericLiftCompare
instance Show1 JsxText where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable JsxText
newtype JsxExpression a = JsxExpression { jsxExpression :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 JsxExpression where liftEq = genericLiftEq
instance Ord1 JsxExpression where liftCompare = genericLiftCompare
instance Show1 JsxExpression where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable JsxExpression
data JsxOpeningElement a = JsxOpeningElement { jsxOpeningElementIdentifier :: !a, jsxAttributes :: ![a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 JsxOpeningElement where liftEq = genericLiftEq
instance Ord1 JsxOpeningElement where liftCompare = genericLiftCompare
instance Show1 JsxOpeningElement where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable JsxOpeningElement
newtype JsxClosingElement a = JsxClosingElement { jsxClosingElementIdentifier :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 JsxClosingElement where liftEq = genericLiftEq
instance Ord1 JsxClosingElement where liftCompare = genericLiftCompare
instance Show1 JsxClosingElement where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable JsxClosingElement
data JsxSelfClosingElement a = JsxSelfClosingElement { jsxSelfClosingElementIdentifier :: !a, jsxSelfClosingElementAttributes :: ![a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 JsxSelfClosingElement where liftEq = genericLiftEq
instance Ord1 JsxSelfClosingElement where liftCompare = genericLiftCompare
instance Show1 JsxSelfClosingElement where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable JsxSelfClosingElement
data JsxAttribute a = JsxAttribute { jsxAttributeTarget :: !a, jsxAttributeValue :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 JsxAttribute where liftEq = genericLiftEq
instance Ord1 JsxAttribute where liftCompare = genericLiftCompare
instance Show1 JsxAttribute where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable JsxAttribute
newtype ImplementsClause a = ImplementsClause { implementsClauseTypes :: [a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ImplementsClause where liftEq = genericLiftEq
instance Ord1 ImplementsClause where liftCompare = genericLiftCompare
instance Show1 ImplementsClause where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ImplementsClause
data OptionalParameter a = OptionalParameter { optionalParameterContext :: ![a], optionalParameterSubject :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 OptionalParameter where liftEq = genericLiftEq
instance Ord1 OptionalParameter where liftCompare = genericLiftCompare
instance Show1 OptionalParameter where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable OptionalParameter
data RequiredParameter a = RequiredParameter { requiredParameterContext :: ![a], requiredParameterSubject :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 RequiredParameter where liftEq = genericLiftEq
instance Ord1 RequiredParameter where liftCompare = genericLiftCompare
instance Show1 RequiredParameter where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable RequiredParameter
data RestParameter a = RestParameter { restParameterContext :: ![a], restParameterSubject :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 RestParameter where liftEq = genericLiftEq
instance Ord1 RestParameter where liftCompare = genericLiftCompare
instance Show1 RestParameter where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable RestParameter
newtype JsxFragment a = JsxFragment { terms :: [a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 JsxFragment where liftEq = genericLiftEq
instance Ord1 JsxFragment where liftCompare = genericLiftCompare
instance Show1 JsxFragment where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable JsxFragment
data JsxNamespaceName a = JsxNamespaceName { left :: a, right :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Mergeable, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 JsxNamespaceName where liftEq = genericLiftEq
instance Ord1 JsxNamespaceName where liftCompare = genericLiftCompare
instance Show1 JsxNamespaceName where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable JsxNamespaceName
import Language.TypeScript.Syntax.JavaScript as X
import Language.TypeScript.Syntax.JSX as X
import Language.TypeScript.Syntax.TypeScript as X

View File

@ -0,0 +1,116 @@
{-# LANGUAGE DeriveAnyClass, DuplicateRecordFields #-}
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
module Language.TypeScript.Syntax.JSX where
import Prologue
import qualified Data.Text as T
import Proto3.Suite
import Data.Abstract.Evaluatable
import Data.JSON.Fields
import Diffing.Algorithm
data JsxElement a = JsxElement { jsxOpeningElement :: !a, jsxElements :: ![a], jsxClosingElement :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 JsxElement where liftEq = genericLiftEq
instance Ord1 JsxElement where liftCompare = genericLiftCompare
instance Show1 JsxElement where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable JsxElement
newtype JsxText a = JsxText { contents :: T.Text }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 JsxText where liftEq = genericLiftEq
instance Ord1 JsxText where liftCompare = genericLiftCompare
instance Show1 JsxText where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable JsxText
newtype JsxExpression a = JsxExpression { jsxExpression :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 JsxExpression where liftEq = genericLiftEq
instance Ord1 JsxExpression where liftCompare = genericLiftCompare
instance Show1 JsxExpression where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable JsxExpression
data JsxOpeningElement a = JsxOpeningElement { jsxOpeningElementIdentifier :: !a, jsxAttributes :: ![a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 JsxOpeningElement where liftEq = genericLiftEq
instance Ord1 JsxOpeningElement where liftCompare = genericLiftCompare
instance Show1 JsxOpeningElement where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable JsxOpeningElement
newtype JsxClosingElement a = JsxClosingElement { jsxClosingElementIdentifier :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 JsxClosingElement where liftEq = genericLiftEq
instance Ord1 JsxClosingElement where liftCompare = genericLiftCompare
instance Show1 JsxClosingElement where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable JsxClosingElement
data JsxSelfClosingElement a = JsxSelfClosingElement { jsxSelfClosingElementIdentifier :: !a, jsxSelfClosingElementAttributes :: ![a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 JsxSelfClosingElement where liftEq = genericLiftEq
instance Ord1 JsxSelfClosingElement where liftCompare = genericLiftCompare
instance Show1 JsxSelfClosingElement where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable JsxSelfClosingElement
data JsxAttribute a = JsxAttribute { jsxAttributeTarget :: !a, jsxAttributeValue :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 JsxAttribute where liftEq = genericLiftEq
instance Ord1 JsxAttribute where liftCompare = genericLiftCompare
instance Show1 JsxAttribute where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable JsxAttribute
newtype ImplementsClause a = ImplementsClause { implementsClauseTypes :: [a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ImplementsClause where liftEq = genericLiftEq
instance Ord1 ImplementsClause where liftCompare = genericLiftCompare
instance Show1 ImplementsClause where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ImplementsClause
data OptionalParameter a = OptionalParameter { optionalParameterContext :: ![a], optionalParameterSubject :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 OptionalParameter where liftEq = genericLiftEq
instance Ord1 OptionalParameter where liftCompare = genericLiftCompare
instance Show1 OptionalParameter where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable OptionalParameter
data RequiredParameter a = RequiredParameter { requiredParameterContext :: ![a], requiredParameterSubject :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 RequiredParameter where liftEq = genericLiftEq
instance Ord1 RequiredParameter where liftCompare = genericLiftCompare
instance Show1 RequiredParameter where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable RequiredParameter
data RestParameter a = RestParameter { restParameterContext :: ![a], restParameterSubject :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 RestParameter where liftEq = genericLiftEq
instance Ord1 RestParameter where liftCompare = genericLiftCompare
instance Show1 RestParameter where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable RestParameter
newtype JsxFragment a = JsxFragment { terms :: [a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 JsxFragment where liftEq = genericLiftEq
instance Ord1 JsxFragment where liftCompare = genericLiftCompare
instance Show1 JsxFragment where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable JsxFragment
data JsxNamespaceName a = JsxNamespaceName { left :: a, right :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 JsxNamespaceName where liftEq = genericLiftEq
instance Ord1 JsxNamespaceName where liftCompare = genericLiftCompare
instance Show1 JsxNamespaceName where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable JsxNamespaceName

View File

@ -0,0 +1,65 @@
{-# LANGUAGE DeriveAnyClass, DuplicateRecordFields #-}
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
module Language.TypeScript.Syntax.JavaScript where
import Prologue
import Proto3.Suite
import Data.Abstract.Evaluatable
import Data.JSON.Fields
import Diffing.Algorithm
import Language.TypeScript.Resolution
data JavaScriptRequire a = JavaScriptRequire { javascriptRequireIden :: !a, javascriptRequireFrom :: ImportPath }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 JavaScriptRequire where liftEq = genericLiftEq
instance Ord1 JavaScriptRequire where liftCompare = genericLiftCompare
instance Show1 JavaScriptRequire where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable JavaScriptRequire where
eval (JavaScriptRequire aliasTerm importPath) = do
modulePath <- resolveWithNodejsStrategy importPath javascriptExtensions
alias <- maybeM (throwEvalError NoNameError) (declaredName (subterm aliasTerm))
rvalBox =<< evalRequire modulePath alias
data Debugger a = Debugger
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Debugger where liftEq = genericLiftEq
instance Ord1 Debugger where liftCompare = genericLiftCompare
instance Show1 Debugger where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Debugger
data This a = This
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 This where liftEq = genericLiftEq
instance Ord1 This where liftCompare = genericLiftCompare
instance Show1 This where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable This
data Super a = Super
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Super where liftEq = genericLiftEq
instance Ord1 Super where liftCompare = genericLiftCompare
instance Show1 Super where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Super
data Undefined a = Undefined
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Undefined where liftEq = genericLiftEq
instance Ord1 Undefined where liftCompare = genericLiftCompare
instance Show1 Undefined where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Undefined
data With a = With { withExpression :: !a, withBody :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 With where liftEq = genericLiftEq
instance Ord1 With where liftCompare = genericLiftCompare
instance Show1 With where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable With

View File

@ -0,0 +1,548 @@
{-# LANGUAGE DeriveAnyClass, DuplicateRecordFields #-}
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
module Language.TypeScript.Syntax.TypeScript where
import Prologue
import Data.Aeson
import qualified Data.Text as T
import Proto3.Suite
import qualified Data.Abstract.Environment as Env
import Data.Abstract.Evaluatable
import Data.JSON.Fields
import Diffing.Algorithm
import Language.TypeScript.Resolution
data Import a = Import { importSymbols :: ![Alias], importFrom :: ImportPath }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Import where liftEq = genericLiftEq
instance Ord1 Import where liftCompare = genericLiftCompare
instance Show1 Import where liftShowsPrec = genericLiftShowsPrec
-- http://www.typescriptlang.org/docs/handbook/module-resolution.html
instance Evaluatable Import where
eval (Import symbols importPath) = do
modulePath <- resolveWithNodejsStrategy importPath typescriptExtensions
importedEnv <- fst <$> require modulePath
bindAll (renamed importedEnv)
rvalBox unit
where
renamed importedEnv
| Prologue.null symbols = importedEnv
| otherwise = Env.overwrite (toTuple <$> symbols) importedEnv
data QualifiedAliasedImport a = QualifiedAliasedImport { qualifiedAliasedImportAlias :: !a, qualifiedAliasedImportFrom :: ImportPath }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 QualifiedAliasedImport where liftEq = genericLiftEq
instance Ord1 QualifiedAliasedImport where liftCompare = genericLiftCompare
instance Show1 QualifiedAliasedImport where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable QualifiedAliasedImport where
eval (QualifiedAliasedImport aliasTerm importPath) = do
modulePath <- resolveWithNodejsStrategy importPath typescriptExtensions
alias <- maybeM (throwEvalError NoNameError) (declaredName (subterm aliasTerm))
rvalBox =<< evalRequire modulePath alias
newtype SideEffectImport a = SideEffectImport { sideEffectImportFrom :: ImportPath }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 SideEffectImport where liftEq = genericLiftEq
instance Ord1 SideEffectImport where liftCompare = genericLiftCompare
instance Show1 SideEffectImport where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable SideEffectImport where
eval (SideEffectImport importPath) = do
modulePath <- resolveWithNodejsStrategy importPath typescriptExtensions
void $ require modulePath
rvalBox unit
-- | Qualified Export declarations
newtype QualifiedExport a = QualifiedExport { qualifiedExportSymbols :: [Alias] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 QualifiedExport where liftEq = genericLiftEq
instance Ord1 QualifiedExport where liftCompare = genericLiftCompare
instance Show1 QualifiedExport where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable QualifiedExport where
eval (QualifiedExport exportSymbols) = do
-- Insert the aliases with no addresses.
for_ exportSymbols $ \Alias{..} ->
export aliasValue aliasName Nothing
rvalBox unit
data Alias = Alias { aliasValue :: Name, aliasName :: Name }
deriving (Eq, Generic, Hashable, Ord, Show, Message, Named, ToJSON)
toTuple :: Alias -> (Name, Name)
toTuple Alias{..} = (aliasValue, aliasName)
-- | Qualified Export declarations that export from another module.
data QualifiedExportFrom a = QualifiedExportFrom { qualifiedExportFrom :: ImportPath, qualifiedExportFromSymbols :: ![Alias]}
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 QualifiedExportFrom where liftEq = genericLiftEq
instance Ord1 QualifiedExportFrom where liftCompare = genericLiftCompare
instance Show1 QualifiedExportFrom where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable QualifiedExportFrom where
eval (QualifiedExportFrom importPath exportSymbols) = do
modulePath <- resolveWithNodejsStrategy importPath typescriptExtensions
importedEnv <- fst <$> require modulePath
-- Look up addresses in importedEnv and insert the aliases with addresses into the exports.
for_ exportSymbols $ \Alias{..} -> do
let address = Env.lookup aliasValue importedEnv
maybe (throwEvalError $ ExportError modulePath aliasValue) (export aliasValue aliasName . Just) address
rvalBox unit
newtype DefaultExport a = DefaultExport { defaultExport :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 DefaultExport where liftEq = genericLiftEq
instance Ord1 DefaultExport where liftCompare = genericLiftCompare
instance Show1 DefaultExport where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable DefaultExport where
eval (DefaultExport term) = do
case declaredName term of
Just name -> do
addr <- lookupOrAlloc name
v <- subtermValue term
assign addr v
export name name Nothing
bind name addr
Nothing -> throwEvalError DefaultExportError
rvalBox unit
-- | Lookup type for a type-level key in a typescript map.
data LookupType a = LookupType { lookupTypeIdentifier :: a, lookupTypeKey :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 LookupType where liftEq = genericLiftEq
instance Ord1 LookupType where liftCompare = genericLiftCompare
instance Show1 LookupType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable LookupType
-- | ShorthandPropertyIdentifier used in object patterns such as var baz = { foo } to mean var baz = { foo: foo }
newtype ShorthandPropertyIdentifier a = ShorthandPropertyIdentifier { contents :: T.Text }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ShorthandPropertyIdentifier where liftEq = genericLiftEq
instance Ord1 ShorthandPropertyIdentifier where liftCompare = genericLiftCompare
instance Show1 ShorthandPropertyIdentifier where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ShorthandPropertyIdentifier
data Union a = Union { unionLeft :: !a, unionRight :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Language.TypeScript.Syntax.TypeScript.Union where liftEq = genericLiftEq
instance Ord1 Language.TypeScript.Syntax.TypeScript.Union where liftCompare = genericLiftCompare
instance Show1 Language.TypeScript.Syntax.TypeScript.Union where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Language.TypeScript.Syntax.TypeScript.Union
data Intersection a = Intersection { intersectionLeft :: !a, intersectionRight :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Intersection where liftEq = genericLiftEq
instance Ord1 Intersection where liftCompare = genericLiftCompare
instance Show1 Intersection where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Intersection
data FunctionType a = FunctionType { functionTypeParameters :: !a, functionFormalParameters :: ![a], functionType :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 FunctionType where liftEq = genericLiftEq
instance Ord1 FunctionType where liftCompare = genericLiftCompare
instance Show1 FunctionType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable FunctionType
data AmbientFunction a = AmbientFunction { ambientFunctionContext :: ![a], ambientFunctionIdentifier :: !a, ambientFunctionParameters :: ![a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 AmbientFunction where liftEq = genericLiftEq
instance Ord1 AmbientFunction where liftCompare = genericLiftCompare
instance Show1 AmbientFunction where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable AmbientFunction
data ImportRequireClause a = ImportRequireClause { importRequireIdentifier :: !a, importRequireSubject :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ImportRequireClause where liftEq = genericLiftEq
instance Ord1 ImportRequireClause where liftCompare = genericLiftCompare
instance Show1 ImportRequireClause where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ImportRequireClause
newtype ImportClause a = ImportClause { importClauseElements :: [a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ImportClause where liftEq = genericLiftEq
instance Ord1 ImportClause where liftCompare = genericLiftCompare
instance Show1 ImportClause where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ImportClause
newtype Tuple a = Tuple { tupleElements :: [a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Tuple where liftEq = genericLiftEq
instance Ord1 Tuple where liftCompare = genericLiftCompare
instance Show1 Tuple where liftShowsPrec = genericLiftShowsPrec
-- This is a tuple type, not a tuple value, so we can't lean on the shared Tuple value
instance Evaluatable Tuple
data Constructor a = Constructor { constructorTypeParameters :: !a, constructorFormalParameters :: ![a], constructorType :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Language.TypeScript.Syntax.TypeScript.Constructor where liftEq = genericLiftEq
instance Ord1 Language.TypeScript.Syntax.TypeScript.Constructor where liftCompare = genericLiftCompare
instance Show1 Language.TypeScript.Syntax.TypeScript.Constructor where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Language.TypeScript.Syntax.TypeScript.Constructor
data TypeParameter a = TypeParameter { typeParameter :: !a, typeParameterConstraint :: !a, typeParameterDefaultType :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 TypeParameter where liftEq = genericLiftEq
instance Ord1 TypeParameter where liftCompare = genericLiftCompare
instance Show1 TypeParameter where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable TypeParameter
data TypeAssertion a = TypeAssertion { typeAssertionParameters :: !a, typeAssertionExpression :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 TypeAssertion where liftEq = genericLiftEq
instance Ord1 TypeAssertion where liftCompare = genericLiftCompare
instance Show1 TypeAssertion where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable TypeAssertion
newtype Annotation a = Annotation { annotationType :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Annotation where liftEq = genericLiftEq
instance Ord1 Annotation where liftCompare = genericLiftCompare
instance Show1 Annotation where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Annotation
newtype Decorator a = Decorator { decoratorTerm :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Decorator where liftEq = genericLiftEq
instance Ord1 Decorator where liftCompare = genericLiftCompare
instance Show1 Decorator where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Decorator
newtype ComputedPropertyName a = ComputedPropertyName { propertyName :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ComputedPropertyName where liftEq = genericLiftEq
instance Ord1 ComputedPropertyName where liftCompare = genericLiftCompare
instance Show1 ComputedPropertyName where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ComputedPropertyName
newtype Constraint a = Constraint { constraintType :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Constraint where liftEq = genericLiftEq
instance Ord1 Constraint where liftCompare = genericLiftCompare
instance Show1 Constraint where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Constraint
newtype DefaultType a = DefaultType { defaultType :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 DefaultType where liftEq = genericLiftEq
instance Ord1 DefaultType where liftCompare = genericLiftCompare
instance Show1 DefaultType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable DefaultType
newtype ParenthesizedType a = ParenthesizedType { parenthesizedType :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ParenthesizedType where liftEq = genericLiftEq
instance Ord1 ParenthesizedType where liftCompare = genericLiftCompare
instance Show1 ParenthesizedType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ParenthesizedType
newtype PredefinedType a = PredefinedType { predefinedType :: T.Text }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 PredefinedType where liftEq = genericLiftEq
instance Ord1 PredefinedType where liftCompare = genericLiftCompare
instance Show1 PredefinedType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable PredefinedType
newtype TypeIdentifier a = TypeIdentifier { contents :: T.Text }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 TypeIdentifier where liftEq = genericLiftEq
instance Ord1 TypeIdentifier where liftCompare = genericLiftCompare
instance Show1 TypeIdentifier where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable TypeIdentifier
data NestedIdentifier a = NestedIdentifier { left :: !a, right :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 NestedIdentifier where liftEq = genericLiftEq
instance Ord1 NestedIdentifier where liftCompare = genericLiftCompare
instance Show1 NestedIdentifier where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable NestedIdentifier
data NestedTypeIdentifier a = NestedTypeIdentifier { left :: !a, right :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 NestedTypeIdentifier where liftEq = genericLiftEq
instance Ord1 NestedTypeIdentifier where liftCompare = genericLiftCompare
instance Show1 NestedTypeIdentifier where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable NestedTypeIdentifier
data GenericType a = GenericType { genericTypeIdentifier :: !a, genericTypeArguments :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 GenericType where liftEq = genericLiftEq
instance Ord1 GenericType where liftCompare = genericLiftCompare
instance Show1 GenericType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable GenericType
data TypePredicate a = TypePredicate { typePredicateIdentifier :: !a, typePredicateType :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 TypePredicate where liftEq = genericLiftEq
instance Ord1 TypePredicate where liftCompare = genericLiftCompare
instance Show1 TypePredicate where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable TypePredicate
newtype ObjectType a = ObjectType { objectTypeElements :: [a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ObjectType where liftEq = genericLiftEq
instance Ord1 ObjectType where liftCompare = genericLiftCompare
instance Show1 ObjectType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ObjectType
newtype AmbientDeclaration a = AmbientDeclaration { ambientDeclarationBody :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 AmbientDeclaration where liftEq = genericLiftEq
instance Ord1 AmbientDeclaration where liftCompare = genericLiftCompare
instance Show1 AmbientDeclaration where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable AmbientDeclaration where
eval (AmbientDeclaration body) = subtermRef body
data EnumDeclaration a = EnumDeclaration { enumDeclarationIdentifier :: !a, enumDeclarationBody :: ![a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 EnumDeclaration where liftEq = genericLiftEq
instance Ord1 EnumDeclaration where liftCompare = genericLiftCompare
instance Show1 EnumDeclaration where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable EnumDeclaration
instance Declarations a => Declarations (EnumDeclaration a) where
declaredName EnumDeclaration{..} = declaredName enumDeclarationIdentifier
newtype ExtendsClause a = ExtendsClause { extendsClauses :: [a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ExtendsClause where liftEq = genericLiftEq
instance Ord1 ExtendsClause where liftCompare = genericLiftCompare
instance Show1 ExtendsClause where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ExtendsClause
newtype ArrayType a = ArrayType { arrayType :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ArrayType where liftEq = genericLiftEq
instance Ord1 ArrayType where liftCompare = genericLiftCompare
instance Show1 ArrayType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ArrayType
newtype FlowMaybeType a = FlowMaybeType { flowMaybeType :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 FlowMaybeType where liftEq = genericLiftEq
instance Ord1 FlowMaybeType where liftCompare = genericLiftCompare
instance Show1 FlowMaybeType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable FlowMaybeType
newtype TypeQuery a = TypeQuery { typeQuerySubject :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 TypeQuery where liftEq = genericLiftEq
instance Ord1 TypeQuery where liftCompare = genericLiftCompare
instance Show1 TypeQuery where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable TypeQuery
newtype IndexTypeQuery a = IndexTypeQuery { indexTypeQuerySubject :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 IndexTypeQuery where liftEq = genericLiftEq
instance Ord1 IndexTypeQuery where liftCompare = genericLiftCompare
instance Show1 IndexTypeQuery where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable IndexTypeQuery
newtype TypeArguments a = TypeArguments { typeArguments :: [a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 TypeArguments where liftEq = genericLiftEq
instance Ord1 TypeArguments where liftCompare = genericLiftCompare
instance Show1 TypeArguments where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable TypeArguments
newtype ThisType a = ThisType { contents :: T.Text }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ThisType where liftEq = genericLiftEq
instance Ord1 ThisType where liftCompare = genericLiftCompare
instance Show1 ThisType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ThisType
newtype ExistentialType a = ExistentialType { contents :: T.Text }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ExistentialType where liftEq = genericLiftEq
instance Ord1 ExistentialType where liftCompare = genericLiftCompare
instance Show1 ExistentialType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ExistentialType
newtype LiteralType a = LiteralType { literalTypeSubject :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 LiteralType where liftEq = genericLiftEq
instance Ord1 LiteralType where liftCompare = genericLiftCompare
instance Show1 LiteralType where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable LiteralType
data PropertySignature a = PropertySignature { modifiers :: ![a], propertySignaturePropertyName :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 PropertySignature where liftEq = genericLiftEq
instance Ord1 PropertySignature where liftCompare = genericLiftCompare
instance Show1 PropertySignature where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable PropertySignature
data CallSignature a = CallSignature { callSignatureTypeParameters :: !a, callSignatureParameters :: ![a], callSignatureType :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 CallSignature where liftEq = genericLiftEq
instance Ord1 CallSignature where liftCompare = genericLiftCompare
instance Show1 CallSignature where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable CallSignature
-- | Todo: Move type params and type to context
data ConstructSignature a = ConstructSignature { constructSignatureTypeParameters :: !a, constructSignatureParameters :: ![a], constructSignatureType :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ConstructSignature where liftEq = genericLiftEq
instance Ord1 ConstructSignature where liftCompare = genericLiftCompare
instance Show1 ConstructSignature where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ConstructSignature
data IndexSignature a = IndexSignature { indexSignatureSubject :: a, indexSignatureType :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 IndexSignature where liftEq = genericLiftEq
instance Ord1 IndexSignature where liftCompare = genericLiftCompare
instance Show1 IndexSignature where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable IndexSignature
data AbstractMethodSignature a = AbstractMethodSignature { abstractMethodSignatureContext :: ![a], abstractMethodSignatureName :: !a, abstractMethodSignatureParameters :: ![a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 AbstractMethodSignature where liftEq = genericLiftEq
instance Ord1 AbstractMethodSignature where liftCompare = genericLiftCompare
instance Show1 AbstractMethodSignature where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable AbstractMethodSignature
data ForOf a = ForOf { forOfBinding :: !a, forOfSubject :: !a, forOfBody :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ForOf where liftEq = genericLiftEq
instance Ord1 ForOf where liftCompare = genericLiftCompare
instance Show1 ForOf where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ForOf
data LabeledStatement a = LabeledStatement { labeledStatementIdentifier :: !a, labeledStatementSubject :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 LabeledStatement where liftEq = genericLiftEq
instance Ord1 LabeledStatement where liftCompare = genericLiftCompare
instance Show1 LabeledStatement where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable LabeledStatement
newtype Update a = Update { updateSubject :: a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Update where liftEq = genericLiftEq
instance Ord1 Update where liftCompare = genericLiftCompare
instance Show1 Update where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Update
data Module a = Module { moduleIdentifier :: !a, moduleStatements :: ![a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 Module where liftEq = genericLiftEq
instance Ord1 Module where liftCompare = genericLiftCompare
instance Show1 Module where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Module where
eval (Module iden xs) = do
name <- maybeM (throwEvalError NoNameError) (declaredName (subterm iden))
rvalBox =<< letrec' name (\addr ->
value =<< (eval xs <* makeNamespace name addr Nothing))
data InternalModule a = InternalModule { internalModuleIdentifier :: !a, internalModuleStatements :: ![a] }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 InternalModule where liftEq = genericLiftEq
instance Ord1 InternalModule where liftCompare = genericLiftCompare
instance Show1 InternalModule where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable InternalModule where
eval (InternalModule iden xs) = do
name <- maybeM (throwEvalError NoNameError) (declaredName (subterm iden))
rvalBox =<< letrec' name (\addr ->
value =<< (eval xs <* makeNamespace name addr Nothing))
instance Declarations a => Declarations (InternalModule a) where
declaredName InternalModule{..} = declaredName internalModuleIdentifier
data ImportAlias a = ImportAlias { importAliasSubject :: !a, importAlias :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ImportAlias where liftEq = genericLiftEq
instance Ord1 ImportAlias where liftCompare = genericLiftCompare
instance Show1 ImportAlias where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ImportAlias
data ClassHeritage a = ClassHeritage { classHeritageExtendsClause :: !a, implementsClause :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 ClassHeritage where liftEq = genericLiftEq
instance Ord1 ClassHeritage where liftCompare = genericLiftCompare
instance Show1 ClassHeritage where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable ClassHeritage
data AbstractClass a = AbstractClass { abstractClassIdentifier :: !a, abstractClassTypeParameters :: !a, classHeritage :: ![a], classBody :: !a }
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
instance Eq1 AbstractClass where liftEq = genericLiftEq
instance Ord1 AbstractClass where liftCompare = genericLiftCompare
instance Show1 AbstractClass where liftShowsPrec = genericLiftShowsPrec
instance Declarations a => Declarations (AbstractClass a) where
declaredName AbstractClass{..} = declaredName abstractClassIdentifier
instance Evaluatable AbstractClass where
eval AbstractClass{..} = do
name <- maybeM (throwEvalError NoNameError) (declaredName (subterm abstractClassIdentifier))
supers <- traverse subtermAddress classHeritage
(v, addr) <- letrec name $ do
void $ subtermValue classBody
classBinds <- Env.head <$> getEnv
klass name supers classBinds
rvalBox =<< (v <$ bind name addr)

View File

@ -29,8 +29,9 @@ module Parsing.Parser
import Assigning.Assignment
import qualified Assigning.Assignment.Deterministic as Deterministic
import qualified CMarkGFM
import Data.Abstract.Evaluatable (HasPrelude, HasPostlude)
import Data.Abstract.Evaluatable (HasPostlude, HasPrelude)
import Data.AST
import Data.Graph.Vertex (VertexDeclaration')
import Data.Kind
import Data.Language
import Data.Record
@ -49,14 +50,14 @@ import qualified Language.Ruby.Assignment as Ruby
import qualified Language.TypeScript.Assignment as TypeScript
import Prologue
import TreeSitter.Go
import TreeSitter.Haskell
import TreeSitter.Java
import TreeSitter.JSON
import qualified TreeSitter.Language as TS (Language, Symbol)
import TreeSitter.Java
import TreeSitter.PHP
import TreeSitter.Python
import TreeSitter.Ruby
import TreeSitter.TypeScript
import TreeSitter.Haskell
type family ApplyAll' (typeclasses :: [(* -> *) -> Constraint]) (fs :: [* -> *]) :: Constraint where
@ -66,6 +67,7 @@ type family ApplyAll' (typeclasses :: [(* -> *) -> Constraint]) (fs :: [* -> *])
-- | A parser, suitable for program analysis, for some specific language, producing 'Term's whose syntax satisfies a list of typeclass constraints.
data SomeAnalysisParser typeclasses ann where
SomeAnalysisParser :: ( ApplyAll' typeclasses fs
, Apply (VertexDeclaration' (Sum fs)) fs
, Element Syntax.Identifier fs
, HasPrelude lang
, HasPostlude lang

View File

@ -47,7 +47,6 @@ import Data.Functor.Classes.Generic as X
import Data.Functor.Foldable as X (Base, Corecursive (..), Recursive (..))
import Data.Hashable as X (Hashable, hash, hashUsing, hashWithSalt)
import Data.Hashable.Lifted as X (Hashable1(..), hashWithSalt1)
import Data.Mergeable as X (Mergeable)
import Data.Monoid as X (First (..), Last (..), Monoid (..))
import Data.Proxy as X (Proxy (..))
import Data.Semigroup as X (Semigroup (..))

View File

@ -1,5 +1,11 @@
{-# LANGUAGE GADTs, RankNTypes #-}
module Semantic.AST where
module Semantic.AST
( SomeAST (..)
, withSomeAST
, astParseBlob
, ASTFormat (..)
, runASTParse
) where
import Data.AST
import Data.Blob

View File

@ -1,6 +1,17 @@
{-# LANGUAGE LambdaCase #-}
module Semantic.Config where
module Semantic.Config
( Config (..)
, defaultConfig
, Options (..)
, defaultOptions
, debugOptions
, lookupStatsAddr
, withHaystackFromConfig
, withLoggerFromConfig
, withStatterFromConfig
, withTelemetry
) where
import Network.BSD
import Network.HTTP.Client.TLS

View File

@ -1,5 +1,12 @@
{-# LANGUAGE ConstraintKinds, GADTs, RankNTypes, ScopedTypeVariables #-}
module Semantic.Diff where
module Semantic.Diff
( runDiff
, runPythonDiff
, runRubyDiff
, runTypeScriptDiff
, runJSONDiff
, diffBlobTOCPairs
) where
import Analysis.ConstructorName (ConstructorName)
import Analysis.Declaration (HasDeclaration, declarationAlgebra)

View File

@ -1,4 +1,7 @@
module Semantic.Env where
module Semantic.Env
( envLookupInt
, envLookupString
) where
import Control.Monad.IO.Class
import Prologue

View File

@ -33,12 +33,12 @@ import Data.Abstract.Module
import qualified Data.Abstract.ModuleTable as ModuleTable
import Data.Abstract.Package as Package
import Data.Abstract.Value.Abstract
import Data.Abstract.Value.Type
import Data.Abstract.Value.Concrete (Value, ValueError (..), runValueErrorWith)
import Data.Abstract.Value.Type
import Data.Graph
import Data.Graph.Vertex (VertexDeclarationStrategy, VertexDeclarationWithStrategy)
import Data.Project
import Data.Record
import qualified Data.Syntax as Syntax
import Data.Term
import Data.Text (pack)
import Language.Haskell.HsColour
@ -67,18 +67,20 @@ runGraph CallGraph includePackages project
modules <- topologicalSort <$> runImportGraph lang package
runCallGraph lang includePackages modules package
runCallGraph :: ( HasField ann Span
, Element Syntax.Identifier syntax
, Base term ~ TermF (Sum syntax) (Record ann)
, Ord term
, Corecursive term
, Declarations term
, Evaluatable (Base term)
runCallGraph :: ( HasField fields Span
, Show (Record fields)
, Ord (Record fields)
, (VertexDeclarationWithStrategy (VertexDeclarationStrategy syntax) syntax syntax)
, Declarations1 syntax
, Ord1 syntax
, Functor syntax
, Evaluatable syntax
, term ~ Term syntax (Record fields)
, FreeVariables term
, Recursive term
, HasPrelude lang
, HasPostlude lang
, Member Trace effs
, Recursive term
, Effects effs
)
=> Proxy lang
@ -104,6 +106,7 @@ runCallGraph lang includePackages modules package = do
. resumingAddressError
. runReader (packageInfo package)
. runReader (lowerBound @Span)
. runReader (lowerBound @Vertex)
. providingLiveSet
. runReader (lowerBound @(ModuleTable (NonEmpty (Module (Environment (Hole (Maybe Name) (Located Monovariant)), Hole (Maybe Name) (Located Monovariant))))))
. raiseHandler (runModules (ModuleTable.modulePaths (packageModules package)))

View File

@ -1,5 +1,11 @@
{-# LANGUAGE GADTs, RankNTypes #-}
module Semantic.Parse where
module Semantic.Parse
( runParse
, runPythonParse
, runRubyParse
, runTypeScriptParse
, runJSONParse
) where
import Analysis.ConstructorName (ConstructorName)
import Analysis.Declaration (HasDeclaration, declarationAlgebra)

View File

@ -1,5 +1,10 @@
{-# LANGUAGE ConstraintKinds, GADTs, KindSignatures, ScopedTypeVariables, TypeOperators, UndecidableInstances #-}
module Semantic.Resolution where
module Semantic.Resolution
( Resolution (..)
, nodeJSResolutionMap
, resolutionMap
, runResolution
) where
import Control.Monad.Effect
import Data.Aeson

View File

@ -1,4 +1,10 @@
module Semantic.Telemetry.Haystack where
module Semantic.Telemetry.Haystack
( HaystackClient (..)
, ErrorReport (..)
, ErrorLogger
, haystackClient
, reportError
) where
import Control.Exception
import Crypto.Hash

View File

@ -1,4 +1,12 @@
module Semantic.Telemetry.Log where
module Semantic.Telemetry.Log
( Level (..)
, LogOptions (..)
, Message (..)
, LogFormatter
, logfmtFormatter
, terminalFormatter
, writeLogMessage
) where
import Control.Monad.IO.Class
import Data.Error (withSGRCode)

View File

@ -1,5 +1,5 @@
{-# LANGUAGE GeneralizedNewtypeDeriving, TypeFamilies, TypeOperators #-}
{-# OPTIONS_GHC -Wno-missing-signatures #-}
{-# OPTIONS_GHC -Wno-missing-signatures -Wno-missing-export-lists #-}
module Semantic.Util where
import Prelude hiding (readFile)

View File

@ -1,6 +1,9 @@
{-# OPTIONS_GHC -fforce-recomp #-} -- So that gitHash is correct.
{-# LANGUAGE TemplateHaskell #-}
module Semantic.Version where
module Semantic.Version
( buildSHA
, buildVersion
) where
import Data.Version (showVersion)
import Development.GitRev

View File

@ -1,10 +1,14 @@
{-# LANGUAGE DefaultSignatures, TypeOperators, UndecidableInstances #-}
module Data.Mergeable where
module Data.Mergeable ( Mergeable (..) ) where
import Control.Applicative
import Data.Functor.Identity
import Data.List.NonEmpty
import Data.Sum
import qualified Data.Syntax as Syntax
import qualified Data.Syntax.Comment as Comment
import qualified Data.Syntax.Declaration as Declaration
import qualified Data.Syntax.Statement as Statement
import GHC.Generics
-- Classes
@ -39,6 +43,14 @@ instance Mergeable Identity where
instance (Apply Functor fs, Apply Mergeable fs) => Mergeable (Sum fs) where
sequenceAlt = apply' @Mergeable (\ reinj t -> reinj <$> sequenceAlt t)
instance Mergeable Comment.Comment
instance Mergeable Declaration.Function
instance Mergeable Declaration.Method
instance Mergeable Statement.If
instance Mergeable Syntax.Context
instance Mergeable Syntax.Empty
instance Mergeable Syntax.Identifier
-- Generics

View File

@ -12,6 +12,7 @@ import Data.Term
import Data.These
import Diffing.Algorithm
import Diffing.Algorithm.RWS
import Diffing.Interpreter.Spec (afterTerm, beforeTerm)
import Test.Hspec.LeanCheck
import SpecHelpers

View File

@ -1,9 +1,14 @@
{-# LANGUAGE DataKinds #-}
module Diffing.Interpreter.Spec where
import Control.Applicative ((<|>))
import Data.Diff
import Data.Foldable (asum)
import Data.Functor.Foldable (cata)
import Data.Functor.Listable
import Data.Maybe
import Data.Mergeable
import Data.Patch (after, before)
import Data.Record
import Data.Sum
import Data.Term
@ -63,3 +68,16 @@ spec = parallel $ do
prop "produces a Delete when the second term is missing" $ do
\ before -> let diff = diffTermPair (This before) :: Diff ListableSyntax (Record '[]) (Record '[]) in
diff `shouldBe` deleting before
-- | Recover the before state of a diff.
beforeTerm :: (Foldable syntax, Mergeable syntax) => Diff syntax ann1 ann2 -> Maybe (Term syntax ann1)
beforeTerm = cata $ \ diff -> case diff of
Patch patch -> (before patch >>= \ (In a l) -> termIn a <$> sequenceAlt l) <|> (after patch >>= asum)
Merge (In (a, _) l) -> termIn a <$> sequenceAlt l
-- | Recover the after state of a diff.
afterTerm :: (Foldable syntax, Mergeable syntax) => Diff syntax ann1 ann2 -> Maybe (Term syntax ann2)
afterTerm = cata $ \ diff -> case diff of
Patch patch -> (after patch >>= \ (In b r) -> termIn b <$> sequenceAlt r) <|> (before patch >>= asum)
Merge (In (_, b) r) -> termIn b <$> sequenceAlt r

View File

@ -9,8 +9,10 @@ import SpecHelpers hiding (readFile)
import Algebra.Graph
import Data.List (uncons)
import Data.Abstract.Module
import "semantic" Data.Graph (Graph (..), topologicalSort)
import Data.Graph.Vertex
import Data.Span
import qualified Data.Language as Language
import Semantic.Config (defaultOptions)
import Semantic.Graph
@ -27,21 +29,21 @@ callGraphPythonProject paths = runTaskWithOptions defaultOptions $ do
spec :: Spec
spec = describe "call graphing" $ do
let needs r n = unGraph r `shouldSatisfy` hasVertex (Variable n)
let needs r v = unGraph r `shouldSatisfy` hasVertex v
it "should work for a simple example" $ do
res <- callGraphPythonProject ["test/fixtures/python/graphing/simple/simple.py"]
res `needs` "magnus"
res `needs` Variable "magnus" "simple.py" (Span (Pos 4 1) (Pos 4 7))
it "should evaluate both sides of an if-statement" $ do
res <- callGraphPythonProject ["test/fixtures/python/graphing/conditional/conditional.py"]
res `needs` "merle"
res `needs` "taako"
res `needs` Variable "merle" "conditional.py" (Span (Pos 5 5) (Pos 5 10))
res `needs` Variable "taako" "conditional.py" (Span (Pos 8 5) (Pos 8 10))
it "should continue even when a type error is encountered" $ do
res <- callGraphPythonProject ["test/fixtures/python/graphing/typeerror/typeerror.py"]
res `needs` "lup"
res `needs` Variable "lup" "typeerror.py" (Span (Pos 5 1) (Pos 5 4))
it "should continue when an unbound variable is encountered" $ do
res <- callGraphPythonProject ["test/fixtures/python/graphing/unbound/unbound.py"]
res `needs` "lucretia"
res `needs` Variable "lucretia" "unbound.py" (Span (Pos 5 1) (Pos 5 9))

5
test/fixtures/java/classLiteral.java vendored Normal file
View File

@ -0,0 +1,5 @@
class Dino {
void normalError() {
error(TestException.class);
}
}

View File

@ -0,0 +1,7 @@
class Dino {
void fn() {
for (File file : snap.index()) {
assert oldFile == null;
}
}
}

View File

@ -0,0 +1,5 @@
class Dino {
void hi() {
assert failure : "expecting non null";
}
}

View File

@ -0,0 +1,6 @@
class Dino {
public void dispose() {
Test.flat(new Function<Integer>() {
});
}
}

5
test/fixtures/java/corpus/lambda.java vendored Normal file
View File

@ -0,0 +1,5 @@
class LambdaTest {
void singleton() {
version -> create;
}
}

View File

@ -0,0 +1,5 @@
class Natural {
int compare(Object a, Object b) {
(a).compareTo(b);
}
}

View File

@ -0,0 +1,11 @@
class TermsSetQueryBuilder {
void Terms() {
min = read(Script::new);
}
}
class TermsSetQueryBuilder {
void Terms() {
min = read(Script::yodawg);
}
}

View File

@ -0,0 +1,3 @@
@interface TerminationHandle {
Bar foo = 1;
}

View File

@ -0,0 +1,3 @@
static final class EventLoopWorker extends Scheduler.Worker {
}

View File

@ -0,0 +1,6 @@
class Dino {
void hi() {
try (CustomAnalyzer analyzer = new CustomAnalyzer()){
}
}
}

View File

@ -0,0 +1,5 @@
class Dinosaur {
void apply() {
(T1)a[0];
}
}

View File

@ -22,7 +22,6 @@
{-(Identifier)-}
{-(Empty)-})-})
->(InterfaceDeclaration
{+(Empty)+}
{+(Empty)+}
{+(Identifier)+}
{+(ObjectType)+}) })
@ -63,7 +62,6 @@
{-(Identifier)-}
{-(Empty)-})-})-}
{-(InterfaceDeclaration
{-(Empty)-}
{-(Empty)-}
{-(Identifier)-}
{-(ObjectType
@ -74,7 +72,6 @@
{-(PredefinedType)-})-}
{-(Identifier)-})-})-})-}
{-(InterfaceDeclaration
{-(Empty)-}
{-(Empty)-}
{-(Identifier)-}
{-(ObjectType

View File

@ -53,7 +53,6 @@
{+(Identifier)+}
{+(Empty)+})+})+}
{+(InterfaceDeclaration
{+(Empty)+}
{+(Empty)+}
{+(Identifier)+}
{+(ObjectType
@ -64,7 +63,6 @@
{+(PredefinedType)+})+}
{+(Identifier)+})+})+})+}
{+(InterfaceDeclaration
{+(Empty)+}
{+(Empty)+}
{+(Identifier)+}
{+(ObjectType
@ -95,7 +93,6 @@
{-(Statements)-})-})-}
{-(AmbientDeclaration
{-(InterfaceDeclaration
{-(Empty)-}
{-(Empty)-}
{-(Identifier)-}
{-(ObjectType)-})-})-}

View File

@ -53,7 +53,6 @@
(Identifier)
(Empty)))
(InterfaceDeclaration
(Empty)
(Empty)
(Identifier)
(ObjectType
@ -64,7 +63,6 @@
(PredefinedType))
(Identifier))))
(InterfaceDeclaration
(Empty)
(Empty)
(Identifier)
(ObjectType

View File

@ -8,7 +8,6 @@
(Statements)))
(AmbientDeclaration
(InterfaceDeclaration
(Empty)
(Empty)
(Identifier)
(ObjectType)))

View File

@ -1,12 +1,11 @@
(Statements
(InterfaceDeclaration
{+(Empty)+}
{-(TypeParameters
{-(TypeParameter
{-(Identifier)-}
{-(Empty)-}
{-(Empty)-})-})-}
(Empty)
{+(Empty)+}
{ (Identifier)
->(Identifier) }
(ObjectType

View File

@ -5,7 +5,6 @@
{+(Identifier)+}
{+(Empty)+}
{+(Empty)+})+})+}
(Empty)
{-(Empty)-}
{ (Identifier)
->(Identifier) }

View File

@ -5,7 +5,6 @@
(Identifier)
(Empty)
(Empty)))
(Empty)
(Identifier)
(ObjectType
(PropertySignature

View File

@ -1,6 +1,5 @@
(Statements
(InterfaceDeclaration
(Empty)
(Empty)
(Identifier)
(ObjectType

@ -1 +1 @@
Subproject commit 9ada8cc48be1a25b971aca1a49c0963897c09d7c
Subproject commit 4a3e8b8bc08a10a0ec5b5d503a92757970672b2a