mirror of
https://github.com/github/semantic.git
synced 2024-12-29 01:42:43 +03:00
Merge pull request #363 from github/we-can’t-have-nice-things
We can’t have nice things
This commit is contained in:
commit
52c6b8c42f
@ -38,10 +38,10 @@ callGraphProject' :: ( Language.SLanguage lang
|
||||
=> TaskSession
|
||||
-> Proxy lang
|
||||
-> Path.RelFile
|
||||
-> IO (Either String (Data.Graph.Graph ControlFlowVertex))
|
||||
-> IO (Either String ())
|
||||
callGraphProject' session proxy path
|
||||
| let lang = Language.reflect proxy
|
||||
, Just (SomeParser parser) <- parserForLanguage analysisParsers lang = fmap (first show) . runTask session $ do
|
||||
, Just (SomeParser parser) <- parserForLanguage analysisParsers lang = fmap (bimap show (const ())) . runTask session $ do
|
||||
blob <- readBlobFromFile' (fileForTypedPath path)
|
||||
package <- fmap snd <$> runParse (Duration.fromSeconds 10) (parsePackage parser (Project (Path.toString (Path.takeDirectory path)) [blob] lang []))
|
||||
modules <- topologicalSort <$> runImportGraphToModules proxy package
|
||||
|
@ -452,17 +452,6 @@ instance Eq address => Eq1 (HeapError address) where
|
||||
liftEq _ (LookupFrameError a) (LookupFrameError b) = a == b
|
||||
liftEq _ _ _ = False
|
||||
|
||||
instance NFData address => NFData1 (HeapError address) where
|
||||
liftRnf _ x = case x of
|
||||
CurrentFrameError -> ()
|
||||
LookupAddressError a -> rnf a
|
||||
LookupFrameError a -> a `seq` ()
|
||||
LookupLinksError a -> rnf a
|
||||
LookupLinkError p -> rnf p
|
||||
|
||||
instance (NFData address, NFData resume) => NFData (HeapError address resume) where
|
||||
rnf = liftRnf rnf
|
||||
|
||||
throwHeapError :: ( Member (Resumable (BaseError (HeapError address))) sig
|
||||
, Member (Reader ModuleInfo) sig
|
||||
, Member (Reader Span) sig
|
||||
@ -485,14 +474,6 @@ data AddressError address value resume where
|
||||
UnallocatedSlot :: Slot address -> AddressError address value (Set value)
|
||||
UninitializedSlot :: Slot address -> AddressError address value value
|
||||
|
||||
instance (NFData address) => NFData1 (AddressError address value) where
|
||||
liftRnf _ x = case x of
|
||||
UnallocatedSlot a -> rnf a
|
||||
UninitializedSlot a -> rnf a
|
||||
|
||||
instance (NFData address, 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
|
||||
|
@ -112,9 +112,6 @@ instance Show1 (LoadError address value) where
|
||||
instance Eq1 (LoadError address value) where
|
||||
liftEq _ (ModuleNotFoundError a) (ModuleNotFoundError b) = a == b
|
||||
|
||||
instance NFData1 (LoadError address value) where
|
||||
liftRnf _ (ModuleNotFoundError p) = rnf p
|
||||
|
||||
runLoadError :: Evaluator term address value (ResumableC (BaseError (LoadError address value)) m) a
|
||||
-> Evaluator term address value m (Either (SomeError (BaseError (LoadError address value))) a)
|
||||
runLoadError = raiseHandler runResumable
|
||||
@ -147,10 +144,6 @@ 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 :: Evaluator term address value (ResumableC (BaseError ResolutionError) m) a
|
||||
-> Evaluator term address value m (Either (SomeError (BaseError ResolutionError)) a)
|
||||
|
@ -362,19 +362,6 @@ instance Eq1 (ScopeError address) where
|
||||
liftEq _ CurrentScopeError CurrentScopeError = True
|
||||
liftEq _ _ _ = False
|
||||
|
||||
instance NFData1 (ScopeError address) where
|
||||
liftRnf _ x = case x of
|
||||
DeclarationByNameError n -> rnf n
|
||||
ScopeError d s -> rnf d `seq` rnf s
|
||||
LookupScopeError -> ()
|
||||
ImportReferenceError -> ()
|
||||
LookupPathError d -> rnf d
|
||||
LookupDeclarationScopeError d -> rnf d
|
||||
CurrentScopeError -> ()
|
||||
|
||||
instance NFData return => NFData (ScopeError address return) where
|
||||
rnf = liftRnf rnf
|
||||
|
||||
alloc :: (Member (Allocator address) sig, Carrier sig m) => Name -> Evaluator term address value m address
|
||||
alloc = send . flip Alloc pure
|
||||
|
||||
|
@ -114,7 +114,7 @@ function name params body scope = sendFunction (Function name params body scope
|
||||
data BuiltIn
|
||||
= Print
|
||||
| Show
|
||||
deriving (Eq, Ord, Show, Generic, NFData)
|
||||
deriving (Eq, Ord, Show, Generic)
|
||||
|
||||
builtIn :: (Member (Function term address value) sig, Carrier sig m) => address -> BuiltIn -> Evaluator term address value m value
|
||||
builtIn address = sendFunction . flip (BuiltIn address) pure
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE GeneralizedNewtypeDeriving, TypeOperators, UndecidableInstances #-}
|
||||
{-# LANGUAGE TypeOperators, UndecidableInstances #-}
|
||||
module Data.Abstract.Address.Precise
|
||||
( Precise(..)
|
||||
) where
|
||||
@ -11,7 +11,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, NFData)
|
||||
deriving (Eq, Ord)
|
||||
|
||||
instance Show Precise where
|
||||
showsPrec d = showsUnaryWith showsPrec "Precise" d . unPrecise
|
||||
|
@ -29,12 +29,6 @@ instance (Eq1 exc) => Eq1 (BaseError exc) where
|
||||
instance Show1 exc => Show1 (BaseError exc) where
|
||||
liftShowsPrec sl sp d (BaseError info span exc) = showParen (d > 10) $ showString "BaseError" . showChar ' ' . showsPrec 11 info . showChar ' ' . showsPrec 11 span . showChar ' ' . liftShowsPrec sl sp 11 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)) sig
|
||||
, Member (Reader M.ModuleInfo) sig
|
||||
, Member (Reader S.Span) sig
|
||||
|
@ -225,23 +225,6 @@ throwNoNameError = throwEvalError . NoNameError
|
||||
deriving instance (Eq term, Eq value) => Eq (EvalError term address value return)
|
||||
deriving instance (Show term, Show value) => Show (EvalError term address value return)
|
||||
|
||||
instance (NFData term, NFData value) => NFData1 (EvalError term address value) where
|
||||
liftRnf _ x = case x of
|
||||
AccessControlError requester requested v -> rnf requester `seq` rnf requested `seq` rnf v
|
||||
ConstructorError n -> rnf n
|
||||
DefaultExportError -> ()
|
||||
DerefError v -> rnf v
|
||||
ExportError p n -> rnf p `seq` rnf n
|
||||
FloatFormatError i -> rnf i
|
||||
IntegerFormatError i -> rnf i
|
||||
NoNameError term -> rnf term
|
||||
RationalFormatError i -> rnf i
|
||||
ReferenceError v n -> rnf v `seq` rnf n
|
||||
ScopedEnvError v -> rnf v
|
||||
|
||||
instance (NFData term, NFData value, NFData return) => NFData (EvalError term address value return) where
|
||||
rnf = liftRnf rnf
|
||||
|
||||
instance (Eq term, Eq value) => Eq1 (EvalError term address value) where
|
||||
liftEq _ (AccessControlError a b c) (AccessControlError a' b' c') = a == a' && b == b' && c == c'
|
||||
liftEq _ (DerefError v) (DerefError v2) = v == v2
|
||||
@ -280,13 +263,6 @@ data UnspecializedError address value resume where
|
||||
UnspecializedError :: String -> UnspecializedError address value value
|
||||
RefUnspecializedError :: String -> UnspecializedError address value (Slot address)
|
||||
|
||||
instance NFData1 (UnspecializedError address value) where
|
||||
liftRnf _ (UnspecializedError s) = rnf s
|
||||
liftRnf _ (RefUnspecializedError s) = rnf s
|
||||
|
||||
instance NFData (UnspecializedError address value resume) where
|
||||
rnf = liftRnf (const ())
|
||||
|
||||
deriving instance Eq (UnspecializedError address value resume)
|
||||
deriving instance Show (UnspecializedError address value resume)
|
||||
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE DeriveAnyClass, DerivingStrategies, GeneralizedNewtypeDeriving #-}
|
||||
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
||||
module Data.Abstract.Heap
|
||||
( Heap(..)
|
||||
, Frame(..)
|
||||
@ -52,15 +52,11 @@ data Frame scopeAddress frameAddress value = Frame
|
||||
, slots :: IntMap (Set value)
|
||||
-- ^ An IntMap of values that are declared in the frame.
|
||||
}
|
||||
deriving (Eq, Ord, Show, Generic, NFData)
|
||||
deriving (Eq, Ord, Show, Generic)
|
||||
|
||||
-- | A Heap is a Map from frame addresses to frames.
|
||||
newtype Heap scopeAddress frameAddress value = Heap { unHeap :: Map frameAddress (Frame scopeAddress frameAddress value) }
|
||||
deriving stock (Eq, Generic, Ord)
|
||||
deriving newtype (NFData)
|
||||
|
||||
instance Lower (Heap scopeAddress frameAddress value) where
|
||||
lowerBound = Heap lowerBound
|
||||
deriving (Eq, Generic, Lower, Ord)
|
||||
|
||||
|
||||
-- | Look up the frame for an 'address' in a 'Heap', if any.
|
||||
|
@ -1,5 +1,3 @@
|
||||
{-# LANGUAGE DeriveAnyClass, DerivingStrategies #-}
|
||||
|
||||
module Data.Abstract.Module
|
||||
( Module(..)
|
||||
, moduleForBlob
|
||||
@ -16,8 +14,7 @@ import Prologue
|
||||
import System.FilePath.Posix
|
||||
|
||||
data Module body = Module { moduleInfo :: ModuleInfo, moduleBody :: body }
|
||||
deriving stock (Eq, Foldable, Functor, Ord, Traversable, Generic)
|
||||
deriving anyclass (NFData)
|
||||
deriving (Eq, Foldable, Functor, Ord, Traversable, Generic)
|
||||
|
||||
instance Show body => Show (Module body) where
|
||||
showsPrec d Module{..} = showsBinaryWith showsPrec showsPrec "Module" d (modulePath moduleInfo) moduleBody
|
||||
@ -36,8 +33,7 @@ moduleForBlob rootDir b = Module info
|
||||
type ModulePath = FilePath
|
||||
|
||||
data ModuleInfo = ModuleInfo { modulePath :: ModulePath, moduleLanguage :: Language, moduleOid :: Text }
|
||||
deriving stock (Eq, Ord, Generic)
|
||||
deriving anyclass (NFData)
|
||||
deriving (Eq, Ord, Generic)
|
||||
|
||||
instance Lower ModuleInfo where
|
||||
lowerBound = ModuleInfo mempty Unknown mempty
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE DeriveAnyClass, DerivingStrategies, GeneralizedNewtypeDeriving #-}
|
||||
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
||||
module Data.Abstract.ModuleTable
|
||||
( ModulePath
|
||||
, ModuleTable (..)
|
||||
@ -21,9 +21,7 @@ import Prologue
|
||||
import System.FilePath.Posix
|
||||
|
||||
newtype ModuleTable a = ModuleTable { unModuleTable :: Map.Map ModulePath a }
|
||||
deriving stock (Eq, Foldable, Functor, Generic1, Generic, Ord, Traversable)
|
||||
deriving newtype (Lower, Monoid, Semigroup)
|
||||
deriving anyclass (NFData)
|
||||
deriving (Eq, Foldable, Functor, Generic1, Generic, Lower, Monoid, Ord, Semigroup, Traversable)
|
||||
|
||||
singleton :: ModulePath -> a -> ModuleTable a
|
||||
singleton name = ModuleTable . Map.singleton name
|
||||
|
@ -1,4 +1,3 @@
|
||||
{-# LANGUAGE DeriveAnyClass #-}
|
||||
module Data.Abstract.Name
|
||||
( Name
|
||||
-- * Constructors
|
||||
@ -20,7 +19,7 @@ import Prologue
|
||||
data Name
|
||||
= Name Text
|
||||
| I Int
|
||||
deriving (Eq, Ord, Generic, NFData)
|
||||
deriving (Eq, Ord, Generic)
|
||||
|
||||
-- | Generate a fresh (unused) name for use in synthesized variables/closures/etc.
|
||||
gensym :: (Member Fresh sig, Carrier sig m) => m Name
|
||||
|
@ -32,12 +32,6 @@ 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,5 +1,3 @@
|
||||
{-# LANGUAGE DeriveAnyClass #-}
|
||||
|
||||
module Data.Abstract.Package
|
||||
( Package (..)
|
||||
, PackageInfo (..)
|
||||
@ -11,7 +9,6 @@ import Data.Abstract.Module
|
||||
import Data.Abstract.ModuleTable as ModuleTable
|
||||
import qualified Data.Map as Map
|
||||
import Data.Abstract.Name
|
||||
import Prologue
|
||||
|
||||
type PackageName = Name
|
||||
|
||||
@ -20,7 +17,7 @@ data PackageInfo = PackageInfo
|
||||
{ packageName :: PackageName
|
||||
, packageResolutions :: Map.Map FilePath FilePath
|
||||
}
|
||||
deriving (Eq, Ord, Show, Generic, NFData)
|
||||
deriving (Eq, Ord, Show)
|
||||
|
||||
-- | 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
|
||||
|
@ -55,13 +55,13 @@ import Source.Span
|
||||
|
||||
-- A slot is a location in the heap where a value is stored.
|
||||
data Slot address = Slot { frameAddress :: address, position :: Position }
|
||||
deriving (Eq, Show, Ord, Generic, NFData)
|
||||
deriving (Eq, Show, Ord)
|
||||
|
||||
|
||||
data AccessControl = Public
|
||||
| Protected
|
||||
| Private
|
||||
deriving (Bounded, Enum, Eq, Generic, Hashable, ToJSON, NFData, Show)
|
||||
deriving (Bounded, Enum, Eq, Generic, Hashable, ToJSON, Show)
|
||||
|
||||
instance ToJSONFields AccessControl where
|
||||
toJSONFields accessControl = ["accessControl" .= accessControl]
|
||||
@ -87,7 +87,7 @@ instance Ord AccessControl where
|
||||
|
||||
|
||||
data Relation = Default | Instance | Prelude | Gensym
|
||||
deriving (Bounded, Enum, Eq, Show, Ord, Generic, NFData)
|
||||
deriving (Bounded, Enum, Eq, Show, Ord)
|
||||
|
||||
instance Lower Relation where
|
||||
lowerBound = Default
|
||||
@ -100,7 +100,7 @@ data Info scopeAddress = Info
|
||||
, infoSpan :: Span
|
||||
, infoKind :: Kind
|
||||
, infoAssociatedScope :: Maybe scopeAddress
|
||||
} deriving (Eq, Show, Ord, Generic, NFData)
|
||||
} deriving (Eq, Show, Ord)
|
||||
|
||||
instance HasSpan (Info scopeAddress) where
|
||||
span_ = lens infoSpan (\i s -> i { infoSpan = s })
|
||||
@ -113,7 +113,7 @@ data ReferenceInfo = ReferenceInfo
|
||||
{ refSpan :: Span
|
||||
, refKind :: Kind
|
||||
, refModule :: ModuleInfo
|
||||
} deriving (Eq, Show, Ord, Generic, NFData)
|
||||
} deriving (Eq, Show, Ord)
|
||||
|
||||
instance HasSpan ReferenceInfo where
|
||||
span_ = lens refSpan (\r s -> r { refSpan = s })
|
||||
@ -143,7 +143,7 @@ data Kind = AbstractClass
|
||||
| Unknown
|
||||
| UnqualifiedImport
|
||||
| VariableDeclaration
|
||||
deriving (Bounded, Enum, Eq, Show, Ord, Generic, NFData)
|
||||
deriving (Bounded, Enum, Eq, Show, Ord)
|
||||
|
||||
instance Lower Kind where
|
||||
lowerBound = Unknown
|
||||
@ -160,7 +160,7 @@ data Scope address =
|
||||
, references :: Map Reference ([ReferenceInfo], Path address)
|
||||
, declarations :: Seq (Info address)
|
||||
}
|
||||
deriving (Eq, Show, Ord, Generic, NFData)
|
||||
deriving (Eq, Show, Ord)
|
||||
|
||||
instance Lower (Scope scopeAddress) where
|
||||
lowerBound = Scope mempty mempty mempty
|
||||
@ -175,10 +175,10 @@ instance AbstractHole (Info address) where
|
||||
hole = lowerBound
|
||||
|
||||
newtype Position = Position { unPosition :: Int }
|
||||
deriving (Eq, Show, Ord, Generic, NFData)
|
||||
deriving (Eq, Show, Ord)
|
||||
|
||||
newtype ScopeGraph scope = ScopeGraph { unScopeGraph :: Map scope (Scope scope) }
|
||||
deriving (Eq, Generic, NFData, Ord, Show)
|
||||
deriving (Eq, Ord, Show)
|
||||
|
||||
instance Ord scope => Lower (ScopeGraph scope) where
|
||||
lowerBound = ScopeGraph mempty
|
||||
@ -189,7 +189,7 @@ data Path scope
|
||||
| DPath Declaration Position
|
||||
-- | Construct an edge from a scope to another declaration path.
|
||||
| EPath EdgeLabel scope (Path scope)
|
||||
deriving (Eq, Functor, Generic, NFData, Ord, Show)
|
||||
deriving (Eq, Functor, Ord, Show)
|
||||
|
||||
instance AbstractHole (Path scope) where
|
||||
hole = Hole
|
||||
@ -399,13 +399,13 @@ associatedScope Declaration{..} g@(ScopeGraph graph) = go (Map.keys graph)
|
||||
lookupAssociatedScope scope = ((lookupDeclaration unDeclaration scope g >>= infoAssociatedScope . fst) <|>)
|
||||
|
||||
newtype Reference = Reference { unReference :: Name }
|
||||
deriving (Eq, Ord, Show, Generic, NFData)
|
||||
deriving (Eq, Ord, Show)
|
||||
|
||||
instance Lower Reference where
|
||||
lowerBound = Reference $ name ""
|
||||
|
||||
newtype Declaration = Declaration { unDeclaration :: Name }
|
||||
deriving (Eq, Ord, Show, Generic, NFData)
|
||||
deriving (Eq, Ord, Show)
|
||||
|
||||
instance Lower Declaration where
|
||||
lowerBound = Declaration $ name ""
|
||||
@ -416,4 +416,4 @@ formatDeclaration = formatName . unDeclaration
|
||||
-- | 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 | Export | Superclass
|
||||
deriving (Bounded, Enum, Eq, Ord, Show, Generic, NFData)
|
||||
deriving (Bounded, Enum, Eq, Ord, Show)
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE DeriveAnyClass, GADTs, LambdaCase, RankNTypes, TypeOperators, UndecidableInstances, ScopedTypeVariables #-}
|
||||
{-# LANGUAGE GADTs, LambdaCase, RankNTypes, ScopedTypeVariables, TypeOperators, UndecidableInstances #-}
|
||||
module Data.Abstract.Value.Concrete
|
||||
( Value (..)
|
||||
, ValueError (..)
|
||||
@ -44,7 +44,7 @@ data Value term address
|
||||
| Hash [Value term address]
|
||||
| Null
|
||||
| Hole
|
||||
deriving (Eq, Ord, Show, Generic, NFData)
|
||||
deriving (Eq, Ord, Show, Generic)
|
||||
|
||||
|
||||
instance ValueRoots address (Value term address) where
|
||||
@ -382,25 +382,6 @@ data ValueError term address resume where
|
||||
-- Out-of-bounds error
|
||||
BoundsError :: [Value term 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
|
||||
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
|
||||
liftEq _ (CallError a) (CallError b) = a == b
|
||||
|
@ -1,5 +1,3 @@
|
||||
{-# LANGUAGE DerivingStrategies, GeneralizedNewtypeDeriving, RankNTypes, KindSignatures #-}
|
||||
|
||||
-- | -- This technique is due to Oleg Grenrus: <http://oleg.fi/gists/posts/2019-03-21-flag.html>
|
||||
-- The implementation is clean-room due to unclear licensing of the original post.
|
||||
module Data.Flag
|
||||
@ -18,9 +16,8 @@ import Prologue
|
||||
-- This is more verbose than using 'Bool' for everything but prevents classes of errors when
|
||||
-- working with multiple flag values in flight, as the 'toBool' deconstructor provides a witness
|
||||
-- that you really want the given semantic flag value from the flag datum.
|
||||
newtype Flag (t :: *) = Flag Bool
|
||||
deriving stock (Eq, Show)
|
||||
deriving newtype NFData
|
||||
newtype Flag t = Flag Bool
|
||||
deriving (Eq, Show)
|
||||
|
||||
-- | The constructor for a 'Flag'. You specify @t@ with a visible type application.
|
||||
flag :: t -> Bool -> Flag t
|
||||
|
@ -9,7 +9,6 @@ module Data.Functor.Classes.Generic
|
||||
, defaultGShow1Options
|
||||
, genericLiftShowsPrec
|
||||
, genericLiftShowsPrecWithOptions
|
||||
, Generically (..)
|
||||
) where
|
||||
|
||||
import Data.Functor.Classes
|
||||
@ -180,11 +179,3 @@ instance (Show1 f, GShow1 g) => GShow1 (f :.: g) where
|
||||
|
||||
showBraces :: Bool -> ShowS -> ShowS
|
||||
showBraces should rest = if should then showChar '{' . rest . showChar '}' else rest
|
||||
|
||||
-- | Used with the `DerivingVia` extension to provide fast derivations for
|
||||
-- 'Eq1', 'Show1', and 'Ord1'.
|
||||
newtype Generically f a = Generically { unGenerically :: f a }
|
||||
|
||||
instance (Generic1 f, GEq1 (Rep1 f)) => Eq1 (Generically f) where liftEq eq (Generically a1) (Generically a2) = genericLiftEq eq a1 a2
|
||||
instance (Generic1 f, GEq1 (Rep1 f), GOrd1 (Rep1 f)) => Ord1 (Generically f) where liftCompare compare (Generically a1) (Generically a2) = genericLiftCompare compare a1 a2
|
||||
instance (Generic1 f, GShow1 (Rep1 f)) => Show1 (Generically f) where liftShowsPrec d sp sl = genericLiftShowsPrec d sp sl . unGenerically
|
||||
|
@ -29,7 +29,7 @@ import Proto.Semantic_Fields as P
|
||||
|
||||
-- | An algebraic graph with 'Ord', 'Semigroup', and 'Monoid' instances.
|
||||
newtype Graph vertex = Graph { unGraph :: G.Graph vertex }
|
||||
deriving (Alternative, Applicative, Eq, Functor, Monad, Show, Class.Graph, NFData)
|
||||
deriving (Alternative, Applicative, Eq, Functor, Monad, Show, Class.Graph)
|
||||
|
||||
instance Ord t => Class.ToGraph (Graph t) where
|
||||
type ToVertex (Graph t) = t
|
||||
|
@ -40,7 +40,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, NFData)
|
||||
deriving (Eq, Ord, Show, Generic, Hashable)
|
||||
|
||||
packageVertex :: PackageInfo -> ControlFlowVertex
|
||||
packageVertex (PackageInfo name _) = Package (formatName name)
|
||||
|
@ -10,10 +10,10 @@ import qualified Data.Text as T
|
||||
import System.FilePath.Posix
|
||||
|
||||
data IsRelative = Unknown | Relative | NonRelative
|
||||
deriving (Bounded, Enum, Eq, Generic, Hashable, Ord, Show, ToJSON, NFData)
|
||||
deriving (Bounded, Enum, Eq, Generic, Hashable, Ord, Show, ToJSON)
|
||||
|
||||
data ImportPath = ImportPath { unPath :: FilePath, pathIsRelative :: IsRelative }
|
||||
deriving (Eq, Generic, Hashable, Ord, Show, ToJSON, NFData)
|
||||
deriving (Eq, Generic, Hashable, Ord, Show, ToJSON)
|
||||
|
||||
-- TODO: fix the duplication present in this and Python
|
||||
importPath :: Text -> ImportPath
|
||||
|
@ -1,5 +1,4 @@
|
||||
{-# LANGUAGE DefaultSignatures, MultiParamTypeClasses, TypeOperators, UndecidableInstances, GADTs #-}
|
||||
{-# OPTIONS_GHC -fno-warn-orphans #-} -- FIXME
|
||||
module Data.JSON.Fields
|
||||
( JSONFields (..)
|
||||
, JSONFields1 (..)
|
||||
|
@ -39,7 +39,7 @@ data Language
|
||||
| TypeScript
|
||||
| PHP
|
||||
| TSX
|
||||
deriving (Eq, Generic, Ord, Read, Show, Bounded, Hashable, ToJSON, Enum, NFData)
|
||||
deriving (Eq, Generic, Ord, Read, Show, Bounded, Hashable, ToJSON, Enum)
|
||||
|
||||
class SLanguage (lang :: Language) where
|
||||
reflect :: proxy lang -> Language
|
||||
|
@ -22,7 +22,7 @@ import Prelude hiding (lookup)
|
||||
import Prologue hiding (Map, empty)
|
||||
|
||||
newtype Map key value = Map { unMap :: Map.Map key value }
|
||||
deriving (Eq, Eq1, Eq2, Foldable, Functor, Ord, Ord1, Ord2, Show, Show1, Show2, ToJSON, Traversable, NFData, Lower)
|
||||
deriving (Eq, Eq1, Eq2, Foldable, Functor, Ord, Ord1, Ord2, Show, Show1, Show2, ToJSON, Traversable, Lower)
|
||||
|
||||
|
||||
singleton :: key -> value -> Map key value
|
||||
|
@ -5,7 +5,6 @@ module Data.Quieterm
|
||||
) where
|
||||
|
||||
import Control.Lens
|
||||
import Control.DeepSeq
|
||||
import Data.Abstract.Declarations (Declarations)
|
||||
import Data.Abstract.FreeVariables (FreeVariables)
|
||||
import Data.Functor.Classes
|
||||
@ -39,12 +38,6 @@ 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
|
||||
|
||||
instance HasSpan ann => HasSpan (Quieterm syntax ann) where
|
||||
span_ = lens (view span_ . unQuieterm) (\(Quieterm i) s -> Quieterm (set span_ s i))
|
||||
{-# INLINE span_ #-}
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE AllowAmbiguousTypes, DeriveAnyClass, DerivingVia, GADTs, TypeOperators, MultiParamTypeClasses, UndecidableInstances, ScopedTypeVariables, KindSignatures, RankNTypes, ConstraintKinds, GeneralizedNewtypeDeriving #-}
|
||||
{-# LANGUAGE AllowAmbiguousTypes, ConstraintKinds, DeriveAnyClass, RankNTypes, ScopedTypeVariables, TypeFamilies, TypeOperators, UndecidableInstances #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists -Wno-redundant-constraints #-} -- For HasCallStack
|
||||
module Data.Syntax where
|
||||
|
||||
@ -115,10 +115,11 @@ instance (Element f all, c f, Generate c all fs) => Generate c all (f ': fs) whe
|
||||
|
||||
-- | An identifier of some other construct, whether a containing declaration (e.g. a class name) or a reference (e.g. a variable).
|
||||
newtype Identifier a = Identifier { name :: Name }
|
||||
deriving newtype (Eq, Ord, Show)
|
||||
deriving stock (Foldable, Functor, Generic1, Traversable)
|
||||
deriving anyclass (Diffable, Hashable1, ToJSONFields1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Identifier
|
||||
deriving (Diffable, Foldable, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Identifier where liftEq = genericLiftEq
|
||||
instance Ord1 Identifier where liftCompare = genericLiftCompare
|
||||
instance Show1 Identifier where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
|
||||
instance Evaluatable Identifier where
|
||||
@ -140,10 +141,11 @@ instance Declarations1 Identifier where
|
||||
|
||||
-- | An accessibility modifier, e.g. private, public, protected, etc.
|
||||
newtype AccessibilityModifier a = AccessibilityModifier { contents :: Text }
|
||||
deriving newtype (Eq, Ord, Show)
|
||||
deriving stock (Foldable, Functor, Generic1, Traversable)
|
||||
deriving anyclass (Declarations1, Diffable, FreeVariables1, Hashable1, ToJSONFields1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically AccessibilityModifier
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 AccessibilityModifier where liftEq = genericLiftEq
|
||||
instance Ord1 AccessibilityModifier where liftCompare = genericLiftCompare
|
||||
instance Show1 AccessibilityModifier where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for AccessibilityModifier
|
||||
instance Evaluatable AccessibilityModifier
|
||||
@ -152,16 +154,22 @@ 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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Empty
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Empty where liftEq = genericLiftEq
|
||||
instance Ord1 Empty where liftCompare = genericLiftCompare
|
||||
instance Show1 Empty where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Empty where
|
||||
eval _ _ _ = unit
|
||||
|
||||
-- | 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, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Error
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Error where liftEq = genericLiftEq
|
||||
instance Ord1 Error where liftCompare = genericLiftCompare
|
||||
instance Show1 Error where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Error
|
||||
|
||||
@ -173,7 +181,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, NFData)
|
||||
deriving (Eq, Show, Generic)
|
||||
|
||||
errorSite :: (String, SrcLoc) -> ErrorSite
|
||||
errorSite = uncurry ErrorSite
|
||||
@ -182,8 +190,7 @@ unErrorSite :: ErrorSite -> (String, SrcLoc)
|
||||
unErrorSite ErrorSite{..} = (errorMessage, errorLocation)
|
||||
|
||||
newtype ErrorStack = ErrorStack { unErrorStack :: [ErrorSite] }
|
||||
deriving stock (Eq, Show, Generic)
|
||||
deriving anyclass (NFData)
|
||||
deriving (Eq, Show, Generic)
|
||||
|
||||
instance ToJSON ErrorStack where
|
||||
toJSON (ErrorStack es) = toJSON (jSite <$> es) where
|
||||
@ -222,8 +229,11 @@ instance (Error :< fs, Apply Foldable fs, Apply Functor fs) => HasErrors (Term (
|
||||
|
||||
|
||||
data Context a = Context { contextTerms :: NonEmpty a, contextSubject :: a }
|
||||
deriving (Eq, Foldable, FreeVariables1, Functor, Generic1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Context
|
||||
deriving (Foldable, FreeVariables1, Functor, Generic1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Context where liftEq = genericLiftEq
|
||||
instance Ord1 Context where liftCompare = genericLiftCompare
|
||||
instance Show1 Context where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Diffable Context where
|
||||
subalgorithmFor blur focus (Context n s) = Context <$> traverse blur n <*> focus s
|
||||
|
@ -10,8 +10,11 @@ import Diffing.Algorithm
|
||||
|
||||
-- | 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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Comment
|
||||
deriving (Diffable, Foldable, Functor, Generic1, Hashable1, Traversable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 Comment where liftEq = genericLiftEq
|
||||
instance Ord1 Comment where liftCompare = genericLiftCompare
|
||||
instance Show1 Comment where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Comment where
|
||||
eval _ _ _ = unit
|
||||
@ -23,8 +26,11 @@ instance Evaluatable Comment where
|
||||
|
||||
-- | HashBang line (e.g. `#!/usr/bin/env node`)
|
||||
newtype HashBang a = HashBang { value :: Text }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically HashBang
|
||||
deriving (Diffable, Foldable, Functor, Generic1, Hashable1, Traversable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 HashBang where liftEq = genericLiftEq
|
||||
instance Ord1 HashBang where liftCompare = genericLiftCompare
|
||||
instance Show1 HashBang where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for HashBang
|
||||
instance Evaluatable HashBang
|
||||
|
@ -17,8 +17,11 @@ import Diffing.Algorithm
|
||||
import Source.Span
|
||||
|
||||
data Function a = Function { functionContext :: ![a], functionName :: !a, functionParameters :: ![a], functionBody :: !a }
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, ToJSONFields1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Function
|
||||
deriving (Foldable, Traversable, Functor, Generic1, Hashable1, ToJSONFields1)
|
||||
|
||||
instance Eq1 Function where liftEq = genericLiftEq
|
||||
instance Ord1 Function where liftCompare = genericLiftCompare
|
||||
instance Show1 Function where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Diffable Function where
|
||||
equivalentBySubterm = Just . functionName
|
||||
@ -72,8 +75,11 @@ data Method a = Method
|
||||
, methodBody :: a
|
||||
, methodAccessControl :: ScopeGraph.AccessControl
|
||||
}
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, ToJSONFields1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Method
|
||||
deriving (Foldable, Traversable, Functor, Generic1, Hashable1, ToJSONFields1)
|
||||
|
||||
instance Eq1 Method where liftEq = genericLiftEq
|
||||
instance Ord1 Method where liftCompare = genericLiftCompare
|
||||
instance Show1 Method where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Diffable Method where
|
||||
equivalentBySubterm = Just . methodName
|
||||
@ -108,16 +114,22 @@ data MethodSignature a = MethodSignature
|
||||
, methodSignatureParameters :: [a]
|
||||
, methodSignatureAccessControl :: ScopeGraph.AccessControl
|
||||
}
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically MethodSignature
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 MethodSignature where liftEq = genericLiftEq
|
||||
instance Ord1 MethodSignature where liftCompare = genericLiftCompare
|
||||
instance Show1 MethodSignature where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for MethodSignature
|
||||
instance Evaluatable MethodSignature
|
||||
|
||||
|
||||
newtype RequiredParameter a = RequiredParameter { requiredParameter :: a }
|
||||
deriving (Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically RequiredParameter
|
||||
deriving (Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 RequiredParameter where liftEq = genericLiftEq
|
||||
instance Ord1 RequiredParameter where liftCompare = genericLiftCompare
|
||||
instance Show1 RequiredParameter where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Declarations1 RequiredParameter where
|
||||
liftDeclaredName declaredName = declaredName . requiredParameter
|
||||
@ -131,8 +143,11 @@ instance Evaluatable RequiredParameter where
|
||||
|
||||
|
||||
newtype OptionalParameter a = OptionalParameter { optionalParameter :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically OptionalParameter
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 OptionalParameter where liftEq = genericLiftEq
|
||||
instance Ord1 OptionalParameter where liftCompare = genericLiftCompare
|
||||
instance Show1 OptionalParameter where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for OptionalParameter
|
||||
instance Evaluatable OptionalParameter
|
||||
@ -143,8 +158,11 @@ 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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically VariableDeclaration
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 VariableDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 VariableDeclaration where liftCompare = genericLiftCompare
|
||||
instance Show1 VariableDeclaration where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable VariableDeclaration where
|
||||
eval _ _ (VariableDeclaration []) = unit
|
||||
@ -163,8 +181,11 @@ 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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically InterfaceDeclaration
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 InterfaceDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 InterfaceDeclaration where liftCompare = genericLiftCompare
|
||||
instance Show1 InterfaceDeclaration where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for InterfaceDeclaration
|
||||
instance Evaluatable InterfaceDeclaration
|
||||
@ -180,8 +201,11 @@ data PublicFieldDefinition a = PublicFieldDefinition
|
||||
, publicFieldValue :: a
|
||||
, publicFieldAccessControl :: ScopeGraph.AccessControl
|
||||
}
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically PublicFieldDefinition
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 PublicFieldDefinition where liftEq = genericLiftEq
|
||||
instance Ord1 PublicFieldDefinition where liftCompare = genericLiftCompare
|
||||
instance Show1 PublicFieldDefinition where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for PublicFieldDefinition
|
||||
instance Evaluatable PublicFieldDefinition where
|
||||
@ -194,15 +218,21 @@ instance Evaluatable PublicFieldDefinition where
|
||||
unit
|
||||
|
||||
data Variable a = Variable { variableName :: !a, variableType :: !a, variableValue :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Variable
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Variable where liftEq = genericLiftEq
|
||||
instance Ord1 Variable where liftCompare = genericLiftCompare
|
||||
instance Show1 Variable where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Variable
|
||||
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, ToJSONFields1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Class
|
||||
deriving (Foldable, Traversable, Functor, Generic1, Hashable1, FreeVariables1, ToJSONFields1)
|
||||
|
||||
instance Eq1 Class where liftEq = genericLiftEq
|
||||
instance Ord1 Class where liftCompare = genericLiftCompare
|
||||
instance Show1 Class where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Declarations a => Declarations (Class a) where
|
||||
declaredName (Class _ name _ _) = declaredName name
|
||||
@ -246,8 +276,11 @@ instance Declarations1 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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Decorator
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Decorator where liftEq = genericLiftEq
|
||||
instance Ord1 Decorator where liftCompare = genericLiftCompare
|
||||
instance Show1 Decorator where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Decorator
|
||||
instance Evaluatable Decorator
|
||||
@ -257,8 +290,11 @@ 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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Datatype
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Datatype where liftEq = genericLiftEq
|
||||
instance Ord1 Datatype where liftCompare = genericLiftCompare
|
||||
instance Show1 Datatype where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Datatype
|
||||
instance Evaluatable Data.Syntax.Declaration.Datatype
|
||||
@ -266,8 +302,11 @@ 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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Constructor
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Constructor where liftEq = genericLiftEq
|
||||
instance Ord1 Constructor where liftCompare = genericLiftCompare
|
||||
instance Show1 Constructor where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Constructor
|
||||
instance Evaluatable Data.Syntax.Declaration.Constructor
|
||||
@ -275,8 +314,11 @@ 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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Comprehension
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Comprehension where liftEq = genericLiftEq
|
||||
instance Ord1 Comprehension where liftCompare = genericLiftCompare
|
||||
instance Show1 Comprehension where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Comprehension
|
||||
instance Evaluatable Comprehension
|
||||
@ -284,8 +326,11 @@ 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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Type
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Type where liftEq = genericLiftEq
|
||||
instance Ord1 Type where liftCompare = genericLiftCompare
|
||||
instance Show1 Type where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Type
|
||||
instance Evaluatable Type
|
||||
@ -293,8 +338,11 @@ 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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically TypeAlias
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 TypeAlias where liftEq = genericLiftEq
|
||||
instance Ord1 TypeAlias where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeAlias where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable TypeAlias where
|
||||
eval _ _ TypeAlias{..} = do
|
||||
|
@ -13,8 +13,11 @@ import Source.Span
|
||||
|
||||
-- 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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically File
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 File where liftEq = genericLiftEq
|
||||
instance Ord1 File where liftCompare = genericLiftCompare
|
||||
instance Show1 File where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable File where
|
||||
eval _ _ File = currentModule >>= string . T.pack . modulePath
|
||||
@ -22,8 +25,11 @@ 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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Line
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Line where liftEq = genericLiftEq
|
||||
instance Ord1 Line where liftCompare = genericLiftCompare
|
||||
instance Show1 Line where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Line where
|
||||
eval _ _ Line = currentSpan >>= integer . fromIntegral . line . start
|
||||
|
@ -18,8 +18,11 @@ import qualified Data.Abstract.ScopeGraph as ScopeGraph
|
||||
|
||||
-- | 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 (Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Call
|
||||
deriving (Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Call where liftEq = genericLiftEq
|
||||
instance Ord1 Call where liftCompare = genericLiftCompare
|
||||
instance Show1 Call where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Declarations1 Call where
|
||||
liftDeclaredName declaredName Call{..} = declaredName callFunction
|
||||
@ -31,40 +34,55 @@ instance Evaluatable Call where
|
||||
call op args
|
||||
|
||||
data LessThan a = LessThan { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically LessThan
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 LessThan where liftEq = genericLiftEq
|
||||
instance Ord1 LessThan where liftCompare = genericLiftCompare
|
||||
instance Show1 LessThan where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable LessThan where
|
||||
eval eval _ t = traverse eval t >>= go where
|
||||
go (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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically LessThanEqual
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 LessThanEqual where liftEq = genericLiftEq
|
||||
instance Ord1 LessThanEqual where liftCompare = genericLiftCompare
|
||||
instance Show1 LessThanEqual where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable LessThanEqual where
|
||||
eval eval _ t = traverse eval t >>= go where
|
||||
go (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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically GreaterThan
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 GreaterThan where liftEq = genericLiftEq
|
||||
instance Ord1 GreaterThan where liftCompare = genericLiftCompare
|
||||
instance Show1 GreaterThan where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable GreaterThan where
|
||||
eval eval _ t = traverse eval t >>= go where
|
||||
go (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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically GreaterThanEqual
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 GreaterThanEqual where liftEq = genericLiftEq
|
||||
instance Ord1 GreaterThanEqual where liftCompare = genericLiftCompare
|
||||
instance Show1 GreaterThanEqual where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable GreaterThanEqual where
|
||||
eval eval _ t = traverse eval t >>= go where
|
||||
go (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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Equal
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Equal where liftEq = genericLiftEq
|
||||
instance Ord1 Equal where liftCompare = genericLiftCompare
|
||||
instance Show1 Equal where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Equal where
|
||||
eval eval _ t = traverse eval t >>= go where
|
||||
@ -73,8 +91,11 @@ instance Evaluatable Equal where
|
||||
go (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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically StrictEqual
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 StrictEqual where liftEq = genericLiftEq
|
||||
instance Ord1 StrictEqual where liftCompare = genericLiftCompare
|
||||
instance Show1 StrictEqual where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable StrictEqual where
|
||||
eval eval _ t = traverse eval t >>= go where
|
||||
@ -83,72 +104,99 @@ instance Evaluatable StrictEqual where
|
||||
go (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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Comparison
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Comparison where liftEq = genericLiftEq
|
||||
instance Ord1 Comparison where liftCompare = genericLiftCompare
|
||||
instance Show1 Comparison where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Comparison where
|
||||
eval eval _ t = traverse eval t >>= go where
|
||||
go (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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Plus
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Plus where liftEq = genericLiftEq
|
||||
instance Ord1 Plus where liftCompare = genericLiftCompare
|
||||
instance Show1 Plus where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Plus where
|
||||
eval eval _ t = traverse eval t >>= go where
|
||||
go (Plus a b) = liftNumeric2 add a b where add = liftReal (+)
|
||||
|
||||
data Minus a = Minus { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Minus
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Minus where liftEq = genericLiftEq
|
||||
instance Ord1 Minus where liftCompare = genericLiftCompare
|
||||
instance Show1 Minus where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Minus where
|
||||
eval eval _ t = traverse eval t >>= go where
|
||||
go (Minus a b) = liftNumeric2 (liftReal (-)) a b
|
||||
|
||||
data Times a = Times { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Times
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Times where liftEq = genericLiftEq
|
||||
instance Ord1 Times where liftCompare = genericLiftCompare
|
||||
instance Show1 Times where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Times where
|
||||
eval eval _ t = traverse eval t >>= go where
|
||||
go (Times a b) = liftNumeric2 (liftReal (*)) a b
|
||||
|
||||
data DividedBy a = DividedBy { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically DividedBy
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 DividedBy where liftEq = genericLiftEq
|
||||
instance Ord1 DividedBy where liftCompare = genericLiftCompare
|
||||
instance Show1 DividedBy where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable DividedBy where
|
||||
eval eval _ t = traverse eval t >>= go where
|
||||
go (DividedBy a b) = liftNumeric2 (liftIntegralFrac div (/)) a b
|
||||
|
||||
data Modulo a = Modulo { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Modulo
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Modulo where liftEq = genericLiftEq
|
||||
instance Ord1 Modulo where liftCompare = genericLiftCompare
|
||||
instance Show1 Modulo where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Modulo where
|
||||
eval eval _ t = traverse eval t >>= go where
|
||||
go (Modulo a b) = liftNumeric2 (liftIntegralFrac mod mod') a b
|
||||
|
||||
data Power a = Power { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Power
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Power where liftEq = genericLiftEq
|
||||
instance Ord1 Power where liftCompare = genericLiftCompare
|
||||
instance Show1 Power where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Power where
|
||||
eval eval _ t = traverse eval t >>= go 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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Negate
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Negate where liftEq = genericLiftEq
|
||||
instance Ord1 Negate where liftCompare = genericLiftCompare
|
||||
instance Show1 Negate where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Negate where
|
||||
eval eval _ t = traverse eval t >>= go 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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically FloorDivision
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 FloorDivision where liftEq = genericLiftEq
|
||||
instance Ord1 FloorDivision where liftCompare = genericLiftCompare
|
||||
instance Show1 FloorDivision where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable FloorDivision where
|
||||
eval eval _ t = traverse eval t >>= go where
|
||||
@ -156,20 +204,29 @@ 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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Matches
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Matches where liftEq = genericLiftEq
|
||||
instance Ord1 Matches where liftCompare = genericLiftCompare
|
||||
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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically NotMatches
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 NotMatches where liftEq = genericLiftEq
|
||||
instance Ord1 NotMatches where liftCompare = genericLiftCompare
|
||||
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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Or
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Or where liftEq = genericLiftEq
|
||||
instance Ord1 Or where liftCompare = genericLiftCompare
|
||||
instance Show1 Or where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Or where
|
||||
eval eval _ (Or a b) = do
|
||||
@ -177,8 +234,11 @@ instance Evaluatable Or where
|
||||
ifthenelse a' (pure a') (eval b)
|
||||
|
||||
data And a = And { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically And
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 And where liftEq = genericLiftEq
|
||||
instance Ord1 And where liftCompare = genericLiftCompare
|
||||
instance Show1 And where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable And where
|
||||
eval eval _ (And a b) = do
|
||||
@ -186,15 +246,21 @@ instance Evaluatable And where
|
||||
ifthenelse a' (eval b) (pure a')
|
||||
|
||||
newtype Not a = Not { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Not
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Not where liftEq = genericLiftEq
|
||||
instance Ord1 Not where liftCompare = genericLiftCompare
|
||||
instance Show1 Not where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Not where
|
||||
eval eval _ (Not a) = eval 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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically XOr
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 XOr where liftEq = genericLiftEq
|
||||
instance Ord1 XOr where liftCompare = genericLiftCompare
|
||||
instance Show1 XOr where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable XOr where
|
||||
-- N.B. we have to use Monad rather than Applicative/Traversable on 'And' and 'Or' so that we don't evaluate both operands
|
||||
@ -202,16 +268,22 @@ 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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Delete
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Delete where liftEq = genericLiftEq
|
||||
instance Ord1 Delete where liftCompare = genericLiftCompare
|
||||
instance Show1 Delete where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Delete where
|
||||
eval _ ref (Delete a) = ref a >>= dealloc >> unit
|
||||
|
||||
-- | 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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically SequenceExpression
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 SequenceExpression where liftEq = genericLiftEq
|
||||
instance Ord1 SequenceExpression where liftCompare = genericLiftCompare
|
||||
instance Show1 SequenceExpression where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable SequenceExpression where
|
||||
eval eval _ (SequenceExpression a b) =
|
||||
@ -219,8 +291,11 @@ 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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Void
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Void where liftEq = genericLiftEq
|
||||
instance Ord1 Void where liftCompare = genericLiftCompare
|
||||
instance Show1 Void where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Void where
|
||||
eval eval _ (Void a) =
|
||||
@ -228,16 +303,22 @@ 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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Typeof
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Typeof where liftEq = genericLiftEq
|
||||
instance Ord1 Typeof where liftCompare = genericLiftCompare
|
||||
instance Show1 Typeof where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Typeof
|
||||
instance Evaluatable Typeof
|
||||
|
||||
-- | Bitwise operators.
|
||||
data BOr a = BOr { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically BOr
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 BOr where liftEq = genericLiftEq
|
||||
instance Ord1 BOr where liftCompare = genericLiftCompare
|
||||
instance Show1 BOr where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable BOr where
|
||||
eval eval _ (BOr a b) = do
|
||||
@ -246,8 +327,11 @@ instance Evaluatable BOr where
|
||||
liftBitwise2 (.|.) a' b'
|
||||
|
||||
data BAnd a = BAnd { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically BAnd
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 BAnd where liftEq = genericLiftEq
|
||||
instance Ord1 BAnd where liftCompare = genericLiftCompare
|
||||
instance Show1 BAnd where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable BAnd where
|
||||
eval eval _ (BAnd a b) = do
|
||||
@ -256,8 +340,11 @@ instance Evaluatable BAnd where
|
||||
liftBitwise2 (.&.) a' b'
|
||||
|
||||
data BXOr a = BXOr { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically BXOr
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 BXOr where liftEq = genericLiftEq
|
||||
instance Ord1 BXOr where liftCompare = genericLiftCompare
|
||||
instance Show1 BXOr where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable BXOr where
|
||||
eval eval _ (BXOr a b) = do
|
||||
@ -266,8 +353,11 @@ instance Evaluatable BXOr where
|
||||
liftBitwise2 xor a' b'
|
||||
|
||||
data LShift a = LShift { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically LShift
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 LShift where liftEq = genericLiftEq
|
||||
instance Ord1 LShift where liftCompare = genericLiftCompare
|
||||
instance Show1 LShift where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable LShift where
|
||||
eval eval _ (LShift a b) = do
|
||||
@ -278,8 +368,11 @@ instance Evaluatable LShift where
|
||||
shiftL' a b = shiftL a (fromIntegral (toInteger b))
|
||||
|
||||
data RShift a = RShift { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically RShift
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 RShift where liftEq = genericLiftEq
|
||||
instance Ord1 RShift where liftCompare = genericLiftCompare
|
||||
instance Show1 RShift where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable RShift where
|
||||
eval eval _ (RShift a b) = do
|
||||
@ -290,8 +383,11 @@ instance Evaluatable RShift where
|
||||
shiftR' a b = shiftR a (fromIntegral (toInteger b))
|
||||
|
||||
data UnsignedRShift a = UnsignedRShift { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically UnsignedRShift
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 UnsignedRShift where liftEq = genericLiftEq
|
||||
instance Ord1 UnsignedRShift where liftCompare = genericLiftCompare
|
||||
instance Show1 UnsignedRShift where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable UnsignedRShift where
|
||||
eval eval _ (UnsignedRShift a b) = do
|
||||
@ -300,8 +396,11 @@ instance Evaluatable UnsignedRShift where
|
||||
unsignedRShift a' b'
|
||||
|
||||
newtype Complement a = Complement { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Complement
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Complement where liftEq = genericLiftEq
|
||||
instance Ord1 Complement where liftCompare = genericLiftCompare
|
||||
instance Show1 Complement where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Complement where
|
||||
eval eval _ (Complement a) = do
|
||||
@ -310,8 +409,11 @@ instance Evaluatable Complement where
|
||||
|
||||
-- | Member Access (e.g. a.b)
|
||||
data MemberAccess a = MemberAccess { lhs :: a, rhs :: a }
|
||||
deriving (Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically MemberAccess
|
||||
deriving (Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 MemberAccess where liftEq = genericLiftEq
|
||||
instance Ord1 MemberAccess where liftCompare = genericLiftCompare
|
||||
instance Show1 MemberAccess where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Declarations1 MemberAccess where
|
||||
liftDeclaredName declaredName MemberAccess{..} = declaredName rhs
|
||||
@ -358,8 +460,11 @@ 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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Subscript
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Subscript where liftEq = genericLiftEq
|
||||
instance Ord1 Subscript where liftCompare = genericLiftCompare
|
||||
instance Show1 Subscript where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Finish Eval instance for Subscript
|
||||
-- TODO return a special LvalSubscript instance here
|
||||
@ -368,23 +473,32 @@ instance Evaluatable Subscript where
|
||||
eval _ _ (Subscript _ _) = 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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Member
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Member where liftEq = genericLiftEq
|
||||
instance Ord1 Member where liftCompare = genericLiftCompare
|
||||
instance Show1 Member where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Enumeration
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Enumeration where liftEq = genericLiftEq
|
||||
instance Ord1 Enumeration where liftCompare = genericLiftCompare
|
||||
instance Show1 Enumeration where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Enumeration
|
||||
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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically InstanceOf
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 InstanceOf where liftEq = genericLiftEq
|
||||
instance Ord1 InstanceOf where liftCompare = genericLiftCompare
|
||||
instance Show1 InstanceOf where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for InstanceOf
|
||||
instance Evaluatable InstanceOf
|
||||
@ -392,8 +506,11 @@ instance Evaluatable InstanceOf
|
||||
|
||||
-- | ScopeResolution (e.g. import a.b in Python or a::b in C++)
|
||||
newtype ScopeResolution a = ScopeResolution { scopes :: NonEmpty a }
|
||||
deriving (Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ScopeResolution
|
||||
deriving (Diffable, Foldable, FreeVariables1, Functor, Generic1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ScopeResolution where liftEq = genericLiftEq
|
||||
instance Ord1 ScopeResolution where liftCompare = genericLiftCompare
|
||||
instance Show1 ScopeResolution where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Hashable1 ScopeResolution where liftHashWithSalt = foldl
|
||||
|
||||
@ -404,8 +521,11 @@ instance Declarations1 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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically NonNullExpression
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 NonNullExpression where liftEq = genericLiftEq
|
||||
instance Ord1 NonNullExpression where liftCompare = genericLiftCompare
|
||||
instance Show1 NonNullExpression where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for NonNullExpression
|
||||
instance Evaluatable NonNullExpression
|
||||
@ -413,8 +533,11 @@ 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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Await
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Await where liftEq = genericLiftEq
|
||||
instance Ord1 Await where liftCompare = genericLiftCompare
|
||||
instance Show1 Await where liftShowsPrec = genericLiftShowsPrec
|
||||
-- TODO: Improve this to model asynchrony or capture some data suggesting async calls are not a problem.
|
||||
-- We are currently dealing with an asynchronous construct synchronously.
|
||||
instance Evaluatable Await where
|
||||
@ -422,8 +545,11 @@ instance Evaluatable Await where
|
||||
|
||||
-- | An object constructor call in Javascript, Java, etc.
|
||||
data New a = New { newSubject :: a , newTypeParameters :: a, newArguments :: [a] }
|
||||
deriving (Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically New
|
||||
deriving (Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 New where liftEq = genericLiftEq
|
||||
instance Ord1 New where liftCompare = genericLiftCompare
|
||||
instance Show1 New where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Declarations1 New where
|
||||
liftDeclaredName declaredName New{..} = declaredName newSubject
|
||||
@ -465,20 +591,29 @@ 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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Cast
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Cast where liftEq = genericLiftEq
|
||||
instance Ord1 Cast where liftCompare = genericLiftCompare
|
||||
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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Super
|
||||
deriving (Diffable, Foldable, Functor, Generic1, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1)
|
||||
|
||||
instance Eq1 Super where liftEq = genericLiftEq
|
||||
instance Ord1 Super where liftCompare = genericLiftCompare
|
||||
instance Show1 Super where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Super
|
||||
|
||||
data This a = This
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically This
|
||||
deriving (Diffable, Foldable, Functor, Generic1, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1)
|
||||
|
||||
instance Eq1 This where liftEq = genericLiftEq
|
||||
instance Ord1 This where liftCompare = genericLiftCompare
|
||||
instance Show1 This where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable This where
|
||||
eval _ _ This = do
|
||||
|
@ -16,9 +16,12 @@ import Text.Read (readMaybe)
|
||||
-- Boolean
|
||||
|
||||
newtype Boolean a = Boolean { booleanContent :: Bool }
|
||||
deriving stock (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1)
|
||||
deriving anyclass (Hashable1, Diffable, FreeVariables1, Declarations1, ToJSONFields1, NFData1)
|
||||
deriving (Eq1, Ord1, Show1) via Generically Boolean
|
||||
deriving stock (Foldable, Traversable, Functor, Generic1)
|
||||
deriving anyclass (Hashable1, Diffable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 Boolean where liftEq = genericLiftEq
|
||||
instance Ord1 Boolean where liftCompare = genericLiftCompare
|
||||
instance Show1 Boolean where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
true :: Boolean a
|
||||
true = Boolean True
|
||||
@ -31,8 +34,11 @@ instance Evaluatable Boolean where
|
||||
|
||||
-- | A literal integer of unspecified width. No particular base is implied.
|
||||
newtype Integer a = Integer { integerContent :: Text }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Ord1, Show1) via Generically Data.Syntax.Literal.Integer
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Data.Syntax.Literal.Integer where liftEq = genericLiftEq
|
||||
instance Ord1 Data.Syntax.Literal.Integer where liftCompare = genericLiftCompare
|
||||
instance Show1 Data.Syntax.Literal.Integer where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Data.Syntax.Literal.Integer where
|
||||
-- TODO: We should use something more robust than shelling out to readMaybe.
|
||||
@ -42,8 +48,11 @@ instance Evaluatable Data.Syntax.Literal.Integer where
|
||||
-- | A literal float of unspecified width.
|
||||
|
||||
newtype Float a = Float { floatContent :: Text }
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, FreeVariables1, Declarations1, ToJSONFields1, NFData1)
|
||||
deriving (Eq1, Ord1, Show1) via Generically Data.Syntax.Literal.Float
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Data.Syntax.Literal.Float where liftEq = genericLiftEq
|
||||
instance Ord1 Data.Syntax.Literal.Float where liftCompare = genericLiftCompare
|
||||
instance Show1 Data.Syntax.Literal.Float where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
|
||||
instance Evaluatable Data.Syntax.Literal.Float where
|
||||
@ -52,8 +61,11 @@ instance Evaluatable Data.Syntax.Literal.Float where
|
||||
|
||||
-- Rational literals e.g. `2/3r`
|
||||
newtype Rational a = Rational { value :: Text }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Ord1, Show1) via Generically Data.Syntax.Literal.Rational
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Data.Syntax.Literal.Rational where liftEq = genericLiftEq
|
||||
instance Ord1 Data.Syntax.Literal.Rational where liftCompare = genericLiftCompare
|
||||
instance Show1 Data.Syntax.Literal.Rational where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Data.Syntax.Literal.Rational where
|
||||
eval _ _ (Rational r) =
|
||||
@ -64,8 +76,11 @@ 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, NFData1)
|
||||
deriving (Eq1, Ord1, Show1) via Generically Complex
|
||||
deriving (Diffable, Foldable, Functor, Generic1, Hashable1, Traversable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 Complex where liftEq = genericLiftEq
|
||||
instance Ord1 Complex where liftCompare = genericLiftCompare
|
||||
instance Show1 Complex where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Complex
|
||||
instance Evaluatable Complex
|
||||
@ -73,8 +88,11 @@ instance Evaluatable Complex
|
||||
-- Strings, symbols
|
||||
|
||||
newtype String a = String { stringElements :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Ord1, Show1) via Generically Data.Syntax.Literal.String
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Data.Syntax.Literal.String where liftEq = genericLiftEq
|
||||
instance Ord1 Data.Syntax.Literal.String where liftCompare = genericLiftCompare
|
||||
instance Show1 Data.Syntax.Literal.String where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Should string literal bodies include escapes too?
|
||||
|
||||
@ -82,23 +100,32 @@ newtype String a = String { stringElements :: [a] }
|
||||
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, NFData1)
|
||||
deriving (Eq1, Ord1, Show1) via Generically Character
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Character where liftEq = genericLiftEq
|
||||
instance Ord1 Character where liftCompare = genericLiftCompare
|
||||
instance Show1 Character where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
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, NFData1)
|
||||
deriving (Eq1, Ord1, Show1) via Generically InterpolationElement
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 InterpolationElement where liftEq = genericLiftEq
|
||||
instance Ord1 InterpolationElement where liftCompare = genericLiftCompare
|
||||
instance Show1 InterpolationElement where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for InterpolationElement
|
||||
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, NFData1)
|
||||
deriving (Eq1, Ord1, Show1) via Generically TextElement
|
||||
deriving (Diffable, Foldable, Functor, Generic1, Hashable1, Traversable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 TextElement where liftEq = genericLiftEq
|
||||
instance Ord1 TextElement where liftCompare = genericLiftCompare
|
||||
instance Show1 TextElement where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable TextElement where
|
||||
eval _ _ (TextElement x) = string x
|
||||
@ -113,35 +140,50 @@ quoted t = TextElement ("\"" <> t <> "\"")
|
||||
|
||||
-- | 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, NFData1)
|
||||
deriving (Eq1, Ord1, Show1) via Generically EscapeSequence
|
||||
deriving (Diffable, Foldable, Functor, Generic1, Hashable1, Traversable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 EscapeSequence where liftEq = genericLiftEq
|
||||
instance Ord1 EscapeSequence where liftCompare = genericLiftCompare
|
||||
instance Show1 EscapeSequence where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for EscapeSequence
|
||||
instance Evaluatable EscapeSequence
|
||||
|
||||
data Null a = Null
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, FreeVariables1, Declarations1, ToJSONFields1, NFData1)
|
||||
deriving (Eq1, Ord1, Show1) via Generically Null
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Null where liftEq = genericLiftEq
|
||||
instance Ord1 Null where liftCompare = genericLiftCompare
|
||||
instance Show1 Null where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Null where eval _ _ _ = pure null
|
||||
|
||||
newtype Symbol a = Symbol { symbolElements :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Ord1, Show1) via Generically Symbol
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Symbol where liftEq = genericLiftEq
|
||||
instance Ord1 Symbol where liftCompare = genericLiftCompare
|
||||
instance Show1 Symbol where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Symbol
|
||||
instance Evaluatable Symbol
|
||||
|
||||
newtype SymbolElement a = SymbolElement { symbolContent :: Text }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Ord1, Show1) via Generically SymbolElement
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 SymbolElement where liftEq = genericLiftEq
|
||||
instance Ord1 SymbolElement where liftCompare = genericLiftCompare
|
||||
instance Show1 SymbolElement where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable SymbolElement where
|
||||
eval _ _ (SymbolElement s) = string s
|
||||
|
||||
newtype Regex a = Regex { regexContent :: Text }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, NFData1)
|
||||
deriving (Eq1, Ord1, Show1) via Generically Regex
|
||||
deriving (Diffable, Foldable, Functor, Generic1, Hashable1, Traversable, FreeVariables1, Declarations1, ToJSONFields1)
|
||||
|
||||
instance Eq1 Regex where liftEq = genericLiftEq
|
||||
instance Ord1 Regex where liftCompare = genericLiftCompare
|
||||
instance Show1 Regex where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Heredoc-style string literals?
|
||||
|
||||
@ -152,15 +194,21 @@ instance Evaluatable Regex where
|
||||
-- Collections
|
||||
|
||||
newtype Array a = Array { arrayElements :: [a] }
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, FreeVariables1, Declarations1, ToJSONFields1, NFData1)
|
||||
deriving (Eq1, Ord1, Show1) via Generically Array
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Array where liftEq = genericLiftEq
|
||||
instance Ord1 Array where liftCompare = genericLiftCompare
|
||||
instance Show1 Array where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Array where
|
||||
eval eval _ Array{..} = array =<< traverse eval arrayElements
|
||||
|
||||
newtype Hash a = Hash { hashElements :: [a] }
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, FreeVariables1, Declarations1, ToJSONFields1, NFData1)
|
||||
deriving (Eq1, Ord1, Show1) via Generically Hash
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Hash where liftEq = genericLiftEq
|
||||
instance Ord1 Hash where liftCompare = genericLiftCompare
|
||||
instance Show1 Hash where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Hash where
|
||||
eval eval _ t = do
|
||||
@ -168,8 +216,11 @@ instance Evaluatable Hash where
|
||||
Eval.hash elements
|
||||
|
||||
data KeyValue a = KeyValue { key :: !a, value :: !a }
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, FreeVariables1, Declarations1, ToJSONFields1, NFData1)
|
||||
deriving (Eq1, Ord1, Show1) via Generically KeyValue
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 KeyValue where liftEq = genericLiftEq
|
||||
instance Ord1 KeyValue where liftCompare = genericLiftCompare
|
||||
instance Show1 KeyValue where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable KeyValue where
|
||||
eval eval _ KeyValue{..} = do
|
||||
@ -178,15 +229,21 @@ instance Evaluatable KeyValue where
|
||||
kvPair k v
|
||||
|
||||
newtype Tuple a = Tuple { tupleContents :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Ord1, Show1) via Generically Tuple
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Tuple where liftEq = genericLiftEq
|
||||
instance Ord1 Tuple where liftCompare = genericLiftCompare
|
||||
instance Show1 Tuple where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Tuple where
|
||||
eval eval _ (Tuple cs) = tuple =<< traverse eval cs
|
||||
|
||||
newtype Set a = Set { setElements :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Ord1, Show1) via Generically Set
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Set where liftEq = genericLiftEq
|
||||
instance Ord1 Set where liftCompare = genericLiftCompare
|
||||
instance Show1 Set where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Set
|
||||
instance Evaluatable Set
|
||||
@ -196,8 +253,11 @@ 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, NFData1)
|
||||
deriving (Eq1, Ord1, Show1) via Generically Pointer
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Pointer where liftEq = genericLiftEq
|
||||
instance Ord1 Pointer where liftCompare = genericLiftCompare
|
||||
instance Show1 Pointer where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Pointer
|
||||
instance Evaluatable Pointer
|
||||
@ -205,8 +265,11 @@ 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, NFData1)
|
||||
deriving (Eq1, Ord1, Show1) via Generically Reference
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Reference where liftEq = genericLiftEq
|
||||
instance Ord1 Reference where liftCompare = genericLiftCompare
|
||||
instance Show1 Reference where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Reference
|
||||
instance Evaluatable Reference
|
||||
|
@ -21,8 +21,11 @@ import Diffing.Algorithm
|
||||
-- 3. Only the last statement’s return value is returned.
|
||||
-- TODO: Separate top-level statement nodes into non-lexical Statement and lexical StatementBlock nodes
|
||||
newtype Statements a = Statements { statements :: [a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Statements
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Statements where liftEq = genericLiftEq
|
||||
instance Ord1 Statements where liftCompare = genericLiftCompare
|
||||
instance Show1 Statements where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSON1 Statements
|
||||
|
||||
@ -31,8 +34,11 @@ instance Evaluatable Statements where
|
||||
maybe unit (runApp . foldMap1 (App . eval)) (nonEmpty xs)
|
||||
|
||||
newtype StatementBlock a = StatementBlock { statements :: [a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically StatementBlock
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 StatementBlock where liftEq = genericLiftEq
|
||||
instance Ord1 StatementBlock where liftCompare = genericLiftCompare
|
||||
instance Show1 StatementBlock where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance ToJSON1 StatementBlock
|
||||
|
||||
@ -42,8 +48,11 @@ instance Evaluatable StatementBlock 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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically If
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 If where liftEq = genericLiftEq
|
||||
instance Ord1 If where liftCompare = genericLiftCompare
|
||||
instance Show1 If where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable If where
|
||||
eval eval _ (If cond if' else') = do
|
||||
@ -53,8 +62,11 @@ instance Evaluatable If where
|
||||
|
||||
-- | Else statement. The else condition is any term, that upon successful completion, continues evaluation to the elseBody, e.g. `for ... else` in Python.
|
||||
data Else a = Else { elseCondition :: !a, elseBody :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Else
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Else where liftEq = genericLiftEq
|
||||
instance Ord1 Else where liftCompare = genericLiftCompare
|
||||
instance Show1 Else where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Else
|
||||
instance Evaluatable Else
|
||||
@ -64,16 +76,22 @@ 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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Goto
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Goto where liftEq = genericLiftEq
|
||||
instance Ord1 Goto where liftCompare = genericLiftCompare
|
||||
instance Show1 Goto where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Goto
|
||||
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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Match
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Match where liftEq = genericLiftEq
|
||||
instance Ord1 Match where liftCompare = genericLiftCompare
|
||||
instance Show1 Match where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Match
|
||||
instance Evaluatable Match
|
||||
@ -81,16 +99,22 @@ 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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Pattern
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Pattern where liftEq = genericLiftEq
|
||||
instance Ord1 Pattern where liftCompare = genericLiftCompare
|
||||
instance Show1 Pattern where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Pattern
|
||||
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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Let
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Let where liftEq = genericLiftEq
|
||||
instance Ord1 Let where liftCompare = genericLiftCompare
|
||||
instance Show1 Let where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Let where
|
||||
eval eval _ Let{..} = do
|
||||
@ -112,8 +136,11 @@ 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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Assignment
|
||||
deriving (Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Assignment where liftEq = genericLiftEq
|
||||
instance Ord1 Assignment where liftCompare = genericLiftCompare
|
||||
instance Show1 Assignment where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Declarations1 Assignment where
|
||||
liftDeclaredName declaredName Assignment{..} = declaredName assignmentTarget
|
||||
@ -139,8 +166,11 @@ 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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically PostIncrement
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 PostIncrement where liftEq = genericLiftEq
|
||||
instance Ord1 PostIncrement where liftCompare = genericLiftCompare
|
||||
instance Show1 PostIncrement where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for PostIncrement
|
||||
instance Evaluatable PostIncrement
|
||||
@ -148,16 +178,22 @@ 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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically PostDecrement
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 PostDecrement where liftEq = genericLiftEq
|
||||
instance Ord1 PostDecrement where liftCompare = genericLiftCompare
|
||||
instance Show1 PostDecrement where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for PostDecrement
|
||||
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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically PreIncrement
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 PreIncrement where liftEq = genericLiftEq
|
||||
instance Ord1 PreIncrement where liftCompare = genericLiftCompare
|
||||
instance Show1 PreIncrement where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for PreIncrement
|
||||
instance Evaluatable PreIncrement
|
||||
@ -165,8 +201,11 @@ 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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically PreDecrement
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 PreDecrement where liftEq = genericLiftEq
|
||||
instance Ord1 PreDecrement where liftCompare = genericLiftCompare
|
||||
instance Show1 PreDecrement where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for PreDecrement
|
||||
instance Evaluatable PreDecrement
|
||||
@ -175,44 +214,62 @@ instance Evaluatable PreDecrement
|
||||
-- Returns
|
||||
|
||||
newtype Return a = Return { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Return
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Return where liftEq = genericLiftEq
|
||||
instance Ord1 Return where liftCompare = genericLiftCompare
|
||||
instance Show1 Return where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Return where
|
||||
eval eval _ (Return x) = eval x >>= earlyReturn
|
||||
|
||||
newtype Yield a = Yield { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Yield
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Yield where liftEq = genericLiftEq
|
||||
instance Ord1 Yield where liftCompare = genericLiftCompare
|
||||
instance Show1 Yield where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Yield
|
||||
instance Evaluatable Yield
|
||||
|
||||
|
||||
newtype Break a = Break { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Break
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Break where liftEq = genericLiftEq
|
||||
instance Ord1 Break where liftCompare = genericLiftCompare
|
||||
instance Show1 Break where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Break where
|
||||
eval eval _ (Break x) = eval x >>= throwBreak
|
||||
|
||||
newtype Continue a = Continue { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Continue
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Continue where liftEq = genericLiftEq
|
||||
instance Ord1 Continue where liftCompare = genericLiftCompare
|
||||
instance Show1 Continue where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Continue where
|
||||
eval eval _ (Continue x) = eval x >>= throwContinue
|
||||
|
||||
newtype Retry a = Retry { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Retry
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Retry where liftEq = genericLiftEq
|
||||
instance Ord1 Retry where liftCompare = genericLiftCompare
|
||||
instance Show1 Retry where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Retry
|
||||
instance Evaluatable Retry
|
||||
|
||||
newtype NoOp a = NoOp { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically NoOp
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 NoOp where liftEq = genericLiftEq
|
||||
instance Ord1 NoOp where liftCompare = genericLiftCompare
|
||||
instance Show1 NoOp where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable NoOp where
|
||||
eval _ _ _ = unit
|
||||
@ -220,29 +277,41 @@ 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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically For
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 For where liftEq = genericLiftEq
|
||||
instance Ord1 For where liftCompare = genericLiftCompare
|
||||
instance Show1 For where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable For where
|
||||
eval eval _ (fmap eval -> For before cond step body) = forLoop before cond step body
|
||||
|
||||
data ForEach a = ForEach { forEachBinding :: !a, forEachSubject :: !a, forEachBody :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ForEach
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ForEach where liftEq = genericLiftEq
|
||||
instance Ord1 ForEach where liftCompare = genericLiftCompare
|
||||
instance Show1 ForEach where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for ForEach
|
||||
instance Evaluatable ForEach
|
||||
|
||||
data While a = While { whileCondition :: !a, whileBody :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically While
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 While where liftEq = genericLiftEq
|
||||
instance Ord1 While where liftCompare = genericLiftCompare
|
||||
instance Show1 While where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable While where
|
||||
eval eval _ While{..} = while (eval whileCondition) (eval whileBody)
|
||||
|
||||
data DoWhile a = DoWhile { doWhileCondition :: !a, doWhileBody :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically DoWhile
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 DoWhile where liftEq = genericLiftEq
|
||||
instance Ord1 DoWhile where liftCompare = genericLiftCompare
|
||||
instance Show1 DoWhile where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable DoWhile where
|
||||
eval eval _ DoWhile{..} = doWhile (eval doWhileBody) (eval doWhileCondition)
|
||||
@ -250,30 +319,42 @@ 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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Throw
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Throw where liftEq = genericLiftEq
|
||||
instance Ord1 Throw where liftCompare = genericLiftCompare
|
||||
instance Show1 Throw where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Throw
|
||||
instance Evaluatable Throw
|
||||
|
||||
|
||||
data Try a = Try { tryBody :: !a, tryCatch :: ![a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Try
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Try where liftEq = genericLiftEq
|
||||
instance Ord1 Try where liftCompare = genericLiftCompare
|
||||
instance Show1 Try where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Try
|
||||
instance Evaluatable Try
|
||||
|
||||
data Catch a = Catch { catchException :: !a, catchBody :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Catch
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Catch where liftEq = genericLiftEq
|
||||
instance Ord1 Catch where liftCompare = genericLiftCompare
|
||||
instance Show1 Catch where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Catch
|
||||
instance Evaluatable Catch
|
||||
|
||||
newtype Finally a = Finally { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Finally
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Finally where liftEq = genericLiftEq
|
||||
instance Ord1 Finally where liftCompare = genericLiftCompare
|
||||
instance Show1 Finally where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Finally
|
||||
instance Evaluatable Finally
|
||||
@ -282,8 +363,11 @@ 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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ScopeEntry
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ScopeEntry where liftEq = genericLiftEq
|
||||
instance Ord1 ScopeEntry where liftCompare = genericLiftCompare
|
||||
instance Show1 ScopeEntry where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for ScopeEntry
|
||||
instance Evaluatable ScopeEntry
|
||||
@ -291,8 +375,11 @@ 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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ScopeExit
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ScopeExit where liftEq = genericLiftEq
|
||||
instance Ord1 ScopeExit where liftCompare = genericLiftCompare
|
||||
instance Show1 ScopeExit where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for ScopeExit
|
||||
instance Evaluatable ScopeExit
|
||||
|
@ -9,8 +9,11 @@ import Prelude hiding (Bool, Float, Int, Double)
|
||||
import Prologue hiding (Map)
|
||||
|
||||
data Array a = Array { arraySize :: Maybe a, arrayElementType :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Array
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Array where liftEq = genericLiftEq
|
||||
instance Ord1 Array where liftCompare = genericLiftCompare
|
||||
instance Show1 Array where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Array
|
||||
instance Evaluatable Array
|
||||
@ -18,8 +21,11 @@ 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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Annotation
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Annotation where liftEq = genericLiftEq
|
||||
instance Ord1 Annotation where liftCompare = genericLiftCompare
|
||||
instance Show1 Annotation where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Specialize Evaluatable for Type to unify the inferred type of the subject with the specified type
|
||||
instance Evaluatable Annotation where
|
||||
@ -27,103 +33,145 @@ instance Evaluatable Annotation where
|
||||
|
||||
|
||||
data Function a = Function { functionParameters :: [a], functionReturn :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Function
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Function where liftEq = genericLiftEq
|
||||
instance Ord1 Function where liftCompare = genericLiftCompare
|
||||
instance Show1 Function where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Function
|
||||
instance Evaluatable Function
|
||||
|
||||
|
||||
newtype Interface a = Interface { values :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Interface
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Interface where liftEq = genericLiftEq
|
||||
instance Ord1 Interface where liftCompare = genericLiftCompare
|
||||
instance Show1 Interface where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Interface
|
||||
instance Evaluatable Interface
|
||||
|
||||
data Map a = Map { mapKeyType :: a, mapElementType :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Map
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Map where liftEq = genericLiftEq
|
||||
instance Ord1 Map where liftCompare = genericLiftCompare
|
||||
instance Show1 Map where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Map
|
||||
instance Evaluatable Map
|
||||
|
||||
newtype Parenthesized a = Parenthesized { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Parenthesized
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Parenthesized where liftEq = genericLiftEq
|
||||
instance Ord1 Parenthesized where liftCompare = genericLiftCompare
|
||||
instance Show1 Parenthesized where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Parenthesized
|
||||
instance Evaluatable Parenthesized
|
||||
|
||||
newtype Pointer a = Pointer { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Pointer
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Pointer where liftEq = genericLiftEq
|
||||
instance Ord1 Pointer where liftCompare = genericLiftCompare
|
||||
instance Show1 Pointer where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Pointer
|
||||
instance Evaluatable Pointer
|
||||
|
||||
newtype Product a = Product { values :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Product
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Product where liftEq = genericLiftEq
|
||||
instance Ord1 Product where liftCompare = genericLiftCompare
|
||||
instance Show1 Product where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Product
|
||||
instance Evaluatable Product
|
||||
|
||||
|
||||
data Readonly a = Readonly
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Readonly
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Readonly where liftEq = genericLiftEq
|
||||
instance Ord1 Readonly where liftCompare = genericLiftCompare
|
||||
instance Show1 Readonly where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Readonly
|
||||
instance Evaluatable Readonly
|
||||
|
||||
newtype Slice a = Slice { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Slice
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Slice where liftEq = genericLiftEq
|
||||
instance Ord1 Slice where liftCompare = genericLiftCompare
|
||||
instance Show1 Slice where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Slice
|
||||
instance Evaluatable Slice
|
||||
|
||||
newtype TypeParameters a = TypeParameters { terms :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically TypeParameters
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 TypeParameters where liftEq = genericLiftEq
|
||||
instance Ord1 TypeParameters where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeParameters where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for TypeParameters
|
||||
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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Void
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Void where liftEq = genericLiftEq
|
||||
instance Ord1 Void where liftCompare = genericLiftCompare
|
||||
instance Show1 Void where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Void
|
||||
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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Int
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Int where liftEq = genericLiftEq
|
||||
instance Ord1 Int where liftCompare = genericLiftCompare
|
||||
instance Show1 Int where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Int
|
||||
instance Evaluatable Int
|
||||
|
||||
data Float a = Float
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Float
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Float where liftEq = genericLiftEq
|
||||
instance Ord1 Float where liftCompare = genericLiftCompare
|
||||
instance Show1 Float where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Float
|
||||
instance Evaluatable Float
|
||||
|
||||
data Double a = Double
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Double
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Double where liftEq = genericLiftEq
|
||||
instance Ord1 Double where liftCompare = genericLiftCompare
|
||||
instance Show1 Double where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Double
|
||||
instance Evaluatable Double
|
||||
|
||||
data Bool a = Bool
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Bool
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Bool where liftEq = genericLiftEq
|
||||
instance Ord1 Bool where liftCompare = genericLiftCompare
|
||||
instance Show1 Bool where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Float
|
||||
instance Evaluatable Bool
|
||||
|
@ -99,12 +99,6 @@ 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)
|
||||
@ -135,9 +129,6 @@ 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
|
||||
|
@ -51,8 +51,11 @@ 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, NFData1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Import
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Import where liftEq = genericLiftEq
|
||||
instance Ord1 Import where liftCompare = genericLiftCompare
|
||||
instance Show1 Import where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Import where
|
||||
eval _ _ (Language.Go.Syntax.Import importPath _) = do
|
||||
@ -69,8 +72,11 @@ 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, NFData1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically QualifiedImport
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 QualifiedImport where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedImport where liftCompare = genericLiftCompare
|
||||
instance Show1 QualifiedImport where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable QualifiedImport where
|
||||
eval _ _ (QualifiedImport importPath aliasTerm) = do
|
||||
@ -99,8 +105,11 @@ 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, NFData1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically SideEffectImport
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 SideEffectImport where liftEq = genericLiftEq
|
||||
instance Ord1 SideEffectImport where liftCompare = genericLiftCompare
|
||||
instance Show1 SideEffectImport where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Revisit this and confirm if this is correct.
|
||||
instance Evaluatable SideEffectImport where
|
||||
@ -112,143 +121,197 @@ 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, NFData1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Composite
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Composite where liftEq = genericLiftEq
|
||||
instance Ord1 Composite where liftCompare = genericLiftCompare
|
||||
instance Show1 Composite where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Composite
|
||||
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, NFData1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically DefaultPattern
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 DefaultPattern where liftEq = genericLiftEq
|
||||
instance Ord1 DefaultPattern where liftCompare = genericLiftCompare
|
||||
instance Show1 DefaultPattern where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for DefaultPattern
|
||||
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, NFData1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Defer
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Defer where liftEq = genericLiftEq
|
||||
instance Ord1 Defer where liftCompare = genericLiftCompare
|
||||
instance Show1 Defer where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Defer
|
||||
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, NFData1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Go
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Go where liftEq = genericLiftEq
|
||||
instance Ord1 Go where liftCompare = genericLiftCompare
|
||||
instance Show1 Go where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Go
|
||||
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, NFData1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Label
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Label where liftEq = genericLiftEq
|
||||
instance Ord1 Label where liftCompare = genericLiftCompare
|
||||
instance Show1 Label where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Label
|
||||
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, NFData1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Rune
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Rune where liftEq = genericLiftEq
|
||||
instance Ord1 Rune where liftCompare = genericLiftCompare
|
||||
instance Show1 Rune where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Rune
|
||||
instance Evaluatable Rune
|
||||
|
||||
-- | 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, NFData1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Select
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Select where liftEq = genericLiftEq
|
||||
instance Ord1 Select where liftCompare = genericLiftCompare
|
||||
instance Show1 Select where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Select
|
||||
instance Evaluatable Select
|
||||
|
||||
-- | 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, NFData1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Send
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Send where liftEq = genericLiftEq
|
||||
instance Ord1 Send where liftCompare = genericLiftCompare
|
||||
instance Show1 Send where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Send
|
||||
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, NFData1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Slice
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Slice where liftEq = genericLiftEq
|
||||
instance Ord1 Slice where liftCompare = genericLiftCompare
|
||||
instance Show1 Slice where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Slice
|
||||
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, NFData1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically TypeSwitch
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 TypeSwitch where liftEq = genericLiftEq
|
||||
instance Ord1 TypeSwitch where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeSwitch where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for TypeSwitch
|
||||
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, NFData1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically TypeSwitchGuard
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 TypeSwitchGuard where liftEq = genericLiftEq
|
||||
instance Ord1 TypeSwitchGuard where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeSwitchGuard where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for TypeSwitchGuard
|
||||
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, NFData1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Receive
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Receive where liftEq = genericLiftEq
|
||||
instance Ord1 Receive where liftCompare = genericLiftCompare
|
||||
instance Show1 Receive where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Receive
|
||||
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, NFData1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ReceiveOperator
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ReceiveOperator where liftEq = genericLiftEq
|
||||
instance Ord1 ReceiveOperator where liftCompare = genericLiftCompare
|
||||
instance Show1 ReceiveOperator where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for ReceiveOperator
|
||||
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, NFData1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Field
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Field where liftEq = genericLiftEq
|
||||
instance Ord1 Field where liftCompare = genericLiftCompare
|
||||
instance Show1 Field where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Field
|
||||
instance Evaluatable Field
|
||||
|
||||
data Package a = Package { packageName :: !a, packageContents :: ![a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, NFData1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Package
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Package where liftEq = genericLiftEq
|
||||
instance Ord1 Package where liftCompare = genericLiftCompare
|
||||
instance Show1 Package where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Package where
|
||||
eval eval _ (Package _ xs) = maybe unit (runApp . foldMap1 (App . eval)) (nonEmpty xs)
|
||||
|
||||
-- | 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, NFData1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically TypeAssertion
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 TypeAssertion where liftEq = genericLiftEq
|
||||
instance Ord1 TypeAssertion where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeAssertion where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for TypeAssertion
|
||||
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, NFData1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically TypeConversion
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 TypeConversion where liftEq = genericLiftEq
|
||||
instance Ord1 TypeConversion where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeConversion where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for TypeConversion
|
||||
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, NFData1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Variadic
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Variadic where liftEq = genericLiftEq
|
||||
instance Ord1 Variadic where liftCompare = genericLiftCompare
|
||||
instance Show1 Variadic where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Variadic
|
||||
instance Evaluatable Variadic
|
||||
|
@ -10,24 +10,33 @@ import Diffing.Algorithm
|
||||
|
||||
-- | 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, NFData1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically BidirectionalChannel
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 BidirectionalChannel where liftEq = genericLiftEq
|
||||
instance Ord1 BidirectionalChannel where liftCompare = genericLiftCompare
|
||||
instance Show1 BidirectionalChannel where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for BidirectionalChannel
|
||||
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, NFData1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ReceiveChannel
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ReceiveChannel where liftEq = genericLiftEq
|
||||
instance Ord1 ReceiveChannel where liftCompare = genericLiftCompare
|
||||
instance Show1 ReceiveChannel where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for ReceiveChannel
|
||||
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, NFData1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically SendChannel
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 SendChannel where liftEq = genericLiftEq
|
||||
instance Ord1 SendChannel where liftCompare = genericLiftCompare
|
||||
instance Show1 SendChannel where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for SendChannel
|
||||
instance Evaluatable SendChannel
|
||||
|
@ -9,83 +9,140 @@ import Diffing.Algorithm
|
||||
import Prologue hiding (Text)
|
||||
|
||||
newtype Document a = Document { values :: [a] }
|
||||
deriving (Eq, Ord, Show, Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Document
|
||||
deriving (Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1)
|
||||
|
||||
instance Eq1 Document where liftEq = genericLiftEq
|
||||
instance Ord1 Document where liftCompare = genericLiftCompare
|
||||
instance Show1 Document where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
|
||||
-- Block elements
|
||||
|
||||
newtype Paragraph a = Paragraph { values :: [a] }
|
||||
deriving (Eq, Ord, Show, Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Paragraph
|
||||
deriving (Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1)
|
||||
|
||||
instance Eq1 Paragraph where liftEq = genericLiftEq
|
||||
instance Ord1 Paragraph where liftCompare = genericLiftCompare
|
||||
instance Show1 Paragraph where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
data Heading a = Heading { headingLevel :: Int, headingContent :: [a], sectionContent :: [a] }
|
||||
deriving (Eq, Ord, Show, Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Heading
|
||||
deriving (Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1)
|
||||
|
||||
instance Eq1 Heading where liftEq = genericLiftEq
|
||||
instance Ord1 Heading where liftCompare = genericLiftCompare
|
||||
instance Show1 Heading where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
newtype UnorderedList a = UnorderedList { values :: [a] }
|
||||
deriving (Eq, Ord, Show, Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically UnorderedList
|
||||
deriving (Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1)
|
||||
|
||||
instance Eq1 UnorderedList where liftEq = genericLiftEq
|
||||
instance Ord1 UnorderedList where liftCompare = genericLiftCompare
|
||||
instance Show1 UnorderedList where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
newtype OrderedList a = OrderedList { values :: [a] }
|
||||
deriving (Eq, Ord, Show, Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically OrderedList
|
||||
deriving (Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1)
|
||||
|
||||
instance Eq1 OrderedList where liftEq = genericLiftEq
|
||||
instance Ord1 OrderedList where liftCompare = genericLiftCompare
|
||||
instance Show1 OrderedList where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
newtype BlockQuote a = BlockQuote { values :: [a] }
|
||||
deriving (Eq, Ord, Show, Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically BlockQuote
|
||||
deriving (Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1)
|
||||
|
||||
instance Eq1 BlockQuote where liftEq = genericLiftEq
|
||||
instance Ord1 BlockQuote where liftCompare = genericLiftCompare
|
||||
instance Show1 BlockQuote where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
data ThematicBreak a = ThematicBreak
|
||||
deriving (Eq, Ord, Show, Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ThematicBreak
|
||||
deriving (Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1)
|
||||
|
||||
instance Eq1 ThematicBreak where liftEq = genericLiftEq
|
||||
instance Ord1 ThematicBreak where liftCompare = genericLiftCompare
|
||||
instance Show1 ThematicBreak where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
newtype HTMLBlock a = HTMLBlock { value :: T.Text }
|
||||
deriving (Eq, Ord, Show, Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically HTMLBlock
|
||||
deriving (Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1)
|
||||
|
||||
instance Eq1 HTMLBlock where liftEq = genericLiftEq
|
||||
instance Ord1 HTMLBlock where liftCompare = genericLiftCompare
|
||||
instance Show1 HTMLBlock where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
newtype Table a = Table { values :: [a] }
|
||||
deriving (Eq, Ord, Show, Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Table
|
||||
deriving (Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1)
|
||||
|
||||
instance Eq1 Table where liftEq = genericLiftEq
|
||||
instance Ord1 Table where liftCompare = genericLiftCompare
|
||||
instance Show1 Table where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
newtype TableRow a = TableRow { values :: [a] }
|
||||
deriving (Eq, Ord, Show, Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically TableRow
|
||||
deriving (Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1)
|
||||
|
||||
instance Eq1 TableRow where liftEq = genericLiftEq
|
||||
instance Ord1 TableRow where liftCompare = genericLiftCompare
|
||||
instance Show1 TableRow where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
newtype TableCell a = TableCell { values :: [a] }
|
||||
deriving (Eq, Ord, Show, Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically TableCell
|
||||
deriving (Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1)
|
||||
|
||||
instance Eq1 TableCell where liftEq = genericLiftEq
|
||||
instance Ord1 TableCell where liftCompare = genericLiftCompare
|
||||
instance Show1 TableCell where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
|
||||
-- Inline elements
|
||||
|
||||
newtype Strong a = Strong { values :: [a] }
|
||||
deriving (Eq, Ord, Show, Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Strong
|
||||
deriving (Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1)
|
||||
|
||||
instance Eq1 Strong where liftEq = genericLiftEq
|
||||
instance Ord1 Strong where liftCompare = genericLiftCompare
|
||||
instance Show1 Strong where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
newtype Emphasis a = Emphasis { values :: [a] }
|
||||
deriving (Eq, Ord, Show, Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Emphasis
|
||||
deriving (Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1)
|
||||
|
||||
instance Eq1 Emphasis where liftEq = genericLiftEq
|
||||
instance Ord1 Emphasis where liftCompare = genericLiftCompare
|
||||
instance Show1 Emphasis where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
newtype Text a = Text { value :: T.Text}
|
||||
deriving (Eq, Ord, Show, Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Text
|
||||
deriving (Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1)
|
||||
|
||||
instance Eq1 Text where liftEq = genericLiftEq
|
||||
instance Ord1 Text where liftCompare = genericLiftCompare
|
||||
instance Show1 Text where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
data Link a = Link { linkURL :: T.Text, linkTitle :: Maybe T.Text }
|
||||
deriving (Eq, Ord, Show, Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Link
|
||||
deriving (Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1)
|
||||
|
||||
instance Eq1 Link where liftEq = genericLiftEq
|
||||
instance Ord1 Link where liftCompare = genericLiftCompare
|
||||
instance Show1 Link where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
data Image a = Image { imageURL :: T.Text, imageTitle :: Maybe T.Text }
|
||||
deriving (Eq, Ord, Show, Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Image
|
||||
deriving (Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1)
|
||||
|
||||
instance Eq1 Image where liftEq = genericLiftEq
|
||||
instance Ord1 Image where liftCompare = genericLiftCompare
|
||||
instance Show1 Image where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
data Code a = Code { codeLanguage :: Maybe T.Text, codeContent :: T.Text }
|
||||
deriving (Eq, Ord, Show, Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Code
|
||||
deriving (Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1)
|
||||
|
||||
instance Eq1 Code where liftEq = genericLiftEq
|
||||
instance Ord1 Code where liftCompare = genericLiftCompare
|
||||
instance Show1 Code where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
data LineBreak a = LineBreak
|
||||
deriving (Eq, Ord, Show, Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically LineBreak
|
||||
deriving (Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1)
|
||||
|
||||
instance Eq1 LineBreak where liftEq = genericLiftEq
|
||||
instance Ord1 LineBreak where liftCompare = genericLiftCompare
|
||||
instance Show1 LineBreak where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
newtype Strikethrough a = Strikethrough { values :: [a] }
|
||||
deriving (Eq, Ord, Show, Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Strikethrough
|
||||
deriving (Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1)
|
||||
|
||||
instance Eq1 Strikethrough where liftEq = genericLiftEq
|
||||
instance Ord1 Strikethrough where liftCompare = genericLiftCompare
|
||||
instance Show1 Strikethrough where liftShowsPrec = genericLiftShowsPrec
|
||||
|
@ -20,14 +20,20 @@ import Diffing.Algorithm
|
||||
import Source.Span
|
||||
|
||||
newtype Text a = Text { value :: T.Text }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Text
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Text where liftEq = genericLiftEq
|
||||
instance Ord1 Text where liftCompare = genericLiftCompare
|
||||
instance Show1 Text where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Text
|
||||
|
||||
newtype VariableName a = VariableName { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically VariableName
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 VariableName where liftEq = genericLiftEq
|
||||
instance Ord1 VariableName where liftCompare = genericLiftCompare
|
||||
instance Show1 VariableName where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable VariableName
|
||||
|
||||
@ -81,104 +87,152 @@ include eval pathTerm f = do
|
||||
pure v
|
||||
|
||||
newtype Require a = Require { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Require
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Require where liftEq = genericLiftEq
|
||||
instance Ord1 Require where liftCompare = genericLiftCompare
|
||||
instance Show1 Require where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Require where
|
||||
eval eval _ (Require path) = include eval path load
|
||||
|
||||
|
||||
newtype RequireOnce a = RequireOnce { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically RequireOnce
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 RequireOnce where liftEq = genericLiftEq
|
||||
instance Ord1 RequireOnce where liftCompare = genericLiftCompare
|
||||
instance Show1 RequireOnce where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable RequireOnce where
|
||||
eval eval _ (RequireOnce path) = include eval path require
|
||||
|
||||
newtype Include a = Include { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Include
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Include where liftEq = genericLiftEq
|
||||
instance Ord1 Include where liftCompare = genericLiftCompare
|
||||
instance Show1 Include where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Include where
|
||||
eval eval _ (Include path) = include eval path load
|
||||
|
||||
newtype IncludeOnce a = IncludeOnce { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically IncludeOnce
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 IncludeOnce where liftEq = genericLiftEq
|
||||
instance Ord1 IncludeOnce where liftCompare = genericLiftCompare
|
||||
instance Show1 IncludeOnce where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable IncludeOnce where
|
||||
eval eval _ (IncludeOnce path) = include eval path require
|
||||
|
||||
newtype ArrayElement a = ArrayElement { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ArrayElement
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ArrayElement where liftEq = genericLiftEq
|
||||
instance Ord1 ArrayElement where liftCompare = genericLiftCompare
|
||||
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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically GlobalDeclaration
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 GlobalDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 GlobalDeclaration where liftCompare = genericLiftCompare
|
||||
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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically SimpleVariable
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 SimpleVariable where liftEq = genericLiftEq
|
||||
instance Ord1 SimpleVariable where liftCompare = genericLiftCompare
|
||||
instance Show1 SimpleVariable where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable SimpleVariable
|
||||
|
||||
data Concat a = Concat { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Concat
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Concat where liftEq = genericLiftEq
|
||||
instance Ord1 Concat where liftCompare = genericLiftCompare
|
||||
instance Show1 Concat where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Concat
|
||||
|
||||
-- | 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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically CastType
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 CastType where liftEq = genericLiftEq
|
||||
instance Ord1 CastType where liftCompare = genericLiftCompare
|
||||
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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ErrorControl
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ErrorControl where liftEq = genericLiftEq
|
||||
instance Ord1 ErrorControl where liftCompare = genericLiftCompare
|
||||
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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Clone
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Clone where liftEq = genericLiftEq
|
||||
instance Ord1 Clone where liftCompare = genericLiftCompare
|
||||
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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ShellCommand
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ShellCommand where liftEq = genericLiftEq
|
||||
instance Ord1 ShellCommand where liftCompare = genericLiftCompare
|
||||
instance Show1 ShellCommand where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Update
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Update where liftEq = genericLiftEq
|
||||
instance Ord1 Update where liftCompare = genericLiftCompare
|
||||
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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically NewVariable
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 NewVariable where liftEq = genericLiftEq
|
||||
instance Ord1 NewVariable where liftCompare = genericLiftCompare
|
||||
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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically RelativeScope
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 RelativeScope where liftEq = genericLiftEq
|
||||
instance Ord1 RelativeScope where liftCompare = genericLiftCompare
|
||||
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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically QualifiedName
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 QualifiedName where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedName where liftCompare = genericLiftCompare
|
||||
instance Show1 QualifiedName where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable QualifiedName where
|
||||
eval _ _ (QualifiedName obj iden) = do
|
||||
@ -202,228 +256,342 @@ instance Evaluatable QualifiedName where
|
||||
unit
|
||||
|
||||
newtype NamespaceName a = NamespaceName { names :: NonEmpty a }
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Diffable, FreeVariables1, Declarations1, ToJSONFields1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically NamespaceName
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 NamespaceName where liftEq = genericLiftEq
|
||||
instance Ord1 NamespaceName where liftCompare = genericLiftCompare
|
||||
instance Show1 NamespaceName where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Hashable1 NamespaceName where liftHashWithSalt = foldl
|
||||
|
||||
instance Evaluatable NamespaceName
|
||||
|
||||
newtype ConstDeclaration a = ConstDeclaration { values :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ConstDeclaration
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ConstDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 ConstDeclaration where liftCompare = genericLiftCompare
|
||||
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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ClassConstDeclaration
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ClassConstDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 ClassConstDeclaration where liftCompare = genericLiftCompare
|
||||
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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ClassInterfaceClause
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ClassInterfaceClause where liftEq = genericLiftEq
|
||||
instance Ord1 ClassInterfaceClause where liftCompare = genericLiftCompare
|
||||
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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ClassBaseClause
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ClassBaseClause where liftEq = genericLiftEq
|
||||
instance Ord1 ClassBaseClause where liftCompare = genericLiftCompare
|
||||
instance Show1 ClassBaseClause where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable ClassBaseClause
|
||||
|
||||
newtype UseClause a = UseClause { values :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically UseClause
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 UseClause where liftEq = genericLiftEq
|
||||
instance Ord1 UseClause where liftCompare = genericLiftCompare
|
||||
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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ReturnType
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ReturnType where liftEq = genericLiftEq
|
||||
instance Ord1 ReturnType where liftCompare = genericLiftCompare
|
||||
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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically TypeDeclaration
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 TypeDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 TypeDeclaration where liftCompare = genericLiftCompare
|
||||
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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically BaseTypeDeclaration
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 BaseTypeDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 BaseTypeDeclaration where liftCompare = genericLiftCompare
|
||||
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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ScalarType
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ScalarType where liftEq = genericLiftEq
|
||||
instance Ord1 ScalarType where liftCompare = genericLiftCompare
|
||||
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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically EmptyIntrinsic
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 EmptyIntrinsic where liftEq = genericLiftEq
|
||||
instance Ord1 EmptyIntrinsic where liftCompare = genericLiftCompare
|
||||
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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ExitIntrinsic
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ExitIntrinsic where liftEq = genericLiftEq
|
||||
instance Ord1 ExitIntrinsic where liftCompare = genericLiftCompare
|
||||
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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically IssetIntrinsic
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 IssetIntrinsic where liftEq = genericLiftEq
|
||||
instance Ord1 IssetIntrinsic where liftCompare = genericLiftCompare
|
||||
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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically EvalIntrinsic
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 EvalIntrinsic where liftEq = genericLiftEq
|
||||
instance Ord1 EvalIntrinsic where liftCompare = genericLiftCompare
|
||||
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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically PrintIntrinsic
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 PrintIntrinsic where liftEq = genericLiftEq
|
||||
instance Ord1 PrintIntrinsic where liftCompare = genericLiftCompare
|
||||
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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically NamespaceAliasingClause
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 NamespaceAliasingClause where liftEq = genericLiftEq
|
||||
instance Ord1 NamespaceAliasingClause where liftCompare = genericLiftCompare
|
||||
instance Show1 NamespaceAliasingClause where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable NamespaceAliasingClause
|
||||
|
||||
newtype NamespaceUseDeclaration a = NamespaceUseDeclaration { values :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically NamespaceUseDeclaration
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 NamespaceUseDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 NamespaceUseDeclaration where liftCompare = genericLiftCompare
|
||||
instance Show1 NamespaceUseDeclaration where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable NamespaceUseDeclaration
|
||||
|
||||
newtype NamespaceUseClause a = NamespaceUseClause { values :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically NamespaceUseClause
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 NamespaceUseClause where liftEq = genericLiftEq
|
||||
instance Ord1 NamespaceUseClause where liftCompare = genericLiftCompare
|
||||
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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically NamespaceUseGroupClause
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 NamespaceUseGroupClause where liftEq = genericLiftEq
|
||||
instance Ord1 NamespaceUseGroupClause where liftCompare = genericLiftCompare
|
||||
instance Show1 NamespaceUseGroupClause where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable NamespaceUseGroupClause
|
||||
|
||||
data Namespace a = Namespace { namespaceName :: [a], namespaceBody :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Namespace
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Namespace where liftEq = genericLiftEq
|
||||
instance Ord1 Namespace where liftCompare = genericLiftCompare
|
||||
instance Show1 Namespace where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Namespace
|
||||
|
||||
data TraitDeclaration a = TraitDeclaration { traitName :: a, traitStatements :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically TraitDeclaration
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 TraitDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 TraitDeclaration where liftCompare = genericLiftCompare
|
||||
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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically AliasAs
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 AliasAs where liftEq = genericLiftEq
|
||||
instance Ord1 AliasAs where liftCompare = genericLiftCompare
|
||||
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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically InsteadOf
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 InsteadOf where liftEq = genericLiftEq
|
||||
instance Ord1 InsteadOf where liftCompare = genericLiftCompare
|
||||
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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically TraitUseSpecification
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 TraitUseSpecification where liftEq = genericLiftEq
|
||||
instance Ord1 TraitUseSpecification where liftCompare = genericLiftCompare
|
||||
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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically TraitUseClause
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 TraitUseClause where liftEq = genericLiftEq
|
||||
instance Ord1 TraitUseClause where liftCompare = genericLiftCompare
|
||||
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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically DestructorDeclaration
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 DestructorDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 DestructorDeclaration where liftCompare = genericLiftCompare
|
||||
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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Static
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Static where liftEq = genericLiftEq
|
||||
instance Ord1 Static where liftCompare = genericLiftCompare
|
||||
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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ClassModifier
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ClassModifier where liftEq = genericLiftEq
|
||||
instance Ord1 ClassModifier where liftCompare = genericLiftCompare
|
||||
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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ConstructorDeclaration
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ConstructorDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 ConstructorDeclaration where liftCompare = genericLiftCompare
|
||||
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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically PropertyDeclaration
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 PropertyDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 PropertyDeclaration where liftCompare = genericLiftCompare
|
||||
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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically PropertyModifier
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 PropertyModifier where liftEq = genericLiftEq
|
||||
instance Ord1 PropertyModifier where liftCompare = genericLiftCompare
|
||||
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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically InterfaceDeclaration
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 InterfaceDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 InterfaceDeclaration where liftCompare = genericLiftCompare
|
||||
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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically InterfaceBaseClause
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 InterfaceBaseClause where liftEq = genericLiftEq
|
||||
instance Ord1 InterfaceBaseClause where liftCompare = genericLiftCompare
|
||||
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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Echo
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Echo where liftEq = genericLiftEq
|
||||
instance Ord1 Echo where liftCompare = genericLiftCompare
|
||||
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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Unset
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Unset where liftEq = genericLiftEq
|
||||
instance Ord1 Unset where liftCompare = genericLiftCompare
|
||||
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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Declare
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Declare where liftEq = genericLiftEq
|
||||
instance Ord1 Declare where liftCompare = genericLiftCompare
|
||||
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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically DeclareDirective
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 DeclareDirective where liftEq = genericLiftEq
|
||||
instance Ord1 DeclareDirective where liftCompare = genericLiftCompare
|
||||
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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically LabeledStatement
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 LabeledStatement where liftEq = genericLiftEq
|
||||
instance Ord1 LabeledStatement where liftCompare = genericLiftCompare
|
||||
instance Show1 LabeledStatement where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable LabeledStatement
|
||||
|
@ -1,6 +1,5 @@
|
||||
{-# LANGUAGE DeriveAnyClass, DerivingVia #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
{-# OPTIONS_GHC -fno-warn-orphans #-} -- FIXME
|
||||
module Language.Python.Syntax where
|
||||
|
||||
import Prologue
|
||||
@ -27,7 +26,7 @@ import Source.Span
|
||||
data QualifiedName
|
||||
= QualifiedName { paths :: NonEmpty FilePath }
|
||||
| RelativeQualifiedName { path :: FilePath, maybeQualifiedName :: Maybe QualifiedName }
|
||||
deriving (Eq, Generic, Hashable, Ord, Show, ToJSON, NFData)
|
||||
deriving (Eq, Generic, Hashable, Ord, Show, ToJSON)
|
||||
|
||||
qualifiedName :: NonEmpty Text -> QualifiedName
|
||||
qualifiedName xs = QualifiedName (T.unpack <$> xs)
|
||||
@ -93,8 +92,11 @@ resolvePythonModules q = do
|
||||
maybeM (throwResolutionError $ NotFoundError path searchPaths Language.Python) modulePath
|
||||
|
||||
data Alias a = Alias { aliasValue :: a, aliasName :: a}
|
||||
deriving (Generic1, Diffable, Eq, Foldable, FreeVariables1, Functor, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Alias
|
||||
deriving (Generic1, Diffable, Foldable, FreeVariables1, Functor, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Alias where liftEq = genericLiftEq
|
||||
instance Ord1 Alias where liftCompare = genericLiftCompare
|
||||
instance Show1 Alias where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Declarations1 Alias where
|
||||
liftDeclaredName declaredName = declaredName . aliasValue
|
||||
@ -106,12 +108,18 @@ instance Evaluatable Alias where
|
||||
--
|
||||
-- If the list of symbols is empty copy everything to the calling environment.
|
||||
data Import a = Import { importFrom :: QualifiedName, importSymbols :: ![a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Import
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Import where liftEq = genericLiftEq
|
||||
instance Ord1 Import where liftCompare = genericLiftCompare
|
||||
instance Show1 Import where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
newtype FutureImport a = FutureImport { futureImportSymbols :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically FutureImport
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 FutureImport where liftEq = genericLiftEq
|
||||
instance Ord1 FutureImport where liftCompare = genericLiftCompare
|
||||
instance Show1 FutureImport where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable FutureImport where
|
||||
|
||||
@ -178,11 +186,13 @@ instance Evaluatable Import where
|
||||
|
||||
unit
|
||||
|
||||
deriving instance Hashable1 NonEmpty
|
||||
|
||||
newtype QualifiedImport a = QualifiedImport { qualifiedImportFrom :: NonEmpty a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically QualifiedImport
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 QualifiedImport where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedImport where liftCompare = genericLiftCompare
|
||||
instance Show1 QualifiedImport where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Hashable1 QualifiedImport where liftHashWithSalt = foldl
|
||||
|
||||
-- import a.b.c
|
||||
instance Evaluatable QualifiedImport where
|
||||
@ -220,8 +230,11 @@ instance Evaluatable QualifiedImport where
|
||||
fun (Map.singleton moduleScope moduleFrame)
|
||||
|
||||
data QualifiedAliasedImport a = QualifiedAliasedImport { qualifiedAliasedImportFrom :: QualifiedName, qualifiedAliasedImportAlias :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically QualifiedAliasedImport
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 QualifiedAliasedImport where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedAliasedImport where liftCompare = genericLiftCompare
|
||||
instance Show1 QualifiedAliasedImport where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- import a.b.c as e
|
||||
instance Evaluatable QualifiedAliasedImport where
|
||||
@ -247,15 +260,21 @@ 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, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Ellipsis
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Ellipsis where liftEq = genericLiftEq
|
||||
instance Ord1 Ellipsis where liftCompare = genericLiftCompare
|
||||
instance Show1 Ellipsis where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Ellipsis
|
||||
instance Evaluatable Ellipsis
|
||||
|
||||
data Redirect a = Redirect { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Redirect
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Redirect where liftEq = genericLiftEq
|
||||
instance Ord1 Redirect where liftCompare = genericLiftCompare
|
||||
instance Show1 Redirect where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Redirect
|
||||
instance Evaluatable Redirect
|
||||
|
@ -59,8 +59,11 @@ 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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Send
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Send where liftEq = genericLiftEq
|
||||
instance Ord1 Send where liftCompare = genericLiftCompare
|
||||
instance Show1 Send where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Send where
|
||||
eval eval _ Send{..} = do
|
||||
@ -83,8 +86,11 @@ instance Evaluatable Send where
|
||||
maybe callFunction (`withScopeAndFrame` callFunction) lhsFrame
|
||||
|
||||
data Require a = Require { requireRelative :: Bool, requirePath :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Require
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Require where liftEq = genericLiftEq
|
||||
instance Ord1 Require where liftCompare = genericLiftCompare
|
||||
instance Show1 Require where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Require where
|
||||
eval eval _ (Require _ x) = do
|
||||
@ -110,8 +116,11 @@ 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, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Load
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Load where liftEq = genericLiftEq
|
||||
instance Ord1 Load where liftCompare = genericLiftCompare
|
||||
instance Show1 Load where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Load where
|
||||
eval eval _ (Load x Nothing) = do
|
||||
@ -151,8 +160,11 @@ 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, ToJSONFields1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Class
|
||||
deriving (Foldable, Traversable, Functor, Generic1, Hashable1, FreeVariables1, ToJSONFields1)
|
||||
|
||||
instance Eq1 Class where liftEq = genericLiftEq
|
||||
instance Ord1 Class where liftCompare = genericLiftCompare
|
||||
instance Show1 Class where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Diffable Class where
|
||||
equivalentBySubterm = Just . classIdentifier
|
||||
@ -208,8 +220,11 @@ instance Declarations1 Class where
|
||||
|
||||
|
||||
data Module a = Module { moduleIdentifier :: !a, moduleStatements :: ![a] }
|
||||
deriving (Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Module
|
||||
deriving (Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Module where liftEq = genericLiftEq
|
||||
instance Ord1 Module where liftCompare = genericLiftCompare
|
||||
instance Show1 Module where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Module where
|
||||
eval eval _ Module{..} = do
|
||||
@ -252,8 +267,11 @@ instance Declarations1 Module where
|
||||
|
||||
|
||||
data LowPrecedenceAnd a = LowPrecedenceAnd { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically LowPrecedenceAnd
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 LowPrecedenceAnd where liftEq = genericLiftEq
|
||||
instance Ord1 LowPrecedenceAnd where liftCompare = genericLiftCompare
|
||||
instance Show1 LowPrecedenceAnd where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
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
|
||||
@ -264,8 +282,11 @@ instance Evaluatable LowPrecedenceAnd where
|
||||
|
||||
|
||||
data LowPrecedenceOr a = LowPrecedenceOr { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically LowPrecedenceOr
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 LowPrecedenceOr where liftEq = genericLiftEq
|
||||
instance Ord1 LowPrecedenceOr where liftCompare = genericLiftCompare
|
||||
instance Show1 LowPrecedenceOr where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
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
|
||||
@ -275,8 +296,11 @@ instance Evaluatable LowPrecedenceOr where
|
||||
ifthenelse cond (pure cond) b
|
||||
|
||||
data Assignment a = Assignment { assignmentContext :: ![a], assignmentTarget :: !a, assignmentValue :: !a }
|
||||
deriving (Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Assignment
|
||||
deriving (Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Assignment where liftEq = genericLiftEq
|
||||
instance Ord1 Assignment where liftCompare = genericLiftCompare
|
||||
instance Show1 Assignment where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Declarations1 Assignment where
|
||||
liftDeclaredName declaredName Assignment{..} = declaredName assignmentTarget
|
||||
@ -312,7 +336,10 @@ instance Evaluatable Assignment where
|
||||
-- the semantics of invoking @super()@ but implicitly passing the current function's
|
||||
-- arguments to the @super()@ invocation.
|
||||
data ZSuper a = ZSuper
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ZSuper
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ZSuper where liftEq = genericLiftEq
|
||||
instance Ord1 ZSuper where liftCompare = genericLiftCompare
|
||||
instance Show1 ZSuper where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable ZSuper
|
||||
|
@ -11,55 +11,82 @@ import Diffing.Algorithm
|
||||
|
||||
|
||||
data JsxElement a = JsxElement { jsxOpeningElement :: !a, jsxElements :: ![a], jsxClosingElement :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically JsxElement
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 JsxElement where liftEq = genericLiftEq
|
||||
instance Ord1 JsxElement where liftCompare = genericLiftCompare
|
||||
instance Show1 JsxElement where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable JsxElement
|
||||
|
||||
newtype JsxText a = JsxText { contents :: T.Text }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically JsxText
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 JsxText where liftEq = genericLiftEq
|
||||
instance Ord1 JsxText where liftCompare = genericLiftCompare
|
||||
instance Show1 JsxText where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable JsxText
|
||||
|
||||
newtype JsxExpression a = JsxExpression { jsxExpression :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically JsxExpression
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 JsxExpression where liftEq = genericLiftEq
|
||||
instance Ord1 JsxExpression where liftCompare = genericLiftCompare
|
||||
instance Show1 JsxExpression where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable JsxExpression
|
||||
|
||||
data JsxOpeningElement a = JsxOpeningElement { jsxOpeningElementIdentifier :: !a, jsxOpeningElementTypeArguments :: a, jsxAttributes :: ![a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically JsxOpeningElement
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 JsxOpeningElement where liftEq = genericLiftEq
|
||||
instance Ord1 JsxOpeningElement where liftCompare = genericLiftCompare
|
||||
instance Show1 JsxOpeningElement where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable JsxOpeningElement
|
||||
|
||||
newtype JsxClosingElement a = JsxClosingElement { jsxClosingElementIdentifier :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically JsxClosingElement
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 JsxClosingElement where liftEq = genericLiftEq
|
||||
instance Ord1 JsxClosingElement where liftCompare = genericLiftCompare
|
||||
instance Show1 JsxClosingElement where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable JsxClosingElement
|
||||
|
||||
data JsxSelfClosingElement a = JsxSelfClosingElement { jsxSelfClosingElementIdentifier :: !a, jsxSelfClosingElementAttributes :: ![a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically JsxSelfClosingElement
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 JsxSelfClosingElement where liftEq = genericLiftEq
|
||||
instance Ord1 JsxSelfClosingElement where liftCompare = genericLiftCompare
|
||||
instance Show1 JsxSelfClosingElement where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable JsxSelfClosingElement
|
||||
|
||||
data JsxAttribute a = JsxAttribute { jsxAttributeTarget :: !a, jsxAttributeValue :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically JsxAttribute
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 JsxAttribute where liftEq = genericLiftEq
|
||||
instance Ord1 JsxAttribute where liftCompare = genericLiftCompare
|
||||
instance Show1 JsxAttribute where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable JsxAttribute
|
||||
|
||||
newtype JsxFragment a = JsxFragment { terms :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically JsxFragment
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 JsxFragment where liftEq = genericLiftEq
|
||||
instance Ord1 JsxFragment where liftCompare = genericLiftCompare
|
||||
instance Show1 JsxFragment where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable JsxFragment
|
||||
|
||||
data JsxNamespaceName a = JsxNamespaceName { left :: a, right :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically JsxNamespaceName
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 JsxNamespaceName where liftEq = genericLiftEq
|
||||
instance Ord1 JsxNamespaceName where liftCompare = genericLiftCompare
|
||||
instance Show1 JsxNamespaceName where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable JsxNamespaceName
|
||||
|
@ -15,8 +15,11 @@ import qualified Data.Map.Strict as Map
|
||||
import Data.Aeson (ToJSON)
|
||||
|
||||
data Import a = Import { importSymbols :: ![Alias], importFrom :: ImportPath }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Import
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Import where liftEq = genericLiftEq
|
||||
instance Ord1 Import where liftCompare = genericLiftCompare
|
||||
instance Show1 Import where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- http://www.typescriptlang.org/docs/handbook/module-resolution.html
|
||||
instance Evaluatable Import where
|
||||
@ -45,8 +48,11 @@ instance Evaluatable Import where
|
||||
unit
|
||||
|
||||
data QualifiedAliasedImport a = QualifiedAliasedImport { qualifiedAliasedImportAlias :: !a, qualifiedAliasedImportFrom :: ImportPath }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically QualifiedAliasedImport
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 QualifiedAliasedImport where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedAliasedImport where liftCompare = genericLiftCompare
|
||||
instance Show1 QualifiedAliasedImport where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable QualifiedAliasedImport where
|
||||
eval _ _ (QualifiedAliasedImport aliasTerm importPath) = do
|
||||
@ -64,8 +70,11 @@ instance Evaluatable QualifiedAliasedImport where
|
||||
unit
|
||||
|
||||
newtype SideEffectImport a = SideEffectImport { sideEffectImportFrom :: ImportPath }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically SideEffectImport
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 SideEffectImport where liftEq = genericLiftEq
|
||||
instance Ord1 SideEffectImport where liftCompare = genericLiftCompare
|
||||
instance Show1 SideEffectImport where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable SideEffectImport where
|
||||
eval _ _ (SideEffectImport importPath) = do
|
||||
@ -75,8 +84,11 @@ instance Evaluatable SideEffectImport where
|
||||
|
||||
-- | Qualified Export declarations
|
||||
newtype QualifiedExport a = QualifiedExport { qualifiedExportSymbols :: [Alias] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically QualifiedExport
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 QualifiedExport where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedExport where liftCompare = genericLiftCompare
|
||||
instance Show1 QualifiedExport where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable QualifiedExport where
|
||||
eval _ _ (QualifiedExport exportSymbols) = do
|
||||
@ -94,15 +106,18 @@ instance Evaluatable QualifiedExport where
|
||||
unit
|
||||
|
||||
data Alias = Alias { aliasValue :: Name, aliasName :: Name }
|
||||
deriving (Eq, Generic, Hashable, Ord, Show, ToJSON, NFData)
|
||||
deriving (Eq, Generic, Hashable, Ord, Show, ToJSON)
|
||||
|
||||
toTuple :: Alias -> (Name, Name)
|
||||
toTuple Alias{..} = (aliasValue, aliasName)
|
||||
|
||||
-- | Qualified Export declarations that export from another module.
|
||||
data QualifiedExportFrom a = QualifiedExportFrom { qualifiedExportFrom :: ImportPath, qualifiedExportFromSymbols :: ![Alias]}
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically QualifiedExportFrom
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 QualifiedExportFrom where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedExportFrom where liftCompare = genericLiftCompare
|
||||
instance Show1 QualifiedExportFrom where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable QualifiedExportFrom where
|
||||
eval _ _ (QualifiedExportFrom importPath exportSymbols) = do
|
||||
@ -123,8 +138,11 @@ instance Evaluatable QualifiedExportFrom where
|
||||
unit
|
||||
|
||||
newtype DefaultExport a = DefaultExport { defaultExport :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically DefaultExport
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 DefaultExport where liftEq = genericLiftEq
|
||||
instance Ord1 DefaultExport where liftCompare = genericLiftCompare
|
||||
instance Show1 DefaultExport where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable DefaultExport where
|
||||
eval eval _ (DefaultExport term) = do
|
||||
@ -146,19 +164,28 @@ instance Evaluatable DefaultExport where
|
||||
unit
|
||||
|
||||
data ImportRequireClause a = ImportRequireClause { importRequireIdentifier :: !a, importRequireSubject :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ImportRequireClause
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ImportRequireClause where liftEq = genericLiftEq
|
||||
instance Ord1 ImportRequireClause where liftCompare = genericLiftCompare
|
||||
instance Show1 ImportRequireClause where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable ImportRequireClause
|
||||
|
||||
newtype ImportClause a = ImportClause { importClauseElements :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ImportClause
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ImportClause where liftEq = genericLiftEq
|
||||
instance Ord1 ImportClause where liftCompare = genericLiftCompare
|
||||
instance Show1 ImportClause where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable ImportClause
|
||||
|
||||
data ImportAlias a = ImportAlias { importAliasSubject :: !a, importAlias :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ImportAlias
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ImportAlias where liftEq = genericLiftEq
|
||||
instance Ord1 ImportAlias where liftCompare = genericLiftCompare
|
||||
instance Show1 ImportAlias where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable ImportAlias
|
||||
|
@ -14,20 +14,29 @@ import Diffing.Algorithm
|
||||
import Language.TypeScript.Resolution
|
||||
|
||||
newtype ImplementsClause a = ImplementsClause { implementsClauseTypes :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ImplementsClause
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ImplementsClause where liftEq = genericLiftEq
|
||||
instance Ord1 ImplementsClause where liftCompare = genericLiftCompare
|
||||
instance Show1 ImplementsClause where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable ImplementsClause
|
||||
|
||||
data OptionalParameter a = OptionalParameter { optionalParameterContext :: ![a], optionalParameterSubject :: !a, optionalParameterAccessControl :: AccessControl }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically OptionalParameter
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 OptionalParameter where liftEq = genericLiftEq
|
||||
instance Ord1 OptionalParameter where liftCompare = genericLiftCompare
|
||||
instance Show1 OptionalParameter where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable OptionalParameter
|
||||
|
||||
data RequiredParameter a = RequiredParameter { requiredParameterContext :: [a], requiredParameterSubject :: a, requiredParameterValue :: a, requiredParameterAccessControl :: AccessControl }
|
||||
deriving (Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically RequiredParameter
|
||||
deriving (Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 RequiredParameter where liftEq = genericLiftEq
|
||||
instance Ord1 RequiredParameter where liftCompare = genericLiftCompare
|
||||
instance Show1 RequiredParameter where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Declarations1 RequiredParameter where
|
||||
liftDeclaredName declaredName RequiredParameter{..} = declaredName requiredParameterSubject
|
||||
@ -55,15 +64,21 @@ instance Evaluatable RequiredParameter where
|
||||
pure rhs
|
||||
|
||||
data RestParameter a = RestParameter { restParameterContext :: ![a], restParameterSubject :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically RestParameter
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 RestParameter where liftEq = genericLiftEq
|
||||
instance Ord1 RestParameter where liftCompare = genericLiftCompare
|
||||
instance Show1 RestParameter where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable RestParameter
|
||||
|
||||
|
||||
data JavaScriptRequire a = JavaScriptRequire { javascriptRequireIden :: !a, javascriptRequireFrom :: ImportPath }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically JavaScriptRequire
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 JavaScriptRequire where liftEq = genericLiftEq
|
||||
instance Ord1 JavaScriptRequire where liftCompare = genericLiftCompare
|
||||
instance Show1 JavaScriptRequire where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable JavaScriptRequire where
|
||||
eval _ _ (JavaScriptRequire aliasTerm importPath) = do
|
||||
@ -85,33 +100,48 @@ instance Evaluatable JavaScriptRequire where
|
||||
unit
|
||||
|
||||
data Debugger a = Debugger
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Debugger
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Debugger where liftEq = genericLiftEq
|
||||
instance Ord1 Debugger where liftCompare = genericLiftCompare
|
||||
instance Show1 Debugger where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Debugger
|
||||
|
||||
data Super a = Super
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Super
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Super where liftEq = genericLiftEq
|
||||
instance Ord1 Super where liftCompare = genericLiftCompare
|
||||
instance Show1 Super where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Super
|
||||
|
||||
data Undefined a = Undefined
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Undefined
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Undefined where liftEq = genericLiftEq
|
||||
instance Ord1 Undefined where liftCompare = genericLiftCompare
|
||||
instance Show1 Undefined where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Undefined
|
||||
|
||||
data With a = With { withExpression :: !a, withBody :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically With
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 With where liftEq = genericLiftEq
|
||||
instance Ord1 With where liftCompare = genericLiftCompare
|
||||
instance Show1 With where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable With
|
||||
|
||||
-- | A sequence expression such as Javascript or C's comma operator.
|
||||
data AnnotatedExpression a = AnnotatedExpression { expression :: !a, typeAnnotation :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically AnnotatedExpression
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 AnnotatedExpression where liftEq = genericLiftEq
|
||||
instance Ord1 AnnotatedExpression where liftCompare = genericLiftCompare
|
||||
instance Show1 AnnotatedExpression where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable AnnotatedExpression where
|
||||
eval eval _ (AnnotatedExpression a b) = eval b >> eval a
|
||||
|
@ -17,83 +17,122 @@ import qualified Data.Abstract.ScopeGraph as ScopeGraph
|
||||
|
||||
-- | 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, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ShorthandPropertyIdentifier
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ShorthandPropertyIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 ShorthandPropertyIdentifier where liftCompare = genericLiftCompare
|
||||
instance Show1 ShorthandPropertyIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable ShorthandPropertyIdentifier
|
||||
|
||||
data Union a = Union { unionLeft :: !a, unionRight :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Union
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Union where liftEq = genericLiftEq
|
||||
instance Ord1 Union where liftCompare = genericLiftCompare
|
||||
instance Show1 Union where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Language.TypeScript.Syntax.TypeScript.Union
|
||||
|
||||
data Intersection a = Intersection { intersectionLeft :: !a, intersectionRight :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Intersection
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Intersection where liftEq = genericLiftEq
|
||||
instance Ord1 Intersection where liftCompare = genericLiftCompare
|
||||
instance Show1 Intersection where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Intersection
|
||||
|
||||
data AmbientFunction a = AmbientFunction { ambientFunctionContext :: ![a], ambientFunctionIdentifier :: !a, ambientFunctionParameters :: ![a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically AmbientFunction
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 AmbientFunction where liftEq = genericLiftEq
|
||||
instance Ord1 AmbientFunction where liftCompare = genericLiftCompare
|
||||
instance Show1 AmbientFunction where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable AmbientFunction
|
||||
|
||||
newtype Tuple a = Tuple { tupleElements :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Tuple
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Tuple where liftEq = genericLiftEq
|
||||
instance Ord1 Tuple where liftCompare = genericLiftCompare
|
||||
instance Show1 Tuple where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- This is a tuple type, not a tuple value, so we can't lean on the shared Tuple value
|
||||
instance Evaluatable Tuple
|
||||
|
||||
data Constructor a = Constructor { constructorTypeParameters :: !a, constructorFormalParameters :: ![a], constructorType :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Constructor
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Constructor where liftEq = genericLiftEq
|
||||
instance Ord1 Constructor where liftCompare = genericLiftCompare
|
||||
instance Show1 Constructor where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Language.TypeScript.Syntax.TypeScript.Constructor
|
||||
|
||||
|
||||
newtype Annotation a = Annotation { annotationType :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Annotation
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Annotation where liftEq = genericLiftEq
|
||||
instance Ord1 Annotation where liftCompare = genericLiftCompare
|
||||
instance Show1 Annotation where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Annotation
|
||||
|
||||
newtype Decorator a = Decorator { decoratorTerm :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Decorator
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Decorator where liftEq = genericLiftEq
|
||||
instance Ord1 Decorator where liftCompare = genericLiftCompare
|
||||
instance Show1 Decorator where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Decorator
|
||||
|
||||
newtype ComputedPropertyName a = ComputedPropertyName { propertyName :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ComputedPropertyName
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ComputedPropertyName where liftEq = genericLiftEq
|
||||
instance Ord1 ComputedPropertyName where liftCompare = genericLiftCompare
|
||||
instance Show1 ComputedPropertyName where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable ComputedPropertyName
|
||||
|
||||
newtype Constraint a = Constraint { constraintType :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Constraint
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Constraint where liftEq = genericLiftEq
|
||||
instance Ord1 Constraint where liftCompare = genericLiftCompare
|
||||
instance Show1 Constraint where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Constraint
|
||||
|
||||
data NestedIdentifier a = NestedIdentifier { left :: !a, right :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically NestedIdentifier
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 NestedIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 NestedIdentifier where liftCompare = genericLiftCompare
|
||||
instance Show1 NestedIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable NestedIdentifier
|
||||
|
||||
newtype AmbientDeclaration a = AmbientDeclaration { ambientDeclarationBody :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically AmbientDeclaration
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 AmbientDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 AmbientDeclaration where liftCompare = genericLiftCompare
|
||||
instance Show1 AmbientDeclaration where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable AmbientDeclaration where
|
||||
eval eval _ (AmbientDeclaration body) = eval body
|
||||
|
||||
data EnumDeclaration a = EnumDeclaration { enumDeclarationIdentifier :: !a, enumDeclarationBody :: ![a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically EnumDeclaration
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 EnumDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 EnumDeclaration where liftCompare = genericLiftCompare
|
||||
instance Show1 EnumDeclaration where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable EnumDeclaration
|
||||
|
||||
@ -101,8 +140,11 @@ 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, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ExtendsClause
|
||||
deriving (Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ExtendsClause where liftEq = genericLiftEq
|
||||
instance Ord1 ExtendsClause where liftCompare = genericLiftCompare
|
||||
instance Show1 ExtendsClause where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Declarations1 ExtendsClause where
|
||||
liftDeclaredName _ (ExtendsClause []) = Nothing
|
||||
@ -116,57 +158,84 @@ instance Evaluatable ExtendsClause where
|
||||
unit
|
||||
|
||||
data PropertySignature a = PropertySignature { modifiers :: [a], propertySignaturePropertyName :: a, propertySignatureAccessControl :: AccessControl }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically PropertySignature
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 PropertySignature where liftEq = genericLiftEq
|
||||
instance Ord1 PropertySignature where liftCompare = genericLiftCompare
|
||||
instance Show1 PropertySignature where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable PropertySignature
|
||||
|
||||
data CallSignature a = CallSignature { callSignatureTypeParameters :: !a, callSignatureParameters :: ![a], callSignatureType :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically CallSignature
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 CallSignature where liftEq = genericLiftEq
|
||||
instance Ord1 CallSignature where liftCompare = genericLiftCompare
|
||||
instance Show1 CallSignature where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable CallSignature
|
||||
|
||||
-- | Todo: Move type params and type to context
|
||||
data ConstructSignature a = ConstructSignature { constructSignatureTypeParameters :: !a, constructSignatureParameters :: ![a], constructSignatureType :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ConstructSignature
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ConstructSignature where liftEq = genericLiftEq
|
||||
instance Ord1 ConstructSignature where liftCompare = genericLiftCompare
|
||||
instance Show1 ConstructSignature where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable ConstructSignature
|
||||
|
||||
data IndexSignature a = IndexSignature { subject :: a, subjectType :: a, typeAnnotation :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically IndexSignature
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 IndexSignature where liftEq = genericLiftEq
|
||||
instance Ord1 IndexSignature where liftCompare = genericLiftCompare
|
||||
instance Show1 IndexSignature where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable IndexSignature
|
||||
|
||||
data AbstractMethodSignature a = AbstractMethodSignature { abstractMethodSignatureContext :: ![a], abstractMethodSignatureName :: a, abstractMethodSignatureParameters :: [a], abstractMethodAccessControl :: AccessControl }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically AbstractMethodSignature
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 AbstractMethodSignature where liftEq = genericLiftEq
|
||||
instance Ord1 AbstractMethodSignature where liftCompare = genericLiftCompare
|
||||
instance Show1 AbstractMethodSignature where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable AbstractMethodSignature
|
||||
|
||||
data ForOf a = ForOf { forOfBinding :: !a, forOfSubject :: !a, forOfBody :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ForOf
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ForOf where liftEq = genericLiftEq
|
||||
instance Ord1 ForOf where liftCompare = genericLiftCompare
|
||||
instance Show1 ForOf where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable ForOf
|
||||
|
||||
data LabeledStatement a = LabeledStatement { labeledStatementIdentifier :: !a, labeledStatementSubject :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically LabeledStatement
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 LabeledStatement where liftEq = genericLiftEq
|
||||
instance Ord1 LabeledStatement where liftCompare = genericLiftCompare
|
||||
instance Show1 LabeledStatement where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable LabeledStatement
|
||||
|
||||
newtype Update a = Update { updateSubject :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Update
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Update where liftEq = genericLiftEq
|
||||
instance Ord1 Update where liftCompare = genericLiftCompare
|
||||
instance Show1 Update where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Update
|
||||
|
||||
data Module a = Module { moduleIdentifier :: !a, moduleStatements :: ![a] }
|
||||
deriving (Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Module
|
||||
deriving (Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Module where liftEq = genericLiftEq
|
||||
instance Ord1 Module where liftCompare = genericLiftCompare
|
||||
instance Show1 Module where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
declareModule :: ( AbstractValue term address value m
|
||||
, Carrier sig m
|
||||
@ -234,8 +303,11 @@ instance Declarations1 Module where
|
||||
liftDeclaredName declaredName = declaredName . moduleIdentifier
|
||||
|
||||
data InternalModule a = InternalModule { internalModuleIdentifier :: !a, internalModuleStatements :: ![a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically InternalModule
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 InternalModule where liftEq = genericLiftEq
|
||||
instance Ord1 InternalModule where liftCompare = genericLiftCompare
|
||||
instance Show1 InternalModule where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable InternalModule where
|
||||
eval eval _ InternalModule{..} =
|
||||
@ -245,14 +317,20 @@ instance Declarations a => Declarations (InternalModule a) where
|
||||
declaredName InternalModule{..} = declaredName internalModuleIdentifier
|
||||
|
||||
data ClassHeritage a = ClassHeritage { classHeritageExtendsClause :: !a, implementsClause :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ClassHeritage
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ClassHeritage where liftEq = genericLiftEq
|
||||
instance Ord1 ClassHeritage where liftCompare = genericLiftCompare
|
||||
instance Show1 ClassHeritage where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable ClassHeritage
|
||||
|
||||
data AbstractClass a = AbstractClass { abstractClassIdentifier :: !a, abstractClassTypeParameters :: !a, classHeritage :: ![a], classBody :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically AbstractClass
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 AbstractClass where liftEq = genericLiftEq
|
||||
instance Ord1 AbstractClass where liftCompare = genericLiftCompare
|
||||
instance Show1 AbstractClass where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Declarations a => Declarations (AbstractClass a) where
|
||||
declaredName AbstractClass{..} = declaredName abstractClassIdentifier
|
||||
@ -289,7 +367,10 @@ instance Evaluatable AbstractClass where
|
||||
unit
|
||||
|
||||
data MetaProperty a = MetaProperty
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically MetaProperty
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 MetaProperty where liftEq = genericLiftEq
|
||||
instance Ord1 MetaProperty where liftCompare = genericLiftCompare
|
||||
instance Show1 MetaProperty where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable MetaProperty
|
||||
|
@ -13,51 +13,75 @@ import qualified Data.Abstract.ScopeGraph as ScopeGraph
|
||||
|
||||
-- | 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, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically LookupType
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 LookupType where liftEq = genericLiftEq
|
||||
instance Ord1 LookupType where liftCompare = genericLiftCompare
|
||||
instance Show1 LookupType where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable LookupType
|
||||
|
||||
data FunctionType a = FunctionType { functionTypeParameters :: !a, functionFormalParameters :: ![a], functionType :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically FunctionType
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 FunctionType where liftEq = genericLiftEq
|
||||
instance Ord1 FunctionType where liftCompare = genericLiftCompare
|
||||
instance Show1 FunctionType where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable FunctionType
|
||||
|
||||
data TypeParameter a = TypeParameter { typeParameter :: !a, typeParameterConstraint :: !a, typeParameterDefaultType :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically TypeParameter
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 TypeParameter where liftEq = genericLiftEq
|
||||
instance Ord1 TypeParameter where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeParameter where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable TypeParameter
|
||||
|
||||
data TypeAssertion a = TypeAssertion { typeAssertionParameters :: !a, typeAssertionExpression :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically TypeAssertion
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 TypeAssertion where liftEq = genericLiftEq
|
||||
instance Ord1 TypeAssertion where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeAssertion where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable TypeAssertion
|
||||
|
||||
newtype DefaultType a = DefaultType { defaultType :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically DefaultType
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 DefaultType where liftEq = genericLiftEq
|
||||
instance Ord1 DefaultType where liftCompare = genericLiftCompare
|
||||
instance Show1 DefaultType where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable DefaultType
|
||||
|
||||
newtype ParenthesizedType a = ParenthesizedType { parenthesizedType :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ParenthesizedType
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ParenthesizedType where liftEq = genericLiftEq
|
||||
instance Ord1 ParenthesizedType where liftCompare = genericLiftCompare
|
||||
instance Show1 ParenthesizedType where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable ParenthesizedType
|
||||
|
||||
newtype PredefinedType a = PredefinedType { predefinedType :: T.Text }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically PredefinedType
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 PredefinedType where liftEq = genericLiftEq
|
||||
instance Ord1 PredefinedType where liftCompare = genericLiftCompare
|
||||
instance Show1 PredefinedType where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for PredefinedType
|
||||
instance Evaluatable PredefinedType
|
||||
|
||||
newtype TypeIdentifier a = TypeIdentifier { contents :: T.Text }
|
||||
deriving (Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically TypeIdentifier
|
||||
deriving (Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 TypeIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 TypeIdentifier where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Declarations1 TypeIdentifier where
|
||||
liftDeclaredName _ (TypeIdentifier identifier) = Just (Evaluatable.name identifier)
|
||||
@ -71,73 +95,109 @@ instance Evaluatable TypeIdentifier where
|
||||
unit
|
||||
|
||||
data NestedTypeIdentifier a = NestedTypeIdentifier { left :: !a, right :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically NestedTypeIdentifier
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 NestedTypeIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 NestedTypeIdentifier where liftCompare = genericLiftCompare
|
||||
instance Show1 NestedTypeIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable NestedTypeIdentifier
|
||||
|
||||
data GenericType a = GenericType { genericTypeIdentifier :: !a, genericTypeArguments :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically GenericType
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 GenericType where liftEq = genericLiftEq
|
||||
instance Ord1 GenericType where liftCompare = genericLiftCompare
|
||||
instance Show1 GenericType where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable GenericType
|
||||
|
||||
data TypePredicate a = TypePredicate { typePredicateIdentifier :: !a, typePredicateType :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically TypePredicate
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 TypePredicate where liftEq = genericLiftEq
|
||||
instance Ord1 TypePredicate where liftCompare = genericLiftCompare
|
||||
instance Show1 TypePredicate where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable TypePredicate
|
||||
|
||||
newtype ObjectType a = ObjectType { objectTypeElements :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ObjectType
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ObjectType where liftEq = genericLiftEq
|
||||
instance Ord1 ObjectType where liftCompare = genericLiftCompare
|
||||
instance Show1 ObjectType where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable ObjectType
|
||||
|
||||
newtype ArrayType a = ArrayType { arrayType :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ArrayType
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ArrayType where liftEq = genericLiftEq
|
||||
instance Ord1 ArrayType where liftCompare = genericLiftCompare
|
||||
instance Show1 ArrayType where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable ArrayType
|
||||
|
||||
newtype FlowMaybeType a = FlowMaybeType { flowMaybeType :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically FlowMaybeType
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 FlowMaybeType where liftEq = genericLiftEq
|
||||
instance Ord1 FlowMaybeType where liftCompare = genericLiftCompare
|
||||
instance Show1 FlowMaybeType where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable FlowMaybeType
|
||||
|
||||
newtype TypeQuery a = TypeQuery { typeQuerySubject :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically TypeQuery
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 TypeQuery where liftEq = genericLiftEq
|
||||
instance Ord1 TypeQuery where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeQuery where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable TypeQuery
|
||||
|
||||
newtype IndexTypeQuery a = IndexTypeQuery { indexTypeQuerySubject :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically IndexTypeQuery
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 IndexTypeQuery where liftEq = genericLiftEq
|
||||
instance Ord1 IndexTypeQuery where liftCompare = genericLiftCompare
|
||||
instance Show1 IndexTypeQuery where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable IndexTypeQuery
|
||||
|
||||
newtype TypeArguments a = TypeArguments { typeArguments :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically TypeArguments
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 TypeArguments where liftEq = genericLiftEq
|
||||
instance Ord1 TypeArguments where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeArguments where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable TypeArguments
|
||||
|
||||
newtype ThisType a = ThisType { contents :: T.Text }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ThisType
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ThisType where liftEq = genericLiftEq
|
||||
instance Ord1 ThisType where liftCompare = genericLiftCompare
|
||||
instance Show1 ThisType where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable ThisType
|
||||
|
||||
newtype ExistentialType a = ExistentialType { contents :: T.Text }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ExistentialType
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ExistentialType where liftEq = genericLiftEq
|
||||
instance Ord1 ExistentialType where liftCompare = genericLiftCompare
|
||||
instance Show1 ExistentialType where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable ExistentialType
|
||||
|
||||
newtype LiteralType a = LiteralType { literalTypeSubject :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, NFData1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically LiteralType
|
||||
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 LiteralType where liftEq = genericLiftEq
|
||||
instance Ord1 LiteralType where liftCompare = genericLiftCompare
|
||||
instance Show1 LiteralType where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable LiteralType
|
||||
|
@ -10,7 +10,6 @@ module Prologue
|
||||
|
||||
|
||||
import Debug.Trace as X (traceShowM, traceM)
|
||||
import Control.DeepSeq as X
|
||||
import Data.Bifunctor.Join as X
|
||||
import Data.Bits as X
|
||||
import Data.ByteString as X (ByteString)
|
||||
|
Loading…
Reference in New Issue
Block a user