mirror of
https://github.com/github/semantic.git
synced 2024-11-23 08:27:56 +03:00
Add NFData instances to enable more accurate benchmarking.
Because we're getting serious about benchmarking in the run-up to Windrose, it's time to bring in the `deepseq` package to ensure that benchmarks can fully evaluate the result of a test case. The `deepseq` package provides an `NFData` typeclass: ``` class NFData a where rnf :: a -> () ``` Instances use the `seq` combinator to ensure that the argument to `rnf` is fully evaluated, returning (). If there is a `Generic` instance for `a`, the implementation can be omitted. This patch adds NFData for every syntax node, graph vertex, environment data structures, and exceptions. It is long, but the work is very straightforward, so don't panick. The benchmark suite (`stack bench`) now produces more accurate results. The benchmarks previously mimicked `rnf` by calling `show` on the result of an evaluation or graph construction; now that we have actual `NFData` instances we can use the `nfIO` combinator from criterion. This has sped up the evaluation benchmarks and reduced their memory consumption, while it has slowed down the call graph benchmarks, as those benchmarks weren't evaluating the whole of the graph. Unfortunately, this patch increases compile times, as we have to derive a few more Generic instances. I wish this weren't the case, but there's little we can do about it now. In the future I have some plans for how to reduce compile time, and I bet that those gains will at least nullify the speed hit from this patch. Now that we have NFData instances for every data type, we can start benchmarking assignments, in preparation for fixing #2205. This patch also pulls in updates to `effects` and `fastsum` that add appropriate NFData instances for the data they vend.
This commit is contained in:
parent
abce41c1e1
commit
ac543651ee
@ -24,16 +24,16 @@ evaluateProject proxy parser paths = withOptions defaultOptions $ \ config logge
|
||||
-- project—coercing the result into a string will suffice, though it throws off the
|
||||
-- memory allocation results a bit.
|
||||
pyEval :: FilePath -> Benchmarkable
|
||||
pyEval p = whnfIO . fmap show . evalPythonProject $ ["bench/bench-fixtures/python/" <> p]
|
||||
pyEval p = nfIO . evalPythonProject $ ["bench/bench-fixtures/python/" <> p]
|
||||
|
||||
rbEval :: FilePath -> Benchmarkable
|
||||
rbEval p = whnfIO . fmap show . evalRubyProject $ ["bench/bench-fixtures/ruby/" <> p]
|
||||
rbEval p = nfIO . evalRubyProject $ ["bench/bench-fixtures/ruby/" <> p]
|
||||
|
||||
pyCall :: FilePath -> Benchmarkable
|
||||
pyCall p = whnfIO $ callGraphProject pythonParser (Proxy @'Language.Python) defaultOptions ["bench/bench-fixtures/python/" <> p]
|
||||
pyCall p = nfIO $ callGraphProject pythonParser (Proxy @'Language.Python) defaultOptions ["bench/bench-fixtures/python/" <> p]
|
||||
|
||||
rbCall :: FilePath -> Benchmarkable
|
||||
rbCall p = whnfIO $ callGraphProject rubyParser (Proxy @'Language.Ruby) defaultOptions ["bench/bench-fixtures/ruby/" <> p]
|
||||
rbCall p = nfIO $ callGraphProject rubyParser (Proxy @'Language.Ruby) defaultOptions ["bench/bench-fixtures/ruby/" <> p]
|
||||
|
||||
main :: IO ()
|
||||
main = defaultMain
|
@ -218,6 +218,7 @@ library
|
||||
, cmark-gfm
|
||||
, containers
|
||||
, cryptohash
|
||||
, deepseq
|
||||
, directory
|
||||
, directory-tree
|
||||
, effects
|
||||
@ -423,7 +424,7 @@ test-suite doctests
|
||||
, doctest
|
||||
|
||||
benchmark evaluation
|
||||
hs-source-dirs: bench
|
||||
hs-source-dirs: bench/evaluation
|
||||
type: exitcode-stdio-1.0
|
||||
main-is: Main.hs
|
||||
ghc-options: -threaded -rtsopts "-with-rtsopts=-N -A4m -n2m -T" -static -j -O1
|
||||
|
@ -138,6 +138,14 @@ data AddressError address value resume where
|
||||
UnallocatedAddress :: address -> AddressError address value (Set value)
|
||||
UninitializedAddress :: address -> AddressError address value value
|
||||
|
||||
instance (NFData address, NFData value) => NFData1 (AddressError address value) where
|
||||
liftRnf _ x = case x of
|
||||
UnallocatedAddress a -> rnf a
|
||||
UninitializedAddress a -> rnf a
|
||||
|
||||
instance (NFData address, NFData value, NFData resume) => NFData (AddressError address value resume) where
|
||||
rnf = liftRnf rnf
|
||||
|
||||
deriving instance Eq address => Eq (AddressError address value resume)
|
||||
deriving instance Show address => Show (AddressError address value resume)
|
||||
instance Show address => Show1 (AddressError address value) where
|
||||
|
@ -109,6 +109,9 @@ instance Show1 (LoadError address) where
|
||||
instance Eq1 (LoadError address) where
|
||||
liftEq _ (ModuleNotFoundError a) (ModuleNotFoundError b) = a == b
|
||||
|
||||
instance NFData1 (LoadError address) where
|
||||
liftRnf _ (ModuleNotFoundError p) = rnf p
|
||||
|
||||
runLoadError :: Effects effects
|
||||
=> Evaluator term address value (Resumable (BaseError (LoadError address)) ': effects) a
|
||||
-> Evaluator term address value effects (Either (SomeExc (BaseError (LoadError address))) a)
|
||||
@ -142,6 +145,10 @@ instance Eq1 ResolutionError where
|
||||
liftEq _ (NotFoundError a _ l1) (NotFoundError b _ l2) = a == b && l1 == l2
|
||||
liftEq _ (GoImportError a) (GoImportError b) = a == b
|
||||
liftEq _ _ _ = False
|
||||
instance NFData1 ResolutionError where
|
||||
liftRnf _ x = case x of
|
||||
NotFoundError p ps l -> rnf p `seq` rnf ps `seq` rnf l
|
||||
GoImportError p -> rnf p
|
||||
|
||||
runResolutionError :: Effects effects
|
||||
=> Evaluator term address value (Resumable (BaseError ResolutionError) ': effects) a
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE GADTs, KindSignatures, Rank2Types #-}
|
||||
{-# LANGUAGE DeriveAnyClass, GADTs, KindSignatures, Rank2Types #-}
|
||||
module Control.Abstract.Value
|
||||
( AbstractValue(..)
|
||||
, AbstractIntro(..)
|
||||
@ -69,7 +69,7 @@ function name params body = sendFunction (Function name params body)
|
||||
data BuiltIn
|
||||
= Print
|
||||
| Show
|
||||
deriving (Eq, Ord, Show)
|
||||
deriving (Eq, Ord, Show, Generic, NFData)
|
||||
|
||||
builtIn :: Member (Function term address value) effects => BuiltIn -> Evaluator term address value effects value
|
||||
builtIn = sendFunction . BuiltIn
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE GADTs, TypeOperators, UndecidableInstances #-}
|
||||
{-# LANGUAGE GeneralizedNewtypeDeriving, GADTs, TypeOperators, UndecidableInstances #-}
|
||||
module Data.Abstract.Address.Precise
|
||||
( Precise(..)
|
||||
, runAllocator
|
||||
@ -13,7 +13,7 @@ import Prologue
|
||||
|
||||
-- | 'Precise' models precise store semantics where only the 'Latest' value is taken. Everything gets it's own address (always makes a new allocation) which makes for a larger store.
|
||||
newtype Precise = Precise { unPrecise :: Int }
|
||||
deriving (Eq, Ord)
|
||||
deriving (Eq, Ord, NFData)
|
||||
|
||||
instance Show Precise where
|
||||
showsPrec d = showsUnaryWith showsPrec "Precise" d . unPrecise
|
||||
|
@ -29,6 +29,12 @@ instance (Eq1 exc) => Eq1 (BaseError exc) where
|
||||
instance Show1 exc => Show1 (BaseError exc) where
|
||||
liftShowsPrec sl sp d (BaseError _ _ exc) = liftShowsPrec sl sp d exc
|
||||
|
||||
instance (NFData1 exc, NFData resume) => NFData (BaseError exc resume) where
|
||||
rnf = liftRnf rnf
|
||||
|
||||
instance (NFData1 exc) => NFData1 (BaseError exc) where
|
||||
liftRnf rnf' (BaseError i s e) = rnf i `seq` rnf s `seq` liftRnf rnf' e
|
||||
|
||||
throwBaseError :: ( Member (Resumable (BaseError exc)) effects
|
||||
, Member (Reader M.ModuleInfo) effects
|
||||
, Member (Reader S.Span) effects
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE GADTs #-}
|
||||
{-# LANGUAGE DeriveAnyClass, DerivingStrategies, GADTs, GeneralizedNewtypeDeriving #-}
|
||||
|
||||
module Data.Abstract.Environment
|
||||
( Environment(..)
|
||||
@ -40,7 +40,8 @@ import Prologue
|
||||
|
||||
-- | A map of names to values. Represents a single scope level of an environment chain.
|
||||
newtype Bindings address = Bindings { unBindings :: Map.Map Name address }
|
||||
deriving (Eq, Ord)
|
||||
deriving stock (Eq, Ord, Generic)
|
||||
deriving anyclass (NFData)
|
||||
|
||||
instance Semigroup (Bindings address) where
|
||||
(<>) (Bindings a) (Bindings b) = Bindings (a <> b)
|
||||
@ -60,15 +61,22 @@ instance Show address => Show (Bindings address) where
|
||||
-- All behaviors can be assumed to be frontmost-biased: looking up "a" will check the most specific
|
||||
-- scope for "a", then the next, and so on.
|
||||
newtype Environment address = Environment { unEnvironment :: NonEmpty (Bindings address) }
|
||||
deriving (Eq, Ord)
|
||||
deriving stock (Eq, Ord, Generic)
|
||||
deriving anyclass (NFData)
|
||||
|
||||
data EvalContext address = EvalContext { ctxSelf :: Maybe address, ctxEnvironment :: Environment address }
|
||||
deriving (Eq, Ord, Show)
|
||||
deriving (Eq, Ord, Show, Generic, NFData)
|
||||
|
||||
-- | Errors involving the environment.
|
||||
data EnvironmentError address return where
|
||||
FreeVariable :: Name -> EnvironmentError address address
|
||||
|
||||
instance NFData1 (EnvironmentError address) where
|
||||
liftRnf _ (FreeVariable n) = rnf n
|
||||
|
||||
instance (NFData address, NFData return) => NFData (EnvironmentError address return) where
|
||||
rnf = liftRnf rnf
|
||||
|
||||
deriving instance Eq (EnvironmentError address return)
|
||||
deriving instance Show (EnvironmentError address return)
|
||||
instance Show1 (EnvironmentError address) where liftShowsPrec _ _ = showsPrec
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE GADTs, KindSignatures, RankNTypes, TypeOperators, UndecidableInstances #-}
|
||||
{-# LANGUAGE DeriveAnyClass, GADTs, KindSignatures, RankNTypes, TypeOperators, UndecidableInstances #-}
|
||||
module Data.Abstract.Evaluatable
|
||||
( module X
|
||||
, Evaluatable(..)
|
||||
@ -257,6 +257,18 @@ data EvalError return where
|
||||
deriving instance Eq (EvalError return)
|
||||
deriving instance Show (EvalError return)
|
||||
|
||||
instance NFData1 EvalError where
|
||||
liftRnf _ x = case x of
|
||||
NoNameError -> ()
|
||||
IntegerFormatError i -> rnf i
|
||||
FloatFormatError i -> rnf i
|
||||
RationalFormatError i -> rnf i
|
||||
DefaultExportError -> ()
|
||||
ExportError p n -> rnf p `seq` rnf n
|
||||
|
||||
instance NFData return => NFData (EvalError return) where
|
||||
rnf = liftRnf rnf
|
||||
|
||||
instance Eq1 EvalError where
|
||||
liftEq _ NoNameError NoNameError = True
|
||||
liftEq _ DefaultExportError DefaultExportError = True
|
||||
@ -287,9 +299,16 @@ throwEvalError = throwBaseError
|
||||
data UnspecializedError a b where
|
||||
UnspecializedError :: String -> UnspecializedError value value
|
||||
|
||||
instance NFData1 (UnspecializedError a) where
|
||||
liftRnf _ (UnspecializedError s) = rnf s
|
||||
|
||||
instance NFData b => NFData (UnspecializedError a b) where
|
||||
rnf = liftRnf rnf
|
||||
|
||||
deriving instance Eq (UnspecializedError a b)
|
||||
deriving instance Show (UnspecializedError a b)
|
||||
|
||||
|
||||
instance Eq1 (UnspecializedError a) where
|
||||
liftEq _ (UnspecializedError a) (UnspecializedError b) = a == b
|
||||
|
||||
|
@ -17,7 +17,7 @@ import Prologue
|
||||
|
||||
-- | A map of addresses onto cells holding their values.
|
||||
newtype Heap address value = Heap { unHeap :: Monoidal.Map address (Set value) }
|
||||
deriving (Eq, Foldable, Lower, Monoid, Ord, Semigroup)
|
||||
deriving (Eq, Foldable, Lower, Monoid, Ord, Semigroup, Generic, NFData)
|
||||
|
||||
-- | Look up the cell of values for an 'Address' in a 'Heap', if any.
|
||||
heapLookup :: Ord address => address -> Heap address value -> Maybe (Set value)
|
||||
|
@ -1,3 +1,5 @@
|
||||
{-# LANGUAGE DeriveAnyClass, DerivingStrategies #-}
|
||||
|
||||
module Data.Abstract.Module
|
||||
( Module(..)
|
||||
, moduleForBlob
|
||||
@ -13,7 +15,8 @@ import Prologue
|
||||
import System.FilePath.Posix
|
||||
|
||||
data Module body = Module { moduleInfo :: ModuleInfo, moduleBody :: body }
|
||||
deriving (Eq, Foldable, Functor, Ord, Traversable)
|
||||
deriving stock (Eq, Foldable, Functor, Ord, Traversable, Generic)
|
||||
deriving anyclass (NFData)
|
||||
|
||||
instance Show body => Show (Module body) where
|
||||
showsPrec d Module{..} = showsBinaryWith showsPrec showsPrec "Module" d (modulePath moduleInfo) moduleBody
|
||||
@ -32,7 +35,8 @@ moduleForBlob rootDir Blob{..} = Module info
|
||||
type ModulePath = FilePath
|
||||
|
||||
newtype ModuleInfo = ModuleInfo { modulePath :: ModulePath }
|
||||
deriving (Eq, Ord)
|
||||
deriving stock (Eq, Ord, Generic)
|
||||
deriving anyclass (NFData)
|
||||
|
||||
instance Show ModuleInfo where
|
||||
showsPrec d = showsUnaryWith showsPrec "ModuleInfo" d . modulePath
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
||||
{-# LANGUAGE DeriveAnyClass, DerivingStrategies, GeneralizedNewtypeDeriving #-}
|
||||
module Data.Abstract.ModuleTable
|
||||
( ModulePath
|
||||
, ModuleTable (..)
|
||||
@ -21,7 +21,9 @@ import Prologue
|
||||
import System.FilePath.Posix
|
||||
|
||||
newtype ModuleTable a = ModuleTable { unModuleTable :: Map.Map ModulePath a }
|
||||
deriving (Eq, Foldable, Functor, Generic1, Lower, Monoid, Ord, Semigroup, Traversable)
|
||||
deriving stock (Eq, Foldable, Functor, Generic1, Generic, Ord, Traversable)
|
||||
deriving newtype (Lower, Monoid, Semigroup)
|
||||
deriving anyclass (NFData)
|
||||
|
||||
singleton :: ModulePath -> a -> ModuleTable a
|
||||
singleton name = ModuleTable . Map.singleton name
|
||||
|
@ -24,7 +24,7 @@ import qualified Proto3.Wire.Encode as Encode
|
||||
data Name
|
||||
= Name Text
|
||||
| I Int
|
||||
deriving (Eq, Ord, MessageField)
|
||||
deriving (Eq, Ord, MessageField, Generic, NFData)
|
||||
|
||||
instance HasDefault Name where
|
||||
def = Name mempty
|
||||
|
@ -32,6 +32,12 @@ data Number a where
|
||||
|
||||
deriving instance Eq a => Eq (Number a)
|
||||
|
||||
instance NFData (Number a) where
|
||||
rnf a = case a of
|
||||
Integer i -> rnf i
|
||||
Ratio r -> rnf r
|
||||
Decimal d -> rnf d
|
||||
|
||||
instance Show (Number a) where
|
||||
show (Integer i) = show i
|
||||
show (Ratio r) = show r
|
||||
|
@ -1,3 +1,5 @@
|
||||
{-# LANGUAGE DeriveAnyClass #-}
|
||||
|
||||
module Data.Abstract.Package
|
||||
( Package (..)
|
||||
, PackageInfo (..)
|
||||
@ -18,7 +20,7 @@ data PackageInfo = PackageInfo
|
||||
{ packageName :: PackageName
|
||||
, packageResolutions :: Map.Map FilePath FilePath
|
||||
}
|
||||
deriving (Eq, Ord, Show)
|
||||
deriving (Eq, Ord, Show, Generic, NFData)
|
||||
|
||||
-- | A package represents the unit of dependency, i.e. something which can depend upon, or be depended upon by, other packages. Packages have modules and may have entry points from which evaluation can proceed.
|
||||
data Package term = Package
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE GADTs #-}
|
||||
{-# LANGUAGE DeriveAnyClass, GADTs #-}
|
||||
module Data.Abstract.ScopeGraph
|
||||
( ScopeGraph(..)
|
||||
, Path
|
||||
@ -40,7 +40,7 @@ data Scope scopeAddress = Scope {
|
||||
edges :: Map EdgeLabel [scopeAddress] -- Maybe Map EdgeLabel [Path scope]?
|
||||
, references :: Map Reference (Path scopeAddress)
|
||||
, declarations :: Map Declaration (Span, Maybe scopeAddress)
|
||||
} deriving (Eq, Show, Ord)
|
||||
} deriving (Eq, Show, Ord, Generic, NFData)
|
||||
|
||||
|
||||
data ScopeGraph scope = ScopeGraph { graph :: Map scope (Scope scope), currentScope :: Maybe scope }
|
||||
@ -51,6 +51,8 @@ instance Ord scope => Lower (ScopeGraph scope) where
|
||||
deriving instance Eq address => Eq (ScopeGraph address)
|
||||
deriving instance Show address => Show (ScopeGraph address)
|
||||
deriving instance Ord address => Ord (ScopeGraph address)
|
||||
deriving instance Generic (ScopeGraph address)
|
||||
deriving instance NFData scope => NFData (ScopeGraph scope)
|
||||
|
||||
data Path scope where
|
||||
-- | Construct a direct path to a declaration.
|
||||
@ -61,6 +63,8 @@ data Path scope where
|
||||
deriving instance Eq scope => Eq (Path scope)
|
||||
deriving instance Show scope => Show (Path scope)
|
||||
deriving instance Ord scope => Ord (Path scope)
|
||||
deriving instance Generic (Path scope)
|
||||
deriving instance NFData scope => NFData (Path scope)
|
||||
|
||||
-- Returns the declaration of a path.
|
||||
pathDeclaration :: Path scope -> Declaration
|
||||
@ -167,15 +171,15 @@ associatedScope declaration g@ScopeGraph{..} = go (Map.keys graph)
|
||||
go [] = Nothing
|
||||
|
||||
newtype Reference = Reference Name
|
||||
deriving (Eq, Ord, Show)
|
||||
deriving (Eq, Ord, Show, Generic, NFData)
|
||||
|
||||
newtype Declaration = Declaration Name
|
||||
deriving (Eq, Ord, Show)
|
||||
deriving (Eq, Ord, Show, Generic, NFData)
|
||||
|
||||
-- | The type of edge from a scope to its parent scopes.
|
||||
-- Either a lexical edge or an import edge in the case of non-lexical edges.
|
||||
data EdgeLabel = Lexical | Import
|
||||
deriving (Eq, Ord, Show)
|
||||
deriving (Eq, Ord, Show, Generic, NFData)
|
||||
|
||||
data Frame scopeAddress frameAddress value = Frame {
|
||||
scopeAddress :: scopeAddress
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE GADTs, RankNTypes, TypeOperators, ScopedTypeVariables, UndecidableInstances, LambdaCase #-}
|
||||
{-# LANGUAGE StandaloneDeriving, DeriveAnyClass, GADTs, RankNTypes, TypeOperators, ScopedTypeVariables, UndecidableInstances, LambdaCase #-}
|
||||
module Data.Abstract.Value.Concrete
|
||||
( Value (..)
|
||||
, ValueError (..)
|
||||
@ -46,7 +46,7 @@ data Value term address
|
||||
| Hash [Value term address]
|
||||
| Null
|
||||
| Hole
|
||||
deriving (Eq, Ord, Show)
|
||||
deriving (Eq, Ord, Show, Generic, NFData)
|
||||
|
||||
|
||||
instance Ord address => ValueRoots address (Value term address) where
|
||||
@ -357,6 +357,25 @@ data ValueError term address resume where
|
||||
-- Out-of-bounds error
|
||||
BoundsError :: [address] -> Prelude.Integer -> ValueError term address (Value term address)
|
||||
|
||||
instance (NFData term, NFData address) => NFData1 (ValueError term address) where
|
||||
liftRnf _ x = case x of
|
||||
StringError i -> rnf i
|
||||
BoolError i -> rnf i
|
||||
IndexError i j -> rnf i `seq` rnf j
|
||||
NamespaceError i -> rnf i
|
||||
CallError i -> rnf i
|
||||
NumericError i -> rnf i
|
||||
Numeric2Error i j -> rnf i `seq` rnf j
|
||||
ComparisonError i j -> rnf i `seq` rnf j
|
||||
BitwiseError i -> rnf i
|
||||
Bitwise2Error i j -> rnf i `seq` rnf j
|
||||
KeyValueError i -> rnf i
|
||||
ArrayError i -> rnf i
|
||||
ArithmeticError i -> i `seq` ()
|
||||
BoundsError i j -> rnf i `seq` rnf j
|
||||
|
||||
instance (NFData term, NFData address, NFData resume) => NFData (ValueError term address resume) where
|
||||
rnf = liftRnf rnf
|
||||
|
||||
instance (Eq address, Eq term) => Eq1 (ValueError term address) where
|
||||
liftEq _ (StringError a) (StringError b) = a == b
|
||||
|
@ -27,7 +27,7 @@ import qualified Data.Set as Set
|
||||
|
||||
-- | An algebraic graph with 'Ord', 'Semigroup', and 'Monoid' instances.
|
||||
newtype Graph vertex = Graph { unGraph :: G.Graph vertex }
|
||||
deriving (Alternative, Applicative, Eq, Foldable, Functor, Monad, Show, Class.Graph, Class.ToGraph, Traversable)
|
||||
deriving (Alternative, Applicative, Eq, Foldable, Functor, Monad, Show, Class.Graph, Class.ToGraph, Traversable, NFData)
|
||||
|
||||
|
||||
simplify :: Ord vertex => Graph vertex -> Graph vertex
|
||||
|
@ -43,7 +43,7 @@ data ControlFlowVertex
|
||||
| Variable { vertexName :: Text, vertexModuleName :: Text, vertexSpan :: Span }
|
||||
| Method { vertexName :: Text, vertexModuleName :: Text, vertexSpan :: Span }
|
||||
| Function { vertexName :: Text, vertexModuleName :: Text, vertexSpan :: Span }
|
||||
deriving (Eq, Ord, Show, Generic, Hashable, Named)
|
||||
deriving (Eq, Ord, Show, Generic, Hashable, Named, NFData)
|
||||
|
||||
packageVertex :: PackageInfo -> ControlFlowVertex
|
||||
packageVertex (PackageInfo name _) = Package (formatName name)
|
||||
|
@ -33,7 +33,7 @@ data Language
|
||||
| Ruby
|
||||
| TypeScript
|
||||
| PHP
|
||||
deriving (Eq, Generic, Ord, Read, Show, Bounded, Hashable, ToJSON, Named, Enum, MessageField)
|
||||
deriving (Eq, Generic, Ord, Read, Show, Bounded, Hashable, ToJSON, Named, Enum, MessageField, NFData)
|
||||
|
||||
class SLanguage (lang :: Language) where
|
||||
reflect :: proxy lang -> Language
|
||||
|
@ -1,9 +1,13 @@
|
||||
{-# LANGUAGE DeriveAnyClass #-}
|
||||
|
||||
module Data.Location
|
||||
( Location(..)
|
||||
, Span(..)
|
||||
, Range(..)
|
||||
) where
|
||||
|
||||
import Prologue (Generic (..), NFData (..))
|
||||
|
||||
import Data.JSON.Fields
|
||||
import Data.Range
|
||||
import Data.Span
|
||||
@ -13,7 +17,7 @@ data Location
|
||||
{ locationByteRange :: {-# UNPACK #-} Range
|
||||
, locationSpan :: {-# UNPACK #-} Span
|
||||
}
|
||||
deriving (Eq, Ord, Show)
|
||||
deriving (Eq, Ord, Show, Generic, NFData)
|
||||
|
||||
instance ToJSONFields Location where
|
||||
toJSONFields Location{..} = toJSONFields locationByteRange <> toJSONFields locationSpan
|
||||
|
@ -20,7 +20,7 @@ import Prelude hiding (lookup)
|
||||
import Prologue hiding (Map)
|
||||
|
||||
newtype Map key value = Map { unMap :: Map.Map key value }
|
||||
deriving (Eq, Eq1, Eq2, Foldable, Functor, Ord, Ord1, Ord2, Show, Show1, Show2, ToJSON, Traversable)
|
||||
deriving (Eq, Eq1, Eq2, Foldable, Functor, Ord, Ord1, Ord2, Show, Show1, Show2, ToJSON, Traversable, NFData)
|
||||
|
||||
|
||||
singleton :: key -> value -> Map key value
|
||||
|
@ -4,6 +4,7 @@ module Data.Quieterm
|
||||
, quieterm
|
||||
) where
|
||||
|
||||
import Control.DeepSeq
|
||||
import Data.Abstract.Declarations (Declarations)
|
||||
import Data.Abstract.FreeVariables (FreeVariables)
|
||||
import Data.Functor.Classes
|
||||
@ -36,5 +37,11 @@ instance Show1 syntax => Show1 (Quieterm syntax) where
|
||||
instance Show1 syntax => Show (Quieterm syntax ann) where
|
||||
showsPrec = liftShowsPrec (const (const id)) (const id)
|
||||
|
||||
instance NFData1 f => NFData1 (Quieterm f) where
|
||||
liftRnf rnf = go where go x = liftRnf2 rnf go (unQuieterm x)
|
||||
|
||||
instance (NFData1 f, NFData a) => NFData (Quieterm f a) where
|
||||
rnf = liftRnf rnf
|
||||
|
||||
quieterm :: (Recursive term, Base term ~ TermF syntax ann) => term -> Quieterm syntax ann
|
||||
quieterm = cata Quieterm
|
||||
|
@ -17,7 +17,7 @@ import Proto3.Wire.Decode as Decode
|
||||
|
||||
-- | A half-open interval of integers, defined by start & end indices.
|
||||
data Range = Range { start :: {-# UNPACK #-} !Int, end :: {-# UNPACK #-} !Int }
|
||||
deriving (Eq, Generic, Named)
|
||||
deriving (Eq, Generic, Named, NFData)
|
||||
|
||||
emptyRange :: Range
|
||||
emptyRange = Range 0 0
|
||||
|
@ -24,14 +24,14 @@ data Pos = Pos
|
||||
{ posLine :: !Int
|
||||
, posColumn :: !Int
|
||||
}
|
||||
deriving (Eq, Ord, Generic, Hashable)
|
||||
deriving (Eq, Ord, Generic, Hashable, NFData)
|
||||
|
||||
-- | A Span of position information
|
||||
data Span = Span
|
||||
{ spanStart :: Pos
|
||||
, spanEnd :: Pos
|
||||
}
|
||||
deriving (Eq, Ord, Generic, Hashable, Named)
|
||||
deriving (Eq, Ord, Generic, Hashable, Named, NFData)
|
||||
|
||||
|
||||
-- Instances
|
||||
|
@ -155,7 +155,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, Message1, Named1, ToJSONFields1)
|
||||
deriving anyclass (Diffable, Hashable1, Message1, Named1, ToJSONFields1, NFData1)
|
||||
|
||||
instance Eq1 Identifier where liftEq = genericLiftEq
|
||||
instance Ord1 Identifier where liftCompare = genericLiftCompare
|
||||
@ -177,7 +177,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, Message1, Named1, ToJSONFields1)
|
||||
deriving anyclass (Declarations1, Diffable, FreeVariables1, Hashable1, Message1, Named1, ToJSONFields1, NFData1)
|
||||
|
||||
instance Eq1 AccessibilityModifier where liftEq = genericLiftEq
|
||||
instance Ord1 AccessibilityModifier where liftCompare = genericLiftCompare
|
||||
@ -190,7 +190,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, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Empty where liftEq _ _ _ = True
|
||||
instance Ord1 Empty where liftCompare _ _ _ = EQ
|
||||
@ -204,7 +204,7 @@ instance Tokenize 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, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
|
||||
instance Eq1 Error where liftEq = genericLiftEq
|
||||
instance Ord1 Error where liftCompare = genericLiftCompare
|
||||
@ -233,7 +233,7 @@ unError span Error{..} = Error.Error span errorExpected errorActual stack
|
||||
where stack = fromCallSiteList $ unErrorSite <$> unErrorStack errorCallStack
|
||||
|
||||
data ErrorSite = ErrorSite { errorMessage :: String, errorLocation :: SrcLoc }
|
||||
deriving (Eq, Show, Generic, Named, Message)
|
||||
deriving (Eq, Show, Generic, Named, Message, NFData)
|
||||
|
||||
errorSite :: (String, SrcLoc) -> ErrorSite
|
||||
errorSite = uncurry ErrorSite
|
||||
@ -243,7 +243,7 @@ unErrorSite ErrorSite{..} = (errorMessage, errorLocation)
|
||||
|
||||
newtype ErrorStack = ErrorStack { unErrorStack :: [ErrorSite] }
|
||||
deriving stock (Eq, Show, Generic)
|
||||
deriving anyclass (Named, Message)
|
||||
deriving anyclass (Named, Message, NFData)
|
||||
deriving newtype (MessageField)
|
||||
|
||||
instance HasDefault ErrorStack where
|
||||
@ -289,7 +289,7 @@ instance Ord ErrorStack where
|
||||
|
||||
|
||||
data Context a = Context { contextTerms :: NonEmpty a, contextSubject :: a }
|
||||
deriving (Declarations1, Eq, Foldable, FreeVariables1, Functor, Generic1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Declarations1, Eq, Foldable, FreeVariables1, Functor, Generic1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
|
||||
instance Diffable Context where
|
||||
subalgorithmFor blur focus (Context n s) = Context <$> traverse blur n <*> focus s
|
||||
|
@ -11,7 +11,7 @@ import Reprinting.Tokenize as Token
|
||||
|
||||
-- | An unnested comment (line or block).
|
||||
newtype Comment a = Comment { commentContent :: Text }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Comment where liftEq = genericLiftEq
|
||||
instance Ord1 Comment where liftCompare = genericLiftCompare
|
||||
@ -30,7 +30,7 @@ instance Tokenize Comment where
|
||||
|
||||
-- | HashBang line (e.g. `#!/usr/bin/env node`)
|
||||
newtype HashBang a = HashBang { value :: Text }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 HashBang where liftEq = genericLiftEq
|
||||
instance Ord1 HashBang where liftCompare = genericLiftCompare
|
||||
|
@ -15,7 +15,7 @@ import Proto3.Suite.Class
|
||||
import Reprinting.Tokenize
|
||||
|
||||
data Function a = Function { functionContext :: ![a], functionName :: !a, functionParameters :: ![a], functionBody :: !a }
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, ToJSONFields1, Named1, Message1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Diffable Function where
|
||||
equivalentBySubterm = Just . functionName
|
||||
@ -49,7 +49,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, ToJSONFields1, Named1, Message1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Method where liftEq = genericLiftEq
|
||||
instance Ord1 Method where liftCompare = genericLiftCompare
|
||||
@ -83,7 +83,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 MethodSignature where liftEq = genericLiftEq
|
||||
instance Ord1 MethodSignature where liftCompare = genericLiftCompare
|
||||
@ -94,7 +94,7 @@ instance Evaluatable MethodSignature
|
||||
|
||||
|
||||
newtype RequiredParameter a = RequiredParameter { requiredParameter :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 RequiredParameter where liftEq = genericLiftEq
|
||||
instance Ord1 RequiredParameter where liftCompare = genericLiftCompare
|
||||
@ -105,7 +105,7 @@ instance Evaluatable RequiredParameter
|
||||
|
||||
|
||||
newtype OptionalParameter a = OptionalParameter { optionalParameter :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 OptionalParameter where liftEq = genericLiftEq
|
||||
instance Ord1 OptionalParameter where liftCompare = genericLiftCompare
|
||||
@ -120,7 +120,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 VariableDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 VariableDeclaration where liftCompare = genericLiftCompare
|
||||
@ -150,7 +150,7 @@ instance Declarations a => Declarations (VariableDeclaration a) where
|
||||
-- | A TypeScript/Java style interface declaration to implement.
|
||||
|
||||
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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 InterfaceDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 InterfaceDeclaration where liftCompare = genericLiftCompare
|
||||
@ -165,7 +165,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 PublicFieldDefinition where liftEq = genericLiftEq
|
||||
instance Ord1 PublicFieldDefinition where liftCompare = genericLiftCompare
|
||||
@ -182,7 +182,7 @@ instance Evaluatable PublicFieldDefinition where
|
||||
|
||||
|
||||
data Variable a = Variable { variableName :: !a, variableType :: !a, variableValue :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Variable where liftEq = genericLiftEq
|
||||
instance Ord1 Variable where liftCompare = genericLiftCompare
|
||||
@ -192,7 +192,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, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Declarations a => Declarations (Class a) where
|
||||
declaredName (Class _ name _ _) = declaredName name
|
||||
@ -234,7 +234,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Decorator where liftEq = genericLiftEq
|
||||
instance Ord1 Decorator where liftCompare = genericLiftCompare
|
||||
@ -248,7 +248,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Data.Syntax.Declaration.Datatype where liftEq = genericLiftEq
|
||||
instance Ord1 Data.Syntax.Declaration.Datatype where liftCompare = genericLiftCompare
|
||||
@ -260,7 +260,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Data.Syntax.Declaration.Constructor where liftEq = genericLiftEq
|
||||
instance Ord1 Data.Syntax.Declaration.Constructor where liftCompare = genericLiftCompare
|
||||
@ -272,7 +272,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Comprehension where liftEq = genericLiftEq
|
||||
instance Ord1 Comprehension where liftCompare = genericLiftCompare
|
||||
@ -284,7 +284,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Type where liftEq = genericLiftEq
|
||||
instance Ord1 Type where liftCompare = genericLiftCompare
|
||||
@ -296,7 +296,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 TypeAlias where liftEq = genericLiftEq
|
||||
instance Ord1 TypeAlias where liftCompare = genericLiftCompare
|
||||
|
@ -13,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 File where liftEq = genericLiftEq
|
||||
instance Ord1 File where liftCompare = genericLiftCompare
|
||||
@ -25,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Line where liftEq = genericLiftEq
|
||||
instance Ord1 Line where liftCompare = genericLiftCompare
|
||||
|
@ -19,7 +19,7 @@ import qualified Data.Reprinting.Token as Token
|
||||
|
||||
-- | 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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Call where liftEq = genericLiftEq
|
||||
instance Ord1 Call where liftCompare = genericLiftCompare
|
||||
@ -40,7 +40,7 @@ instance Tokenize Call where
|
||||
callBlock
|
||||
|
||||
data LessThan a = LessThan { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 LessThan where liftEq = genericLiftEq
|
||||
instance Ord1 LessThan where liftCompare = genericLiftCompare
|
||||
@ -52,7 +52,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 LessThanEqual where liftEq = genericLiftEq
|
||||
instance Ord1 LessThanEqual where liftCompare = genericLiftCompare
|
||||
@ -64,7 +64,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 GreaterThan where liftEq = genericLiftEq
|
||||
instance Ord1 GreaterThan where liftCompare = genericLiftCompare
|
||||
@ -76,7 +76,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 GreaterThanEqual where liftEq = genericLiftEq
|
||||
instance Ord1 GreaterThanEqual where liftCompare = genericLiftCompare
|
||||
@ -88,7 +88,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Equal where liftEq = genericLiftEq
|
||||
instance Ord1 Equal where liftCompare = genericLiftCompare
|
||||
@ -102,7 +102,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 StrictEqual where liftEq = genericLiftEq
|
||||
instance Ord1 StrictEqual where liftCompare = genericLiftCompare
|
||||
@ -116,7 +116,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Comparison where liftEq = genericLiftEq
|
||||
instance Ord1 Comparison where liftCompare = genericLiftCompare
|
||||
@ -128,7 +128,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Plus where liftEq = genericLiftEq
|
||||
instance Ord1 Plus where liftCompare = genericLiftCompare
|
||||
@ -142,7 +142,7 @@ instance Tokenize Plus where
|
||||
tokenize Plus{..} = within' (Scope.InfixL Add 6) $ lhs *> yield Token.Sym <* rhs
|
||||
|
||||
data Minus a = Minus { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Minus where liftEq = genericLiftEq
|
||||
instance Ord1 Minus where liftCompare = genericLiftCompare
|
||||
@ -156,7 +156,7 @@ instance Tokenize Minus where
|
||||
tokenize Minus{..} = within' (Scope.InfixL Subtract 6) $ lhs *> yield Token.Sym <* rhs
|
||||
|
||||
data Times a = Times { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Times where liftEq = genericLiftEq
|
||||
instance Ord1 Times where liftCompare = genericLiftCompare
|
||||
@ -170,7 +170,7 @@ instance Tokenize Times where
|
||||
tokenize Times{..} = within' (Scope.InfixL Multiply 7) $ lhs *> yield Token.Sym <* rhs
|
||||
|
||||
data DividedBy a = DividedBy { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 DividedBy where liftEq = genericLiftEq
|
||||
instance Ord1 DividedBy where liftCompare = genericLiftCompare
|
||||
@ -181,7 +181,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Modulo where liftEq = genericLiftEq
|
||||
instance Ord1 Modulo where liftCompare = genericLiftCompare
|
||||
@ -192,7 +192,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Power where liftEq = genericLiftEq
|
||||
instance Ord1 Power where liftCompare = genericLiftCompare
|
||||
@ -203,7 +203,7 @@ instance Evaluatable Power where
|
||||
go (Power a b) = liftNumeric2 liftedExponent a b
|
||||
|
||||
newtype Negate a = Negate { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Negate where liftEq = genericLiftEq
|
||||
instance Ord1 Negate where liftCompare = genericLiftCompare
|
||||
@ -214,7 +214,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 FloorDivision where liftEq = genericLiftEq
|
||||
instance Ord1 FloorDivision where liftCompare = genericLiftCompare
|
||||
@ -226,7 +226,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Matches where liftEq = genericLiftEq
|
||||
instance Ord1 Matches where liftCompare = genericLiftCompare
|
||||
@ -234,7 +234,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 NotMatches where liftEq = genericLiftEq
|
||||
instance Ord1 NotMatches where liftCompare = genericLiftCompare
|
||||
@ -242,7 +242,7 @@ 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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Or where liftEq = genericLiftEq
|
||||
instance Ord1 Or where liftCompare = genericLiftCompare
|
||||
@ -252,7 +252,7 @@ instance Evaluatable Or where
|
||||
eval eval (Or a b) = disjunction (eval a >>= Abstract.value) (eval b >>= Abstract.value) >>= rvalBox
|
||||
|
||||
data And a = And { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 And where liftEq = genericLiftEq
|
||||
instance Ord1 And where liftCompare = genericLiftCompare
|
||||
@ -264,7 +264,7 @@ instance Evaluatable And where
|
||||
ifthenelse cond b (pure cond)
|
||||
|
||||
newtype Not a = Not { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Not where liftEq = genericLiftEq
|
||||
instance Ord1 Not where liftCompare = genericLiftCompare
|
||||
@ -275,7 +275,7 @@ instance Evaluatable Not where
|
||||
go (Not a) = a >>= asBool >>= boolean . not
|
||||
|
||||
data XOr a = XOr { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 XOr where liftEq = genericLiftEq
|
||||
instance Ord1 XOr where liftCompare = genericLiftCompare
|
||||
@ -288,7 +288,7 @@ instance Evaluatable XOr where
|
||||
|
||||
-- | Javascript delete operator
|
||||
newtype Delete a = Delete { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Delete where liftEq = genericLiftEq
|
||||
instance Ord1 Delete where liftCompare = genericLiftCompare
|
||||
@ -303,7 +303,7 @@ instance Evaluatable Delete where
|
||||
|
||||
-- | 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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 SequenceExpression where liftEq = genericLiftEq
|
||||
instance Ord1 SequenceExpression where liftCompare = genericLiftCompare
|
||||
@ -315,7 +315,7 @@ instance Evaluatable SequenceExpression where
|
||||
|
||||
-- | Javascript void operator
|
||||
newtype Void a = Void { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Void where liftEq = genericLiftEq
|
||||
instance Ord1 Void where liftCompare = genericLiftCompare
|
||||
@ -327,7 +327,7 @@ instance Evaluatable Void where
|
||||
|
||||
-- | Javascript typeof operator
|
||||
newtype Typeof a = Typeof { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Typeof where liftEq = genericLiftEq
|
||||
instance Ord1 Typeof where liftCompare = genericLiftCompare
|
||||
@ -338,7 +338,7 @@ instance Evaluatable Typeof
|
||||
|
||||
-- | Bitwise operators.
|
||||
data BOr a = BOr { left :: a, right :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 BOr where liftEq = genericLiftEq
|
||||
instance Ord1 BOr where liftCompare = genericLiftCompare
|
||||
@ -350,7 +350,7 @@ instance Evaluatable BOr where
|
||||
liftBitwise2 (.|.) a' b' >>= rvalBox
|
||||
|
||||
data BAnd a = BAnd { left :: a, right :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 BAnd where liftEq = genericLiftEq
|
||||
instance Ord1 BAnd where liftCompare = genericLiftCompare
|
||||
@ -363,7 +363,7 @@ instance Evaluatable BAnd where
|
||||
|
||||
|
||||
data BXOr a = BXOr { left :: a, right :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 BXOr where liftEq = genericLiftEq
|
||||
instance Ord1 BXOr where liftCompare = genericLiftCompare
|
||||
@ -375,7 +375,7 @@ instance Evaluatable BXOr where
|
||||
liftBitwise2 xor a' b' >>= rvalBox
|
||||
|
||||
data LShift a = LShift { left :: a, right :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 LShift where liftEq = genericLiftEq
|
||||
instance Ord1 LShift where liftCompare = genericLiftCompare
|
||||
@ -389,7 +389,7 @@ instance Evaluatable LShift where
|
||||
shiftL' a b = shiftL a (fromIntegral (toInteger b))
|
||||
|
||||
data RShift a = RShift { left :: a, right :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 RShift where liftEq = genericLiftEq
|
||||
instance Ord1 RShift where liftCompare = genericLiftCompare
|
||||
@ -403,7 +403,7 @@ instance Evaluatable RShift where
|
||||
shiftR' a b = shiftR a (fromIntegral (toInteger b))
|
||||
|
||||
data UnsignedRShift a = UnsignedRShift { left :: a, right :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 UnsignedRShift where liftEq = genericLiftEq
|
||||
instance Ord1 UnsignedRShift where liftCompare = genericLiftCompare
|
||||
@ -415,7 +415,7 @@ instance Evaluatable UnsignedRShift where
|
||||
unsignedRShift a' b' >>= rvalBox
|
||||
|
||||
newtype Complement a = Complement { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Complement where liftEq = genericLiftEq
|
||||
instance Ord1 Complement where liftCompare = genericLiftCompare
|
||||
@ -428,7 +428,7 @@ instance Evaluatable Complement where
|
||||
|
||||
-- | Member Access (e.g. a.b)
|
||||
data MemberAccess a = MemberAccess { lhs :: a, rhs :: Name }
|
||||
deriving (Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Declarations1 MemberAccess where
|
||||
liftDeclaredName _ MemberAccess{..} = Just rhs
|
||||
@ -454,7 +454,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Subscript where liftEq = genericLiftEq
|
||||
instance Ord1 Subscript where liftCompare = genericLiftCompare
|
||||
@ -467,7 +467,7 @@ instance Evaluatable Subscript where
|
||||
eval _ (Subscript _ _) = rvalBox =<< throwUnspecializedError (UnspecializedError "Eval unspecialized for subscript with slices")
|
||||
|
||||
data Member a = Member { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Member where liftEq = genericLiftEq
|
||||
instance Ord1 Member where liftCompare = genericLiftCompare
|
||||
@ -477,7 +477,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Enumeration where liftEq = genericLiftEq
|
||||
instance Ord1 Enumeration where liftCompare = genericLiftCompare
|
||||
@ -489,7 +489,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 InstanceOf where liftEq = genericLiftEq
|
||||
instance Ord1 InstanceOf where liftCompare = genericLiftCompare
|
||||
@ -501,7 +501,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Hashable1 ScopeResolution where liftHashWithSalt = foldl
|
||||
instance Eq1 ScopeResolution where liftEq = genericLiftEq
|
||||
@ -515,7 +515,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 NonNullExpression where liftEq = genericLiftEq
|
||||
instance Ord1 NonNullExpression where liftCompare = genericLiftCompare
|
||||
@ -527,7 +527,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Await where liftEq = genericLiftEq
|
||||
instance Ord1 Await where liftCompare = genericLiftCompare
|
||||
@ -540,7 +540,7 @@ instance Evaluatable Await where
|
||||
|
||||
-- | An object constructor call in Javascript, Java, etc.
|
||||
newtype New a = New { newSubject :: [a] }
|
||||
deriving (Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Declarations1 New where
|
||||
liftDeclaredName _ (New []) = Nothing
|
||||
@ -563,7 +563,7 @@ instance Evaluatable New where
|
||||
|
||||
-- | A cast expression to a specified type.
|
||||
data Cast a = Cast { castSubject :: !a, castType :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Cast where liftEq = genericLiftEq
|
||||
instance Ord1 Cast where liftCompare = genericLiftCompare
|
||||
@ -572,7 +572,7 @@ instance Show1 Cast where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable Cast
|
||||
|
||||
data Super a = Super
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1, Named1, Message1)
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Super where liftEq = genericLiftEq
|
||||
instance Ord1 Super where liftCompare = genericLiftCompare
|
||||
@ -581,7 +581,7 @@ instance Evaluatable Super where
|
||||
eval _ Super = Rval <$> (maybeM (box unit) =<< self)
|
||||
|
||||
data This a = This
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1, Named1, Message1)
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 This where liftEq = genericLiftEq
|
||||
instance Ord1 This where liftCompare = genericLiftCompare
|
||||
|
@ -18,7 +18,7 @@ import Text.Read (readMaybe)
|
||||
-- Boolean
|
||||
|
||||
newtype Boolean a = Boolean { booleanContent :: Bool }
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
true :: Boolean a
|
||||
true = Boolean True
|
||||
@ -40,7 +40,7 @@ instance Tokenize 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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Data.Syntax.Literal.Integer where liftEq = genericLiftEq
|
||||
instance Ord1 Data.Syntax.Literal.Integer where liftCompare = genericLiftCompare
|
||||
@ -57,7 +57,7 @@ instance Tokenize 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, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Data.Syntax.Literal.Float where liftEq = genericLiftEq
|
||||
instance Ord1 Data.Syntax.Literal.Float where liftCompare = genericLiftCompare
|
||||
@ -72,7 +72,7 @@ instance Tokenize 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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Data.Syntax.Literal.Rational where liftEq = genericLiftEq
|
||||
instance Ord1 Data.Syntax.Literal.Rational where liftCompare = genericLiftCompare
|
||||
@ -87,7 +87,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, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Data.Syntax.Literal.Complex where liftEq = genericLiftEq
|
||||
instance Ord1 Data.Syntax.Literal.Complex where liftCompare = genericLiftCompare
|
||||
@ -99,7 +99,7 @@ instance Evaluatable Complex
|
||||
-- Strings, symbols
|
||||
|
||||
newtype String a = String { stringElements :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Data.Syntax.Literal.String where liftEq = genericLiftEq
|
||||
instance Ord1 Data.Syntax.Literal.String where liftCompare = genericLiftCompare
|
||||
@ -111,7 +111,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Data.Syntax.Literal.Character where liftEq = genericLiftEq
|
||||
instance Ord1 Data.Syntax.Literal.Character where liftCompare = genericLiftCompare
|
||||
@ -121,7 +121,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 InterpolationElement where liftEq = genericLiftEq
|
||||
instance Ord1 InterpolationElement where liftCompare = genericLiftCompare
|
||||
@ -132,7 +132,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, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 TextElement where liftEq = genericLiftEq
|
||||
instance Ord1 TextElement where liftCompare = genericLiftCompare
|
||||
@ -146,7 +146,7 @@ instance Tokenize TextElement where
|
||||
|
||||
-- | A sequence of textual contents within a string literal.
|
||||
newtype EscapeSequence a = EscapeSequence { value :: Text }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 EscapeSequence where liftEq = genericLiftEq
|
||||
instance Ord1 EscapeSequence where liftCompare = genericLiftCompare
|
||||
@ -156,7 +156,7 @@ instance Show1 EscapeSequence where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable EscapeSequence
|
||||
|
||||
data Null a = Null
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Null where liftEq = genericLiftEq
|
||||
instance Ord1 Null where liftCompare = genericLiftCompare
|
||||
@ -168,7 +168,7 @@ instance Tokenize Null where
|
||||
tokenize _ = yield Nullity
|
||||
|
||||
newtype Symbol a = Symbol { symbolElements :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Symbol where liftEq = genericLiftEq
|
||||
instance Ord1 Symbol where liftCompare = genericLiftCompare
|
||||
@ -178,7 +178,7 @@ instance Show1 Symbol where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable Symbol
|
||||
|
||||
newtype SymbolElement a = SymbolElement { symbolContent :: Text }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 SymbolElement where liftEq = genericLiftEq
|
||||
instance Ord1 SymbolElement where liftCompare = genericLiftCompare
|
||||
@ -188,7 +188,7 @@ instance Evaluatable SymbolElement where
|
||||
eval _ (SymbolElement s) = rvalBox (symbol s)
|
||||
|
||||
newtype Regex a = Regex { regexContent :: Text }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Regex where liftEq = genericLiftEq
|
||||
instance Ord1 Regex where liftCompare = genericLiftCompare
|
||||
@ -203,7 +203,7 @@ instance Evaluatable Regex where
|
||||
-- Collections
|
||||
|
||||
newtype Array a = Array { arrayElements :: [a] }
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Array where liftEq = genericLiftEq
|
||||
instance Ord1 Array where liftCompare = genericLiftCompare
|
||||
@ -216,7 +216,7 @@ instance Tokenize Array where
|
||||
tokenize = list . arrayElements
|
||||
|
||||
newtype Hash a = Hash { hashElements :: [a] }
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Hash where liftEq = genericLiftEq
|
||||
instance Ord1 Hash where liftCompare = genericLiftCompare
|
||||
@ -229,7 +229,7 @@ instance Tokenize Hash where
|
||||
tokenize = Tok.hash . hashElements
|
||||
|
||||
data KeyValue a = KeyValue { key :: !a, value :: !a }
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 KeyValue where liftEq = genericLiftEq
|
||||
instance Ord1 KeyValue where liftCompare = genericLiftCompare
|
||||
@ -243,7 +243,7 @@ instance Tokenize KeyValue where
|
||||
tokenize (KeyValue k v) = pair k v
|
||||
|
||||
newtype Tuple a = Tuple { tupleContents :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Tuple where liftEq = genericLiftEq
|
||||
instance Ord1 Tuple where liftCompare = genericLiftCompare
|
||||
@ -253,7 +253,7 @@ instance Evaluatable Tuple where
|
||||
eval eval (Tuple cs) = rvalBox =<< tuple =<< traverse (eval >=> address) cs
|
||||
|
||||
newtype Set a = Set { setElements :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Set where liftEq = genericLiftEq
|
||||
instance Ord1 Set where liftCompare = genericLiftCompare
|
||||
@ -267,7 +267,7 @@ instance Evaluatable Set
|
||||
|
||||
-- | A declared pointer (e.g. var pointer *int in Go)
|
||||
newtype Pointer a = Pointer { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Pointer where liftEq = genericLiftEq
|
||||
instance Ord1 Pointer where liftCompare = genericLiftCompare
|
||||
@ -279,7 +279,7 @@ instance Evaluatable Pointer
|
||||
|
||||
-- | A reference to a pointer's address (e.g. &pointer in Go)
|
||||
newtype Reference a = Reference { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Reference where liftEq = genericLiftEq
|
||||
instance Ord1 Reference where liftCompare = genericLiftCompare
|
||||
|
@ -24,7 +24,7 @@ import qualified Data.Reprinting.Scope as Scope
|
||||
-- 2. Each statement can affect the environment of later statements (e.g. by 'modify'-ing the environment); and
|
||||
-- 3. Only the last statement’s return value is returned.
|
||||
newtype Statements a = Statements { statements :: [a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Statements where liftEq = genericLiftEq
|
||||
instance Ord1 Statements where liftCompare = genericLiftCompare
|
||||
@ -43,7 +43,7 @@ instance Tokenize 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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 If where liftEq = genericLiftEq
|
||||
instance Ord1 If where liftCompare = genericLiftCompare
|
||||
@ -64,7 +64,7 @@ instance Tokenize 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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Else where liftEq = genericLiftEq
|
||||
instance Ord1 Else where liftCompare = genericLiftCompare
|
||||
@ -77,7 +77,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Goto where liftEq = genericLiftEq
|
||||
instance Ord1 Goto where liftCompare = genericLiftCompare
|
||||
@ -89,7 +89,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Match where liftEq = genericLiftEq
|
||||
instance Ord1 Match where liftCompare = genericLiftCompare
|
||||
@ -101,7 +101,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Pattern where liftEq = genericLiftEq
|
||||
instance Ord1 Pattern where liftCompare = genericLiftCompare
|
||||
@ -113,7 +113,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Let where liftEq = genericLiftEq
|
||||
instance Ord1 Let where liftCompare = genericLiftCompare
|
||||
@ -130,7 +130,7 @@ instance Evaluatable Let where
|
||||
|
||||
-- | Assignment to a variable or other lvalue.
|
||||
data Assignment a = Assignment { assignmentContext :: ![a], assignmentTarget :: !a, assignmentValue :: !a }
|
||||
deriving (Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Declarations1 Assignment where
|
||||
liftDeclaredName declaredName Assignment{..} = declaredName assignmentTarget
|
||||
@ -169,7 +169,7 @@ instance Evaluatable Assignment where
|
||||
|
||||
-- | Post increment operator (e.g. 1++ in Go, or i++ in C).
|
||||
newtype PostIncrement a = PostIncrement { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 PostIncrement where liftEq = genericLiftEq
|
||||
instance Ord1 PostIncrement where liftCompare = genericLiftCompare
|
||||
@ -181,7 +181,7 @@ instance Evaluatable PostIncrement
|
||||
|
||||
-- | Post decrement operator (e.g. 1-- in Go, or i-- in C).
|
||||
newtype PostDecrement a = PostDecrement { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 PostDecrement where liftEq = genericLiftEq
|
||||
instance Ord1 PostDecrement where liftCompare = genericLiftCompare
|
||||
@ -192,7 +192,7 @@ instance Evaluatable PostDecrement
|
||||
|
||||
-- | Pre increment operator (e.g. ++1 in C or Java).
|
||||
newtype PreIncrement a = PreIncrement { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 PreIncrement where liftEq = genericLiftEq
|
||||
instance Ord1 PreIncrement where liftCompare = genericLiftCompare
|
||||
@ -204,7 +204,7 @@ instance Evaluatable PreIncrement
|
||||
|
||||
-- | Pre decrement operator (e.g. --1 in C or Java).
|
||||
newtype PreDecrement a = PreDecrement { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 PreDecrement where liftEq = genericLiftEq
|
||||
instance Ord1 PreDecrement where liftCompare = genericLiftCompare
|
||||
@ -217,7 +217,7 @@ instance Evaluatable PreDecrement
|
||||
-- Returns
|
||||
|
||||
newtype Return a = Return { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Return where liftEq = genericLiftEq
|
||||
instance Ord1 Return where liftCompare = genericLiftCompare
|
||||
@ -230,7 +230,7 @@ instance Tokenize Return where
|
||||
tokenize (Return x) = within' Scope.Return x
|
||||
|
||||
newtype Yield a = Yield { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Yield where liftEq = genericLiftEq
|
||||
instance Ord1 Yield where liftCompare = genericLiftCompare
|
||||
@ -241,7 +241,7 @@ instance Evaluatable Yield
|
||||
|
||||
|
||||
newtype Break a = Break { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Break where liftEq = genericLiftEq
|
||||
instance Ord1 Break where liftCompare = genericLiftCompare
|
||||
@ -251,7 +251,7 @@ instance Evaluatable Break where
|
||||
eval eval (Break x) = Rval <$> (eval x >>= address >>= throwBreak)
|
||||
|
||||
newtype Continue a = Continue { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Continue where liftEq = genericLiftEq
|
||||
instance Ord1 Continue where liftCompare = genericLiftCompare
|
||||
@ -261,7 +261,7 @@ instance Evaluatable Continue where
|
||||
eval eval (Continue x) = Rval <$> (eval x >>= address >>= throwContinue)
|
||||
|
||||
newtype Retry a = Retry { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Retry where liftEq = genericLiftEq
|
||||
instance Ord1 Retry where liftCompare = genericLiftCompare
|
||||
@ -272,7 +272,7 @@ instance Evaluatable Retry
|
||||
|
||||
|
||||
newtype NoOp a = NoOp { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 NoOp where liftEq = genericLiftEq
|
||||
instance Ord1 NoOp where liftCompare = genericLiftCompare
|
||||
@ -284,7 +284,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 For where liftEq = genericLiftEq
|
||||
instance Ord1 For where liftCompare = genericLiftCompare
|
||||
@ -295,7 +295,7 @@ instance Evaluatable For where
|
||||
|
||||
|
||||
data ForEach a = ForEach { forEachBinding :: !a, forEachSubject :: !a, forEachBody :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ForEach where liftEq = genericLiftEq
|
||||
instance Ord1 ForEach where liftCompare = genericLiftCompare
|
||||
@ -306,7 +306,7 @@ instance Evaluatable ForEach
|
||||
|
||||
|
||||
data While a = While { whileCondition :: !a, whileBody :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 While where liftEq = genericLiftEq
|
||||
instance Ord1 While where liftCompare = genericLiftCompare
|
||||
@ -316,7 +316,7 @@ instance Evaluatable While where
|
||||
eval eval While{..} = rvalBox =<< while (eval whileCondition >>= Abstract.value) (eval whileBody >>= Abstract.value)
|
||||
|
||||
data DoWhile a = DoWhile { doWhileCondition :: !a, doWhileBody :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 DoWhile where liftEq = genericLiftEq
|
||||
instance Ord1 DoWhile where liftCompare = genericLiftCompare
|
||||
@ -328,7 +328,7 @@ instance Evaluatable DoWhile where
|
||||
-- Exception handling
|
||||
|
||||
newtype Throw a = Throw { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Throw where liftEq = genericLiftEq
|
||||
instance Ord1 Throw where liftCompare = genericLiftCompare
|
||||
@ -339,7 +339,7 @@ instance Evaluatable Throw
|
||||
|
||||
|
||||
data Try a = Try { tryBody :: !a, tryCatch :: ![a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Try where liftEq = genericLiftEq
|
||||
instance Ord1 Try where liftCompare = genericLiftCompare
|
||||
@ -350,7 +350,7 @@ instance Evaluatable Try
|
||||
|
||||
|
||||
data Catch a = Catch { catchException :: !a, catchBody :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Catch where liftEq = genericLiftEq
|
||||
instance Ord1 Catch where liftCompare = genericLiftCompare
|
||||
@ -361,7 +361,7 @@ instance Evaluatable Catch
|
||||
|
||||
|
||||
newtype Finally a = Finally { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Finally where liftEq = genericLiftEq
|
||||
instance Ord1 Finally where liftCompare = genericLiftCompare
|
||||
@ -375,7 +375,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ScopeEntry where liftEq = genericLiftEq
|
||||
instance Ord1 ScopeEntry where liftCompare = genericLiftCompare
|
||||
@ -387,7 +387,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ScopeExit where liftEq = genericLiftEq
|
||||
instance Ord1 ScopeExit where liftCompare = genericLiftCompare
|
||||
|
@ -11,7 +11,7 @@ import Proto3.Suite.Class
|
||||
import Reprinting.Tokenize
|
||||
|
||||
data Array a = Array { arraySize :: !(Maybe a), arrayElementType :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Message1, NFData1)
|
||||
|
||||
instance Named1 Array where nameOf1 _ = "TypeArray"
|
||||
|
||||
@ -25,7 +25,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Annotation where liftEq = genericLiftEq
|
||||
instance Ord1 Annotation where liftCompare = genericLiftCompare
|
||||
@ -42,7 +42,7 @@ instance Tokenize Annotation where
|
||||
|
||||
|
||||
data Function a = Function { functionParameters :: ![a], functionReturn :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Message1, NFData1)
|
||||
|
||||
instance Named1 Function where nameOf1 _ = "TypeFunction"
|
||||
instance Eq1 Function where liftEq = genericLiftEq
|
||||
@ -54,7 +54,7 @@ instance Evaluatable Function
|
||||
|
||||
|
||||
newtype Interface a = Interface { values :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Interface where liftEq = genericLiftEq
|
||||
instance Ord1 Interface where liftCompare = genericLiftCompare
|
||||
@ -65,7 +65,7 @@ instance Evaluatable Interface
|
||||
|
||||
|
||||
data Map a = Map { mapKeyType :: !a, mapElementType :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Map where liftEq = genericLiftEq
|
||||
instance Ord1 Map where liftCompare = genericLiftCompare
|
||||
@ -76,7 +76,7 @@ instance Evaluatable Map
|
||||
|
||||
|
||||
newtype Parenthesized a = Parenthesized { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Parenthesized where liftEq = genericLiftEq
|
||||
instance Ord1 Parenthesized where liftCompare = genericLiftCompare
|
||||
@ -87,7 +87,7 @@ instance Evaluatable Parenthesized
|
||||
|
||||
|
||||
newtype Pointer a = Pointer { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Message1, NFData1)
|
||||
|
||||
instance Named1 Pointer where nameOf1 _ = "TypePointer"
|
||||
instance Eq1 Pointer where liftEq = genericLiftEq
|
||||
@ -99,7 +99,7 @@ instance Evaluatable Pointer
|
||||
|
||||
|
||||
newtype Product a = Product { values :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Product where liftEq = genericLiftEq
|
||||
instance Ord1 Product where liftCompare = genericLiftCompare
|
||||
@ -110,7 +110,7 @@ instance Evaluatable Product
|
||||
|
||||
|
||||
data Readonly a = Readonly
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Readonly where liftEq = genericLiftEq
|
||||
instance Ord1 Readonly where liftCompare = genericLiftCompare
|
||||
@ -121,7 +121,7 @@ instance Evaluatable Readonly
|
||||
|
||||
|
||||
newtype Slice a = Slice { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Message1, NFData1)
|
||||
|
||||
instance Named1 Slice where nameOf1 _ = "TypeSlice"
|
||||
instance Eq1 Slice where liftEq = genericLiftEq
|
||||
@ -133,7 +133,7 @@ instance Evaluatable Slice
|
||||
|
||||
|
||||
newtype TypeParameters a = TypeParameters { terms :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 TypeParameters where liftEq = genericLiftEq
|
||||
instance Ord1 TypeParameters where liftCompare = genericLiftCompare
|
||||
@ -144,7 +144,7 @@ instance Evaluatable TypeParameters
|
||||
|
||||
-- data instead of newtype because no payload
|
||||
data Void a = Void
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Void where liftEq = genericLiftEq
|
||||
instance Ord1 Void where liftCompare = genericLiftCompare
|
||||
@ -155,7 +155,7 @@ instance Evaluatable Void
|
||||
|
||||
-- data instead of newtype because no payload
|
||||
data Int a = Int
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Int where liftEq = genericLiftEq
|
||||
instance Ord1 Int where liftCompare = genericLiftCompare
|
||||
@ -165,7 +165,7 @@ instance Show1 Int where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable Int
|
||||
|
||||
data Float a = Float
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Message1, NFData1)
|
||||
|
||||
instance Named1 Float where nameOf1 _ = "TypeFloat"
|
||||
|
||||
@ -177,7 +177,7 @@ instance Show1 Float where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable Float
|
||||
|
||||
data Double a = Double
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Double where liftEq = genericLiftEq
|
||||
instance Ord1 Double where liftCompare = genericLiftCompare
|
||||
@ -187,7 +187,7 @@ instance Show1 Double where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable Double
|
||||
|
||||
data Bool a = Bool
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Bool where liftEq = genericLiftEq
|
||||
instance Ord1 Bool where liftCompare = genericLiftCompare
|
||||
|
@ -113,6 +113,12 @@ instance Ord1 f => Ord1 (Term f) where
|
||||
instance (Ord1 f, Ord a) => Ord (Term f a) where
|
||||
compare = compare1
|
||||
|
||||
instance NFData1 f => NFData1 (Term f) where
|
||||
liftRnf rnf = go where go x = liftRnf2 rnf go (unTerm x)
|
||||
|
||||
instance (NFData1 f, NFData a) => NFData (Term f a) where
|
||||
rnf = liftRnf rnf
|
||||
|
||||
|
||||
instance Functor f => Bifunctor (TermF f) where
|
||||
bimap f g (In a r) = In (f a) (fmap g r)
|
||||
@ -127,6 +133,7 @@ instance Traversable f => Bitraversable (TermF f) where
|
||||
instance Eq1 f => Eq2 (TermF f) where
|
||||
liftEq2 eqA eqB (In a1 f1) (In a2 f2) = eqA a1 a2 && liftEq eqB f1 f2
|
||||
|
||||
|
||||
instance (Eq1 f, Eq a) => Eq1 (TermF f a) where
|
||||
liftEq = liftEq2 (==)
|
||||
|
||||
@ -142,6 +149,9 @@ instance Ord1 f => Ord2 (TermF f) where
|
||||
instance (Ord1 f, Ord a) => Ord1 (TermF f a) where
|
||||
liftCompare = liftCompare2 compare
|
||||
|
||||
instance NFData1 f => NFData2 (TermF f) where
|
||||
liftRnf2 rnf1 rnf2 (In a1 f1) = rnf1 a1 `seq` liftRnf rnf2 f1
|
||||
|
||||
instance (ToJSONFields a, ToJSONFields1 f) => ToJSON (Term f a) where
|
||||
toJSON = object . toJSONFields
|
||||
toEncoding = pairs . mconcat . toJSONFields
|
||||
|
@ -24,7 +24,7 @@ import qualified Proto3.Wire.Decode as Decode
|
||||
import System.FilePath.Posix
|
||||
|
||||
data IsRelative = Unknown | Relative | NonRelative
|
||||
deriving (Bounded, Enum, Finite, Eq, Generic, Hashable, Ord, Show, ToJSON, Named, MessageField)
|
||||
deriving (Bounded, Enum, Finite, Eq, Generic, Hashable, Ord, Show, ToJSON, Named, MessageField, NFData)
|
||||
|
||||
instance Primitive IsRelative where
|
||||
primType _ = primType (Proxy @(Enumerated IsRelative))
|
||||
@ -37,7 +37,7 @@ instance HasDefault IsRelative where
|
||||
def = Unknown
|
||||
|
||||
data ImportPath = ImportPath { unPath :: FilePath, pathIsRelative :: IsRelative }
|
||||
deriving (Eq, Generic, Hashable, Ord, Show, ToJSON, Named, Message)
|
||||
deriving (Eq, Generic, Hashable, Ord, Show, ToJSON, Named, Message, NFData)
|
||||
|
||||
instance MessageField ImportPath where
|
||||
encodeMessageField num = Encode.embedded num . encodeMessage (fieldNumber 1)
|
||||
@ -86,7 +86,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, Ord, Show, ToJSONFields1, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 Import where liftEq = genericLiftEq
|
||||
instance Ord1 Import where liftCompare = genericLiftCompare
|
||||
@ -106,7 +106,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, Ord, Show, ToJSONFields1, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 QualifiedImport where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedImport where liftCompare = genericLiftCompare
|
||||
@ -125,7 +125,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, Ord, Show, ToJSONFields1, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 SideEffectImport where liftEq = genericLiftEq
|
||||
instance Ord1 SideEffectImport where liftCompare = genericLiftCompare
|
||||
@ -140,7 +140,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, Ord, Show, ToJSONFields1, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 Composite where liftEq = genericLiftEq
|
||||
instance Ord1 Composite where liftCompare = genericLiftCompare
|
||||
@ -151,7 +151,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, Ord, Show, ToJSONFields1, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 DefaultPattern where liftEq = genericLiftEq
|
||||
instance Ord1 DefaultPattern where liftCompare = genericLiftCompare
|
||||
@ -162,7 +162,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, Ord, Show, ToJSONFields1, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 Defer where liftEq = genericLiftEq
|
||||
instance Ord1 Defer where liftCompare = genericLiftCompare
|
||||
@ -173,7 +173,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, Ord, Show, ToJSONFields1, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 Go where liftEq = genericLiftEq
|
||||
instance Ord1 Go where liftCompare = genericLiftCompare
|
||||
@ -184,7 +184,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, Ord, Show, ToJSONFields1, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 Label where liftEq = genericLiftEq
|
||||
instance Ord1 Label where liftCompare = genericLiftCompare
|
||||
@ -195,7 +195,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, Ord, Show, ToJSONFields1, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
-- TODO: Implement Eval instance for Rune
|
||||
instance Evaluatable Rune
|
||||
@ -206,7 +206,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, Ord, Show, ToJSONFields1, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
-- TODO: Implement Eval instance for Select
|
||||
instance Evaluatable Select
|
||||
@ -217,7 +217,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, Ord, Show, ToJSONFields1, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 Send where liftEq = genericLiftEq
|
||||
instance Ord1 Send where liftCompare = genericLiftCompare
|
||||
@ -228,7 +228,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, Ord, Show, ToJSONFields1, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 Slice where liftEq = genericLiftEq
|
||||
instance Ord1 Slice where liftCompare = genericLiftCompare
|
||||
@ -239,7 +239,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, Ord, Show, ToJSONFields1, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 TypeSwitch where liftEq = genericLiftEq
|
||||
instance Ord1 TypeSwitch where liftCompare = genericLiftCompare
|
||||
@ -250,7 +250,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, Ord, Show, ToJSONFields1, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 TypeSwitchGuard where liftEq = genericLiftEq
|
||||
instance Ord1 TypeSwitchGuard where liftCompare = genericLiftCompare
|
||||
@ -261,7 +261,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, Ord, Show, ToJSONFields1, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 Receive where liftEq = genericLiftEq
|
||||
instance Ord1 Receive where liftCompare = genericLiftCompare
|
||||
@ -272,7 +272,7 @@ instance Evaluatable Receive
|
||||
|
||||
-- | A receive operator unary expression in Go (e.g. `<-channel` )
|
||||
newtype ReceiveOperator a = ReceiveOperator { value :: a}
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 ReceiveOperator where liftEq = genericLiftEq
|
||||
instance Ord1 ReceiveOperator where liftCompare = genericLiftCompare
|
||||
@ -283,7 +283,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, Ord, Show, ToJSONFields1, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 Field where liftEq = genericLiftEq
|
||||
instance Ord1 Field where liftCompare = genericLiftCompare
|
||||
@ -294,7 +294,7 @@ instance Evaluatable Field
|
||||
|
||||
|
||||
data Package a = Package { packageName :: !a, packageContents :: ![a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 Package where liftEq = genericLiftEq
|
||||
instance Ord1 Package where liftCompare = genericLiftCompare
|
||||
@ -310,7 +310,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, Ord, Show, ToJSONFields1, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 TypeAssertion where liftEq = genericLiftEq
|
||||
instance Ord1 TypeAssertion where liftCompare = genericLiftCompare
|
||||
@ -321,7 +321,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, Ord, Show, ToJSONFields1, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 TypeConversion where liftEq = genericLiftEq
|
||||
instance Ord1 TypeConversion where liftCompare = genericLiftCompare
|
||||
@ -332,7 +332,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, Ord, Show, ToJSONFields1, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 Variadic where liftEq = genericLiftEq
|
||||
instance Ord1 Variadic where liftCompare = genericLiftCompare
|
||||
|
@ -11,7 +11,7 @@ import Proto3.Suite.Class
|
||||
|
||||
-- | A Bidirectional channel in Go (e.g. `chan`).
|
||||
newtype BidirectionalChannel a = BidirectionalChannel { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 BidirectionalChannel where liftEq = genericLiftEq
|
||||
instance Ord1 BidirectionalChannel where liftCompare = genericLiftCompare
|
||||
@ -22,7 +22,7 @@ instance Evaluatable BidirectionalChannel
|
||||
|
||||
-- | A Receive channel in Go (e.g. `<-chan`).
|
||||
newtype ReceiveChannel a = ReceiveChannel { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 ReceiveChannel where liftEq = genericLiftEq
|
||||
instance Ord1 ReceiveChannel where liftCompare = genericLiftCompare
|
||||
@ -33,7 +33,7 @@ instance Evaluatable ReceiveChannel
|
||||
|
||||
-- | A Send channel in Go (e.g. `chan<-`).
|
||||
newtype SendChannel a = SendChannel { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 SendChannel where liftEq = genericLiftEq
|
||||
instance Ord1 SendChannel where liftCompare = genericLiftCompare
|
||||
|
@ -15,7 +15,7 @@ data Module a = Module { moduleContext :: [a]
|
||||
, moduleExports :: [a]
|
||||
, moduleStatements :: a
|
||||
}
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Module where liftEq = genericLiftEq
|
||||
instance Ord1 Module where liftCompare = genericLiftCompare
|
||||
@ -24,7 +24,7 @@ instance Show1 Module where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable Module
|
||||
|
||||
newtype StrictPattern a = StrictPattern { value :: a}
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 StrictPattern where liftEq = genericLiftEq
|
||||
instance Ord1 StrictPattern where liftCompare = genericLiftCompare
|
||||
@ -33,7 +33,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 StrictType where liftEq = genericLiftEq
|
||||
instance Ord1 StrictType where liftCompare = genericLiftCompare
|
||||
@ -42,7 +42,7 @@ instance Show1 StrictType where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable StrictType
|
||||
|
||||
newtype StrictTypeVariable a = StrictTypeVariable { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 StrictTypeVariable where liftEq = genericLiftEq
|
||||
instance Ord1 StrictTypeVariable where liftCompare = genericLiftCompare
|
||||
@ -51,7 +51,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Type where liftEq = genericLiftEq
|
||||
instance Ord1 Type where liftCompare = genericLiftCompare
|
||||
@ -60,7 +60,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 TypeSynonym where liftEq = genericLiftEq
|
||||
instance Ord1 TypeSynonym where liftCompare = genericLiftCompare
|
||||
@ -69,7 +69,7 @@ instance Show1 TypeSynonym where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable TypeSynonym
|
||||
|
||||
data UnitConstructor a = UnitConstructor
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 UnitConstructor where liftEq = genericLiftEq
|
||||
instance Ord1 UnitConstructor where liftCompare = genericLiftCompare
|
||||
@ -78,7 +78,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 TupleConstructor where liftEq = genericLiftEq
|
||||
instance Ord1 TupleConstructor where liftCompare = genericLiftCompare
|
||||
@ -87,7 +87,7 @@ instance Show1 TupleConstructor where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable TupleConstructor
|
||||
|
||||
data ListConstructor a = ListConstructor
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ListConstructor where liftEq = genericLiftEq
|
||||
instance Ord1 ListConstructor where liftCompare = genericLiftCompare
|
||||
@ -96,7 +96,7 @@ instance Show1 ListConstructor where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ListConstructor
|
||||
|
||||
data FunctionConstructor a = FunctionConstructor
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 FunctionConstructor where liftEq = genericLiftEq
|
||||
instance Ord1 FunctionConstructor where liftCompare = genericLiftCompare
|
||||
@ -105,7 +105,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 RecordDataConstructor where liftEq = genericLiftEq
|
||||
instance Ord1 RecordDataConstructor where liftCompare = genericLiftCompare
|
||||
@ -114,7 +114,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Field where liftEq = genericLiftEq
|
||||
instance Ord1 Field where liftCompare = genericLiftCompare
|
||||
@ -123,7 +123,7 @@ instance Show1 Field where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable Field
|
||||
|
||||
newtype Pragma a = Pragma { value :: Text }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Pragma where liftEq = genericLiftEq
|
||||
instance Ord1 Pragma where liftCompare = genericLiftCompare
|
||||
@ -132,7 +132,7 @@ instance Show1 Pragma where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable Pragma
|
||||
|
||||
newtype Deriving a = Deriving { values :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Deriving where liftEq = genericLiftEq
|
||||
instance Ord1 Deriving where liftCompare = genericLiftCompare
|
||||
@ -140,7 +140,7 @@ instance Show1 Deriving where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Deriving
|
||||
newtype ContextAlt a = ContextAlt { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ContextAlt where liftEq = genericLiftEq
|
||||
instance Ord1 ContextAlt where liftCompare = genericLiftCompare
|
||||
@ -149,7 +149,7 @@ instance Show1 ContextAlt where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ContextAlt
|
||||
|
||||
newtype Class a = Class { classContent :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Class where liftEq = genericLiftEq
|
||||
instance Ord1 Class where liftCompare = genericLiftCompare
|
||||
@ -158,7 +158,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 GADT where liftEq = genericLiftEq
|
||||
instance Ord1 GADT where liftCompare = genericLiftCompare
|
||||
@ -167,7 +167,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 GADTConstructor where liftEq = genericLiftEq
|
||||
instance Ord1 GADTConstructor where liftCompare = genericLiftCompare
|
||||
@ -176,7 +176,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 FunctionType where liftEq = genericLiftEq
|
||||
instance Ord1 FunctionType where liftCompare = genericLiftCompare
|
||||
@ -185,7 +185,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 TypeSignature where liftEq = genericLiftEq
|
||||
instance Ord1 TypeSignature where liftCompare = genericLiftCompare
|
||||
@ -194,7 +194,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ExpressionTypeSignature where liftEq = genericLiftEq
|
||||
instance Ord1 ExpressionTypeSignature where liftCompare = genericLiftCompare
|
||||
@ -203,7 +203,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 KindSignature where liftEq = genericLiftEq
|
||||
instance Ord1 KindSignature where liftCompare = genericLiftCompare
|
||||
@ -212,7 +212,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 KindFunctionType where liftEq = genericLiftEq
|
||||
instance Ord1 KindFunctionType where liftCompare = genericLiftCompare
|
||||
@ -221,7 +221,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Kind where liftEq = genericLiftEq
|
||||
instance Ord1 Kind where liftCompare = genericLiftCompare
|
||||
@ -230,7 +230,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 KindListType where liftEq = genericLiftEq
|
||||
instance Ord1 KindListType where liftCompare = genericLiftCompare
|
||||
@ -239,7 +239,7 @@ instance Show1 KindListType where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable KindListType
|
||||
|
||||
data Star a = Star
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Star where liftEq = genericLiftEq
|
||||
instance Ord1 Star where liftCompare = genericLiftCompare
|
||||
@ -248,7 +248,7 @@ instance Show1 Star where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable Star
|
||||
|
||||
newtype QualifiedTypeClassIdentifier a = QualifiedTypeClassIdentifier { values :: NonEmpty a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 QualifiedTypeClassIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedTypeClassIdentifier where liftCompare = genericLiftCompare
|
||||
@ -258,7 +258,7 @@ instance Hashable1 QualifiedTypeClassIdentifier where liftHashWithSalt = foldl
|
||||
instance Evaluatable QualifiedTypeClassIdentifier
|
||||
|
||||
newtype QualifiedTypeConstructorIdentifier a = QualifiedTypeConstructorIdentifier { values :: NonEmpty a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 QualifiedTypeConstructorIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedTypeConstructorIdentifier where liftCompare = genericLiftCompare
|
||||
@ -268,7 +268,7 @@ instance Hashable1 QualifiedTypeConstructorIdentifier where liftHashWithSalt = f
|
||||
instance Evaluatable QualifiedTypeConstructorIdentifier
|
||||
|
||||
newtype QualifiedConstructorIdentifier a = QualifiedConstructorIdentifier { values :: NonEmpty a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 QualifiedConstructorIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedConstructorIdentifier where liftCompare = genericLiftCompare
|
||||
@ -278,7 +278,7 @@ instance Hashable1 QualifiedConstructorIdentifier where liftHashWithSalt = foldl
|
||||
instance Evaluatable QualifiedConstructorIdentifier
|
||||
|
||||
newtype QualifiedInfixVariableIdentifier a = QualifiedInfixVariableIdentifier { values :: NonEmpty a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 QualifiedInfixVariableIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedInfixVariableIdentifier where liftCompare = genericLiftCompare
|
||||
@ -288,7 +288,7 @@ instance Hashable1 QualifiedInfixVariableIdentifier where liftHashWithSalt = fol
|
||||
instance Evaluatable QualifiedInfixVariableIdentifier
|
||||
|
||||
newtype QualifiedModuleIdentifier a = QualifiedModuleIdentifier { values :: NonEmpty a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 QualifiedModuleIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedModuleIdentifier where liftCompare = genericLiftCompare
|
||||
@ -298,7 +298,7 @@ instance Hashable1 QualifiedModuleIdentifier where liftHashWithSalt = foldl
|
||||
instance Evaluatable QualifiedModuleIdentifier
|
||||
|
||||
newtype QualifiedVariableIdentifier a = QualifiedVariableIdentifier { values :: NonEmpty a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 QualifiedVariableIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedVariableIdentifier where liftCompare = genericLiftCompare
|
||||
@ -308,7 +308,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 AnnotatedTypeVariable where liftEq = genericLiftEq
|
||||
instance Ord1 AnnotatedTypeVariable where liftCompare = genericLiftCompare
|
||||
@ -317,7 +317,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Export where liftEq = genericLiftEq
|
||||
instance Ord1 Export where liftCompare = genericLiftCompare
|
||||
@ -326,7 +326,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ModuleExport where liftEq = genericLiftEq
|
||||
instance Ord1 ModuleExport where liftCompare = genericLiftCompare
|
||||
@ -335,7 +335,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 TypeConstructorExport where liftEq = genericLiftEq
|
||||
instance Ord1 TypeConstructorExport where liftCompare = genericLiftCompare
|
||||
@ -344,7 +344,7 @@ instance Show1 TypeConstructorExport where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable TypeConstructorExport
|
||||
|
||||
data AllConstructors a = AllConstructors
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 AllConstructors where liftEq = genericLiftEq
|
||||
instance Ord1 AllConstructors where liftCompare = genericLiftCompare
|
||||
@ -353,7 +353,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 InfixOperatorPattern where liftEq = genericLiftEq
|
||||
instance Ord1 InfixOperatorPattern where liftCompare = genericLiftCompare
|
||||
@ -362,7 +362,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 QuotedName where liftEq = genericLiftEq
|
||||
instance Ord1 QuotedName where liftCompare = genericLiftCompare
|
||||
@ -371,7 +371,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 TypePattern where liftEq = genericLiftEq
|
||||
instance Ord1 TypePattern where liftCompare = genericLiftCompare
|
||||
@ -380,7 +380,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ScopedTypeVariables where liftEq = genericLiftEq
|
||||
instance Ord1 ScopedTypeVariables where liftCompare = genericLiftCompare
|
||||
@ -389,7 +389,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 NewType where liftEq = genericLiftEq
|
||||
instance Ord1 NewType where liftCompare = genericLiftCompare
|
||||
@ -398,7 +398,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 DefaultDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 DefaultDeclaration where liftCompare = genericLiftCompare
|
||||
@ -407,7 +407,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 EqualityConstraint where liftEq = genericLiftEq
|
||||
instance Ord1 EqualityConstraint where liftCompare = genericLiftCompare
|
||||
@ -416,7 +416,7 @@ instance Show1 EqualityConstraint where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable EqualityConstraint
|
||||
|
||||
newtype TypeVariableIdentifier a = TypeVariableIdentifier { name :: Name }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 TypeVariableIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 TypeVariableIdentifier where liftCompare = genericLiftCompare
|
||||
@ -425,7 +425,7 @@ instance Show1 TypeVariableIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable TypeVariableIdentifier
|
||||
|
||||
newtype TypeConstructorIdentifier a = TypeConstructorIdentifier { name :: Name }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 TypeConstructorIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 TypeConstructorIdentifier where liftCompare = genericLiftCompare
|
||||
@ -434,7 +434,7 @@ instance Show1 TypeConstructorIdentifier where liftShowsPrec = genericLiftShowsP
|
||||
instance Evaluatable TypeConstructorIdentifier
|
||||
|
||||
newtype ModuleIdentifier a = ModuleIdentifier { name :: Name }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ModuleIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 ModuleIdentifier where liftCompare = genericLiftCompare
|
||||
@ -443,7 +443,7 @@ instance Show1 ModuleIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ModuleIdentifier
|
||||
|
||||
newtype ConstructorIdentifier a = ConstructorIdentifier { name :: Name }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ConstructorIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 ConstructorIdentifier where liftCompare = genericLiftCompare
|
||||
@ -452,7 +452,7 @@ instance Show1 ConstructorIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ConstructorIdentifier
|
||||
|
||||
newtype ImplicitParameterIdentifier a = ImplicitParameterIdentifier { name :: Name }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ImplicitParameterIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 ImplicitParameterIdentifier where liftCompare = genericLiftCompare
|
||||
@ -461,7 +461,7 @@ instance Show1 ImplicitParameterIdentifier where liftShowsPrec = genericLiftShow
|
||||
instance Evaluatable ImplicitParameterIdentifier
|
||||
|
||||
newtype InfixConstructorIdentifier a = InfixConstructorIdentifier { name :: Name }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 InfixConstructorIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 InfixConstructorIdentifier where liftCompare = genericLiftCompare
|
||||
@ -470,7 +470,7 @@ instance Show1 InfixConstructorIdentifier where liftShowsPrec = genericLiftShows
|
||||
instance Evaluatable InfixConstructorIdentifier
|
||||
|
||||
newtype InfixVariableIdentifier a = InfixVariableIdentifier { name :: Name }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 InfixVariableIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 InfixVariableIdentifier where liftCompare = genericLiftCompare
|
||||
@ -479,7 +479,7 @@ instance Show1 InfixVariableIdentifier where liftShowsPrec = genericLiftShowsPre
|
||||
instance Evaluatable InfixVariableIdentifier
|
||||
|
||||
newtype TypeClassIdentifier a = TypeClassIdentifier { name :: Name }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 TypeClassIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 TypeClassIdentifier where liftCompare = genericLiftCompare
|
||||
@ -488,7 +488,7 @@ instance Show1 TypeClassIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable TypeClassIdentifier
|
||||
|
||||
newtype VariableIdentifier a = VariableIdentifier { name :: Name }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 VariableIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 VariableIdentifier where liftCompare = genericLiftCompare
|
||||
@ -497,7 +497,7 @@ instance Show1 VariableIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable VariableIdentifier
|
||||
|
||||
newtype PrimitiveConstructorIdentifier a = PrimitiveConstructorIdentifier { name :: Name }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 PrimitiveConstructorIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 PrimitiveConstructorIdentifier where liftCompare = genericLiftCompare
|
||||
@ -506,7 +506,7 @@ instance Show1 PrimitiveConstructorIdentifier where liftShowsPrec = genericLiftS
|
||||
instance Evaluatable PrimitiveConstructorIdentifier
|
||||
|
||||
newtype PrimitiveVariableIdentifier a = PrimitiveVariableIdentifier { name :: Name }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 PrimitiveVariableIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 PrimitiveVariableIdentifier where liftCompare = genericLiftCompare
|
||||
@ -515,7 +515,7 @@ instance Show1 PrimitiveVariableIdentifier where liftShowsPrec = genericLiftShow
|
||||
instance Evaluatable PrimitiveVariableIdentifier
|
||||
|
||||
newtype VariableOperator a = VariableOperator { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 VariableOperator where liftEq = genericLiftEq
|
||||
instance Ord1 VariableOperator where liftCompare = genericLiftCompare
|
||||
@ -524,7 +524,7 @@ instance Show1 VariableOperator where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable VariableOperator
|
||||
|
||||
newtype ConstructorOperator a = ConstructorOperator { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ConstructorOperator where liftEq = genericLiftEq
|
||||
instance Ord1 ConstructorOperator where liftCompare = genericLiftCompare
|
||||
@ -533,7 +533,7 @@ instance Show1 ConstructorOperator where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ConstructorOperator
|
||||
|
||||
newtype TypeOperator a = TypeOperator { name :: Name }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 TypeOperator where liftEq = genericLiftEq
|
||||
instance Ord1 TypeOperator where liftCompare = genericLiftCompare
|
||||
@ -542,7 +542,7 @@ instance Show1 TypeOperator where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable TypeOperator
|
||||
|
||||
newtype PromotedTypeOperator a = PromotedTypeOperator { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 PromotedTypeOperator where liftEq = genericLiftEq
|
||||
instance Ord1 PromotedTypeOperator where liftCompare = genericLiftCompare
|
||||
@ -551,7 +551,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ConstructorSymbol where liftEq = genericLiftEq
|
||||
instance Ord1 ConstructorSymbol where liftCompare = genericLiftCompare
|
||||
@ -560,7 +560,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 VariableSymbol where liftEq = genericLiftEq
|
||||
instance Ord1 VariableSymbol where liftCompare = genericLiftCompare
|
||||
@ -569,7 +569,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 StandaloneDerivingInstance where liftEq = genericLiftEq
|
||||
instance Ord1 StandaloneDerivingInstance where liftCompare = genericLiftCompare
|
||||
@ -578,7 +578,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ImportDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 ImportDeclaration where liftCompare = genericLiftCompare
|
||||
@ -587,7 +587,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 QualifiedImportDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedImportDeclaration where liftCompare = genericLiftCompare
|
||||
@ -596,7 +596,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Import where liftEq = genericLiftEq
|
||||
instance Ord1 Import where liftCompare = genericLiftCompare
|
||||
@ -605,7 +605,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 HiddenImport where liftEq = genericLiftEq
|
||||
instance Ord1 HiddenImport where liftCompare = genericLiftCompare
|
||||
@ -614,7 +614,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ImportAlias where liftEq = genericLiftEq
|
||||
instance Ord1 ImportAlias where liftCompare = genericLiftCompare
|
||||
@ -623,7 +623,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 App where liftEq = genericLiftEq
|
||||
instance Ord1 App where liftCompare = genericLiftCompare
|
||||
@ -632,7 +632,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 InfixOperatorApp where liftEq = genericLiftEq
|
||||
instance Ord1 InfixOperatorApp where liftCompare = genericLiftCompare
|
||||
@ -641,7 +641,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 TypeApp where liftEq = genericLiftEq
|
||||
instance Ord1 TypeApp where liftCompare = genericLiftCompare
|
||||
@ -650,7 +650,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ListComprehension where liftEq = genericLiftEq
|
||||
instance Ord1 ListComprehension where liftCompare = genericLiftCompare
|
||||
@ -659,7 +659,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Generator where liftEq = genericLiftEq
|
||||
instance Ord1 Generator where liftCompare = genericLiftCompare
|
||||
@ -668,7 +668,7 @@ instance Show1 Generator where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable Generator
|
||||
|
||||
newtype TupleExpression a = TupleExpression { values :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 TupleExpression where liftEq = genericLiftEq
|
||||
instance Ord1 TupleExpression where liftCompare = genericLiftCompare
|
||||
@ -677,7 +677,7 @@ instance Show1 TupleExpression where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable TupleExpression
|
||||
|
||||
newtype TuplePattern a = TuplePattern { value :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 TuplePattern where liftEq = genericLiftEq
|
||||
instance Ord1 TuplePattern where liftCompare = genericLiftCompare
|
||||
@ -687,7 +687,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ArithmeticSequence where liftEq = genericLiftEq
|
||||
instance Ord1 ArithmeticSequence where liftCompare = genericLiftCompare
|
||||
@ -696,7 +696,7 @@ instance Show1 ArithmeticSequence where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ArithmeticSequence
|
||||
|
||||
data RightOperatorSection a = RightOperatorSection { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 RightOperatorSection where liftEq = genericLiftEq
|
||||
instance Ord1 RightOperatorSection where liftCompare = genericLiftCompare
|
||||
@ -705,7 +705,7 @@ instance Show1 RightOperatorSection where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable RightOperatorSection
|
||||
|
||||
data LeftOperatorSection a = LeftOperatorSection { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 LeftOperatorSection where liftEq = genericLiftEq
|
||||
instance Ord1 LeftOperatorSection where liftCompare = genericLiftCompare
|
||||
@ -714,7 +714,7 @@ instance Show1 LeftOperatorSection where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable LeftOperatorSection
|
||||
|
||||
newtype ConstructorPattern a = ConstructorPattern { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ConstructorPattern where liftEq = genericLiftEq
|
||||
instance Ord1 ConstructorPattern where liftCompare = genericLiftCompare
|
||||
@ -724,7 +724,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 BindPattern where liftEq = genericLiftEq
|
||||
instance Ord1 BindPattern where liftCompare = genericLiftCompare
|
||||
@ -733,7 +733,7 @@ instance Show1 BindPattern where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable BindPattern
|
||||
|
||||
newtype Do a = Do { values :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Do where liftEq = genericLiftEq
|
||||
instance Ord1 Do where liftCompare = genericLiftCompare
|
||||
@ -742,7 +742,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Lambda where liftEq = genericLiftEq
|
||||
instance Ord1 Lambda where liftCompare = genericLiftCompare
|
||||
@ -752,7 +752,7 @@ instance Evaluatable Lambda
|
||||
|
||||
-- e.g. -1 or (-a) as an expression and not `-` as a variable operator.
|
||||
newtype PrefixNegation a = PrefixNegation { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 PrefixNegation where liftEq = genericLiftEq
|
||||
instance Ord1 PrefixNegation where liftCompare = genericLiftCompare
|
||||
@ -761,7 +761,7 @@ instance Show1 PrefixNegation where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable PrefixNegation
|
||||
|
||||
newtype CPPDirective a = CPPDirective { value :: Text }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 CPPDirective where liftEq = genericLiftEq
|
||||
instance Ord1 CPPDirective where liftCompare = genericLiftCompare
|
||||
@ -770,7 +770,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 QuasiQuotation where liftEq = genericLiftEq
|
||||
instance Ord1 QuasiQuotation where liftCompare = genericLiftCompare
|
||||
@ -779,7 +779,7 @@ instance Show1 QuasiQuotation where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable QuasiQuotation
|
||||
|
||||
newtype QuasiQuotationExpressionBody a = QuasiQuotationExpressionBody { name :: Name }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 QuasiQuotationExpressionBody where liftEq = genericLiftEq
|
||||
instance Ord1 QuasiQuotationExpressionBody where liftCompare = genericLiftCompare
|
||||
@ -788,7 +788,7 @@ instance Show1 QuasiQuotationExpressionBody where liftShowsPrec = genericLiftSho
|
||||
instance Evaluatable QuasiQuotationExpressionBody
|
||||
|
||||
data QuasiQuotationPattern a = QuasiQuotationPattern
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 QuasiQuotationPattern where liftEq = genericLiftEq
|
||||
instance Ord1 QuasiQuotationPattern where liftCompare = genericLiftCompare
|
||||
@ -797,7 +797,7 @@ instance Show1 QuasiQuotationPattern where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable QuasiQuotationPattern
|
||||
|
||||
data QuasiQuotationType a = QuasiQuotationType
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 QuasiQuotationType where liftEq = genericLiftEq
|
||||
instance Ord1 QuasiQuotationType where liftCompare = genericLiftCompare
|
||||
@ -806,7 +806,7 @@ instance Show1 QuasiQuotationType where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable QuasiQuotationType
|
||||
|
||||
data QuasiQuotationDeclaration a = QuasiQuotationDeclaration
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 QuasiQuotationDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 QuasiQuotationDeclaration where liftCompare = genericLiftCompare
|
||||
@ -815,7 +815,7 @@ instance Show1 QuasiQuotationDeclaration where liftShowsPrec = genericLiftShowsP
|
||||
instance Evaluatable QuasiQuotationDeclaration
|
||||
|
||||
newtype QuasiQuotationQuoter a = QuasiQuotationQuoter { name :: Name }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 QuasiQuotationQuoter where liftEq = genericLiftEq
|
||||
instance Ord1 QuasiQuotationQuoter where liftCompare = genericLiftCompare
|
||||
@ -824,7 +824,7 @@ instance Show1 QuasiQuotationQuoter where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable QuasiQuotationQuoter
|
||||
|
||||
data QuasiQuotationExpression a = QuasiQuotationExpression
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 QuasiQuotationExpression where liftEq = genericLiftEq
|
||||
instance Ord1 QuasiQuotationExpression where liftCompare = genericLiftCompare
|
||||
@ -833,7 +833,7 @@ instance Show1 QuasiQuotationExpression where liftShowsPrec = genericLiftShowsPr
|
||||
instance Evaluatable QuasiQuotationExpression
|
||||
|
||||
newtype Splice a = Splice { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Splice where liftEq = genericLiftEq
|
||||
instance Ord1 Splice where liftCompare = genericLiftCompare
|
||||
@ -842,7 +842,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 TypeClass where liftEq = genericLiftEq
|
||||
instance Ord1 TypeClass where liftCompare = genericLiftCompare
|
||||
@ -851,7 +851,7 @@ instance Show1 TypeClass where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable TypeClass
|
||||
|
||||
data FixityAlt a = FixityAlt { fixityPrecedence :: a, fixityIdentifier :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 FixityAlt where liftEq = genericLiftEq
|
||||
instance Ord1 FixityAlt where liftCompare = genericLiftCompare
|
||||
@ -861,7 +861,7 @@ instance Evaluatable FixityAlt
|
||||
|
||||
-- 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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 DefaultSignature where liftEq = genericLiftEq
|
||||
instance Ord1 DefaultSignature where liftCompare = genericLiftCompare
|
||||
@ -870,7 +870,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 TypeFamily where liftEq = genericLiftEq
|
||||
instance Ord1 TypeFamily where liftCompare = genericLiftCompare
|
||||
@ -879,7 +879,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 FunctionalDependency where liftEq = genericLiftEq
|
||||
instance Ord1 FunctionalDependency where liftCompare = genericLiftCompare
|
||||
@ -888,7 +888,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 TypeClassInstance where liftEq = genericLiftEq
|
||||
instance Ord1 TypeClassInstance where liftCompare = genericLiftCompare
|
||||
@ -897,7 +897,7 @@ instance Show1 TypeClassInstance where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable TypeClassInstance
|
||||
|
||||
newtype Instance a = Instance { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Instance where liftEq = genericLiftEq
|
||||
instance Ord1 Instance where liftCompare = genericLiftCompare
|
||||
@ -907,7 +907,7 @@ instance Evaluatable Instance
|
||||
|
||||
-- e.g. The `Bar{..}` in `foo Bar{..} = baz`.
|
||||
newtype LabeledPattern a = LabeledPattern { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 LabeledPattern where liftEq = genericLiftEq
|
||||
instance Ord1 LabeledPattern where liftCompare = genericLiftCompare
|
||||
@ -917,7 +917,7 @@ instance Evaluatable LabeledPattern
|
||||
|
||||
-- e.g. The `{..}` in `foo Bar{..} = baz`
|
||||
data RecordWildCards a = RecordWildCards
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 RecordWildCards where liftEq = genericLiftEq
|
||||
instance Ord1 RecordWildCards where liftCompare = genericLiftCompare
|
||||
@ -927,7 +927,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 TypeInstance where liftEq = genericLiftEq
|
||||
instance Ord1 TypeInstance where liftCompare = genericLiftCompare
|
||||
@ -936,7 +936,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 KindParenthesizedConstructor where liftEq = genericLiftEq
|
||||
instance Ord1 KindParenthesizedConstructor where liftCompare = genericLiftCompare
|
||||
@ -945,7 +945,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 KindTupleType where liftEq = genericLiftEq
|
||||
instance Ord1 KindTupleType where liftCompare = genericLiftCompare
|
||||
@ -954,7 +954,7 @@ instance Show1 KindTupleType where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable KindTupleType
|
||||
|
||||
data Wildcard a = Wildcard
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Wildcard where liftEq = genericLiftEq
|
||||
instance Ord1 Wildcard where liftCompare = genericLiftCompare
|
||||
@ -963,7 +963,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Let where liftEq = genericLiftEq
|
||||
instance Ord1 Let where liftCompare = genericLiftCompare
|
||||
@ -972,7 +972,7 @@ instance Show1 Let where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable Let
|
||||
|
||||
newtype ListPattern a = ListPattern { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ListPattern where liftEq = genericLiftEq
|
||||
instance Ord1 ListPattern where liftCompare = genericLiftCompare
|
||||
@ -982,7 +982,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 AsPattern where liftEq = genericLiftEq
|
||||
instance Ord1 AsPattern where liftCompare = genericLiftCompare
|
||||
@ -992,7 +992,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 FieldPattern where liftEq = genericLiftEq
|
||||
instance Ord1 FieldPattern where liftCompare = genericLiftCompare
|
||||
@ -1002,7 +1002,7 @@ instance Evaluatable FieldPattern
|
||||
|
||||
-- e.g. The `start` or `end` in `f Blob{start, end} = [start, end]`.
|
||||
newtype NamedFieldPun a = NamedFieldPun { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 NamedFieldPun where liftEq = genericLiftEq
|
||||
instance Ord1 NamedFieldPun where liftCompare = genericLiftCompare
|
||||
@ -1012,7 +1012,7 @@ instance Evaluatable NamedFieldPun
|
||||
|
||||
-- e.g. The `-(1)` in `f (-(1)) = 1`.
|
||||
newtype NegativeLiteral a = NegativeLiteral { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 NegativeLiteral where liftEq = genericLiftEq
|
||||
instance Ord1 NegativeLiteral where liftCompare = genericLiftCompare
|
||||
@ -1022,7 +1022,7 @@ instance Evaluatable NegativeLiteral
|
||||
|
||||
-- e.g. The `~a` in `f ~a = 1`
|
||||
newtype IrrefutablePattern a = IrrefutablePattern { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 IrrefutablePattern where liftEq = genericLiftEq
|
||||
instance Ord1 IrrefutablePattern where liftCompare = genericLiftCompare
|
||||
@ -1032,7 +1032,7 @@ instance Evaluatable IrrefutablePattern
|
||||
|
||||
-- For handling guards in case alternative expressions.
|
||||
newtype CaseGuardPattern a = CaseGuardPattern { values :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 CaseGuardPattern where liftEq = genericLiftEq
|
||||
instance Ord1 CaseGuardPattern where liftCompare = genericLiftCompare
|
||||
@ -1041,7 +1041,7 @@ instance Show1 CaseGuardPattern where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable CaseGuardPattern
|
||||
|
||||
newtype Guard a = Guard { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Guard where liftEq = genericLiftEq
|
||||
instance Ord1 Guard where liftCompare = genericLiftCompare
|
||||
@ -1050,7 +1050,7 @@ instance Show1 Guard where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable Guard
|
||||
|
||||
newtype LambdaCase a = LambdaCase { values :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 LambdaCase where liftEq = genericLiftEq
|
||||
instance Ord1 LambdaCase where liftCompare = genericLiftCompare
|
||||
@ -1060,7 +1060,7 @@ instance Evaluatable LambdaCase
|
||||
|
||||
-- For handling guards in function declarations.
|
||||
newtype FunctionGuardPattern a = FunctionGuardPattern { values :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 FunctionGuardPattern where liftEq = genericLiftEq
|
||||
instance Ord1 FunctionGuardPattern where liftCompare = genericLiftCompare
|
||||
@ -1070,7 +1070,7 @@ instance Evaluatable FunctionGuardPattern
|
||||
|
||||
-- The `y { a = 1, b = 2} in `f y@Example = y { a = 1, b = 2 }`.
|
||||
newtype LabeledUpdate a = LabeledUpdate { values :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 LabeledUpdate where liftEq = genericLiftEq
|
||||
instance Ord1 LabeledUpdate where liftCompare = genericLiftCompare
|
||||
@ -1080,7 +1080,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 FieldBind where liftEq = genericLiftEq
|
||||
instance Ord1 FieldBind where liftCompare = genericLiftCompare
|
||||
@ -1089,7 +1089,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ViewPattern where liftEq = genericLiftEq
|
||||
instance Ord1 ViewPattern where liftCompare = genericLiftCompare
|
||||
@ -1099,7 +1099,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 PatternGuard where liftEq = genericLiftEq
|
||||
instance Ord1 PatternGuard where liftCompare = genericLiftCompare
|
||||
@ -1108,7 +1108,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 LabeledConstruction where liftEq = genericLiftEq
|
||||
instance Ord1 LabeledConstruction where liftCompare = genericLiftCompare
|
||||
@ -1117,7 +1117,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 InfixDataConstructor where liftEq = genericLiftEq
|
||||
instance Ord1 InfixDataConstructor where liftCompare = genericLiftCompare
|
||||
|
@ -9,7 +9,7 @@ import Prologue hiding (Constructor)
|
||||
import Proto3.Suite.Class
|
||||
|
||||
newtype Import a = Import { imports :: [a]}
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
|
||||
instance Eq1 Import where liftEq = genericLiftEq
|
||||
@ -20,7 +20,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, Ord, Show, ToJSONFields1, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
|
||||
instance Eq1 Module where liftEq = genericLiftEq
|
||||
@ -30,7 +30,7 @@ instance Show1 Module where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable Module
|
||||
|
||||
newtype Package a = Package { packages :: [a]}
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
|
||||
instance Eq1 Package where liftEq = genericLiftEq
|
||||
@ -41,7 +41,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, Ord, Show, ToJSONFields1, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 EnumDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 EnumDeclaration where liftCompare = genericLiftCompare
|
||||
@ -50,7 +50,7 @@ instance Evaluatable EnumDeclaration
|
||||
|
||||
|
||||
data Variable a = Variable { variableModifiers :: ![a], variableType :: !a, variableName :: !a}
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 Variable where liftEq = genericLiftEq
|
||||
instance Ord1 Variable where liftCompare = genericLiftCompare
|
||||
@ -60,7 +60,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, Ord, Show, ToJSONFields1, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 Synchronized where liftEq = genericLiftEq
|
||||
instance Ord1 Synchronized where liftCompare = genericLiftCompare
|
||||
@ -70,7 +70,7 @@ instance Show1 Synchronized where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable Synchronized
|
||||
|
||||
data New a = New { newType :: !a, newArgs :: ![a], newClassBody :: Maybe a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 New where liftEq = genericLiftEq
|
||||
instance Ord1 New where liftCompare = genericLiftCompare
|
||||
@ -80,7 +80,7 @@ instance Show1 New where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable New
|
||||
|
||||
data Asterisk a = Asterisk
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 Asterisk where liftEq = genericLiftEq
|
||||
instance Ord1 Asterisk where liftCompare = genericLiftCompare
|
||||
@ -91,7 +91,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, Ord, Show, ToJSONFields1, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 Constructor where liftEq = genericLiftEq
|
||||
instance Ord1 Constructor where liftCompare = genericLiftCompare
|
||||
@ -101,7 +101,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, Ord, Show, ToJSONFields1, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 TypeParameter where liftEq = genericLiftEq
|
||||
instance Ord1 TypeParameter where liftCompare = genericLiftCompare
|
||||
@ -111,7 +111,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, Ord, Show, ToJSONFields1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Named1 Annotation where nameOf1 _ = "JavaAnnotation"
|
||||
instance Eq1 Annotation where liftEq = genericLiftEq
|
||||
@ -122,7 +122,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, Ord, Show, ToJSONFields1, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 AnnotationField where liftEq = genericLiftEq
|
||||
instance Ord1 AnnotationField where liftCompare = genericLiftCompare
|
||||
@ -132,7 +132,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, Ord, Show, ToJSONFields1, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 GenericType where liftEq = genericLiftEq
|
||||
instance Ord1 GenericType where liftCompare = genericLiftCompare
|
||||
@ -142,7 +142,7 @@ instance Show1 GenericType where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable GenericType
|
||||
|
||||
data AnnotatedType a = AnnotatedType { annotationes :: [a], annotatedType :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 AnnotatedType where liftEq = genericLiftEq
|
||||
instance Ord1 AnnotatedType where liftCompare = genericLiftCompare
|
||||
@ -152,7 +152,7 @@ instance Show1 AnnotatedType where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable AnnotatedType
|
||||
|
||||
newtype CatchType a = CatchType { types :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 CatchType where liftEq = genericLiftEq
|
||||
instance Ord1 CatchType where liftCompare = genericLiftCompare
|
||||
@ -162,7 +162,7 @@ instance Show1 CatchType where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable CatchType
|
||||
|
||||
data TypeWithModifiers a = TypeWithModifiers { types :: [a], modifier :: a}
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 TypeWithModifiers where liftEq = genericLiftEq
|
||||
instance Ord1 TypeWithModifiers where liftCompare = genericLiftCompare
|
||||
@ -172,7 +172,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, Ord, Show, ToJSONFields1, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 Wildcard where liftEq = genericLiftEq
|
||||
instance Ord1 Wildcard where liftCompare = genericLiftCompare
|
||||
@ -182,7 +182,7 @@ instance Show1 Wildcard where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable Wildcard
|
||||
|
||||
data WildcardBounds a = WildcardBoundExtends { wildcardBoundExtendsType :: a} | WildcardBoundSuper { wildcardBoundSuperType :: a}
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 WildcardBounds where liftEq = genericLiftEq
|
||||
instance Ord1 WildcardBounds where liftCompare = genericLiftCompare
|
||||
@ -192,7 +192,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, Ord, Show, ToJSONFields1, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 SpreadParameter where liftEq = genericLiftEq
|
||||
instance Ord1 SpreadParameter where liftCompare = genericLiftCompare
|
||||
@ -202,7 +202,7 @@ instance Show1 SpreadParameter where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable SpreadParameter
|
||||
|
||||
newtype StaticInitializer a = StaticInitializer { staticInitializerBlock :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
|
||||
instance Eq1 StaticInitializer where liftEq = genericLiftEq
|
||||
@ -212,7 +212,7 @@ 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, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 MethodReference where liftEq = genericLiftEq
|
||||
instance Ord1 MethodReference where liftCompare = genericLiftCompare
|
||||
@ -222,7 +222,7 @@ instance Show1 MethodReference where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable MethodReference
|
||||
|
||||
data NewKeyword a = NewKeyword
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 NewKeyword where liftEq = genericLiftEq
|
||||
instance Ord1 NewKeyword where liftCompare = genericLiftCompare
|
||||
@ -232,7 +232,7 @@ instance Show1 NewKeyword where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable NewKeyword
|
||||
|
||||
data Lambda a = Lambda { lambdaParams :: ![a], lambdaBody :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 Lambda where liftEq = genericLiftEq
|
||||
instance Ord1 Lambda where liftCompare = genericLiftCompare
|
||||
@ -241,7 +241,7 @@ 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, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 LambdaBody where liftEq = genericLiftEq
|
||||
instance Ord1 LambdaBody where liftCompare = genericLiftCompare
|
||||
@ -250,7 +250,7 @@ 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, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 ArrayCreationExpression where liftEq = genericLiftEq
|
||||
instance Ord1 ArrayCreationExpression where liftCompare = genericLiftCompare
|
||||
@ -259,7 +259,7 @@ instance Show1 ArrayCreationExpression where liftShowsPrec = genericLiftShowsPre
|
||||
instance Evaluatable ArrayCreationExpression
|
||||
|
||||
data DimsExpr a = DimsExpr { dimsExprAnnotation :: ![a], dimsExprExpression :: ![a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 DimsExpr where liftEq = genericLiftEq
|
||||
instance Ord1 DimsExpr where liftCompare = genericLiftCompare
|
||||
@ -268,7 +268,7 @@ 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, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 ClassBody where liftEq = genericLiftEq
|
||||
instance Ord1 ClassBody where liftCompare = genericLiftCompare
|
||||
@ -277,7 +277,7 @@ 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, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 ClassLiteral where liftEq = genericLiftEq
|
||||
instance Ord1 ClassLiteral where liftCompare = genericLiftCompare
|
||||
@ -286,7 +286,7 @@ 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, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 TryWithResources where liftEq = genericLiftEq
|
||||
instance Ord1 TryWithResources where liftCompare = genericLiftCompare
|
||||
@ -296,7 +296,7 @@ instance Show1 TryWithResources where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable TryWithResources
|
||||
|
||||
data AssertStatement a = AssertStatement { assertLHS :: !a, assertRHS :: !(Maybe a) }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 AssertStatement where liftEq = genericLiftEq
|
||||
instance Ord1 AssertStatement where liftCompare = genericLiftCompare
|
||||
@ -306,7 +306,7 @@ instance Show1 AssertStatement where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable AssertStatement
|
||||
|
||||
newtype DefaultValue a = DefaultValue { defaultValueElement :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 DefaultValue where liftEq = genericLiftEq
|
||||
instance Ord1 DefaultValue where liftCompare = genericLiftCompare
|
||||
@ -315,7 +315,7 @@ 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, Named1, Message1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 AnnotationTypeElement where liftEq = genericLiftEq
|
||||
instance Ord1 AnnotationTypeElement where liftCompare = genericLiftCompare
|
||||
|
@ -10,7 +10,7 @@ import Proto3.Suite
|
||||
import qualified Proto3.Suite as PB
|
||||
|
||||
newtype Document a = Document { values :: [a] }
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, Named1, Message1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Document where liftEq = genericLiftEq
|
||||
instance Ord1 Document where liftCompare = genericLiftCompare
|
||||
@ -20,70 +20,70 @@ instance Show1 Document where liftShowsPrec = genericLiftShowsPrec
|
||||
-- Block elements
|
||||
|
||||
newtype Paragraph a = Paragraph { values :: [a] }
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, Named1, Message1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
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, ToJSONFields1, Named1, Message1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Heading where liftEq = genericLiftEq
|
||||
instance Ord1 Heading where liftCompare = genericLiftCompare
|
||||
instance Show1 Heading where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
newtype UnorderedList a = UnorderedList { values :: [a] }
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, Named1, Message1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 UnorderedList where liftEq = genericLiftEq
|
||||
instance Ord1 UnorderedList where liftCompare = genericLiftCompare
|
||||
instance Show1 UnorderedList where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
newtype OrderedList a = OrderedList { values :: [a] }
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, Named1, Message1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 OrderedList where liftEq = genericLiftEq
|
||||
instance Ord1 OrderedList where liftCompare = genericLiftCompare
|
||||
instance Show1 OrderedList where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
newtype BlockQuote a = BlockQuote { values :: [a] }
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, Named1, Message1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
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, ToJSONFields1, Named1, Message1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ThematicBreak where liftEq = genericLiftEq
|
||||
instance Ord1 ThematicBreak where liftCompare = genericLiftCompare
|
||||
instance Show1 ThematicBreak where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
newtype HTMLBlock a = HTMLBlock { value :: T.Text }
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, Named1, Message1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 HTMLBlock where liftEq = genericLiftEq
|
||||
instance Ord1 HTMLBlock where liftCompare = genericLiftCompare
|
||||
instance Show1 HTMLBlock where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
newtype Table a = Table { values :: [a] }
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, Named1, Message1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Table where liftEq = genericLiftEq
|
||||
instance Ord1 Table where liftCompare = genericLiftCompare
|
||||
instance Show1 Table where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
newtype TableRow a = TableRow { values :: [a] }
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, Named1, Message1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 TableRow where liftEq = genericLiftEq
|
||||
instance Ord1 TableRow where liftCompare = genericLiftCompare
|
||||
instance Show1 TableRow where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
newtype TableCell a = TableCell { values :: [a] }
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, Named1, Message1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 TableCell where liftEq = genericLiftEq
|
||||
instance Ord1 TableCell where liftCompare = genericLiftCompare
|
||||
@ -93,28 +93,28 @@ instance Show1 TableCell where liftShowsPrec = genericLiftShowsPrec
|
||||
-- Inline elements
|
||||
|
||||
newtype Strong a = Strong { values :: [a] }
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, Named1, Message1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Strong where liftEq = genericLiftEq
|
||||
instance Ord1 Strong where liftCompare = genericLiftCompare
|
||||
instance Show1 Strong where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
newtype Emphasis a = Emphasis { values :: [a] }
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, Named1, Message1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Emphasis where liftEq = genericLiftEq
|
||||
instance Ord1 Emphasis where liftCompare = genericLiftCompare
|
||||
instance Show1 Emphasis where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
newtype Text a = Text { value :: T.Text}
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, Named1, Message1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
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, ToJSONFields1, Named1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, Named1, NFData1)
|
||||
|
||||
instance Message1 Link where
|
||||
liftEncodeMessage _ _ Link{..} = encodeMessageField 1 linkURL <> maybe mempty (encodeMessageField 2) linkTitle
|
||||
@ -129,7 +129,7 @@ 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, ToJSONFields1, Named1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, Named1, NFData1)
|
||||
|
||||
instance Message1 Image where
|
||||
liftEncodeMessage _ _ Image{..} = encodeMessageField 1 imageURL <> maybe mempty (encodeMessageField 2) imageTitle
|
||||
@ -144,7 +144,7 @@ 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, ToJSONFields1, Named1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, Named1, NFData1)
|
||||
|
||||
instance Message1 Code where
|
||||
liftEncodeMessage _ _ Code{..} = maybe mempty (encodeMessageField 1) codeLanguage <> encodeMessageField 2 codeContent
|
||||
@ -160,14 +160,14 @@ 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, ToJSONFields1, Named1, Message1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 LineBreak where liftEq = genericLiftEq
|
||||
instance Ord1 LineBreak where liftCompare = genericLiftCompare
|
||||
instance Show1 LineBreak where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
newtype Strikethrough a = Strikethrough { values :: [a] }
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, Named1, Message1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Strikethrough where liftEq = genericLiftEq
|
||||
instance Ord1 Strikethrough where liftCompare = genericLiftCompare
|
||||
|
@ -14,7 +14,7 @@ import Prologue hiding (Text)
|
||||
import Proto3.Suite.Class
|
||||
|
||||
newtype Text a = Text { value :: T.Text }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Text where liftEq = genericLiftEq
|
||||
instance Ord1 Text where liftCompare = genericLiftCompare
|
||||
@ -23,7 +23,7 @@ instance Evaluatable Text
|
||||
|
||||
|
||||
newtype VariableName a = VariableName { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 VariableName where liftEq = genericLiftEq
|
||||
instance Ord1 VariableName where liftCompare = genericLiftCompare
|
||||
@ -77,7 +77,7 @@ include eval pathTerm f = do
|
||||
pure (Rval v)
|
||||
|
||||
newtype Require a = Require { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Require where liftEq = genericLiftEq
|
||||
instance Ord1 Require where liftCompare = genericLiftCompare
|
||||
@ -88,7 +88,7 @@ instance Evaluatable Require where
|
||||
|
||||
|
||||
newtype RequireOnce a = RequireOnce { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 RequireOnce where liftEq = genericLiftEq
|
||||
instance Ord1 RequireOnce where liftCompare = genericLiftCompare
|
||||
@ -99,7 +99,7 @@ instance Evaluatable RequireOnce where
|
||||
|
||||
|
||||
newtype Include a = Include { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Include where liftEq = genericLiftEq
|
||||
instance Ord1 Include where liftCompare = genericLiftCompare
|
||||
@ -110,7 +110,7 @@ instance Evaluatable Include where
|
||||
|
||||
|
||||
newtype IncludeOnce a = IncludeOnce { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 IncludeOnce where liftEq = genericLiftEq
|
||||
instance Ord1 IncludeOnce where liftCompare = genericLiftCompare
|
||||
@ -121,7 +121,7 @@ instance Evaluatable IncludeOnce where
|
||||
|
||||
|
||||
newtype ArrayElement a = ArrayElement { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ArrayElement where liftEq = genericLiftEq
|
||||
instance Ord1 ArrayElement where liftCompare = genericLiftCompare
|
||||
@ -129,7 +129,7 @@ instance Show1 ArrayElement where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ArrayElement
|
||||
|
||||
newtype GlobalDeclaration a = GlobalDeclaration { values :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 GlobalDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 GlobalDeclaration where liftCompare = genericLiftCompare
|
||||
@ -137,7 +137,7 @@ instance Show1 GlobalDeclaration where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable GlobalDeclaration
|
||||
|
||||
newtype SimpleVariable a = SimpleVariable { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 SimpleVariable where liftEq = genericLiftEq
|
||||
instance Ord1 SimpleVariable where liftCompare = genericLiftCompare
|
||||
@ -147,7 +147,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 CastType where liftEq = genericLiftEq
|
||||
instance Ord1 CastType where liftCompare = genericLiftCompare
|
||||
@ -155,7 +155,7 @@ instance Show1 CastType where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable CastType
|
||||
|
||||
newtype ErrorControl a = ErrorControl { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ErrorControl where liftEq = genericLiftEq
|
||||
instance Ord1 ErrorControl where liftCompare = genericLiftCompare
|
||||
@ -163,7 +163,7 @@ instance Show1 ErrorControl where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ErrorControl
|
||||
|
||||
newtype Clone a = Clone { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Clone where liftEq = genericLiftEq
|
||||
instance Ord1 Clone where liftCompare = genericLiftCompare
|
||||
@ -171,7 +171,7 @@ instance Show1 Clone where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable Clone
|
||||
|
||||
newtype ShellCommand a = ShellCommand { value :: T.Text }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ShellCommand where liftEq = genericLiftEq
|
||||
instance Ord1 ShellCommand where liftCompare = genericLiftCompare
|
||||
@ -180,7 +180,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Update where liftEq = genericLiftEq
|
||||
instance Ord1 Update where liftCompare = genericLiftCompare
|
||||
@ -188,7 +188,7 @@ instance Show1 Update where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable Update
|
||||
|
||||
newtype NewVariable a = NewVariable { values :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 NewVariable where liftEq = genericLiftEq
|
||||
instance Ord1 NewVariable where liftCompare = genericLiftCompare
|
||||
@ -196,7 +196,7 @@ instance Show1 NewVariable where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable NewVariable
|
||||
|
||||
newtype RelativeScope a = RelativeScope { value :: T.Text }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 RelativeScope where liftEq = genericLiftEq
|
||||
instance Ord1 RelativeScope where liftCompare = genericLiftCompare
|
||||
@ -204,7 +204,7 @@ instance Show1 RelativeScope where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable RelativeScope
|
||||
|
||||
data QualifiedName a = QualifiedName { name :: a, identifier :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 QualifiedName where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedName where liftCompare = genericLiftCompare
|
||||
@ -216,7 +216,7 @@ instance Evaluatable QualifiedName where
|
||||
Rval <$> evaluateInScopedEnv namePtr (eval iden >>= address)
|
||||
|
||||
newtype NamespaceName a = NamespaceName { names :: NonEmpty a }
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Diffable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Diffable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Hashable1 NamespaceName where liftHashWithSalt = foldl
|
||||
instance Eq1 NamespaceName where liftEq = genericLiftEq
|
||||
@ -228,7 +228,7 @@ instance Evaluatable NamespaceName where
|
||||
where f ns id = ns >>= flip evaluateInScopedEnv id
|
||||
|
||||
newtype ConstDeclaration a = ConstDeclaration { values :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ConstDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 ConstDeclaration where liftCompare = genericLiftCompare
|
||||
@ -236,7 +236,7 @@ instance Show1 ConstDeclaration where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ConstDeclaration
|
||||
|
||||
data ClassConstDeclaration a = ClassConstDeclaration { visibility :: a, elements :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ClassConstDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 ClassConstDeclaration where liftCompare = genericLiftCompare
|
||||
@ -244,7 +244,7 @@ instance Show1 ClassConstDeclaration where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ClassConstDeclaration
|
||||
|
||||
newtype ClassInterfaceClause a = ClassInterfaceClause { values :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ClassInterfaceClause where liftEq = genericLiftEq
|
||||
instance Ord1 ClassInterfaceClause where liftCompare = genericLiftCompare
|
||||
@ -252,7 +252,7 @@ instance Show1 ClassInterfaceClause where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ClassInterfaceClause
|
||||
|
||||
newtype ClassBaseClause a = ClassBaseClause { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ClassBaseClause where liftEq = genericLiftEq
|
||||
instance Ord1 ClassBaseClause where liftCompare = genericLiftCompare
|
||||
@ -261,7 +261,7 @@ instance Evaluatable ClassBaseClause
|
||||
|
||||
|
||||
newtype UseClause a = UseClause { values :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 UseClause where liftEq = genericLiftEq
|
||||
instance Ord1 UseClause where liftCompare = genericLiftCompare
|
||||
@ -269,7 +269,7 @@ instance Show1 UseClause where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable UseClause
|
||||
|
||||
newtype ReturnType a = ReturnType { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ReturnType where liftEq = genericLiftEq
|
||||
instance Ord1 ReturnType where liftCompare = genericLiftCompare
|
||||
@ -277,7 +277,7 @@ instance Show1 ReturnType where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ReturnType
|
||||
|
||||
newtype TypeDeclaration a = TypeDeclaration { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 TypeDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 TypeDeclaration where liftCompare = genericLiftCompare
|
||||
@ -285,7 +285,7 @@ instance Show1 TypeDeclaration where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable TypeDeclaration
|
||||
|
||||
newtype BaseTypeDeclaration a = BaseTypeDeclaration { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 BaseTypeDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 BaseTypeDeclaration where liftCompare = genericLiftCompare
|
||||
@ -293,7 +293,7 @@ instance Show1 BaseTypeDeclaration where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable BaseTypeDeclaration
|
||||
|
||||
newtype ScalarType a = ScalarType { value :: T.Text }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ScalarType where liftEq = genericLiftEq
|
||||
instance Ord1 ScalarType where liftCompare = genericLiftCompare
|
||||
@ -301,7 +301,7 @@ instance Show1 ScalarType where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ScalarType
|
||||
|
||||
newtype EmptyIntrinsic a = EmptyIntrinsic { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 EmptyIntrinsic where liftEq = genericLiftEq
|
||||
instance Ord1 EmptyIntrinsic where liftCompare = genericLiftCompare
|
||||
@ -309,7 +309,7 @@ instance Show1 EmptyIntrinsic where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable EmptyIntrinsic
|
||||
|
||||
newtype ExitIntrinsic a = ExitIntrinsic { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ExitIntrinsic where liftEq = genericLiftEq
|
||||
instance Ord1 ExitIntrinsic where liftCompare = genericLiftCompare
|
||||
@ -317,7 +317,7 @@ instance Show1 ExitIntrinsic where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ExitIntrinsic
|
||||
|
||||
newtype IssetIntrinsic a = IssetIntrinsic { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 IssetIntrinsic where liftEq = genericLiftEq
|
||||
instance Ord1 IssetIntrinsic where liftCompare = genericLiftCompare
|
||||
@ -325,7 +325,7 @@ instance Show1 IssetIntrinsic where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable IssetIntrinsic
|
||||
|
||||
newtype EvalIntrinsic a = EvalIntrinsic { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 EvalIntrinsic where liftEq = genericLiftEq
|
||||
instance Ord1 EvalIntrinsic where liftCompare = genericLiftCompare
|
||||
@ -333,7 +333,7 @@ instance Show1 EvalIntrinsic where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable EvalIntrinsic
|
||||
|
||||
newtype PrintIntrinsic a = PrintIntrinsic { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 PrintIntrinsic where liftEq = genericLiftEq
|
||||
instance Ord1 PrintIntrinsic where liftCompare = genericLiftCompare
|
||||
@ -341,7 +341,7 @@ instance Show1 PrintIntrinsic where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable PrintIntrinsic
|
||||
|
||||
newtype NamespaceAliasingClause a = NamespaceAliasingClause { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 NamespaceAliasingClause where liftEq = genericLiftEq
|
||||
instance Ord1 NamespaceAliasingClause where liftCompare = genericLiftCompare
|
||||
@ -349,7 +349,7 @@ instance Show1 NamespaceAliasingClause where liftShowsPrec = genericLiftShowsPre
|
||||
instance Evaluatable NamespaceAliasingClause
|
||||
|
||||
newtype NamespaceUseDeclaration a = NamespaceUseDeclaration { values :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 NamespaceUseDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 NamespaceUseDeclaration where liftCompare = genericLiftCompare
|
||||
@ -357,7 +357,7 @@ instance Show1 NamespaceUseDeclaration where liftShowsPrec = genericLiftShowsPre
|
||||
instance Evaluatable NamespaceUseDeclaration
|
||||
|
||||
newtype NamespaceUseClause a = NamespaceUseClause { values :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 NamespaceUseClause where liftEq = genericLiftEq
|
||||
instance Ord1 NamespaceUseClause where liftCompare = genericLiftCompare
|
||||
@ -365,7 +365,7 @@ instance Show1 NamespaceUseClause where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable NamespaceUseClause
|
||||
|
||||
newtype NamespaceUseGroupClause a = NamespaceUseGroupClause { values :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 NamespaceUseGroupClause where liftEq = genericLiftEq
|
||||
instance Ord1 NamespaceUseGroupClause where liftCompare = genericLiftCompare
|
||||
@ -373,7 +373,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Namespace where liftEq = genericLiftEq
|
||||
instance Ord1 Namespace where liftCompare = genericLiftCompare
|
||||
@ -396,7 +396,7 @@ instance Evaluatable Namespace where
|
||||
go [] = eval namespaceBody >>= address
|
||||
|
||||
data TraitDeclaration a = TraitDeclaration { traitName :: a, traitStatements :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 TraitDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 TraitDeclaration where liftCompare = genericLiftCompare
|
||||
@ -404,7 +404,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 AliasAs where liftEq = genericLiftEq
|
||||
instance Ord1 AliasAs where liftCompare = genericLiftCompare
|
||||
@ -412,7 +412,7 @@ instance Show1 AliasAs where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable AliasAs
|
||||
|
||||
data InsteadOf a = InsteadOf { left :: a, right :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 InsteadOf where liftEq = genericLiftEq
|
||||
instance Ord1 InsteadOf where liftCompare = genericLiftCompare
|
||||
@ -420,7 +420,7 @@ instance Show1 InsteadOf where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable InsteadOf
|
||||
|
||||
newtype TraitUseSpecification a = TraitUseSpecification { values :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 TraitUseSpecification where liftEq = genericLiftEq
|
||||
instance Ord1 TraitUseSpecification where liftCompare = genericLiftCompare
|
||||
@ -428,7 +428,7 @@ instance Show1 TraitUseSpecification where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable TraitUseSpecification
|
||||
|
||||
data TraitUseClause a = TraitUseClause { namespace :: [a], alias :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 TraitUseClause where liftEq = genericLiftEq
|
||||
instance Ord1 TraitUseClause where liftCompare = genericLiftCompare
|
||||
@ -436,7 +436,7 @@ instance Show1 TraitUseClause where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable TraitUseClause
|
||||
|
||||
data DestructorDeclaration a = DestructorDeclaration { body:: [a], name :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 DestructorDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 DestructorDeclaration where liftCompare = genericLiftCompare
|
||||
@ -444,7 +444,7 @@ instance Show1 DestructorDeclaration where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable DestructorDeclaration
|
||||
|
||||
newtype Static a = Static { value :: T.Text }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Static where liftEq = genericLiftEq
|
||||
instance Ord1 Static where liftCompare = genericLiftCompare
|
||||
@ -452,7 +452,7 @@ instance Show1 Static where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable Static
|
||||
|
||||
newtype ClassModifier a = ClassModifier { value :: T.Text }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ClassModifier where liftEq = genericLiftEq
|
||||
instance Ord1 ClassModifier where liftCompare = genericLiftCompare
|
||||
@ -460,7 +460,7 @@ instance Show1 ClassModifier where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ClassModifier
|
||||
|
||||
data ConstructorDeclaration a = ConstructorDeclaration { modifiers :: [a], parameters :: [a], body :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ConstructorDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 ConstructorDeclaration where liftCompare = genericLiftCompare
|
||||
@ -468,7 +468,7 @@ instance Show1 ConstructorDeclaration where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ConstructorDeclaration
|
||||
|
||||
data PropertyDeclaration a = PropertyDeclaration { modifier :: a, elements :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 PropertyDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 PropertyDeclaration where liftCompare = genericLiftCompare
|
||||
@ -476,7 +476,7 @@ instance Show1 PropertyDeclaration where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable PropertyDeclaration
|
||||
|
||||
data PropertyModifier a = PropertyModifier { visibility :: a , static :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 PropertyModifier where liftEq = genericLiftEq
|
||||
instance Ord1 PropertyModifier where liftCompare = genericLiftCompare
|
||||
@ -484,7 +484,7 @@ instance Show1 PropertyModifier where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable PropertyModifier
|
||||
|
||||
data InterfaceDeclaration a = InterfaceDeclaration { name :: a, base :: a, declarations :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 InterfaceDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 InterfaceDeclaration where liftCompare = genericLiftCompare
|
||||
@ -492,7 +492,7 @@ instance Show1 InterfaceDeclaration where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable InterfaceDeclaration
|
||||
|
||||
newtype InterfaceBaseClause a = InterfaceBaseClause { values :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 InterfaceBaseClause where liftEq = genericLiftEq
|
||||
instance Ord1 InterfaceBaseClause where liftCompare = genericLiftCompare
|
||||
@ -500,7 +500,7 @@ instance Show1 InterfaceBaseClause where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable InterfaceBaseClause
|
||||
|
||||
newtype Echo a = Echo { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Echo where liftEq = genericLiftEq
|
||||
instance Ord1 Echo where liftCompare = genericLiftCompare
|
||||
@ -508,7 +508,7 @@ instance Show1 Echo where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable Echo
|
||||
|
||||
newtype Unset a = Unset { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Unset where liftEq = genericLiftEq
|
||||
instance Ord1 Unset where liftCompare = genericLiftCompare
|
||||
@ -516,7 +516,7 @@ instance Show1 Unset where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable Unset
|
||||
|
||||
data Declare a = Declare { left :: a, right :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Declare where liftEq = genericLiftEq
|
||||
instance Ord1 Declare where liftCompare = genericLiftCompare
|
||||
@ -524,7 +524,7 @@ instance Show1 Declare where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable Declare
|
||||
|
||||
newtype DeclareDirective a = DeclareDirective { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 DeclareDirective where liftEq = genericLiftEq
|
||||
instance Ord1 DeclareDirective where liftCompare = genericLiftCompare
|
||||
@ -532,7 +532,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 LabeledStatement where liftEq = genericLiftEq
|
||||
instance Ord1 LabeledStatement where liftCompare = genericLiftCompare
|
||||
|
@ -25,7 +25,7 @@ import qualified Proto3.Wire.Decode as Decode
|
||||
data QualifiedName
|
||||
= QualifiedName { paths :: NonEmpty FilePath }
|
||||
| RelativeQualifiedName { path :: FilePath, maybeQualifiedName :: Maybe QualifiedName }
|
||||
deriving (Eq, Generic, Hashable, Ord, Show, ToJSON, Named, Message)
|
||||
deriving (Eq, Generic, Hashable, Ord, Show, ToJSON, Named, Message, NFData)
|
||||
|
||||
instance MessageField QualifiedName where
|
||||
encodeMessageField num QualifiedName{..} = Encode.embedded num (encodeMessageField 1 paths)
|
||||
@ -103,14 +103,14 @@ 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, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
|
||||
instance Eq1 Import where liftEq = genericLiftEq
|
||||
instance Ord1 Import where liftCompare = genericLiftCompare
|
||||
instance Show1 Import where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
newtype FutureImport a = FutureImport { futureImportSymbols :: [Alias] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
|
||||
instance Eq1 FutureImport where liftEq = genericLiftEq
|
||||
instance Ord1 FutureImport where liftCompare = genericLiftCompare
|
||||
@ -119,7 +119,7 @@ instance Show1 FutureImport where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable FutureImport where
|
||||
|
||||
data Alias = Alias { aliasValue :: Name, aliasName :: Name }
|
||||
deriving (Eq, Generic, Hashable, Ord, Show, Message, Named, ToJSON)
|
||||
deriving (Eq, Generic, Hashable, Ord, Show, Message, Named, ToJSON, NFData)
|
||||
|
||||
toTuple :: Alias -> (Name, Name)
|
||||
toTuple Alias{..} = (aliasValue, aliasName)
|
||||
@ -168,7 +168,7 @@ evalQualifiedImport name path = letrec' name $ \addr -> do
|
||||
unit <$ makeNamespace name addr Nothing (bindAll . fst . snd =<< require path)
|
||||
|
||||
newtype QualifiedImport a = QualifiedImport { qualifiedImportFrom :: NonEmpty FilePath }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Named1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
|
||||
instance Message1 QualifiedImport where
|
||||
liftEncodeMessage _ _ QualifiedImport{..} = encodeMessageField 1 qualifiedImportFrom
|
||||
@ -200,7 +200,7 @@ instance Evaluatable QualifiedImport where
|
||||
makeNamespace name addr Nothing (void (require path >> go (NonEmpty.fromList xs)))
|
||||
|
||||
data QualifiedAliasedImport a = QualifiedAliasedImport { qualifiedAliasedImportFrom :: QualifiedName, qualifiedAliasedImportAlias :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
|
||||
instance Eq1 QualifiedAliasedImport where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedAliasedImport where liftCompare = genericLiftCompare
|
||||
@ -222,7 +222,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, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
|
||||
instance Eq1 Ellipsis where liftEq = genericLiftEq
|
||||
instance Ord1 Ellipsis where liftCompare = genericLiftCompare
|
||||
@ -233,7 +233,7 @@ instance Evaluatable Ellipsis
|
||||
|
||||
|
||||
data Redirect a = Redirect { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
|
||||
instance Eq1 Redirect where liftEq = genericLiftEq
|
||||
instance Ord1 Redirect where liftCompare = genericLiftCompare
|
||||
|
@ -52,7 +52,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Send where liftEq = genericLiftEq
|
||||
instance Ord1 Send where liftCompare = genericLiftCompare
|
||||
@ -76,7 +76,7 @@ instance Tokenize Send where
|
||||
fromMaybe (pure ()) sendBlock
|
||||
|
||||
data Require a = Require { requireRelative :: Bool, requirePath :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Require where liftEq = genericLiftEq
|
||||
instance Ord1 Require where liftCompare = genericLiftCompare
|
||||
@ -104,7 +104,7 @@ doRequire path = do
|
||||
|
||||
|
||||
data Load a = Load { loadPath :: a, loadWrap :: Maybe a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Load where liftEq = genericLiftEq
|
||||
instance Ord1 Load where liftCompare = genericLiftCompare
|
||||
@ -140,7 +140,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, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1)
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Diffable Class where
|
||||
equivalentBySubterm = Just . classIdentifier
|
||||
@ -157,7 +157,7 @@ instance Evaluatable Class where
|
||||
makeNamespace name addr super (void (eval classBody)))
|
||||
|
||||
data Module a = Module { moduleIdentifier :: !a, moduleStatements :: ![a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Module where liftEq = genericLiftEq
|
||||
instance Ord1 Module where liftCompare = genericLiftCompare
|
||||
@ -170,7 +170,7 @@ instance Evaluatable Module where
|
||||
makeNamespace name addr Nothing (traverse_ eval xs))
|
||||
|
||||
data LowPrecedenceAnd a = LowPrecedenceAnd { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
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
|
||||
@ -184,7 +184,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, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
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
|
||||
|
@ -30,7 +30,7 @@ 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)
|
||||
deriving (Bounded, Enum, Finite, MessageField, Named, Eq, Generic, Hashable, Ord, Show, ToJSON, NFData)
|
||||
|
||||
instance Primitive IsRelative where
|
||||
encodePrimitive = Encode.enum
|
||||
@ -41,7 +41,7 @@ instance HasDefault IsRelative where
|
||||
def = Unknown
|
||||
|
||||
data ImportPath = ImportPath { unPath :: FilePath, pathIsRelative :: IsRelative }
|
||||
deriving (Eq, Generic, Hashable, Message, Named, Ord, Show, ToJSON)
|
||||
deriving (Eq, Generic, Hashable, Message, Named, Ord, Show, ToJSON, NFData)
|
||||
|
||||
instance MessageField ImportPath where
|
||||
encodeMessageField num = Encode.embedded num . encodeMessage (fieldNumber 1)
|
||||
|
@ -12,7 +12,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 JsxElement where liftEq = genericLiftEq
|
||||
instance Ord1 JsxElement where liftCompare = genericLiftCompare
|
||||
@ -20,7 +20,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 JsxText where liftEq = genericLiftEq
|
||||
instance Ord1 JsxText where liftCompare = genericLiftCompare
|
||||
@ -28,7 +28,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 JsxExpression where liftEq = genericLiftEq
|
||||
instance Ord1 JsxExpression where liftCompare = genericLiftCompare
|
||||
@ -36,7 +36,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 JsxOpeningElement where liftEq = genericLiftEq
|
||||
instance Ord1 JsxOpeningElement where liftCompare = genericLiftCompare
|
||||
@ -44,7 +44,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 JsxClosingElement where liftEq = genericLiftEq
|
||||
instance Ord1 JsxClosingElement where liftCompare = genericLiftCompare
|
||||
@ -52,7 +52,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 JsxSelfClosingElement where liftEq = genericLiftEq
|
||||
instance Ord1 JsxSelfClosingElement where liftCompare = genericLiftCompare
|
||||
@ -60,7 +60,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 JsxAttribute where liftEq = genericLiftEq
|
||||
instance Ord1 JsxAttribute where liftCompare = genericLiftCompare
|
||||
@ -68,7 +68,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ImplementsClause where liftEq = genericLiftEq
|
||||
instance Ord1 ImplementsClause where liftCompare = genericLiftCompare
|
||||
@ -76,7 +76,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 OptionalParameter where liftEq = genericLiftEq
|
||||
instance Ord1 OptionalParameter where liftCompare = genericLiftCompare
|
||||
@ -84,7 +84,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 RequiredParameter where liftEq = genericLiftEq
|
||||
instance Ord1 RequiredParameter where liftCompare = genericLiftCompare
|
||||
@ -92,7 +92,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 RestParameter where liftEq = genericLiftEq
|
||||
instance Ord1 RestParameter where liftCompare = genericLiftCompare
|
||||
@ -100,7 +100,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 JsxFragment where liftEq = genericLiftEq
|
||||
instance Ord1 JsxFragment where liftCompare = genericLiftCompare
|
||||
@ -108,7 +108,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 JsxNamespaceName where liftEq = genericLiftEq
|
||||
instance Ord1 JsxNamespaceName where liftCompare = genericLiftCompare
|
||||
|
@ -12,7 +12,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 JavaScriptRequire where liftEq = genericLiftEq
|
||||
instance Ord1 JavaScriptRequire where liftCompare = genericLiftCompare
|
||||
@ -25,7 +25,7 @@ instance Evaluatable JavaScriptRequire where
|
||||
rvalBox =<< evalRequire modulePath alias
|
||||
|
||||
data Debugger a = Debugger
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Debugger where liftEq = genericLiftEq
|
||||
instance Ord1 Debugger where liftCompare = genericLiftCompare
|
||||
@ -33,7 +33,7 @@ instance Show1 Debugger where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable Debugger
|
||||
|
||||
data Super a = Super
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Super where liftEq = genericLiftEq
|
||||
instance Ord1 Super where liftCompare = genericLiftCompare
|
||||
@ -41,7 +41,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Undefined where liftEq = genericLiftEq
|
||||
instance Ord1 Undefined where liftCompare = genericLiftCompare
|
||||
@ -49,7 +49,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 With where liftEq = genericLiftEq
|
||||
instance Ord1 With where liftCompare = genericLiftCompare
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE DeriveAnyClass, DuplicateRecordFields #-}
|
||||
{-# LANGUAGE DeriveAnyClass, DerivingStrategies, DuplicateRecordFields #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
module Language.TypeScript.Syntax.TypeScript where
|
||||
|
||||
@ -16,7 +16,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Import where liftEq = genericLiftEq
|
||||
instance Ord1 Import where liftCompare = genericLiftCompare
|
||||
@ -35,7 +35,7 @@ instance Evaluatable Import where
|
||||
| otherwise = Env.aliasBindings (toTuple <$> symbols) importedBinds
|
||||
|
||||
data QualifiedAliasedImport a = QualifiedAliasedImport { qualifiedAliasedImportAlias :: !a, qualifiedAliasedImportFrom :: ImportPath }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 QualifiedAliasedImport where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedAliasedImport where liftCompare = genericLiftCompare
|
||||
@ -48,7 +48,7 @@ instance Evaluatable QualifiedAliasedImport where
|
||||
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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 SideEffectImport where liftEq = genericLiftEq
|
||||
instance Ord1 SideEffectImport where liftCompare = genericLiftCompare
|
||||
@ -63,7 +63,7 @@ instance Evaluatable SideEffectImport where
|
||||
|
||||
-- | Qualified Export declarations
|
||||
newtype QualifiedExport a = QualifiedExport { qualifiedExportSymbols :: [Alias] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 QualifiedExport where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedExport where liftCompare = genericLiftCompare
|
||||
@ -77,14 +77,14 @@ instance Evaluatable QualifiedExport where
|
||||
rvalBox unit
|
||||
|
||||
data Alias = Alias { aliasValue :: Name, aliasName :: Name }
|
||||
deriving (Eq, Generic, Hashable, Ord, Show, Message, Named, ToJSON)
|
||||
deriving (Eq, Generic, Hashable, Ord, Show, Message, Named, ToJSON, NFData)
|
||||
|
||||
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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 QualifiedExportFrom where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedExportFrom where liftCompare = genericLiftCompare
|
||||
@ -101,7 +101,7 @@ instance Evaluatable QualifiedExportFrom where
|
||||
rvalBox unit
|
||||
|
||||
newtype DefaultExport a = DefaultExport { defaultExport :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 DefaultExport where liftEq = genericLiftEq
|
||||
instance Ord1 DefaultExport where liftCompare = genericLiftCompare
|
||||
@ -120,7 +120,7 @@ instance Evaluatable DefaultExport where
|
||||
|
||||
-- | 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 LookupType where liftEq = genericLiftEq
|
||||
instance Ord1 LookupType where liftCompare = genericLiftCompare
|
||||
@ -129,7 +129,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ShorthandPropertyIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 ShorthandPropertyIdentifier where liftCompare = genericLiftCompare
|
||||
@ -137,7 +137,7 @@ instance Show1 ShorthandPropertyIdentifier where liftShowsPrec = genericLiftShow
|
||||
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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, 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
|
||||
@ -145,7 +145,7 @@ instance Show1 Language.TypeScript.Syntax.TypeScript.Union where liftShowsPrec =
|
||||
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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Intersection where liftEq = genericLiftEq
|
||||
instance Ord1 Intersection where liftCompare = genericLiftCompare
|
||||
@ -153,7 +153,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 FunctionType where liftEq = genericLiftEq
|
||||
instance Ord1 FunctionType where liftCompare = genericLiftCompare
|
||||
@ -161,7 +161,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 AmbientFunction where liftEq = genericLiftEq
|
||||
instance Ord1 AmbientFunction where liftCompare = genericLiftCompare
|
||||
@ -169,7 +169,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ImportRequireClause where liftEq = genericLiftEq
|
||||
instance Ord1 ImportRequireClause where liftCompare = genericLiftCompare
|
||||
@ -177,7 +177,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ImportClause where liftEq = genericLiftEq
|
||||
instance Ord1 ImportClause where liftCompare = genericLiftCompare
|
||||
@ -185,7 +185,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Tuple where liftEq = genericLiftEq
|
||||
instance Ord1 Tuple where liftCompare = genericLiftCompare
|
||||
@ -195,7 +195,7 @@ instance Show1 Tuple where liftShowsPrec = genericLiftShowsPrec
|
||||
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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, 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
|
||||
@ -203,7 +203,7 @@ instance Show1 Language.TypeScript.Syntax.TypeScript.Constructor where liftShows
|
||||
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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 TypeParameter where liftEq = genericLiftEq
|
||||
instance Ord1 TypeParameter where liftCompare = genericLiftCompare
|
||||
@ -211,7 +211,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 TypeAssertion where liftEq = genericLiftEq
|
||||
instance Ord1 TypeAssertion where liftCompare = genericLiftCompare
|
||||
@ -219,7 +219,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Annotation where liftEq = genericLiftEq
|
||||
instance Ord1 Annotation where liftCompare = genericLiftCompare
|
||||
@ -227,7 +227,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Decorator where liftEq = genericLiftEq
|
||||
instance Ord1 Decorator where liftCompare = genericLiftCompare
|
||||
@ -235,7 +235,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ComputedPropertyName where liftEq = genericLiftEq
|
||||
instance Ord1 ComputedPropertyName where liftCompare = genericLiftCompare
|
||||
@ -243,7 +243,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Constraint where liftEq = genericLiftEq
|
||||
instance Ord1 Constraint where liftCompare = genericLiftCompare
|
||||
@ -251,7 +251,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 DefaultType where liftEq = genericLiftEq
|
||||
instance Ord1 DefaultType where liftCompare = genericLiftCompare
|
||||
@ -259,7 +259,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ParenthesizedType where liftEq = genericLiftEq
|
||||
instance Ord1 ParenthesizedType where liftCompare = genericLiftCompare
|
||||
@ -267,7 +267,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 PredefinedType where liftEq = genericLiftEq
|
||||
instance Ord1 PredefinedType where liftCompare = genericLiftCompare
|
||||
@ -276,7 +276,7 @@ instance Show1 PredefinedType where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable PredefinedType
|
||||
|
||||
newtype TypeIdentifier a = TypeIdentifier { contents :: T.Text }
|
||||
deriving (Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Declarations1 TypeIdentifier where
|
||||
liftDeclaredName _ (TypeIdentifier identifier) = Just (name identifier)
|
||||
@ -292,7 +292,7 @@ instance Evaluatable TypeIdentifier where
|
||||
rvalBox unit
|
||||
|
||||
data NestedIdentifier a = NestedIdentifier { left :: !a, right :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 NestedIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 NestedIdentifier where liftCompare = genericLiftCompare
|
||||
@ -300,7 +300,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 NestedTypeIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 NestedTypeIdentifier where liftCompare = genericLiftCompare
|
||||
@ -308,7 +308,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 GenericType where liftEq = genericLiftEq
|
||||
instance Ord1 GenericType where liftCompare = genericLiftCompare
|
||||
@ -316,7 +316,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 TypePredicate where liftEq = genericLiftEq
|
||||
instance Ord1 TypePredicate where liftCompare = genericLiftCompare
|
||||
@ -324,7 +324,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ObjectType where liftEq = genericLiftEq
|
||||
instance Ord1 ObjectType where liftCompare = genericLiftCompare
|
||||
@ -332,7 +332,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 AmbientDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 AmbientDeclaration where liftCompare = genericLiftCompare
|
||||
@ -342,7 +342,7 @@ instance Evaluatable AmbientDeclaration where
|
||||
eval eval (AmbientDeclaration body) = eval body
|
||||
|
||||
data EnumDeclaration a = EnumDeclaration { enumDeclarationIdentifier :: !a, enumDeclarationBody :: ![a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 EnumDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 EnumDeclaration where liftCompare = genericLiftCompare
|
||||
@ -353,7 +353,7 @@ instance Declarations a => Declarations (EnumDeclaration a) where
|
||||
declaredName EnumDeclaration{..} = declaredName enumDeclarationIdentifier
|
||||
|
||||
newtype ExtendsClause a = ExtendsClause { extendsClauses :: [a] }
|
||||
deriving (Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Declarations1 ExtendsClause where
|
||||
liftDeclaredName _ (ExtendsClause []) = Nothing
|
||||
@ -370,7 +370,7 @@ instance Evaluatable ExtendsClause where
|
||||
rvalBox unit
|
||||
|
||||
newtype ArrayType a = ArrayType { arrayType :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ArrayType where liftEq = genericLiftEq
|
||||
instance Ord1 ArrayType where liftCompare = genericLiftCompare
|
||||
@ -378,7 +378,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 FlowMaybeType where liftEq = genericLiftEq
|
||||
instance Ord1 FlowMaybeType where liftCompare = genericLiftCompare
|
||||
@ -386,7 +386,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 TypeQuery where liftEq = genericLiftEq
|
||||
instance Ord1 TypeQuery where liftCompare = genericLiftCompare
|
||||
@ -394,7 +394,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 IndexTypeQuery where liftEq = genericLiftEq
|
||||
instance Ord1 IndexTypeQuery where liftCompare = genericLiftCompare
|
||||
@ -402,7 +402,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 TypeArguments where liftEq = genericLiftEq
|
||||
instance Ord1 TypeArguments where liftCompare = genericLiftCompare
|
||||
@ -410,7 +410,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ThisType where liftEq = genericLiftEq
|
||||
instance Ord1 ThisType where liftCompare = genericLiftCompare
|
||||
@ -418,7 +418,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ExistentialType where liftEq = genericLiftEq
|
||||
instance Ord1 ExistentialType where liftCompare = genericLiftCompare
|
||||
@ -426,7 +426,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 LiteralType where liftEq = genericLiftEq
|
||||
instance Ord1 LiteralType where liftCompare = genericLiftCompare
|
||||
@ -434,7 +434,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 PropertySignature where liftEq = genericLiftEq
|
||||
instance Ord1 PropertySignature where liftCompare = genericLiftCompare
|
||||
@ -442,7 +442,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 CallSignature where liftEq = genericLiftEq
|
||||
instance Ord1 CallSignature where liftCompare = genericLiftCompare
|
||||
@ -451,7 +451,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ConstructSignature where liftEq = genericLiftEq
|
||||
instance Ord1 ConstructSignature where liftCompare = genericLiftCompare
|
||||
@ -459,7 +459,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 IndexSignature where liftEq = genericLiftEq
|
||||
instance Ord1 IndexSignature where liftCompare = genericLiftCompare
|
||||
@ -467,7 +467,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 AbstractMethodSignature where liftEq = genericLiftEq
|
||||
instance Ord1 AbstractMethodSignature where liftCompare = genericLiftCompare
|
||||
@ -475,7 +475,7 @@ instance Show1 AbstractMethodSignature where liftShowsPrec = genericLiftShowsPre
|
||||
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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ForOf where liftEq = genericLiftEq
|
||||
instance Ord1 ForOf where liftCompare = genericLiftCompare
|
||||
@ -483,7 +483,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 LabeledStatement where liftEq = genericLiftEq
|
||||
instance Ord1 LabeledStatement where liftCompare = genericLiftCompare
|
||||
@ -491,7 +491,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Update where liftEq = genericLiftEq
|
||||
instance Ord1 Update where liftCompare = genericLiftCompare
|
||||
@ -499,7 +499,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Module where liftEq = genericLiftEq
|
||||
instance Ord1 Module where liftCompare = genericLiftCompare
|
||||
@ -513,7 +513,7 @@ instance Evaluatable Module where
|
||||
|
||||
|
||||
data InternalModule a = InternalModule { internalModuleIdentifier :: !a, internalModuleStatements :: ![a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 InternalModule where liftEq = genericLiftEq
|
||||
instance Ord1 InternalModule where liftCompare = genericLiftCompare
|
||||
@ -530,7 +530,7 @@ instance Declarations a => Declarations (InternalModule a) where
|
||||
|
||||
|
||||
data ImportAlias a = ImportAlias { importAliasSubject :: !a, importAlias :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ImportAlias where liftEq = genericLiftEq
|
||||
instance Ord1 ImportAlias where liftCompare = genericLiftCompare
|
||||
@ -538,7 +538,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ClassHeritage where liftEq = genericLiftEq
|
||||
instance Ord1 ClassHeritage where liftCompare = genericLiftCompare
|
||||
@ -546,7 +546,7 @@ 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)
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 AbstractClass where liftEq = genericLiftEq
|
||||
instance Ord1 AbstractClass where liftCompare = genericLiftCompare
|
||||
|
@ -8,6 +8,7 @@ module Prologue
|
||||
) where
|
||||
|
||||
|
||||
import Control.DeepSeq as X
|
||||
import Data.Bifunctor.Join as X
|
||||
import Data.Bits as X
|
||||
import Data.ByteString as X (ByteString)
|
||||
|
@ -9,6 +9,8 @@ import Analysis.Abstract.Collecting
|
||||
import Control.Abstract
|
||||
import Control.Exception (displayException)
|
||||
import Control.Monad.Effect.Trace (runPrintingTrace)
|
||||
import qualified Language.TypeScript.Assignment as Ruby
|
||||
import qualified Data.Syntax.Literal as Literal
|
||||
import Data.Abstract.Address.Monovariant as Monovariant
|
||||
import Data.Abstract.Address.Precise as Precise
|
||||
import Data.Abstract.Evaluatable
|
||||
@ -22,6 +24,7 @@ import Data.Graph (topologicalSort)
|
||||
import qualified Data.Language as Language
|
||||
import Data.List (uncons)
|
||||
import Data.Project hiding (readFile)
|
||||
import Data.Term
|
||||
import Data.Quieterm (quieterm)
|
||||
import Data.Sum (weaken)
|
||||
import Parsing.Parser
|
||||
@ -83,6 +86,8 @@ callGraphProject parser proxy opts paths = runTaskWithOptions opts $ do
|
||||
|
||||
evaluatePythonProject = justEvaluating <=< evaluatePythonProjects (Proxy @'Language.Python) pythonParser Language.Python
|
||||
|
||||
nfPythonProject = rnf ((injectTerm () (Literal.Float "5.0")) :: Term (Sum Ruby.Syntax) ())
|
||||
|
||||
callGraphRubyProject = callGraphProject rubyParser (Proxy @'Language.Ruby) debugOptions
|
||||
|
||||
-- Evaluate a project consisting of the listed paths.
|
||||
|
2
vendor/effects
vendored
2
vendor/effects
vendored
@ -1 +1 @@
|
||||
Subproject commit e7858dacce6fbb43e76a49e4dbeff1f1815aa290
|
||||
Subproject commit 9616e462c58645b0017cbc66858e7123cdf77611
|
2
vendor/fastsum
vendored
2
vendor/fastsum
vendored
@ -1 +1 @@
|
||||
Subproject commit dc5020d447b510a11650692d2d61864ec458ea2c
|
||||
Subproject commit 487fedfb6e9123d349b87ab2080a571623b58112
|
Loading…
Reference in New Issue
Block a user