mirror of
https://github.com/github/semantic.git
synced 2024-12-29 18:06:14 +03:00
Merge pull request #2322 from github/deriving-via
Use -XDerivingVia to clean up Eq1/Show1/Ord1/Semigroup/Monoid instances.
This commit is contained in:
commit
b153fe8c2c
38
.licenses/semantic/cabal/generic-monoid.txt
Normal file
38
.licenses/semantic/cabal/generic-monoid.txt
Normal file
@ -0,0 +1,38 @@
|
||||
---
|
||||
type: cabal
|
||||
name: generic-monoid
|
||||
version: '0.1.0.0'
|
||||
summary: Derive monoid instances for product types.
|
||||
homepage: https://github.com/luke-clifton/generic-monoid
|
||||
license: bsd-3-clause
|
||||
---
|
||||
Copyright (c) 2018, Luke Clifton
|
||||
|
||||
All rights reserved.
|
||||
|
||||
Redistribution and use in source and binary forms, with or without
|
||||
modification, are permitted provided that the following conditions are met:
|
||||
|
||||
* Redistributions of source code must retain the above copyright
|
||||
notice, this list of conditions and the following disclaimer.
|
||||
|
||||
* Redistributions in binary form must reproduce the above
|
||||
copyright notice, this list of conditions and the following
|
||||
disclaimer in the documentation and/or other materials provided
|
||||
with the distribution.
|
||||
|
||||
* Neither the name of Luke Clifton nor the names of other
|
||||
contributors may be used to endorse or promote products derived
|
||||
from this software without specific prior written permission.
|
||||
|
||||
THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
|
||||
"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
|
||||
LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR
|
||||
A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT
|
||||
OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL,
|
||||
SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT
|
||||
LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
|
||||
DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
|
||||
THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
|
||||
(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE
|
||||
OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
|
@ -235,6 +235,7 @@ library
|
||||
, free
|
||||
, freer-cofreer
|
||||
, fused-effects
|
||||
, generic-monoid
|
||||
, ghc-prim
|
||||
, gitrev
|
||||
, Glob
|
||||
|
@ -7,7 +7,7 @@ module Analysis.Abstract.Caching.FlowInsensitive
|
||||
|
||||
import Control.Abstract
|
||||
import Data.Abstract.Module
|
||||
import Data.Map.Monoidal as Monoidal
|
||||
import Data.Map.Monoidal as Monoidal hiding (empty)
|
||||
import Prologue
|
||||
|
||||
-- | Look up the set of values for a given configuration in the in-cache.
|
||||
|
@ -7,7 +7,7 @@ module Analysis.Abstract.Caching.FlowSensitive
|
||||
|
||||
import Control.Abstract
|
||||
import Data.Abstract.Module
|
||||
import Data.Map.Monoidal as Monoidal
|
||||
import Data.Map.Monoidal as Monoidal hiding (empty)
|
||||
import Prologue
|
||||
|
||||
-- | Look up the set of values for a given configuration in the in-cache.
|
||||
|
@ -1,3 +1,4 @@
|
||||
{-# LANGUAGE DerivingVia #-}
|
||||
module Assigning.Assignment.Table
|
||||
( Table(tableAddresses)
|
||||
, singleton
|
||||
@ -12,8 +13,8 @@ import qualified Data.IntMap as IntMap
|
||||
import qualified Data.IntSet as IntSet
|
||||
|
||||
data Table i a = Table { tableAddresses :: [i], tableBranches :: IntMap a }
|
||||
deriving (Eq, Foldable, Functor, Show, Traversable)
|
||||
|
||||
deriving (Eq, Foldable, Functor, Show, Traversable, Generic)
|
||||
deriving Monoid via GenericMonoid (Table i a)
|
||||
|
||||
singleton :: Enum i => i -> a -> Table i a
|
||||
singleton i a = Table [i] (IntMap.singleton (fromEnum i) a)
|
||||
@ -28,13 +29,8 @@ toPairs Table{..} = first toEnum <$> IntMap.toList tableBranches
|
||||
lookup :: Enum i => i -> Table i a -> Maybe a
|
||||
lookup i = IntMap.lookup (fromEnum i) . tableBranches
|
||||
|
||||
|
||||
instance (Enum i, Monoid a) => Semigroup (Table i a) where
|
||||
(Table i1 b1) <> (Table i2 b2) = Table (i1 `mappend` i2) (IntMap.unionWith mappend b1 b2)
|
||||
|
||||
instance (Enum i, Monoid a) => Monoid (Table i a) where
|
||||
mempty = Table mempty mempty
|
||||
mappend = (<>)
|
||||
instance (Enum i, Semigroup a) => Semigroup (Table i a) where
|
||||
(Table i1 b1) <> (Table i2 b2) = Table (i1 <> i2) (IntMap.unionWith (<>) b1 b2)
|
||||
|
||||
instance (Enum i, Show i) => Show1 (Table i) where
|
||||
liftShowsPrec spA slA d t = showsBinaryWith showsPrec (const (liftShowList spA slA)) "Table" d (tableAddresses t) (toPairs t)
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE TypeOperators #-}
|
||||
{-# LANGUAGE TypeOperators, RankNTypes, UndecidableInstances #-}
|
||||
module Data.Functor.Classes.Generic
|
||||
( Eq1(..)
|
||||
, genericLiftEq
|
||||
@ -9,6 +9,7 @@ module Data.Functor.Classes.Generic
|
||||
, defaultGShow1Options
|
||||
, genericLiftShowsPrec
|
||||
, genericLiftShowsPrecWithOptions
|
||||
, Generically (..)
|
||||
) where
|
||||
|
||||
import Data.Functor.Classes
|
||||
@ -179,3 +180,11 @@ 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
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE DeriveAnyClass #-}
|
||||
{-# LANGUAGE DeriveAnyClass, DerivingVia #-}
|
||||
|
||||
module Data.Location
|
||||
( Location(..)
|
||||
@ -6,7 +6,7 @@ module Data.Location
|
||||
, Range(..)
|
||||
) where
|
||||
|
||||
import Prologue (Generic, NFData (..))
|
||||
import Prologue
|
||||
|
||||
import Data.JSON.Fields
|
||||
import Data.Range
|
||||
@ -18,9 +18,7 @@ data Location
|
||||
, locationSpan :: {-# UNPACK #-} Span
|
||||
}
|
||||
deriving (Eq, Ord, Show, Generic, NFData)
|
||||
deriving Semigroup via GenericSemigroup Location
|
||||
|
||||
instance ToJSONFields Location where
|
||||
toJSONFields Location{..} = toJSONFields locationByteRange <> toJSONFields locationSpan
|
||||
|
||||
instance Semigroup Location where
|
||||
(Location r1 sp1) <> (Location r2 sp2) = Location (r1 <> r2) (sp1 <> sp2)
|
||||
|
@ -2,6 +2,7 @@
|
||||
-- | This module defines a 'Map' type whose 'Monoid' and 'Reducer' instances merge values using the 'Semigroup' instance for the underlying type.
|
||||
module Data.Map.Monoidal
|
||||
( Map
|
||||
, empty
|
||||
, lookup
|
||||
, singleton
|
||||
, size
|
||||
@ -9,6 +10,7 @@ module Data.Map.Monoidal
|
||||
, delete
|
||||
, filterWithKey
|
||||
, pairs
|
||||
, elems
|
||||
, keys
|
||||
, module Reducer
|
||||
) where
|
||||
@ -17,15 +19,17 @@ import Data.Aeson (ToJSON)
|
||||
import qualified Data.Map as Map
|
||||
import Data.Semigroup.Reducer as Reducer
|
||||
import Prelude hiding (lookup)
|
||||
import Prologue hiding (Map)
|
||||
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)
|
||||
deriving (Eq, Eq1, Eq2, Foldable, Functor, Ord, Ord1, Ord2, Show, Show1, Show2, ToJSON, Traversable, NFData, Lower)
|
||||
|
||||
|
||||
singleton :: key -> value -> Map key value
|
||||
singleton k v = Map (Map.singleton k v)
|
||||
|
||||
empty :: Map k a
|
||||
empty = Map Map.empty
|
||||
|
||||
lookup :: Ord key => key -> Map key value -> Maybe value
|
||||
lookup key = Map.lookup key . unMap
|
||||
@ -48,17 +52,17 @@ keys = map fst . pairs
|
||||
pairs :: Map key value -> [(key, value)]
|
||||
pairs = Map.toList . unMap
|
||||
|
||||
elems :: Map key value -> [value]
|
||||
elems = Map.elems . unMap
|
||||
|
||||
|
||||
instance (Ord key, Semigroup value) => Semigroup (Map key value) where
|
||||
Map a <> Map b = Map (Map.unionWith (<>) a b)
|
||||
|
||||
instance (Ord key, Semigroup value) => Monoid (Map key value) where
|
||||
mempty = Map Map.empty
|
||||
mappend = (<>)
|
||||
mempty = empty
|
||||
|
||||
instance (Ord key, Reducer a value) => Reducer (key, a) (Map key value) where
|
||||
unit (key, a) = Map (Map.singleton key (unit a))
|
||||
cons (key, a) (Map m) = Map (Map.insertWith (<>) key (unit a) m)
|
||||
snoc (Map m) (key, a) = Map (Map.insertWith (flip (<>)) key (unit a) m)
|
||||
|
||||
instance Lower (Map key value) where lowerBound = Map lowerBound
|
||||
|
@ -43,7 +43,7 @@ import Proto3.Suite
|
||||
-- 'ByteString' under the hood. Construct these with 'fromUTF8'; obviously,
|
||||
-- passing 'fromUTF8' non-UTF8 bytes will cause crashes.
|
||||
newtype Source = Source { sourceBytes :: B.ByteString }
|
||||
deriving (Eq, IsString, Show, Generic, MessageField)
|
||||
deriving (Eq, Semigroup, Monoid, IsString, Show, Generic, MessageField)
|
||||
|
||||
fromUTF8 :: B.ByteString -> Source
|
||||
fromUTF8 = Source
|
||||
@ -158,13 +158,3 @@ rangeToSpan source (Range rangeStart rangeEnd) = Span startPos endPos
|
||||
(lineRanges, _) = span ((<= rangeEnd) . start) rest
|
||||
firstRange = fromMaybe emptyRange (getFirst (foldMap (First . Just) lineRanges))
|
||||
lastRange = fromMaybe firstRange (getLast (foldMap (Last . Just) lineRanges))
|
||||
|
||||
|
||||
-- Instances
|
||||
|
||||
instance Semigroup Source where
|
||||
Source a <> Source b = Source (a <> b)
|
||||
|
||||
instance Monoid Source where
|
||||
mempty = Source B.empty
|
||||
mappend = (<>)
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE AllowAmbiguousTypes, DeriveAnyClass, GADTs, TypeOperators, MultiParamTypeClasses, UndecidableInstances, ScopedTypeVariables, KindSignatures, RankNTypes, ConstraintKinds, GeneralizedNewtypeDeriving, DerivingStrategies #-}
|
||||
{-# LANGUAGE AllowAmbiguousTypes, DeriveAnyClass, DerivingVia, GADTs, TypeOperators, MultiParamTypeClasses, UndecidableInstances, ScopedTypeVariables, KindSignatures, RankNTypes, ConstraintKinds, GeneralizedNewtypeDeriving, DerivingStrategies #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists -Wno-redundant-constraints -fno-warn-orphans #-} -- For HasCallStack
|
||||
module Data.Syntax where
|
||||
|
||||
@ -159,10 +159,8 @@ newtype Identifier a = Identifier { name :: Name }
|
||||
deriving newtype (Eq, Ord, Show)
|
||||
deriving stock (Foldable, Functor, Generic1, Traversable)
|
||||
deriving anyclass (Diffable, Hashable1, Message1, Named1, ToJSONFields1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Identifier
|
||||
|
||||
instance Eq1 Identifier where liftEq = genericLiftEq
|
||||
instance Ord1 Identifier where liftCompare = genericLiftCompare
|
||||
instance Show1 Identifier where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Identifier where
|
||||
eval eval ref' = ref eval ref' >=> deref
|
||||
@ -186,10 +184,7 @@ newtype AccessibilityModifier a = AccessibilityModifier { contents :: Text }
|
||||
deriving newtype (Eq, Ord, Show)
|
||||
deriving stock (Foldable, Functor, Generic1, Traversable)
|
||||
deriving anyclass (Declarations1, Diffable, FreeVariables1, Hashable1, Message1, Named1, ToJSONFields1, NFData1)
|
||||
|
||||
instance Eq1 AccessibilityModifier where liftEq = genericLiftEq
|
||||
instance Ord1 AccessibilityModifier where liftCompare = genericLiftCompare
|
||||
instance Show1 AccessibilityModifier where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically AccessibilityModifier
|
||||
|
||||
-- TODO: Implement Eval instance for AccessibilityModifier
|
||||
instance Evaluatable AccessibilityModifier
|
||||
@ -199,10 +194,7 @@ instance Evaluatable AccessibilityModifier
|
||||
-- This can be used to represent an implicit no-op, e.g. the alternative in an 'if' statement without an 'else'.
|
||||
data Empty a = Empty
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Empty where liftEq _ _ _ = True
|
||||
instance Ord1 Empty where liftCompare _ _ _ = EQ
|
||||
instance Show1 Empty where liftShowsPrec _ _ _ _ = showString "Empty"
|
||||
deriving (Eq1, Show1, Ord1) via Generically Empty
|
||||
|
||||
instance Evaluatable Empty where
|
||||
eval _ _ _ = pure unit
|
||||
@ -213,10 +205,7 @@ instance Tokenize Empty where
|
||||
-- | Syntax representing a parsing or assignment error.
|
||||
data Error a = Error { errorCallStack :: ErrorStack, errorExpected :: [String], errorActual :: Maybe String, errorChildren :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
|
||||
instance Eq1 Error where liftEq = genericLiftEq
|
||||
instance Ord1 Error where liftCompare = genericLiftCompare
|
||||
instance Show1 Error where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Error
|
||||
|
||||
instance Evaluatable Error
|
||||
|
||||
@ -232,7 +221,6 @@ instance Message String where
|
||||
decodeMessage = Decode.at decodeMessageField
|
||||
dotProto _ = [ Proto.DotProtoMessageField $ protoType (Proxy @String) ]
|
||||
|
||||
|
||||
errorSyntax :: Error.Error String -> [a] -> Error a
|
||||
errorSyntax Error.Error{..} = Error (ErrorStack $ errorSite <$> getCallStack callStack) errorExpected errorActual
|
||||
|
||||
@ -298,6 +286,7 @@ instance Ord ErrorStack where
|
||||
|
||||
data Context a = Context { contextTerms :: NonEmpty a, contextSubject :: a }
|
||||
deriving (Eq, Foldable, FreeVariables1, Functor, Generic1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Context
|
||||
|
||||
instance Diffable Context where
|
||||
subalgorithmFor blur focus (Context n s) = Context <$> traverse blur n <*> focus s
|
||||
@ -306,10 +295,6 @@ instance Diffable Context where
|
||||
|
||||
instance Hashable1 Context where liftHashWithSalt = foldl
|
||||
|
||||
instance Eq1 Context where liftEq = genericLiftEq
|
||||
instance Ord1 Context where liftCompare = genericLiftCompare
|
||||
instance Show1 Context where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Context where
|
||||
eval eval _ Context{..} = eval contextSubject
|
||||
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE DeriveAnyClass, MultiParamTypeClasses #-}
|
||||
{-# LANGUAGE DeriveAnyClass, DerivingVia, MultiParamTypeClasses #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
module Data.Syntax.Comment where
|
||||
|
||||
@ -12,10 +12,7 @@ import Reprinting.Tokenize as Token
|
||||
-- | An unnested comment (line or block).
|
||||
newtype Comment a = Comment { commentContent :: Text }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Comment where liftEq = genericLiftEq
|
||||
instance Ord1 Comment where liftCompare = genericLiftCompare
|
||||
instance Show1 Comment where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Comment
|
||||
|
||||
instance Evaluatable Comment where
|
||||
eval _ _ _ = pure unit
|
||||
@ -31,10 +28,7 @@ instance Tokenize Comment where
|
||||
-- | HashBang line (e.g. `#!/usr/bin/env node`)
|
||||
newtype HashBang a = HashBang { value :: Text }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 HashBang where liftEq = genericLiftEq
|
||||
instance Ord1 HashBang where liftCompare = genericLiftCompare
|
||||
instance Show1 HashBang where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically HashBang
|
||||
|
||||
-- TODO: Implement Eval instance for HashBang
|
||||
instance Evaluatable HashBang
|
||||
|
@ -1,30 +1,29 @@
|
||||
{-# LANGUAGE DeriveAnyClass, MultiParamTypeClasses, ScopedTypeVariables, TupleSections, UndecidableInstances #-}
|
||||
{-# LANGUAGE DeriveAnyClass, DerivingVia, MultiParamTypeClasses, ScopedTypeVariables, TupleSections, UndecidableInstances #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
module Data.Syntax.Declaration where
|
||||
|
||||
import Prologue
|
||||
|
||||
import Proto3.Suite.Class
|
||||
import qualified Data.Map.Strict as Map
|
||||
import qualified Data.Set as Set
|
||||
|
||||
import Control.Abstract hiding (Function)
|
||||
import Data.Abstract.Evaluatable
|
||||
import Data.Abstract.Name (__self)
|
||||
import Data.JSON.Fields
|
||||
import qualified Data.Reprinting.Scope as Scope
|
||||
import qualified Data.Set as Set
|
||||
import qualified Data.Map.Strict as Map
|
||||
import Data.Span (emptySpan)
|
||||
import Diffing.Algorithm
|
||||
import Prologue
|
||||
import Proto3.Suite.Class
|
||||
import Reprinting.Tokenize hiding (Superclass)
|
||||
import Data.Span (emptySpan)
|
||||
import Data.Abstract.Name (__self)
|
||||
|
||||
data Function a = Function { functionContext :: ![a], functionName :: !a, functionParameters :: ![a], functionBody :: !a }
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, ToJSONFields1, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Function
|
||||
|
||||
instance Diffable Function where
|
||||
equivalentBySubterm = Just . functionName
|
||||
|
||||
instance Eq1 Function where liftEq = genericLiftEq
|
||||
instance Ord1 Function where liftCompare = genericLiftCompare
|
||||
instance Show1 Function where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Filter the closed-over environment by the free variables in the term.
|
||||
-- TODO: How should we represent function types, where applicable?
|
||||
|
||||
@ -74,10 +73,7 @@ instance FreeVariables1 Function where
|
||||
|
||||
data Method a = Method { methodContext :: ![a], methodReceiver :: !a, methodName :: !a, methodParameters :: ![a], methodBody :: !a }
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Method where liftEq = genericLiftEq
|
||||
instance Ord1 Method where liftCompare = genericLiftCompare
|
||||
instance Show1 Method where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Method
|
||||
|
||||
instance Diffable Method where
|
||||
equivalentBySubterm = Just . methodName
|
||||
@ -117,10 +113,7 @@ instance FreeVariables1 Method where
|
||||
-- | A method signature in TypeScript or a method spec in Go.
|
||||
data MethodSignature a = MethodSignature { methodSignatureContext :: ![a], methodSignatureName :: !a, methodSignatureParameters :: ![a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 MethodSignature where liftEq = genericLiftEq
|
||||
instance Ord1 MethodSignature where liftCompare = genericLiftCompare
|
||||
instance Show1 MethodSignature where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically MethodSignature
|
||||
|
||||
-- TODO: Implement Eval instance for MethodSignature
|
||||
instance Evaluatable MethodSignature
|
||||
@ -128,21 +121,14 @@ instance Evaluatable MethodSignature
|
||||
|
||||
newtype RequiredParameter a = RequiredParameter { requiredParameter :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 RequiredParameter where liftEq = genericLiftEq
|
||||
instance Ord1 RequiredParameter where liftCompare = genericLiftCompare
|
||||
instance Show1 RequiredParameter where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically RequiredParameter
|
||||
|
||||
-- TODO: Implement Eval instance for RequiredParameter
|
||||
instance Evaluatable RequiredParameter
|
||||
|
||||
|
||||
newtype OptionalParameter a = OptionalParameter { optionalParameter :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 OptionalParameter where liftEq = genericLiftEq
|
||||
instance Ord1 OptionalParameter where liftCompare = genericLiftCompare
|
||||
instance Show1 OptionalParameter where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically OptionalParameter
|
||||
|
||||
-- TODO: Implement Eval instance for OptionalParameter
|
||||
instance Evaluatable OptionalParameter
|
||||
@ -154,10 +140,7 @@ instance Evaluatable OptionalParameter
|
||||
-- | A declaration of possibly many variables such as var foo = 5, bar = 6 in JavaScript.
|
||||
newtype VariableDeclaration a = VariableDeclaration { variableDeclarations :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 VariableDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 VariableDeclaration where liftCompare = genericLiftCompare
|
||||
instance Show1 VariableDeclaration where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically VariableDeclaration
|
||||
|
||||
instance Evaluatable VariableDeclaration where
|
||||
eval _ _ (VariableDeclaration []) = pure unit
|
||||
@ -183,10 +166,7 @@ instance Declarations a => Declarations (VariableDeclaration a) where
|
||||
|
||||
data InterfaceDeclaration a = InterfaceDeclaration { interfaceDeclarationContext :: ![a], interfaceDeclarationIdentifier :: !a, interfaceDeclarationSuperInterfaces :: ![a], interfaceDeclarationBody :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 InterfaceDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 InterfaceDeclaration where liftCompare = genericLiftCompare
|
||||
instance Show1 InterfaceDeclaration where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically InterfaceDeclaration
|
||||
|
||||
-- TODO: Implement Eval instance for InterfaceDeclaration
|
||||
instance Evaluatable InterfaceDeclaration
|
||||
@ -198,10 +178,7 @@ instance Declarations a => Declarations (InterfaceDeclaration a) where
|
||||
-- | A public field definition such as a field definition in a JavaScript class.
|
||||
data PublicFieldDefinition a = PublicFieldDefinition { publicFieldContext :: ![a], publicFieldPropertyName :: !a, publicFieldValue :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 PublicFieldDefinition where liftEq = genericLiftEq
|
||||
instance Ord1 PublicFieldDefinition where liftCompare = genericLiftCompare
|
||||
instance Show1 PublicFieldDefinition where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically PublicFieldDefinition
|
||||
|
||||
-- TODO: Implement Eval instance for PublicFieldDefinition
|
||||
instance Evaluatable PublicFieldDefinition where
|
||||
@ -217,16 +194,14 @@ instance Evaluatable PublicFieldDefinition where
|
||||
|
||||
data Variable a = Variable { variableName :: !a, variableType :: !a, variableValue :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Variable where liftEq = genericLiftEq
|
||||
instance Ord1 Variable where liftCompare = genericLiftCompare
|
||||
instance Show1 Variable where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Variable
|
||||
|
||||
-- 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, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Class
|
||||
|
||||
instance Declarations a => Declarations (Class a) where
|
||||
declaredName (Class _ name _ _) = declaredName name
|
||||
@ -234,10 +209,6 @@ instance Declarations a => Declarations (Class a) where
|
||||
instance Diffable Class where
|
||||
equivalentBySubterm = Just . classIdentifier
|
||||
|
||||
instance Eq1 Class where liftEq = genericLiftEq
|
||||
instance Ord1 Class where liftCompare = genericLiftCompare
|
||||
instance Show1 Class where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Class where
|
||||
eval eval _ Class{..} = do
|
||||
name <- maybeM (throwNoNameError classIdentifier) (declaredName classIdentifier)
|
||||
@ -276,10 +247,7 @@ 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, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Decorator where liftEq = genericLiftEq
|
||||
instance Ord1 Decorator where liftCompare = genericLiftCompare
|
||||
instance Show1 Decorator where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Decorator
|
||||
|
||||
-- TODO: Implement Eval instance for Decorator
|
||||
instance Evaluatable Decorator
|
||||
@ -290,10 +258,7 @@ instance Evaluatable Decorator
|
||||
-- | An ADT, i.e. a disjoint sum of products, like 'data' in Haskell, or 'enum' in Rust or Swift.
|
||||
data Datatype a = Datatype { datatypeContext :: a, datatypeName :: a, datatypeConstructors :: [a], datatypeDeriving :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Data.Syntax.Declaration.Datatype where liftEq = genericLiftEq
|
||||
instance Ord1 Data.Syntax.Declaration.Datatype where liftCompare = genericLiftCompare
|
||||
instance Show1 Data.Syntax.Declaration.Datatype where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Datatype
|
||||
|
||||
-- TODO: Implement Eval instance for Datatype
|
||||
instance Evaluatable Data.Syntax.Declaration.Datatype
|
||||
@ -302,10 +267,7 @@ instance Evaluatable Data.Syntax.Declaration.Datatype
|
||||
-- | A single constructor in a datatype, or equally a 'struct' in C, Rust, or Swift.
|
||||
data Constructor a = Constructor { constructorContext :: [a], constructorName :: a, constructorFields :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Data.Syntax.Declaration.Constructor where liftEq = genericLiftEq
|
||||
instance Ord1 Data.Syntax.Declaration.Constructor where liftCompare = genericLiftCompare
|
||||
instance Show1 Data.Syntax.Declaration.Constructor where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Constructor
|
||||
|
||||
-- TODO: Implement Eval instance for Constructor
|
||||
instance Evaluatable Data.Syntax.Declaration.Constructor
|
||||
@ -314,10 +276,7 @@ instance Evaluatable Data.Syntax.Declaration.Constructor
|
||||
-- | Comprehension (e.g. ((a for b in c if a()) in Python)
|
||||
data Comprehension a = Comprehension { comprehensionValue :: !a, comprehensionBody :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Comprehension where liftEq = genericLiftEq
|
||||
instance Ord1 Comprehension where liftCompare = genericLiftCompare
|
||||
instance Show1 Comprehension where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Comprehension
|
||||
|
||||
-- TODO: Implement Eval instance for Comprehension
|
||||
instance Evaluatable Comprehension
|
||||
@ -326,10 +285,7 @@ instance Evaluatable Comprehension
|
||||
-- | A declared type (e.g. `a []int` in Go).
|
||||
data Type a = Type { typeName :: !a, typeKind :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Type where liftEq = genericLiftEq
|
||||
instance Ord1 Type where liftCompare = genericLiftCompare
|
||||
instance Show1 Type where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Type
|
||||
|
||||
-- TODO: Implement Eval instance for Type
|
||||
instance Evaluatable Type
|
||||
@ -338,10 +294,7 @@ instance Evaluatable Type
|
||||
-- | Type alias declarations in Javascript/Haskell, etc.
|
||||
data TypeAlias a = TypeAlias { typeAliasContext :: ![a], typeAliasIdentifier :: !a, typeAliasKind :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 TypeAlias where liftEq = genericLiftEq
|
||||
instance Ord1 TypeAlias where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeAlias where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically TypeAlias
|
||||
|
||||
instance Evaluatable TypeAlias where
|
||||
eval _ _ TypeAlias{..} = do
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE DeriveAnyClass, MultiParamTypeClasses, ScopedTypeVariables, UndecidableInstances #-}
|
||||
{-# LANGUAGE DeriveAnyClass, DerivingVia, MultiParamTypeClasses, ScopedTypeVariables, UndecidableInstances #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
module Data.Syntax.Directive where
|
||||
|
||||
@ -17,10 +17,7 @@ import Reprinting.Tokenize
|
||||
-- A file directive like the Ruby constant `__FILE__`.
|
||||
data File a = File
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 File where liftEq = genericLiftEq
|
||||
instance Ord1 File where liftCompare = genericLiftCompare
|
||||
instance Show1 File where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically File
|
||||
|
||||
instance Evaluatable File where
|
||||
eval _ _ File = string . T.pack . modulePath <$> currentModule
|
||||
@ -33,10 +30,7 @@ instance Tokenize File where
|
||||
-- A line directive like the Ruby constant `__LINE__`.
|
||||
data Line a = Line
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Line where liftEq = genericLiftEq
|
||||
instance Ord1 Line where liftCompare = genericLiftCompare
|
||||
instance Show1 Line where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Line
|
||||
|
||||
instance Evaluatable Line where
|
||||
eval _ _ Line = integer . fromIntegral . posLine . spanStart <$> currentSpan
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE DeriveAnyClass, DuplicateRecordFields, MultiParamTypeClasses, ScopedTypeVariables, UndecidableInstances #-}
|
||||
{-# LANGUAGE DeriveAnyClass, DerivingVia, DuplicateRecordFields, MultiParamTypeClasses, ScopedTypeVariables, UndecidableInstances #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
module Data.Syntax.Expression where
|
||||
|
||||
@ -24,14 +24,11 @@ import Reprinting.Tokenize hiding (Superclass)
|
||||
-- | 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, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Call
|
||||
|
||||
instance Declarations1 Call where
|
||||
liftDeclaredName declaredName Call{..} = declaredName callFunction
|
||||
|
||||
instance Eq1 Call where liftEq = genericLiftEq
|
||||
instance Ord1 Call where liftCompare = genericLiftCompare
|
||||
instance Show1 Call where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
|
||||
instance Evaluatable Call where
|
||||
eval eval _ Call{..} = do
|
||||
op <- eval callFunction
|
||||
@ -47,10 +44,7 @@ instance Tokenize Call where
|
||||
|
||||
data LessThan a = LessThan { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 LessThan where liftEq = genericLiftEq
|
||||
instance Ord1 LessThan where liftCompare = genericLiftCompare
|
||||
instance Show1 LessThan where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically LessThan
|
||||
|
||||
instance Evaluatable LessThan where
|
||||
eval eval _ t = traverse eval t >>= go where
|
||||
@ -61,10 +55,7 @@ instance Tokenize LessThan where
|
||||
|
||||
data LessThanEqual a = LessThanEqual { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 LessThanEqual where liftEq = genericLiftEq
|
||||
instance Ord1 LessThanEqual where liftCompare = genericLiftCompare
|
||||
instance Show1 LessThanEqual where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically LessThanEqual
|
||||
|
||||
instance Evaluatable LessThanEqual where
|
||||
eval eval _ t = traverse eval t >>= go where
|
||||
@ -75,10 +66,7 @@ instance Tokenize LessThanEqual where
|
||||
|
||||
data GreaterThan a = GreaterThan { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 GreaterThan where liftEq = genericLiftEq
|
||||
instance Ord1 GreaterThan where liftCompare = genericLiftCompare
|
||||
instance Show1 GreaterThan where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically GreaterThan
|
||||
|
||||
instance Evaluatable GreaterThan where
|
||||
eval eval _ t = traverse eval t >>= go where
|
||||
@ -89,10 +77,7 @@ instance Tokenize GreaterThan where
|
||||
|
||||
data GreaterThanEqual a = GreaterThanEqual { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 GreaterThanEqual where liftEq = genericLiftEq
|
||||
instance Ord1 GreaterThanEqual where liftCompare = genericLiftCompare
|
||||
instance Show1 GreaterThanEqual where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically GreaterThanEqual
|
||||
|
||||
instance Evaluatable GreaterThanEqual where
|
||||
eval eval _ t = traverse eval t >>= go where
|
||||
@ -103,10 +88,7 @@ instance Tokenize GreaterThanEqual where
|
||||
|
||||
data Equal a = Equal { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Equal where liftEq = genericLiftEq
|
||||
instance Ord1 Equal where liftCompare = genericLiftCompare
|
||||
instance Show1 Equal where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Equal
|
||||
|
||||
instance Evaluatable Equal where
|
||||
eval eval _ t = traverse eval t >>= go where
|
||||
@ -119,10 +101,7 @@ instance Tokenize Equal where
|
||||
|
||||
data StrictEqual a = StrictEqual { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 StrictEqual where liftEq = genericLiftEq
|
||||
instance Ord1 StrictEqual where liftCompare = genericLiftCompare
|
||||
instance Show1 StrictEqual where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically StrictEqual
|
||||
|
||||
instance Evaluatable StrictEqual where
|
||||
eval eval _ t = traverse eval t >>= go where
|
||||
@ -135,10 +114,7 @@ instance Tokenize StrictEqual where
|
||||
|
||||
data Comparison a = Comparison { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Comparison where liftEq = genericLiftEq
|
||||
instance Ord1 Comparison where liftCompare = genericLiftCompare
|
||||
instance Show1 Comparison where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Comparison
|
||||
|
||||
instance Evaluatable Comparison where
|
||||
eval eval _ t = traverse eval t >>= go where
|
||||
@ -149,10 +125,7 @@ instance Tokenize Comparison where
|
||||
|
||||
data Plus a = Plus { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Plus where liftEq = genericLiftEq
|
||||
instance Ord1 Plus where liftCompare = genericLiftCompare
|
||||
instance Show1 Plus where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Plus
|
||||
|
||||
instance Evaluatable Plus where
|
||||
eval eval _ t = traverse eval t >>= go where
|
||||
@ -163,10 +136,7 @@ instance Tokenize Plus where
|
||||
|
||||
data Minus a = Minus { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Minus where liftEq = genericLiftEq
|
||||
instance Ord1 Minus where liftCompare = genericLiftCompare
|
||||
instance Show1 Minus where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Minus
|
||||
|
||||
instance Evaluatable Minus where
|
||||
eval eval _ t = traverse eval t >>= go where
|
||||
@ -177,10 +147,7 @@ instance Tokenize Minus where
|
||||
|
||||
data Times a = Times { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Times where liftEq = genericLiftEq
|
||||
instance Ord1 Times where liftCompare = genericLiftCompare
|
||||
instance Show1 Times where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Times
|
||||
|
||||
instance Evaluatable Times where
|
||||
eval eval _ t = traverse eval t >>= go where
|
||||
@ -191,10 +158,7 @@ instance Tokenize Times where
|
||||
|
||||
data DividedBy a = DividedBy { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 DividedBy where liftEq = genericLiftEq
|
||||
instance Ord1 DividedBy where liftCompare = genericLiftCompare
|
||||
instance Show1 DividedBy where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically DividedBy
|
||||
|
||||
instance Evaluatable DividedBy where
|
||||
eval eval _ t = traverse eval t >>= go where
|
||||
@ -205,10 +169,7 @@ instance Tokenize DividedBy where
|
||||
|
||||
data Modulo a = Modulo { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Modulo where liftEq = genericLiftEq
|
||||
instance Ord1 Modulo where liftCompare = genericLiftCompare
|
||||
instance Show1 Modulo where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Modulo
|
||||
|
||||
instance Evaluatable Modulo where
|
||||
eval eval _ t = traverse eval t >>= go where
|
||||
@ -219,10 +180,7 @@ instance Tokenize Modulo where
|
||||
|
||||
data Power a = Power { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Power where liftEq = genericLiftEq
|
||||
instance Ord1 Power where liftCompare = genericLiftCompare
|
||||
instance Show1 Power where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Power
|
||||
|
||||
instance Evaluatable Power where
|
||||
eval eval _ t = traverse eval t >>= go where
|
||||
@ -233,10 +191,7 @@ instance Tokenize Power where
|
||||
|
||||
newtype Negate a = Negate { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Negate where liftEq = genericLiftEq
|
||||
instance Ord1 Negate where liftCompare = genericLiftCompare
|
||||
instance Show1 Negate where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Negate
|
||||
|
||||
instance Evaluatable Negate where
|
||||
eval eval _ t = traverse eval t >>= go where
|
||||
@ -247,10 +202,7 @@ instance Tokenize Negate where
|
||||
|
||||
data FloorDivision a = FloorDivision { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 FloorDivision where liftEq = genericLiftEq
|
||||
instance Ord1 FloorDivision where liftCompare = genericLiftCompare
|
||||
instance Show1 FloorDivision where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically FloorDivision
|
||||
|
||||
instance Evaluatable FloorDivision where
|
||||
eval eval _ t = traverse eval t >>= go where
|
||||
@ -262,10 +214,8 @@ instance Tokenize FloorDivision where
|
||||
-- | Regex matching operators (Ruby's =~ and ~!)
|
||||
data Matches a = Matches { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Matches
|
||||
|
||||
instance Eq1 Matches where liftEq = genericLiftEq
|
||||
instance Ord1 Matches where liftCompare = genericLiftCompare
|
||||
instance Show1 Matches where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable Matches
|
||||
|
||||
instance Tokenize Matches where
|
||||
@ -273,10 +223,8 @@ instance Tokenize Matches where
|
||||
|
||||
data NotMatches a = NotMatches { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically NotMatches
|
||||
|
||||
instance Eq1 NotMatches where liftEq = genericLiftEq
|
||||
instance Ord1 NotMatches where liftCompare = genericLiftCompare
|
||||
instance Show1 NotMatches where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable NotMatches
|
||||
|
||||
instance Tokenize NotMatches where
|
||||
@ -284,10 +232,7 @@ instance Tokenize NotMatches where
|
||||
|
||||
data Or a = Or { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Or where liftEq = genericLiftEq
|
||||
instance Ord1 Or where liftCompare = genericLiftCompare
|
||||
instance Show1 Or where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Or
|
||||
|
||||
instance Evaluatable Or where
|
||||
eval eval _ (Or a b) = do
|
||||
@ -299,10 +244,8 @@ instance Tokenize Or where
|
||||
|
||||
data And a = And { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically And
|
||||
|
||||
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
|
||||
a' <- eval a
|
||||
@ -313,10 +256,7 @@ instance Tokenize And where
|
||||
|
||||
newtype Not a = Not { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Not where liftEq = genericLiftEq
|
||||
instance Ord1 Not where liftCompare = genericLiftCompare
|
||||
instance Show1 Not where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Not
|
||||
|
||||
instance Evaluatable Not where
|
||||
eval eval _ (Not a) = eval a >>= asBool >>= boolean . not
|
||||
@ -326,10 +266,7 @@ instance Tokenize Not where
|
||||
|
||||
data XOr a = XOr { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 XOr where liftEq = genericLiftEq
|
||||
instance Ord1 XOr where liftCompare = genericLiftCompare
|
||||
instance Show1 XOr where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically XOr
|
||||
|
||||
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
|
||||
@ -341,10 +278,7 @@ instance Tokenize XOr where
|
||||
-- | Javascript delete operator
|
||||
newtype Delete a = Delete { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Delete where liftEq = genericLiftEq
|
||||
instance Ord1 Delete where liftCompare = genericLiftCompare
|
||||
instance Show1 Delete where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Delete
|
||||
|
||||
instance Evaluatable Delete where
|
||||
eval _ ref (Delete a) = ref a >>= dealloc >> pure unit
|
||||
@ -352,10 +286,7 @@ instance Evaluatable Delete where
|
||||
-- | A sequence expression such as Javascript or C's comma operator.
|
||||
data SequenceExpression a = SequenceExpression { firstExpression :: !a, secondExpression :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 SequenceExpression where liftEq = genericLiftEq
|
||||
instance Ord1 SequenceExpression where liftCompare = genericLiftCompare
|
||||
instance Show1 SequenceExpression where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically SequenceExpression
|
||||
|
||||
instance Evaluatable SequenceExpression where
|
||||
eval eval _ (SequenceExpression a b) =
|
||||
@ -364,10 +295,7 @@ instance Evaluatable SequenceExpression where
|
||||
-- | Javascript void operator
|
||||
newtype Void a = Void { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Void where liftEq = genericLiftEq
|
||||
instance Ord1 Void where liftCompare = genericLiftCompare
|
||||
instance Show1 Void where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Void
|
||||
|
||||
instance Evaluatable Void where
|
||||
eval eval _ (Void a) =
|
||||
@ -376,10 +304,7 @@ instance Evaluatable Void where
|
||||
-- | Javascript typeof operator
|
||||
newtype Typeof a = Typeof { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Typeof where liftEq = genericLiftEq
|
||||
instance Ord1 Typeof where liftCompare = genericLiftCompare
|
||||
instance Show1 Typeof where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Typeof
|
||||
|
||||
-- TODO: Implement Eval instance for Typeof
|
||||
instance Evaluatable Typeof
|
||||
@ -387,10 +312,8 @@ 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, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically BOr
|
||||
|
||||
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
|
||||
a' <- eval a >>= castToInteger
|
||||
@ -402,10 +325,8 @@ instance Tokenize BOr where
|
||||
|
||||
data BAnd a = BAnd { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically BAnd
|
||||
|
||||
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
|
||||
a' <- eval a >>= castToInteger
|
||||
@ -417,10 +338,8 @@ instance Tokenize BAnd where
|
||||
|
||||
data BXOr a = BXOr { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically BXOr
|
||||
|
||||
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
|
||||
a' <- eval a >>= castToInteger
|
||||
@ -432,10 +351,8 @@ instance Tokenize BXOr where
|
||||
|
||||
data LShift a = LShift { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically LShift
|
||||
|
||||
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
|
||||
a' <- eval a >>= castToInteger
|
||||
@ -449,10 +366,8 @@ instance Tokenize LShift where
|
||||
|
||||
data RShift a = RShift { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically RShift
|
||||
|
||||
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
|
||||
a' <- eval a >>= castToInteger
|
||||
@ -466,10 +381,8 @@ instance Tokenize RShift where
|
||||
|
||||
data UnsignedRShift a = UnsignedRShift { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically UnsignedRShift
|
||||
|
||||
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
|
||||
a' <- eval a >>= castToInteger
|
||||
@ -478,10 +391,7 @@ instance Evaluatable UnsignedRShift where
|
||||
|
||||
newtype Complement a = Complement { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Complement where liftEq = genericLiftEq
|
||||
instance Ord1 Complement where liftCompare = genericLiftCompare
|
||||
instance Show1 Complement where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Complement
|
||||
|
||||
instance Evaluatable Complement where
|
||||
eval eval _ (Complement a) = do
|
||||
@ -494,14 +404,11 @@ instance Tokenize Complement where
|
||||
-- | Member Access (e.g. a.b)
|
||||
data MemberAccess a = MemberAccess { lhs :: a, rhs :: Name }
|
||||
deriving (Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically MemberAccess
|
||||
|
||||
instance Declarations1 MemberAccess where
|
||||
liftDeclaredName _ MemberAccess{..} = Just rhs
|
||||
|
||||
instance Eq1 MemberAccess where liftEq = genericLiftEq
|
||||
instance Ord1 MemberAccess where liftCompare = genericLiftCompare
|
||||
instance Show1 MemberAccess where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable MemberAccess where
|
||||
eval eval _ MemberAccess{..} = do
|
||||
lhsValue <- eval lhs
|
||||
@ -534,10 +441,7 @@ instance Tokenize MemberAccess where
|
||||
-- | Subscript (e.g a[1])
|
||||
data Subscript a = Subscript { lhs :: a, rhs :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Subscript where liftEq = genericLiftEq
|
||||
instance Ord1 Subscript where liftCompare = genericLiftCompare
|
||||
instance Show1 Subscript where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Subscript
|
||||
|
||||
-- TODO: Finish Eval instance for Subscript
|
||||
-- TODO return a special LvalSubscript instance here
|
||||
@ -550,10 +454,7 @@ instance Tokenize Subscript where
|
||||
|
||||
data Member a = Member { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Member where liftEq = genericLiftEq
|
||||
instance Ord1 Member where liftCompare = genericLiftCompare
|
||||
instance Show1 Member where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Member
|
||||
|
||||
instance Evaluatable Member where
|
||||
|
||||
@ -563,10 +464,7 @@ instance Tokenize Member where
|
||||
-- | Enumeration (e.g. a[1:10:1] in Python (start at index 1, stop at index 10, step 1 element from start to stop))
|
||||
data Enumeration a = Enumeration { enumerationStart :: !a, enumerationEnd :: !a, enumerationStep :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Enumeration where liftEq = genericLiftEq
|
||||
instance Ord1 Enumeration where liftCompare = genericLiftCompare
|
||||
instance Show1 Enumeration where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Enumeration
|
||||
|
||||
-- TODO: Implement Eval instance for Enumeration
|
||||
instance Evaluatable Enumeration
|
||||
@ -577,10 +475,7 @@ instance Tokenize Enumeration where
|
||||
-- | InstanceOf (e.g. a instanceof b in JavaScript
|
||||
data InstanceOf a = InstanceOf { instanceOfSubject :: !a, instanceOfObject :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 InstanceOf where liftEq = genericLiftEq
|
||||
instance Ord1 InstanceOf where liftCompare = genericLiftCompare
|
||||
instance Show1 InstanceOf where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically InstanceOf
|
||||
|
||||
-- TODO: Implement Eval instance for InstanceOf
|
||||
instance Evaluatable InstanceOf
|
||||
@ -589,11 +484,9 @@ 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, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ScopeResolution
|
||||
|
||||
instance Hashable1 ScopeResolution where liftHashWithSalt = foldl
|
||||
instance Eq1 ScopeResolution where liftEq = genericLiftEq
|
||||
instance Ord1 ScopeResolution where liftCompare = genericLiftCompare
|
||||
instance Show1 ScopeResolution where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable ScopeResolution
|
||||
|
||||
@ -607,10 +500,7 @@ 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, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 NonNullExpression where liftEq = genericLiftEq
|
||||
instance Ord1 NonNullExpression where liftCompare = genericLiftCompare
|
||||
instance Show1 NonNullExpression where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically NonNullExpression
|
||||
|
||||
-- TODO: Implement Eval instance for NonNullExpression
|
||||
instance Evaluatable NonNullExpression
|
||||
@ -619,11 +509,7 @@ instance Evaluatable NonNullExpression
|
||||
-- | An await expression in Javascript or C#.
|
||||
newtype Await a = Await { awaitSubject :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Await where liftEq = genericLiftEq
|
||||
instance Ord1 Await where liftCompare = genericLiftCompare
|
||||
instance Show1 Await where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
deriving (Eq1, Show1, Ord1) via Generically Await
|
||||
-- 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
|
||||
@ -632,14 +518,11 @@ instance Evaluatable Await where
|
||||
-- | An object constructor call in Javascript, Java, etc.
|
||||
data New a = New { subject :: a , typeParameters :: a, arguments :: [a] }
|
||||
deriving (Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically New
|
||||
|
||||
instance Declarations1 New where
|
||||
liftDeclaredName declaredName New{..} = declaredName subject
|
||||
|
||||
instance Eq1 New where liftEq = genericLiftEq
|
||||
instance Ord1 New where liftCompare = genericLiftCompare
|
||||
instance Show1 New where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for New
|
||||
instance Evaluatable New where
|
||||
eval eval _ New{..} = do
|
||||
@ -673,19 +556,14 @@ instance Evaluatable New where
|
||||
-- | A cast expression to a specified type.
|
||||
data Cast a = Cast { castSubject :: !a, castType :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Cast where liftEq = genericLiftEq
|
||||
instance Ord1 Cast where liftCompare = genericLiftCompare
|
||||
instance Show1 Cast where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Cast
|
||||
|
||||
instance Evaluatable Cast
|
||||
|
||||
data Super a = Super
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Super
|
||||
|
||||
instance Eq1 Super where liftEq = genericLiftEq
|
||||
instance Ord1 Super where liftCompare = genericLiftCompare
|
||||
instance Show1 Super where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable Super
|
||||
|
||||
instance Tokenize Super where
|
||||
@ -693,13 +571,11 @@ instance Tokenize Super where
|
||||
|
||||
data This a = This
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically This
|
||||
|
||||
instance Tokenize This where
|
||||
tokenize _ = yield Self
|
||||
|
||||
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
|
||||
reference (Reference __self) (Declaration __self)
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE DeriveAnyClass, DuplicateRecordFields, ScopedTypeVariables, ViewPatterns #-}
|
||||
{-# LANGUAGE DeriveAnyClass, DerivingVia, DuplicateRecordFields, ScopedTypeVariables, ViewPatterns #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
module Data.Syntax.Literal where
|
||||
|
||||
@ -19,7 +19,9 @@ import Text.Read (readMaybe)
|
||||
-- Boolean
|
||||
|
||||
newtype Boolean a = Boolean { booleanContent :: Bool }
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1, NFData1)
|
||||
deriving stock (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1)
|
||||
deriving anyclass (Hashable1, Diffable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Ord1, Show1) via Generically Boolean
|
||||
|
||||
true :: Boolean a
|
||||
true = Boolean True
|
||||
@ -27,25 +29,16 @@ true = Boolean True
|
||||
false :: Boolean a
|
||||
false = Boolean False
|
||||
|
||||
instance Eq1 Boolean where liftEq = genericLiftEq
|
||||
instance Ord1 Boolean where liftCompare = genericLiftCompare
|
||||
instance Show1 Boolean where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Boolean where
|
||||
eval _ _ (Boolean x) = boolean x
|
||||
|
||||
instance Tokenize Boolean where
|
||||
tokenize = yield . Truth . booleanContent
|
||||
|
||||
-- Numeric
|
||||
|
||||
-- | A literal integer of unspecified width. No particular base is implied.
|
||||
newtype Integer a = Integer { integerContent :: Text }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
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
|
||||
deriving (Eq1, Ord1, Show1) via Generically Data.Syntax.Literal.Integer
|
||||
|
||||
instance Evaluatable Data.Syntax.Literal.Integer where
|
||||
-- TODO: We should use something more robust than shelling out to readMaybe.
|
||||
@ -59,10 +52,8 @@ instance Tokenize Data.Syntax.Literal.Integer where
|
||||
|
||||
newtype Float a = Float { floatContent :: Text }
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Ord1, Show1) via Generically Data.Syntax.Literal.Float
|
||||
|
||||
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
|
||||
eval _ _ (Float s) =
|
||||
@ -74,10 +65,7 @@ instance Tokenize Data.Syntax.Literal.Float where
|
||||
-- Rational literals e.g. `2/3r`
|
||||
newtype Rational a = Rational { value :: Text }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
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
|
||||
deriving (Eq1, Ord1, Show1) via Generically Data.Syntax.Literal.Rational
|
||||
|
||||
instance Evaluatable Data.Syntax.Literal.Rational where
|
||||
eval _ _ (Rational r) =
|
||||
@ -92,10 +80,7 @@ instance Tokenize Data.Syntax.Literal.Rational where
|
||||
-- Complex literals e.g. `3 + 2i`
|
||||
newtype Complex a = Complex { value :: Text }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Data.Syntax.Literal.Complex where liftEq = genericLiftEq
|
||||
instance Ord1 Data.Syntax.Literal.Complex where liftCompare = genericLiftCompare
|
||||
instance Show1 Data.Syntax.Literal.Complex where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Ord1, Show1) via Generically Complex
|
||||
|
||||
-- TODO: Implement Eval instance for Complex
|
||||
instance Evaluatable Complex
|
||||
@ -107,10 +92,7 @@ instance Tokenize Complex where
|
||||
|
||||
newtype String a = String { stringElements :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Data.Syntax.Literal.String where liftEq = genericLiftEq
|
||||
instance Ord1 Data.Syntax.Literal.String where liftCompare = genericLiftCompare
|
||||
instance Show1 Data.Syntax.Literal.String where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Ord1, Show1) via Generically Data.Syntax.Literal.String
|
||||
|
||||
-- TODO: Should string literal bodies include escapes too?
|
||||
|
||||
@ -122,10 +104,7 @@ instance Tokenize Data.Syntax.Literal.String where
|
||||
|
||||
newtype Character a = Character { characterContent :: Text }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Data.Syntax.Literal.Character where liftEq = genericLiftEq
|
||||
instance Ord1 Data.Syntax.Literal.Character where liftCompare = genericLiftCompare
|
||||
instance Show1 Data.Syntax.Literal.Character where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Ord1, Show1) via Generically Character
|
||||
|
||||
instance Evaluatable Data.Syntax.Literal.Character
|
||||
|
||||
@ -135,10 +114,7 @@ instance Tokenize Character where
|
||||
-- | An interpolation element within a string literal.
|
||||
newtype InterpolationElement a = InterpolationElement { interpolationBody :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 InterpolationElement where liftEq = genericLiftEq
|
||||
instance Ord1 InterpolationElement where liftCompare = genericLiftCompare
|
||||
instance Show1 InterpolationElement where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Ord1, Show1) via Generically InterpolationElement
|
||||
|
||||
-- TODO: Implement Eval instance for InterpolationElement
|
||||
instance Evaluatable InterpolationElement
|
||||
@ -149,10 +125,7 @@ instance Tokenize InterpolationElement where
|
||||
-- | A sequence of textual contents within a string literal.
|
||||
newtype TextElement a = TextElement { textElementContent :: Text }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 TextElement where liftEq = genericLiftEq
|
||||
instance Ord1 TextElement where liftCompare = genericLiftCompare
|
||||
instance Show1 TextElement where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Ord1, Show1) via Generically TextElement
|
||||
|
||||
instance Evaluatable TextElement where
|
||||
eval _ _ (TextElement x) = pure (string x)
|
||||
@ -171,10 +144,7 @@ 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, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 EscapeSequence where liftEq = genericLiftEq
|
||||
instance Ord1 EscapeSequence where liftCompare = genericLiftCompare
|
||||
instance Show1 EscapeSequence where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Ord1, Show1) via Generically EscapeSequence
|
||||
|
||||
-- TODO: Implement Eval instance for EscapeSequence
|
||||
instance Evaluatable EscapeSequence
|
||||
@ -184,10 +154,7 @@ instance Tokenize EscapeSequence where
|
||||
|
||||
data Null a = Null
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Null where liftEq = genericLiftEq
|
||||
instance Ord1 Null where liftCompare = genericLiftCompare
|
||||
instance Show1 Null where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Ord1, Show1) via Generically Null
|
||||
|
||||
instance Evaluatable Null where eval _ _ _ = pure null
|
||||
|
||||
@ -196,10 +163,7 @@ instance Tokenize Null where
|
||||
|
||||
newtype Symbol a = Symbol { symbolElements :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Symbol where liftEq = genericLiftEq
|
||||
instance Ord1 Symbol where liftCompare = genericLiftCompare
|
||||
instance Show1 Symbol where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Ord1, Show1) via Generically Symbol
|
||||
|
||||
-- TODO: Implement Eval instance for Symbol
|
||||
instance Evaluatable Symbol
|
||||
@ -209,10 +173,7 @@ instance Tokenize Symbol where
|
||||
|
||||
newtype SymbolElement a = SymbolElement { symbolContent :: Text }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 SymbolElement where liftEq = genericLiftEq
|
||||
instance Ord1 SymbolElement where liftCompare = genericLiftCompare
|
||||
instance Show1 SymbolElement where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Ord1, Show1) via Generically SymbolElement
|
||||
|
||||
instance Evaluatable SymbolElement where
|
||||
eval _ _ (SymbolElement s) = pure (symbol s)
|
||||
@ -222,10 +183,7 @@ instance Tokenize SymbolElement where
|
||||
|
||||
newtype Regex a = Regex { regexContent :: Text }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Regex where liftEq = genericLiftEq
|
||||
instance Ord1 Regex where liftCompare = genericLiftCompare
|
||||
instance Show1 Regex where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Ord1, Show1) via Generically Regex
|
||||
|
||||
-- TODO: Heredoc-style string literals?
|
||||
|
||||
@ -240,10 +198,7 @@ instance Tokenize Regex where
|
||||
|
||||
newtype Array a = Array { arrayElements :: [a] }
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Array where liftEq = genericLiftEq
|
||||
instance Ord1 Array where liftCompare = genericLiftCompare
|
||||
instance Show1 Array where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Ord1, Show1) via Generically Array
|
||||
|
||||
instance Evaluatable Array where
|
||||
eval eval _ Array{..} = array =<< traverse eval arrayElements
|
||||
@ -253,10 +208,7 @@ instance Tokenize Array where
|
||||
|
||||
newtype Hash a = Hash { hashElements :: [a] }
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Hash where liftEq = genericLiftEq
|
||||
instance Ord1 Hash where liftCompare = genericLiftCompare
|
||||
instance Show1 Hash where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Ord1, Show1) via Generically Hash
|
||||
|
||||
instance Evaluatable Hash where
|
||||
eval eval _ t = Eval.hash <$> traverse (eval >=> asPair) (hashElements t)
|
||||
@ -266,10 +218,7 @@ instance Tokenize Hash where
|
||||
|
||||
data KeyValue a = KeyValue { key :: !a, value :: !a }
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 KeyValue where liftEq = genericLiftEq
|
||||
instance Ord1 KeyValue where liftCompare = genericLiftCompare
|
||||
instance Show1 KeyValue where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Ord1, Show1) via Generically KeyValue
|
||||
|
||||
instance Evaluatable KeyValue where
|
||||
eval eval _ (fmap eval -> KeyValue{..}) =
|
||||
@ -280,20 +229,14 @@ instance Tokenize KeyValue where
|
||||
|
||||
newtype Tuple a = Tuple { tupleContents :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Tuple where liftEq = genericLiftEq
|
||||
instance Ord1 Tuple where liftCompare = genericLiftCompare
|
||||
instance Show1 Tuple where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Ord1, Show1) via Generically Tuple
|
||||
|
||||
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, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Set where liftEq = genericLiftEq
|
||||
instance Ord1 Set where liftCompare = genericLiftCompare
|
||||
instance Show1 Set where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Ord1, Show1) via Generically Set
|
||||
|
||||
-- TODO: Implement Eval instance for Set
|
||||
instance Evaluatable Set
|
||||
@ -304,10 +247,7 @@ instance Evaluatable Set
|
||||
-- | A declared pointer (e.g. var pointer *int in Go)
|
||||
newtype Pointer a = Pointer { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Pointer where liftEq = genericLiftEq
|
||||
instance Ord1 Pointer where liftCompare = genericLiftCompare
|
||||
instance Show1 Pointer where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Ord1, Show1) via Generically Pointer
|
||||
|
||||
-- TODO: Implement Eval instance for Pointer
|
||||
instance Evaluatable Pointer
|
||||
@ -316,10 +256,7 @@ instance Evaluatable Pointer
|
||||
-- | A reference to a pointer's address (e.g. &pointer in Go)
|
||||
newtype Reference a = Reference { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Reference where liftEq = genericLiftEq
|
||||
instance Ord1 Reference where liftCompare = genericLiftCompare
|
||||
instance Show1 Reference where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Ord1, Show1) via Generically Reference
|
||||
|
||||
-- TODO: Implement Eval instance for Reference
|
||||
instance Evaluatable Reference
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE DeriveAnyClass, ScopedTypeVariables, UndecidableInstances, ViewPatterns, DuplicateRecordFields #-}
|
||||
{-# LANGUAGE DeriveAnyClass, DerivingVia, ScopedTypeVariables, UndecidableInstances, ViewPatterns, DuplicateRecordFields #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
module Data.Syntax.Statement where
|
||||
|
||||
@ -26,10 +26,8 @@ import qualified Data.Reprinting.Scope as Scope
|
||||
-- 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, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Statements
|
||||
|
||||
instance Eq1 Statements where liftEq = genericLiftEq
|
||||
instance Ord1 Statements where liftCompare = genericLiftCompare
|
||||
instance Show1 Statements where liftShowsPrec = genericLiftShowsPrec
|
||||
instance ToJSON1 Statements
|
||||
|
||||
instance Evaluatable Statements where
|
||||
@ -41,10 +39,8 @@ instance Tokenize Statements where
|
||||
|
||||
newtype StatementBlock a = StatementBlock { statements :: [a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically StatementBlock
|
||||
|
||||
instance Eq1 StatementBlock where liftEq = genericLiftEq
|
||||
instance Ord1 StatementBlock where liftCompare = genericLiftCompare
|
||||
instance Show1 StatementBlock where liftShowsPrec = genericLiftShowsPrec
|
||||
instance ToJSON1 StatementBlock
|
||||
|
||||
instance Evaluatable StatementBlock where
|
||||
@ -57,10 +53,7 @@ instance Tokenize 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, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 If where liftEq = genericLiftEq
|
||||
instance Ord1 If where liftCompare = genericLiftCompare
|
||||
instance Show1 If where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically If
|
||||
|
||||
instance Evaluatable If where
|
||||
eval eval _ (If cond if' else') = do
|
||||
@ -78,10 +71,7 @@ instance Tokenize If where
|
||||
-- | Else statement. The else condition is any term, that upon successful completion, continues evaluation to the elseBody, e.g. `for ... else` in Python.
|
||||
data Else a = Else { elseCondition :: !a, elseBody :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Else where liftEq = genericLiftEq
|
||||
instance Ord1 Else where liftCompare = genericLiftCompare
|
||||
instance Show1 Else where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Else
|
||||
|
||||
-- TODO: Implement Eval instance for Else
|
||||
instance Evaluatable Else
|
||||
@ -94,22 +84,15 @@ instance Tokenize Else where
|
||||
-- | Goto statement (e.g. `goto a` in Go).
|
||||
newtype Goto a = Goto { gotoLocation :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Goto where liftEq = genericLiftEq
|
||||
instance Ord1 Goto where liftCompare = genericLiftCompare
|
||||
instance Show1 Goto where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Goto
|
||||
|
||||
-- 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, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Match where liftEq = genericLiftEq
|
||||
instance Ord1 Match where liftCompare = genericLiftCompare
|
||||
instance Show1 Match where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Match
|
||||
|
||||
-- TODO: Implement Eval instance for Match
|
||||
instance Evaluatable Match
|
||||
@ -124,10 +107,7 @@ instance Tokenize Match where
|
||||
-- | A pattern in a pattern-matching or computed jump control-flow statement, like 'case' in C or JavaScript, 'when' in Ruby, or the left-hand side of '->' in the body of Haskell 'case' expressions.
|
||||
data Pattern a = Pattern { value :: !a, patternBody :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Pattern where liftEq = genericLiftEq
|
||||
instance Ord1 Pattern where liftCompare = genericLiftCompare
|
||||
instance Show1 Pattern where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Pattern
|
||||
|
||||
-- TODO: Implement Eval instance for Pattern
|
||||
instance Evaluatable Pattern
|
||||
@ -138,10 +118,7 @@ instance Tokenize Pattern where
|
||||
-- | A let statement or local binding, like 'a as b' or 'let a = b'.
|
||||
data Let a = Let { letVariable :: !a, letValue :: !a, letBody :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Let where liftEq = genericLiftEq
|
||||
instance Ord1 Let where liftCompare = genericLiftCompare
|
||||
instance Show1 Let where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Let
|
||||
|
||||
instance Evaluatable Let where
|
||||
eval eval _ Let{..} = do
|
||||
@ -164,14 +141,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, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Assignment
|
||||
|
||||
instance Declarations1 Assignment where
|
||||
liftDeclaredName declaredName Assignment{..} = declaredName assignmentTarget
|
||||
|
||||
instance Eq1 Assignment where liftEq = genericLiftEq
|
||||
instance Ord1 Assignment where liftCompare = genericLiftCompare
|
||||
instance Show1 Assignment where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Assignment where
|
||||
eval eval ref Assignment{..} = do
|
||||
lhs <- ref assignmentTarget
|
||||
@ -198,10 +172,7 @@ instance Tokenize Assignment where
|
||||
-- | Post increment operator (e.g. 1++ in Go, or i++ in C).
|
||||
newtype PostIncrement a = PostIncrement { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 PostIncrement where liftEq = genericLiftEq
|
||||
instance Ord1 PostIncrement where liftCompare = genericLiftCompare
|
||||
instance Show1 PostIncrement where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically PostIncrement
|
||||
|
||||
-- TODO: Implement Eval instance for PostIncrement
|
||||
instance Evaluatable PostIncrement
|
||||
@ -210,10 +181,7 @@ instance Evaluatable PostIncrement
|
||||
-- | Post decrement operator (e.g. 1-- in Go, or i-- in C).
|
||||
newtype PostDecrement a = PostDecrement { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 PostDecrement where liftEq = genericLiftEq
|
||||
instance Ord1 PostDecrement where liftCompare = genericLiftCompare
|
||||
instance Show1 PostDecrement where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically PostDecrement
|
||||
|
||||
-- TODO: Implement Eval instance for PostDecrement
|
||||
instance Evaluatable PostDecrement
|
||||
@ -221,10 +189,7 @@ instance Evaluatable PostDecrement
|
||||
-- | Pre increment operator (e.g. ++1 in C or Java).
|
||||
newtype PreIncrement a = PreIncrement { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 PreIncrement where liftEq = genericLiftEq
|
||||
instance Ord1 PreIncrement where liftCompare = genericLiftCompare
|
||||
instance Show1 PreIncrement where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically PreIncrement
|
||||
|
||||
-- TODO: Implement Eval instance for PreIncrement
|
||||
instance Evaluatable PreIncrement
|
||||
@ -233,10 +198,7 @@ instance Evaluatable PreIncrement
|
||||
-- | Pre decrement operator (e.g. --1 in C or Java).
|
||||
newtype PreDecrement a = PreDecrement { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 PreDecrement where liftEq = genericLiftEq
|
||||
instance Ord1 PreDecrement where liftCompare = genericLiftCompare
|
||||
instance Show1 PreDecrement where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically PreDecrement
|
||||
|
||||
-- TODO: Implement Eval instance for PreDecrement
|
||||
instance Evaluatable PreDecrement
|
||||
@ -246,10 +208,7 @@ instance Evaluatable PreDecrement
|
||||
|
||||
newtype Return a = Return { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Return where liftEq = genericLiftEq
|
||||
instance Ord1 Return where liftCompare = genericLiftCompare
|
||||
instance Show1 Return where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Return
|
||||
|
||||
instance Evaluatable Return where
|
||||
eval eval _ (Return x) = eval x >>= earlyReturn
|
||||
@ -259,10 +218,7 @@ instance Tokenize Return where
|
||||
|
||||
newtype Yield a = Yield { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Yield where liftEq = genericLiftEq
|
||||
instance Ord1 Yield where liftCompare = genericLiftCompare
|
||||
instance Show1 Yield where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Yield
|
||||
|
||||
-- TODO: Implement Eval instance for Yield
|
||||
instance Evaluatable Yield
|
||||
@ -273,10 +229,7 @@ instance Tokenize Yield where
|
||||
|
||||
newtype Break a = Break { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Break where liftEq = genericLiftEq
|
||||
instance Ord1 Break where liftCompare = genericLiftCompare
|
||||
instance Show1 Break where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Break
|
||||
|
||||
instance Evaluatable Break where
|
||||
eval eval _ (Break x) = eval x >>= throwBreak
|
||||
@ -286,10 +239,7 @@ instance Tokenize Break where
|
||||
|
||||
newtype Continue a = Continue { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Continue where liftEq = genericLiftEq
|
||||
instance Ord1 Continue where liftCompare = genericLiftCompare
|
||||
instance Show1 Continue where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Continue
|
||||
|
||||
instance Evaluatable Continue where
|
||||
eval eval _ (Continue x) = eval x >>= throwContinue
|
||||
@ -299,10 +249,7 @@ instance Tokenize Continue where
|
||||
|
||||
newtype Retry a = Retry { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Retry where liftEq = genericLiftEq
|
||||
instance Ord1 Retry where liftCompare = genericLiftCompare
|
||||
instance Show1 Retry where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Retry
|
||||
|
||||
-- TODO: Implement Eval instance for Retry
|
||||
instance Evaluatable Retry
|
||||
@ -312,10 +259,7 @@ instance Tokenize Retry where
|
||||
|
||||
newtype NoOp a = NoOp { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 NoOp where liftEq = genericLiftEq
|
||||
instance Ord1 NoOp where liftCompare = genericLiftCompare
|
||||
instance Show1 NoOp where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically NoOp
|
||||
|
||||
instance Evaluatable NoOp where
|
||||
eval _ _ _ = pure unit
|
||||
@ -324,21 +268,14 @@ instance Evaluatable NoOp where
|
||||
|
||||
data For a = For { forBefore :: !a, forCondition :: !a, forStep :: !a, forBody :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 For where liftEq = genericLiftEq
|
||||
instance Ord1 For where liftCompare = genericLiftCompare
|
||||
instance Show1 For where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically For
|
||||
|
||||
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, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ForEach where liftEq = genericLiftEq
|
||||
instance Ord1 ForEach where liftCompare = genericLiftCompare
|
||||
instance Show1 ForEach where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically ForEach
|
||||
|
||||
-- TODO: Implement Eval instance for ForEach
|
||||
instance Evaluatable ForEach
|
||||
@ -353,10 +290,7 @@ instance Tokenize ForEach where
|
||||
|
||||
data While a = While { whileCondition :: !a, whileBody :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 While where liftEq = genericLiftEq
|
||||
instance Ord1 While where liftCompare = genericLiftCompare
|
||||
instance Show1 While where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically While
|
||||
|
||||
instance Evaluatable While where
|
||||
eval eval _ While{..} = while (eval whileCondition) (eval whileBody)
|
||||
@ -369,10 +303,7 @@ instance Tokenize While where
|
||||
|
||||
data DoWhile a = DoWhile { doWhileCondition :: !a, doWhileBody :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 DoWhile where liftEq = genericLiftEq
|
||||
instance Ord1 DoWhile where liftCompare = genericLiftCompare
|
||||
instance Show1 DoWhile where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically DoWhile
|
||||
|
||||
instance Evaluatable DoWhile where
|
||||
eval eval _ DoWhile{..} = doWhile (eval doWhileBody) (eval doWhileCondition)
|
||||
@ -381,10 +312,7 @@ instance Evaluatable DoWhile where
|
||||
|
||||
newtype Throw a = Throw { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Throw where liftEq = genericLiftEq
|
||||
instance Ord1 Throw where liftCompare = genericLiftCompare
|
||||
instance Show1 Throw where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Throw
|
||||
|
||||
-- TODO: Implement Eval instance for Throw
|
||||
instance Evaluatable Throw
|
||||
@ -392,10 +320,7 @@ instance Evaluatable Throw
|
||||
|
||||
data Try a = Try { tryBody :: !a, tryCatch :: ![a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Try where liftEq = genericLiftEq
|
||||
instance Ord1 Try where liftCompare = genericLiftCompare
|
||||
instance Show1 Try where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Try
|
||||
|
||||
-- TODO: Implement Eval instance for Try
|
||||
instance Evaluatable Try
|
||||
@ -409,10 +334,7 @@ instance Tokenize Try where
|
||||
|
||||
data Catch a = Catch { catchException :: !a, catchBody :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Catch where liftEq = genericLiftEq
|
||||
instance Ord1 Catch where liftCompare = genericLiftCompare
|
||||
instance Show1 Catch where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Catch
|
||||
|
||||
-- TODO: Implement Eval instance for Catch
|
||||
instance Evaluatable Catch
|
||||
@ -422,10 +344,7 @@ instance Tokenize Catch where
|
||||
|
||||
newtype Finally a = Finally { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Finally where liftEq = genericLiftEq
|
||||
instance Ord1 Finally where liftCompare = genericLiftCompare
|
||||
instance Show1 Finally where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Finally
|
||||
|
||||
-- TODO: Implement Eval instance for Finally
|
||||
instance Evaluatable Finally
|
||||
@ -438,10 +357,7 @@ instance Tokenize Finally where
|
||||
-- | ScopeEntry (e.g. `BEGIN {}` block in Ruby or Perl).
|
||||
newtype ScopeEntry a = ScopeEntry { terms :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ScopeEntry where liftEq = genericLiftEq
|
||||
instance Ord1 ScopeEntry where liftCompare = genericLiftCompare
|
||||
instance Show1 ScopeEntry where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically ScopeEntry
|
||||
|
||||
-- TODO: Implement Eval instance for ScopeEntry
|
||||
instance Evaluatable ScopeEntry
|
||||
@ -453,10 +369,7 @@ instance Tokenize ScopeEntry where
|
||||
-- | ScopeExit (e.g. `END {}` block in Ruby or Perl).
|
||||
newtype ScopeExit a = ScopeExit { terms :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ScopeExit where liftEq = genericLiftEq
|
||||
instance Ord1 ScopeExit where liftCompare = genericLiftCompare
|
||||
instance Show1 ScopeExit where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically ScopeExit
|
||||
|
||||
-- TODO: Implement Eval instance for ScopeExit
|
||||
instance Evaluatable ScopeExit
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE DataKinds, DeriveAnyClass, DuplicateRecordFields, DeriveGeneric, MultiParamTypeClasses, UndecidableInstances #-}
|
||||
{-# LANGUAGE DataKinds, DeriveAnyClass, DerivingVia, DuplicateRecordFields, DeriveGeneric, MultiParamTypeClasses, UndecidableInstances #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
module Data.Syntax.Type where
|
||||
|
||||
@ -10,26 +10,21 @@ import Prologue hiding (Map)
|
||||
import Proto3.Suite.Class
|
||||
import Reprinting.Tokenize
|
||||
|
||||
data Array a = Array { arraySize :: !(Maybe a), arrayElementType :: !a }
|
||||
data Array a = Array { arraySize :: Maybe a, arrayElementType :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Array
|
||||
|
||||
instance Named1 Array where nameOf1 _ = "TypeArray"
|
||||
|
||||
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
|
||||
|
||||
|
||||
-- TODO: What about type variables? re: FreeVariables1
|
||||
data Annotation a = Annotation { annotationSubject :: !a, annotationType :: !a }
|
||||
data Annotation a = Annotation { annotationSubject :: a, annotationType :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Annotation where liftEq = genericLiftEq
|
||||
instance Ord1 Annotation where liftCompare = genericLiftCompare
|
||||
instance Show1 Annotation where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Annotation
|
||||
|
||||
-- TODO: Specialize Evaluatable for Type to unify the inferred type of the subject with the specified type
|
||||
instance Evaluatable Annotation where
|
||||
@ -41,13 +36,11 @@ instance Tokenize Annotation where
|
||||
tokenize Annotation{..} = annotationSubject
|
||||
|
||||
|
||||
data Function a = Function { functionParameters :: ![a], functionReturn :: !a }
|
||||
data Function a = Function { functionParameters :: [a], functionReturn :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Function
|
||||
|
||||
instance Named1 Function where nameOf1 _ = "TypeFunction"
|
||||
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
|
||||
@ -55,55 +48,37 @@ instance Evaluatable Function
|
||||
|
||||
newtype Interface a = Interface { values :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Interface where liftEq = genericLiftEq
|
||||
instance Ord1 Interface where liftCompare = genericLiftCompare
|
||||
instance Show1 Interface where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Interface
|
||||
|
||||
-- TODO: Implement Eval instance for Interface
|
||||
instance Evaluatable Interface
|
||||
|
||||
|
||||
data Map a = Map { mapKeyType :: !a, mapElementType :: !a }
|
||||
data Map a = Map { mapKeyType :: a, mapElementType :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Map where liftEq = genericLiftEq
|
||||
instance Ord1 Map where liftCompare = genericLiftCompare
|
||||
instance Show1 Map where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Map
|
||||
|
||||
-- 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, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Parenthesized where liftEq = genericLiftEq
|
||||
instance Ord1 Parenthesized where liftCompare = genericLiftCompare
|
||||
instance Show1 Parenthesized where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Parenthesized
|
||||
|
||||
-- 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, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Pointer
|
||||
|
||||
instance Named1 Pointer where nameOf1 _ = "TypePointer"
|
||||
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, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Product where liftEq = genericLiftEq
|
||||
instance Ord1 Product where liftCompare = genericLiftCompare
|
||||
instance Show1 Product where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Product
|
||||
|
||||
-- TODO: Implement Eval instance for Product
|
||||
instance Evaluatable Product
|
||||
@ -111,33 +86,23 @@ instance Evaluatable Product
|
||||
|
||||
data Readonly a = Readonly
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Readonly where liftEq = genericLiftEq
|
||||
instance Ord1 Readonly where liftCompare = genericLiftCompare
|
||||
instance Show1 Readonly where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Readonly
|
||||
|
||||
-- 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, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Slice
|
||||
|
||||
instance Named1 Slice where nameOf1 _ = "TypeSlice"
|
||||
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, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 TypeParameters where liftEq = genericLiftEq
|
||||
instance Ord1 TypeParameters where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeParameters where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically TypeParameters
|
||||
|
||||
-- TODO: Implement Eval instance for TypeParameters
|
||||
instance Evaluatable TypeParameters
|
||||
@ -145,10 +110,7 @@ instance Evaluatable TypeParameters
|
||||
-- data instead of newtype because no payload
|
||||
data Void a = Void
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Void where liftEq = genericLiftEq
|
||||
instance Ord1 Void where liftCompare = genericLiftCompare
|
||||
instance Show1 Void where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Void
|
||||
|
||||
-- TODO: Implement Eval instance for Void
|
||||
instance Evaluatable Void
|
||||
@ -156,42 +118,30 @@ instance Evaluatable Void
|
||||
-- data instead of newtype because no payload
|
||||
data Int a = Int
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Int where liftEq = genericLiftEq
|
||||
instance Ord1 Int where liftCompare = genericLiftCompare
|
||||
instance Show1 Int where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Int
|
||||
|
||||
-- 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, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Float
|
||||
|
||||
instance Named1 Float where nameOf1 _ = "TypeFloat"
|
||||
|
||||
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, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Double where liftEq = genericLiftEq
|
||||
instance Ord1 Double where liftCompare = genericLiftCompare
|
||||
instance Show1 Double where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Double
|
||||
|
||||
-- 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, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Bool where liftEq = genericLiftEq
|
||||
instance Ord1 Bool where liftCompare = genericLiftCompare
|
||||
instance Show1 Bool where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Bool
|
||||
|
||||
-- TODO: Implement Eval instance for Float
|
||||
instance Evaluatable Bool
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE DeriveAnyClass #-}
|
||||
{-# LANGUAGE DeriveAnyClass, DerivingVia #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
module Language.Go.Syntax where
|
||||
|
||||
@ -53,10 +53,7 @@ resolveGoImport (ImportPath path NonRelative) = do
|
||||
-- If the list of symbols is empty copy everything to the calling environment.
|
||||
data Import a = Import { importFrom :: ImportPath, importWildcardToken :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 Import where liftEq = genericLiftEq
|
||||
instance Ord1 Import where liftCompare = genericLiftCompare
|
||||
instance Show1 Import where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Import
|
||||
|
||||
instance Evaluatable Import where
|
||||
eval _ _ (Language.Go.Syntax.Import importPath _) = do
|
||||
@ -74,10 +71,7 @@ instance Evaluatable Import where
|
||||
-- If the list of symbols is empty copy and qualify everything to the calling environment.
|
||||
data QualifiedImport a = QualifiedImport { qualifiedImportFrom :: !ImportPath, qualifiedImportAlias :: !a}
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 QualifiedImport where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedImport where liftCompare = genericLiftCompare
|
||||
instance Show1 QualifiedImport where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically QualifiedImport
|
||||
|
||||
instance Evaluatable QualifiedImport where
|
||||
eval _ _ (QualifiedImport importPath aliasTerm) = do
|
||||
@ -108,10 +102,7 @@ instance Evaluatable QualifiedImport where
|
||||
-- | Side effect only imports (no symbols made available to the calling environment).
|
||||
data SideEffectImport a = SideEffectImport { sideEffectImportFrom :: !ImportPath, sideEffectImportToken :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 SideEffectImport where liftEq = genericLiftEq
|
||||
instance Ord1 SideEffectImport where liftCompare = genericLiftCompare
|
||||
instance Show1 SideEffectImport where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically SideEffectImport
|
||||
|
||||
-- TODO: Revisit this and confirm if this is correct.
|
||||
instance Evaluatable SideEffectImport where
|
||||
@ -124,10 +115,7 @@ instance Evaluatable SideEffectImport where
|
||||
-- A composite literal in Go
|
||||
data Composite a = Composite { compositeType :: !a, compositeElement :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 Composite where liftEq = genericLiftEq
|
||||
instance Ord1 Composite where liftCompare = genericLiftCompare
|
||||
instance Show1 Composite where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Composite
|
||||
|
||||
-- TODO: Implement Eval instance for Composite
|
||||
instance Evaluatable Composite
|
||||
@ -135,10 +123,7 @@ instance Evaluatable Composite
|
||||
-- | A default pattern in a Go select or switch statement (e.g. `switch { default: s() }`).
|
||||
newtype DefaultPattern a = DefaultPattern { defaultPatternBody :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 DefaultPattern where liftEq = genericLiftEq
|
||||
instance Ord1 DefaultPattern where liftCompare = genericLiftCompare
|
||||
instance Show1 DefaultPattern where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically DefaultPattern
|
||||
|
||||
-- TODO: Implement Eval instance for DefaultPattern
|
||||
instance Evaluatable DefaultPattern
|
||||
@ -146,10 +131,7 @@ instance Evaluatable DefaultPattern
|
||||
-- | A defer statement in Go (e.g. `defer x()`).
|
||||
newtype Defer a = Defer { deferBody :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 Defer where liftEq = genericLiftEq
|
||||
instance Ord1 Defer where liftCompare = genericLiftCompare
|
||||
instance Show1 Defer where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Defer
|
||||
|
||||
-- TODO: Implement Eval instance for Defer
|
||||
instance Evaluatable Defer
|
||||
@ -157,10 +139,7 @@ instance Evaluatable Defer
|
||||
-- | A go statement (i.e. go routine) in Go (e.g. `go x()`).
|
||||
newtype Go a = Go { goBody :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 Go where liftEq = genericLiftEq
|
||||
instance Ord1 Go where liftCompare = genericLiftCompare
|
||||
instance Show1 Go where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Go
|
||||
|
||||
-- TODO: Implement Eval instance for Go
|
||||
instance Evaluatable Go
|
||||
@ -168,10 +147,7 @@ instance Evaluatable Go
|
||||
-- | A label statement in Go (e.g. `label:continue`).
|
||||
data Label a = Label { labelName :: !a, labelStatement :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 Label where liftEq = genericLiftEq
|
||||
instance Ord1 Label where liftCompare = genericLiftCompare
|
||||
instance Show1 Label where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Label
|
||||
|
||||
-- TODO: Implement Eval instance for Label
|
||||
instance Evaluatable Label
|
||||
@ -179,32 +155,23 @@ instance Evaluatable Label
|
||||
-- | A rune literal in Go (e.g. `'⌘'`).
|
||||
newtype Rune a = Rune { runeLiteral :: Text }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Rune
|
||||
|
||||
-- TODO: Implement Eval instance for Rune
|
||||
instance Evaluatable Rune
|
||||
|
||||
instance Eq1 Rune where liftEq = genericLiftEq
|
||||
instance Ord1 Rune where liftCompare = genericLiftCompare
|
||||
instance Show1 Rune where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- | A select statement in Go (e.g. `select { case x := <-c: x() }` where each case is a send or receive operation on channels).
|
||||
newtype Select a = Select { selectCases :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Select
|
||||
|
||||
-- TODO: Implement Eval instance for Select
|
||||
instance Evaluatable Select
|
||||
|
||||
instance Eq1 Select where liftEq = genericLiftEq
|
||||
instance Ord1 Select where liftCompare = genericLiftCompare
|
||||
instance Show1 Select where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- | A send statement in Go (e.g. `channel <- value`).
|
||||
data Send a = Send { sendReceiver :: !a, sendValue :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 Send where liftEq = genericLiftEq
|
||||
instance Ord1 Send where liftCompare = genericLiftCompare
|
||||
instance Show1 Send where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Send
|
||||
|
||||
-- TODO: Implement Eval instance for Send
|
||||
instance Evaluatable Send
|
||||
@ -212,10 +179,7 @@ instance Evaluatable Send
|
||||
-- | A slice expression in Go (e.g. `a[1:4:3]` where a is a list, 1 is the low bound, 4 is the high bound, and 3 is the max capacity).
|
||||
data Slice a = Slice { sliceName :: !a, sliceLow :: !a, sliceHigh :: !a, sliceCapacity :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 Slice where liftEq = genericLiftEq
|
||||
instance Ord1 Slice where liftCompare = genericLiftCompare
|
||||
instance Show1 Slice where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Slice
|
||||
|
||||
-- TODO: Implement Eval instance for Slice
|
||||
instance Evaluatable Slice
|
||||
@ -223,10 +187,7 @@ instance Evaluatable Slice
|
||||
-- | A type switch statement in Go (e.g. `switch x.(type) { // cases }`).
|
||||
data TypeSwitch a = TypeSwitch { typeSwitchSubject :: !a, typeSwitchCases :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 TypeSwitch where liftEq = genericLiftEq
|
||||
instance Ord1 TypeSwitch where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeSwitch where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically TypeSwitch
|
||||
|
||||
-- TODO: Implement Eval instance for TypeSwitch
|
||||
instance Evaluatable TypeSwitch
|
||||
@ -234,10 +195,7 @@ instance Evaluatable TypeSwitch
|
||||
-- | A type switch guard statement in a Go type switch statement (e.g. `switch i := x.(type) { // cases}`).
|
||||
newtype TypeSwitchGuard a = TypeSwitchGuard { typeSwitchGuardSubject :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 TypeSwitchGuard where liftEq = genericLiftEq
|
||||
instance Ord1 TypeSwitchGuard where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeSwitchGuard where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically TypeSwitchGuard
|
||||
|
||||
-- TODO: Implement Eval instance for TypeSwitchGuard
|
||||
instance Evaluatable TypeSwitchGuard
|
||||
@ -245,10 +203,7 @@ instance Evaluatable TypeSwitchGuard
|
||||
-- | A receive statement in a Go select statement (e.g. `case value := <-channel` )
|
||||
data Receive a = Receive { receiveSubject :: !a, receiveExpression :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 Receive where liftEq = genericLiftEq
|
||||
instance Ord1 Receive where liftCompare = genericLiftCompare
|
||||
instance Show1 Receive where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Receive
|
||||
|
||||
-- TODO: Implement Eval instance for Receive
|
||||
instance Evaluatable Receive
|
||||
@ -256,10 +211,7 @@ instance Evaluatable Receive
|
||||
-- | A receive operator unary expression in Go (e.g. `<-channel` )
|
||||
newtype ReceiveOperator a = ReceiveOperator { value :: a}
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 ReceiveOperator where liftEq = genericLiftEq
|
||||
instance Ord1 ReceiveOperator where liftCompare = genericLiftCompare
|
||||
instance Show1 ReceiveOperator where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically ReceiveOperator
|
||||
|
||||
-- TODO: Implement Eval instance for ReceiveOperator
|
||||
instance Evaluatable ReceiveOperator
|
||||
@ -267,33 +219,22 @@ instance Evaluatable ReceiveOperator
|
||||
-- | A field declaration in a Go struct type declaration.
|
||||
data Field a = Field { fieldContext :: ![a], fieldName :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 Field where liftEq = genericLiftEq
|
||||
instance Ord1 Field where liftCompare = genericLiftCompare
|
||||
instance Show1 Field where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Field
|
||||
|
||||
-- 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, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 Package where liftEq = genericLiftEq
|
||||
instance Ord1 Package where liftCompare = genericLiftCompare
|
||||
instance Show1 Package where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Package
|
||||
|
||||
instance Evaluatable Package where
|
||||
eval eval _ (Package _ xs) = maybe (pure 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, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 TypeAssertion where liftEq = genericLiftEq
|
||||
instance Ord1 TypeAssertion where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeAssertion where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically TypeAssertion
|
||||
|
||||
-- TODO: Implement Eval instance for TypeAssertion
|
||||
instance Evaluatable TypeAssertion
|
||||
@ -301,10 +242,7 @@ instance Evaluatable TypeAssertion
|
||||
-- | A type conversion expression in Go (e.g. `T(x)` where `T` is a type and `x` is an expression that can be converted to type `T`).
|
||||
data TypeConversion a = TypeConversion { typeConversionType :: !a, typeConversionSubject :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 TypeConversion where liftEq = genericLiftEq
|
||||
instance Ord1 TypeConversion where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeConversion where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically TypeConversion
|
||||
|
||||
-- TODO: Implement Eval instance for TypeConversion
|
||||
instance Evaluatable TypeConversion
|
||||
@ -312,10 +250,7 @@ instance Evaluatable TypeConversion
|
||||
-- | Variadic arguments and parameters in Go (e.g. parameter: `param ...Type`, argument: `Type...`).
|
||||
data Variadic a = Variadic { variadicContext :: [a], variadicIdentifier :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 Variadic where liftEq = genericLiftEq
|
||||
instance Ord1 Variadic where liftCompare = genericLiftCompare
|
||||
instance Show1 Variadic where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Variadic
|
||||
|
||||
-- TODO: Implement Eval instance for Variadic
|
||||
instance Evaluatable Variadic
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE DeriveAnyClass, DuplicateRecordFields #-}
|
||||
{-# LANGUAGE DeriveAnyClass, DerivingVia, DuplicateRecordFields #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
module Language.Go.Type where
|
||||
|
||||
@ -12,10 +12,7 @@ import Proto3.Suite.Class
|
||||
-- | A Bidirectional channel in Go (e.g. `chan`).
|
||||
newtype BidirectionalChannel a = BidirectionalChannel { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 BidirectionalChannel where liftEq = genericLiftEq
|
||||
instance Ord1 BidirectionalChannel where liftCompare = genericLiftCompare
|
||||
instance Show1 BidirectionalChannel where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically BidirectionalChannel
|
||||
|
||||
-- TODO: Implement Eval instance for BidirectionalChannel
|
||||
instance Evaluatable BidirectionalChannel
|
||||
@ -23,10 +20,7 @@ instance Evaluatable BidirectionalChannel
|
||||
-- | A Receive channel in Go (e.g. `<-chan`).
|
||||
newtype ReceiveChannel a = ReceiveChannel { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 ReceiveChannel where liftEq = genericLiftEq
|
||||
instance Ord1 ReceiveChannel where liftCompare = genericLiftCompare
|
||||
instance Show1 ReceiveChannel where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically ReceiveChannel
|
||||
|
||||
-- TODO: Implement Eval instance for ReceiveChannel
|
||||
instance Evaluatable ReceiveChannel
|
||||
@ -34,10 +28,7 @@ instance Evaluatable ReceiveChannel
|
||||
-- | A Send channel in Go (e.g. `chan<-`).
|
||||
newtype SendChannel a = SendChannel { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 SendChannel where liftEq = genericLiftEq
|
||||
instance Ord1 SendChannel where liftCompare = genericLiftCompare
|
||||
instance Show1 SendChannel where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically SendChannel
|
||||
|
||||
-- TODO: Implement Eval instance for SendChannel
|
||||
instance Evaluatable SendChannel
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE DeriveAnyClass, DuplicateRecordFields #-}
|
||||
{-# LANGUAGE DeriveAnyClass, DerivingVia, DuplicateRecordFields #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
|
||||
module Language.Haskell.Syntax.Constructor where
|
||||
@ -12,107 +12,72 @@ import Proto3.Suite.Class
|
||||
|
||||
data UnitConstructor a = UnitConstructor
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 UnitConstructor where liftEq = genericLiftEq
|
||||
instance Ord1 UnitConstructor where liftCompare = genericLiftCompare
|
||||
instance Show1 UnitConstructor where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically UnitConstructor
|
||||
|
||||
instance Evaluatable UnitConstructor
|
||||
|
||||
newtype TupleConstructor a = TupleConstructor { tupleConstructorArity :: Int }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 TupleConstructor where liftEq = genericLiftEq
|
||||
instance Ord1 TupleConstructor where liftCompare = genericLiftCompare
|
||||
instance Show1 TupleConstructor where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically TupleConstructor
|
||||
|
||||
instance Evaluatable TupleConstructor
|
||||
|
||||
data ListConstructor a = ListConstructor
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ListConstructor where liftEq = genericLiftEq
|
||||
instance Ord1 ListConstructor where liftCompare = genericLiftCompare
|
||||
instance Show1 ListConstructor where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically ListConstructor
|
||||
|
||||
instance Evaluatable ListConstructor
|
||||
|
||||
data FunctionConstructor a = FunctionConstructor
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 FunctionConstructor where liftEq = genericLiftEq
|
||||
instance Ord1 FunctionConstructor where liftCompare = genericLiftCompare
|
||||
instance Show1 FunctionConstructor where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically FunctionConstructor
|
||||
|
||||
instance Evaluatable FunctionConstructor
|
||||
|
||||
data RecordDataConstructor a = RecordDataConstructor { recordDataConstructorContext :: [a], recordDataConstructorName :: !a, recordDataConstructorFields :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 RecordDataConstructor where liftEq = genericLiftEq
|
||||
instance Ord1 RecordDataConstructor where liftCompare = genericLiftCompare
|
||||
instance Show1 RecordDataConstructor where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically RecordDataConstructor
|
||||
|
||||
instance Evaluatable RecordDataConstructor
|
||||
|
||||
newtype TypeConstructorExport a = TypeConstructorExport { typeConstructorExportContent :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 TypeConstructorExport where liftEq = genericLiftEq
|
||||
instance Ord1 TypeConstructorExport where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeConstructorExport where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically TypeConstructorExport
|
||||
|
||||
instance Evaluatable TypeConstructorExport
|
||||
|
||||
data AllConstructors a = AllConstructors
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 AllConstructors where liftEq = genericLiftEq
|
||||
instance Ord1 AllConstructors where liftCompare = genericLiftCompare
|
||||
instance Show1 AllConstructors where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically AllConstructors
|
||||
|
||||
instance Evaluatable AllConstructors
|
||||
|
||||
newtype KindParenthesizedConstructor a = KindParenthesizedConstructor { kindParenthesizedConstructorContent :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 KindParenthesizedConstructor where liftEq = genericLiftEq
|
||||
instance Ord1 KindParenthesizedConstructor where liftCompare = genericLiftCompare
|
||||
instance Show1 KindParenthesizedConstructor where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically KindParenthesizedConstructor
|
||||
|
||||
instance Evaluatable KindParenthesizedConstructor
|
||||
|
||||
data GADTConstructor a = GADTConstructor { gadtConstructorContext :: a, gadtConstructorName :: a, gadtConstructorTypeSignature :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 GADTConstructor where liftEq = genericLiftEq
|
||||
instance Ord1 GADTConstructor where liftCompare = genericLiftCompare
|
||||
instance Show1 GADTConstructor where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically GADTConstructor
|
||||
|
||||
instance Evaluatable GADTConstructor
|
||||
|
||||
newtype ConstructorSymbol a = ConstructorSymbol { constructorSymbolName :: Name }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ConstructorSymbol where liftEq = genericLiftEq
|
||||
instance Ord1 ConstructorSymbol where liftCompare = genericLiftCompare
|
||||
instance Show1 ConstructorSymbol where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically ConstructorSymbol
|
||||
|
||||
instance Evaluatable ConstructorSymbol
|
||||
|
||||
data LabeledConstruction a = LabeledConstruction { labeledConstructionConstructor :: a, labeledConstructionFields :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 LabeledConstruction where liftEq = genericLiftEq
|
||||
instance Ord1 LabeledConstruction where liftCompare = genericLiftCompare
|
||||
instance Show1 LabeledConstruction where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically LabeledConstruction
|
||||
|
||||
instance Evaluatable LabeledConstruction
|
||||
|
||||
data InfixDataConstructor a = InfixDataConstructor { infixDataConstructorContext :: [a], infixDataConstructorLeft :: a, infixDataConstructorOperator :: a, infixDataConstructorRight :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 InfixDataConstructor where liftEq = genericLiftEq
|
||||
instance Ord1 InfixDataConstructor where liftCompare = genericLiftCompare
|
||||
instance Show1 InfixDataConstructor where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically InfixDataConstructor
|
||||
|
||||
instance Evaluatable InfixDataConstructor
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE DeriveAnyClass, DuplicateRecordFields #-}
|
||||
{-# LANGUAGE DeriveAnyClass, DerivingVia, DuplicateRecordFields #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
|
||||
module Language.Haskell.Syntax.Haskell where
|
||||
@ -16,450 +16,302 @@ data Module a = Module { moduleContext :: [a]
|
||||
, moduleStatements :: a
|
||||
}
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Module where liftEq = genericLiftEq
|
||||
instance Ord1 Module where liftCompare = genericLiftCompare
|
||||
instance Show1 Module where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Module
|
||||
|
||||
instance Evaluatable Module
|
||||
|
||||
data Field a = Field { fieldName :: !a, fieldBody :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Field where liftEq = genericLiftEq
|
||||
instance Ord1 Field where liftCompare = genericLiftCompare
|
||||
instance Show1 Field where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Field
|
||||
|
||||
instance Evaluatable Field
|
||||
|
||||
newtype Pragma a = Pragma { value :: Text }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Pragma where liftEq = genericLiftEq
|
||||
instance Ord1 Pragma where liftCompare = genericLiftCompare
|
||||
instance Show1 Pragma where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Pragma
|
||||
|
||||
instance Evaluatable Pragma
|
||||
|
||||
newtype Deriving a = Deriving { values :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Deriving where liftEq = genericLiftEq
|
||||
instance Ord1 Deriving where liftCompare = genericLiftCompare
|
||||
instance Show1 Deriving where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Deriving
|
||||
|
||||
instance Evaluatable Deriving
|
||||
|
||||
newtype ContextAlt a = ContextAlt { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ContextAlt where liftEq = genericLiftEq
|
||||
instance Ord1 ContextAlt where liftCompare = genericLiftCompare
|
||||
instance Show1 ContextAlt where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically ContextAlt
|
||||
|
||||
instance Evaluatable ContextAlt
|
||||
|
||||
newtype Class a = Class { classContent :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Class where liftEq = genericLiftEq
|
||||
instance Ord1 Class where liftCompare = genericLiftCompare
|
||||
instance Show1 Class where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Class
|
||||
|
||||
instance Evaluatable Class
|
||||
|
||||
data GADT a = GADT { gadtContext :: a, gadtName :: a, gadtConstructors :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 GADT where liftEq = genericLiftEq
|
||||
instance Ord1 GADT where liftCompare = genericLiftCompare
|
||||
instance Show1 GADT where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically GADT
|
||||
|
||||
instance Evaluatable GADT
|
||||
|
||||
newtype Export a = Export { exportContent :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Export where liftEq = genericLiftEq
|
||||
instance Ord1 Export where liftCompare = genericLiftCompare
|
||||
instance Show1 Export where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Export
|
||||
|
||||
instance Evaluatable Export
|
||||
|
||||
newtype ModuleExport a = ModuleExport { moduleExportContent :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ModuleExport where liftEq = genericLiftEq
|
||||
instance Ord1 ModuleExport where liftCompare = genericLiftCompare
|
||||
instance Show1 ModuleExport where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically ModuleExport
|
||||
|
||||
instance Evaluatable ModuleExport
|
||||
|
||||
data InfixOperatorPattern a = InfixOperatorPattern { infixOperatorPatternLeft :: a, infixOperatorPatternOperator :: a, infixOperatorPatternRight :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 InfixOperatorPattern where liftEq = genericLiftEq
|
||||
instance Ord1 InfixOperatorPattern where liftCompare = genericLiftCompare
|
||||
instance Show1 InfixOperatorPattern where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically InfixOperatorPattern
|
||||
|
||||
instance Evaluatable InfixOperatorPattern
|
||||
|
||||
newtype QuotedName a = QuotedName { quotedNameContent :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 QuotedName where liftEq = genericLiftEq
|
||||
instance Ord1 QuotedName where liftCompare = genericLiftCompare
|
||||
instance Show1 QuotedName where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically QuotedName
|
||||
|
||||
instance Evaluatable QuotedName
|
||||
|
||||
newtype ScopedTypeVariables a = ScopedTypeVariables { scopedTypeVariablesContent :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ScopedTypeVariables where liftEq = genericLiftEq
|
||||
instance Ord1 ScopedTypeVariables where liftCompare = genericLiftCompare
|
||||
instance Show1 ScopedTypeVariables where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically ScopedTypeVariables
|
||||
|
||||
instance Evaluatable ScopedTypeVariables
|
||||
|
||||
data NewType a = NewType { newTypeContext :: [a], newTypeLeft :: a, newTypeRight :: a, newTypeDeriving :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 NewType where liftEq = genericLiftEq
|
||||
instance Ord1 NewType where liftCompare = genericLiftCompare
|
||||
instance Show1 NewType where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically NewType
|
||||
|
||||
instance Evaluatable NewType
|
||||
|
||||
newtype DefaultDeclaration a = DefaultDeclaration { defaultDeclarationContent :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 DefaultDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 DefaultDeclaration where liftCompare = genericLiftCompare
|
||||
instance Show1 DefaultDeclaration where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically DefaultDeclaration
|
||||
|
||||
instance Evaluatable DefaultDeclaration
|
||||
|
||||
|
||||
newtype VariableOperator a = VariableOperator { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 VariableOperator where liftEq = genericLiftEq
|
||||
instance Ord1 VariableOperator where liftCompare = genericLiftCompare
|
||||
instance Show1 VariableOperator where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically VariableOperator
|
||||
|
||||
instance Evaluatable VariableOperator
|
||||
|
||||
newtype ConstructorOperator a = ConstructorOperator { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ConstructorOperator where liftEq = genericLiftEq
|
||||
instance Ord1 ConstructorOperator where liftCompare = genericLiftCompare
|
||||
instance Show1 ConstructorOperator where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically ConstructorOperator
|
||||
|
||||
instance Evaluatable ConstructorOperator
|
||||
|
||||
newtype TypeOperator a = TypeOperator { name :: Name }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 TypeOperator where liftEq = genericLiftEq
|
||||
instance Ord1 TypeOperator where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeOperator where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically TypeOperator
|
||||
|
||||
instance Evaluatable TypeOperator
|
||||
|
||||
newtype PromotedTypeOperator a = PromotedTypeOperator { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 PromotedTypeOperator where liftEq = genericLiftEq
|
||||
instance Ord1 PromotedTypeOperator where liftCompare = genericLiftCompare
|
||||
instance Show1 PromotedTypeOperator where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically PromotedTypeOperator
|
||||
|
||||
instance Evaluatable PromotedTypeOperator
|
||||
|
||||
newtype VariableSymbol a = VariableSymbol { variableSymbolName :: Name }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 VariableSymbol where liftEq = genericLiftEq
|
||||
instance Ord1 VariableSymbol where liftCompare = genericLiftCompare
|
||||
instance Show1 VariableSymbol where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically VariableSymbol
|
||||
|
||||
instance Evaluatable VariableSymbol
|
||||
|
||||
data ImportDeclaration a = ImportDeclaration { importPackageQualifiedContent :: a, importModule :: a, importSpec :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ImportDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 ImportDeclaration where liftCompare = genericLiftCompare
|
||||
instance Show1 ImportDeclaration where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically ImportDeclaration
|
||||
|
||||
instance Evaluatable ImportDeclaration
|
||||
|
||||
data QualifiedImportDeclaration a = QualifiedImportDeclaration { qualifiedImportPackageQualifiedContent :: a, qualifiedImportModule :: a, qualifiedImportSpec :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 QualifiedImportDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedImportDeclaration where liftCompare = genericLiftCompare
|
||||
instance Show1 QualifiedImportDeclaration where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically QualifiedImportDeclaration
|
||||
|
||||
instance Evaluatable QualifiedImportDeclaration
|
||||
|
||||
newtype Import a = Import { importContent :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Import where liftEq = genericLiftEq
|
||||
instance Ord1 Import where liftCompare = genericLiftCompare
|
||||
instance Show1 Import where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Import
|
||||
|
||||
instance Evaluatable Import
|
||||
|
||||
newtype HiddenImport a = HiddenImport { hiddenimportContent :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 HiddenImport where liftEq = genericLiftEq
|
||||
instance Ord1 HiddenImport where liftCompare = genericLiftCompare
|
||||
instance Show1 HiddenImport where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically HiddenImport
|
||||
|
||||
instance Evaluatable HiddenImport
|
||||
|
||||
data ImportAlias a = ImportAlias { importAliasSource :: a, importAliasName :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ImportAlias where liftEq = genericLiftEq
|
||||
instance Ord1 ImportAlias where liftCompare = genericLiftCompare
|
||||
instance Show1 ImportAlias where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically ImportAlias
|
||||
|
||||
instance Evaluatable ImportAlias
|
||||
|
||||
data App a = App { appLeft :: a, appLeftTypeApp :: a, appRight :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 App where liftEq = genericLiftEq
|
||||
instance Ord1 App where liftCompare = genericLiftCompare
|
||||
instance Show1 App where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically App
|
||||
|
||||
instance Evaluatable App
|
||||
|
||||
data InfixOperatorApp a = InfixOperatorApp { infixOperatorAppLeft :: a, infixOperatorAppLeftTypeApp :: a, infixOperatorAppOperator :: a, infixOperatorAppRight :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 InfixOperatorApp where liftEq = genericLiftEq
|
||||
instance Ord1 InfixOperatorApp where liftCompare = genericLiftCompare
|
||||
instance Show1 InfixOperatorApp where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically InfixOperatorApp
|
||||
|
||||
instance Evaluatable InfixOperatorApp
|
||||
|
||||
newtype TypeApp a = TypeApp { typeAppType :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 TypeApp where liftEq = genericLiftEq
|
||||
instance Ord1 TypeApp where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeApp where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically TypeApp
|
||||
|
||||
instance Evaluatable TypeApp
|
||||
|
||||
data ListComprehension a = ListComprehension { comprehensionValue :: a, comprehensionSource :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ListComprehension where liftEq = genericLiftEq
|
||||
instance Ord1 ListComprehension where liftCompare = genericLiftCompare
|
||||
instance Show1 ListComprehension where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically ListComprehension
|
||||
|
||||
instance Evaluatable ListComprehension
|
||||
|
||||
data Generator a = Generator { generatorValue :: a, generatorSource :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Generator where liftEq = genericLiftEq
|
||||
instance Ord1 Generator where liftCompare = genericLiftCompare
|
||||
instance Show1 Generator where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Generator
|
||||
|
||||
instance Evaluatable Generator
|
||||
|
||||
newtype TupleExpression a = TupleExpression { values :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 TupleExpression where liftEq = genericLiftEq
|
||||
instance Ord1 TupleExpression where liftCompare = genericLiftCompare
|
||||
instance Show1 TupleExpression where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically TupleExpression
|
||||
|
||||
instance Evaluatable TupleExpression
|
||||
|
||||
newtype TuplePattern a = TuplePattern { value :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 TuplePattern where liftEq = genericLiftEq
|
||||
instance Ord1 TuplePattern where liftCompare = genericLiftCompare
|
||||
instance Show1 TuplePattern where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically TuplePattern
|
||||
|
||||
instance Evaluatable TuplePattern
|
||||
|
||||
-- e.g. [1..], [1,2..], [1,2..10]
|
||||
data ArithmeticSequence a = ArithmeticSequence { from :: a, next :: Maybe a, to :: Maybe a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ArithmeticSequence where liftEq = genericLiftEq
|
||||
instance Ord1 ArithmeticSequence where liftCompare = genericLiftCompare
|
||||
instance Show1 ArithmeticSequence where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically ArithmeticSequence
|
||||
|
||||
instance Evaluatable ArithmeticSequence
|
||||
|
||||
data RightOperatorSection a = RightOperatorSection { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 RightOperatorSection where liftEq = genericLiftEq
|
||||
instance Ord1 RightOperatorSection where liftCompare = genericLiftCompare
|
||||
instance Show1 RightOperatorSection where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically RightOperatorSection
|
||||
|
||||
instance Evaluatable RightOperatorSection
|
||||
|
||||
data LeftOperatorSection a = LeftOperatorSection { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 LeftOperatorSection where liftEq = genericLiftEq
|
||||
instance Ord1 LeftOperatorSection where liftCompare = genericLiftCompare
|
||||
instance Show1 LeftOperatorSection where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically LeftOperatorSection
|
||||
|
||||
instance Evaluatable LeftOperatorSection
|
||||
|
||||
newtype ConstructorPattern a = ConstructorPattern { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ConstructorPattern where liftEq = genericLiftEq
|
||||
instance Ord1 ConstructorPattern where liftCompare = genericLiftCompare
|
||||
instance Show1 ConstructorPattern where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically ConstructorPattern
|
||||
|
||||
instance Evaluatable ConstructorPattern
|
||||
|
||||
-- e.g. `a <- b` in a Haskell do block.
|
||||
data BindPattern a = BindPattern { bindPatternLeft :: [a], bindPatternRight :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 BindPattern where liftEq = genericLiftEq
|
||||
instance Ord1 BindPattern where liftCompare = genericLiftCompare
|
||||
instance Show1 BindPattern where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically BindPattern
|
||||
|
||||
instance Evaluatable BindPattern
|
||||
|
||||
newtype Do a = Do { values :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Do where liftEq = genericLiftEq
|
||||
instance Ord1 Do where liftCompare = genericLiftCompare
|
||||
instance Show1 Do where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Do
|
||||
|
||||
instance Evaluatable Do
|
||||
|
||||
data Lambda a = Lambda { lambdaHead :: a, lambdaBody :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Lambda where liftEq = genericLiftEq
|
||||
instance Ord1 Lambda where liftCompare = genericLiftCompare
|
||||
instance Show1 Lambda where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Lambda
|
||||
|
||||
instance Evaluatable Lambda
|
||||
|
||||
-- e.g. -1 or (-a) as an expression and not `-` as a variable operator.
|
||||
newtype PrefixNegation a = PrefixNegation { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 PrefixNegation where liftEq = genericLiftEq
|
||||
instance Ord1 PrefixNegation where liftCompare = genericLiftCompare
|
||||
instance Show1 PrefixNegation where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically PrefixNegation
|
||||
|
||||
instance Evaluatable PrefixNegation
|
||||
|
||||
newtype CPPDirective a = CPPDirective { value :: Text }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 CPPDirective where liftEq = genericLiftEq
|
||||
instance Ord1 CPPDirective where liftCompare = genericLiftCompare
|
||||
instance Show1 CPPDirective where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically CPPDirective
|
||||
|
||||
instance Evaluatable CPPDirective
|
||||
|
||||
data FixityAlt a = FixityAlt { fixityPrecedence :: a, fixityIdentifier :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 FixityAlt where liftEq = genericLiftEq
|
||||
instance Ord1 FixityAlt where liftCompare = genericLiftCompare
|
||||
instance Show1 FixityAlt where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically FixityAlt
|
||||
|
||||
instance Evaluatable FixityAlt
|
||||
|
||||
-- e.g. The `{..}` in `foo Bar{..} = baz`
|
||||
data RecordWildCards a = RecordWildCards
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 RecordWildCards where liftEq = genericLiftEq
|
||||
instance Ord1 RecordWildCards where liftCompare = genericLiftCompare
|
||||
instance Show1 RecordWildCards where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically RecordWildCards
|
||||
|
||||
instance Evaluatable RecordWildCards
|
||||
|
||||
data Wildcard a = Wildcard
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Wildcard where liftEq = genericLiftEq
|
||||
instance Ord1 Wildcard where liftCompare = genericLiftCompare
|
||||
instance Show1 Wildcard where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Wildcard
|
||||
|
||||
instance Evaluatable Wildcard
|
||||
|
||||
data Let a = Let { letStatements :: [a], letInClause :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Let where liftEq = genericLiftEq
|
||||
instance Ord1 Let where liftCompare = genericLiftCompare
|
||||
instance Show1 Let where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Let
|
||||
|
||||
instance Evaluatable Let
|
||||
|
||||
-- e.g. The `start` or `end` in `f Blob{start, end} = [start, end]`.
|
||||
newtype NamedFieldPun a = NamedFieldPun { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 NamedFieldPun where liftEq = genericLiftEq
|
||||
instance Ord1 NamedFieldPun where liftCompare = genericLiftCompare
|
||||
instance Show1 NamedFieldPun where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically NamedFieldPun
|
||||
|
||||
instance Evaluatable NamedFieldPun
|
||||
|
||||
-- e.g. The `-(1)` in `f (-(1)) = 1`.
|
||||
newtype NegativeLiteral a = NegativeLiteral { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 NegativeLiteral where liftEq = genericLiftEq
|
||||
instance Ord1 NegativeLiteral where liftCompare = genericLiftCompare
|
||||
instance Show1 NegativeLiteral where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically NegativeLiteral
|
||||
|
||||
instance Evaluatable NegativeLiteral
|
||||
|
||||
newtype LambdaCase a = LambdaCase { values :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 LambdaCase where liftEq = genericLiftEq
|
||||
instance Ord1 LambdaCase where liftCompare = genericLiftCompare
|
||||
instance Show1 LambdaCase where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically LambdaCase
|
||||
|
||||
instance Evaluatable LambdaCase
|
||||
|
||||
-- The `y { a = 1, b = 2} in `f y@Example = y { a = 1, b = 2 }`.
|
||||
newtype LabeledUpdate a = LabeledUpdate { values :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 LabeledUpdate where liftEq = genericLiftEq
|
||||
instance Ord1 LabeledUpdate where liftCompare = genericLiftCompare
|
||||
instance Show1 LabeledUpdate where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically LabeledUpdate
|
||||
|
||||
instance Evaluatable LabeledUpdate
|
||||
|
||||
-- The `a = 1` in `f y@Example = y { a = 1, b = 2 }`.
|
||||
data FieldBind a = FieldBind { fieldBindLeft :: a, fieldBindRight :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 FieldBind where liftEq = genericLiftEq
|
||||
instance Ord1 FieldBind where liftCompare = genericLiftCompare
|
||||
instance Show1 FieldBind where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically FieldBind
|
||||
|
||||
instance Evaluatable FieldBind
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE DeriveAnyClass, DuplicateRecordFields #-}
|
||||
{-# LANGUAGE DeriveAnyClass, DerivingVia, DuplicateRecordFields #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
|
||||
module Language.Haskell.Syntax.Identifier where
|
||||
@ -12,159 +12,114 @@ import Proto3.Suite.Class
|
||||
|
||||
newtype QualifiedTypeClassIdentifier a = QualifiedTypeClassIdentifier { values :: NonEmpty a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically QualifiedTypeClassIdentifier
|
||||
|
||||
instance Eq1 QualifiedTypeClassIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedTypeClassIdentifier where liftCompare = genericLiftCompare
|
||||
instance Show1 QualifiedTypeClassIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Hashable1 QualifiedTypeClassIdentifier where liftHashWithSalt = foldl
|
||||
|
||||
instance Evaluatable QualifiedTypeClassIdentifier
|
||||
|
||||
newtype QualifiedTypeConstructorIdentifier a = QualifiedTypeConstructorIdentifier { values :: NonEmpty a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically QualifiedTypeConstructorIdentifier
|
||||
|
||||
instance Eq1 QualifiedTypeConstructorIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedTypeConstructorIdentifier where liftCompare = genericLiftCompare
|
||||
instance Show1 QualifiedTypeConstructorIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Hashable1 QualifiedTypeConstructorIdentifier where liftHashWithSalt = foldl
|
||||
|
||||
instance Evaluatable QualifiedTypeConstructorIdentifier
|
||||
|
||||
newtype QualifiedConstructorIdentifier a = QualifiedConstructorIdentifier { values :: NonEmpty a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically QualifiedConstructorIdentifier
|
||||
|
||||
instance Eq1 QualifiedConstructorIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedConstructorIdentifier where liftCompare = genericLiftCompare
|
||||
instance Show1 QualifiedConstructorIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Hashable1 QualifiedConstructorIdentifier where liftHashWithSalt = foldl
|
||||
|
||||
instance Evaluatable QualifiedConstructorIdentifier
|
||||
|
||||
newtype QualifiedInfixVariableIdentifier a = QualifiedInfixVariableIdentifier { values :: NonEmpty a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically QualifiedInfixVariableIdentifier
|
||||
|
||||
instance Eq1 QualifiedInfixVariableIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedInfixVariableIdentifier where liftCompare = genericLiftCompare
|
||||
instance Show1 QualifiedInfixVariableIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Hashable1 QualifiedInfixVariableIdentifier where liftHashWithSalt = foldl
|
||||
|
||||
instance Evaluatable QualifiedInfixVariableIdentifier
|
||||
|
||||
newtype QualifiedModuleIdentifier a = QualifiedModuleIdentifier { values :: NonEmpty a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically QualifiedModuleIdentifier
|
||||
|
||||
instance Eq1 QualifiedModuleIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedModuleIdentifier where liftCompare = genericLiftCompare
|
||||
instance Show1 QualifiedModuleIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Hashable1 QualifiedModuleIdentifier where liftHashWithSalt = foldl
|
||||
|
||||
instance Evaluatable QualifiedModuleIdentifier
|
||||
|
||||
newtype QualifiedVariableIdentifier a = QualifiedVariableIdentifier { values :: NonEmpty a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically QualifiedVariableIdentifier
|
||||
|
||||
instance Eq1 QualifiedVariableIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedVariableIdentifier where liftCompare = genericLiftCompare
|
||||
instance Show1 QualifiedVariableIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Hashable1 QualifiedVariableIdentifier where liftHashWithSalt = foldl
|
||||
|
||||
instance Evaluatable QualifiedVariableIdentifier
|
||||
|
||||
newtype TypeVariableIdentifier a = TypeVariableIdentifier { name :: Name }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 TypeVariableIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 TypeVariableIdentifier where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeVariableIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically TypeVariableIdentifier
|
||||
|
||||
instance Evaluatable TypeVariableIdentifier
|
||||
|
||||
newtype TypeConstructorIdentifier a = TypeConstructorIdentifier { name :: Name }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 TypeConstructorIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 TypeConstructorIdentifier where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeConstructorIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically TypeConstructorIdentifier
|
||||
|
||||
instance Evaluatable TypeConstructorIdentifier
|
||||
|
||||
newtype ModuleIdentifier a = ModuleIdentifier { name :: Name }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ModuleIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 ModuleIdentifier where liftCompare = genericLiftCompare
|
||||
instance Show1 ModuleIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically ModuleIdentifier
|
||||
|
||||
instance Evaluatable ModuleIdentifier
|
||||
|
||||
newtype ConstructorIdentifier a = ConstructorIdentifier { name :: Name }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ConstructorIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 ConstructorIdentifier where liftCompare = genericLiftCompare
|
||||
instance Show1 ConstructorIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically ConstructorIdentifier
|
||||
|
||||
instance Evaluatable ConstructorIdentifier
|
||||
|
||||
newtype ImplicitParameterIdentifier a = ImplicitParameterIdentifier { name :: Name }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ImplicitParameterIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 ImplicitParameterIdentifier where liftCompare = genericLiftCompare
|
||||
instance Show1 ImplicitParameterIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically ImplicitParameterIdentifier
|
||||
|
||||
instance Evaluatable ImplicitParameterIdentifier
|
||||
|
||||
newtype InfixConstructorIdentifier a = InfixConstructorIdentifier { name :: Name }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 InfixConstructorIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 InfixConstructorIdentifier where liftCompare = genericLiftCompare
|
||||
instance Show1 InfixConstructorIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically InfixConstructorIdentifier
|
||||
|
||||
instance Evaluatable InfixConstructorIdentifier
|
||||
|
||||
newtype InfixVariableIdentifier a = InfixVariableIdentifier { name :: Name }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 InfixVariableIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 InfixVariableIdentifier where liftCompare = genericLiftCompare
|
||||
instance Show1 InfixVariableIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically InfixVariableIdentifier
|
||||
|
||||
instance Evaluatable InfixVariableIdentifier
|
||||
|
||||
newtype TypeClassIdentifier a = TypeClassIdentifier { name :: Name }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 TypeClassIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 TypeClassIdentifier where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeClassIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically TypeClassIdentifier
|
||||
|
||||
instance Evaluatable TypeClassIdentifier
|
||||
|
||||
newtype VariableIdentifier a = VariableIdentifier { name :: Name }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 VariableIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 VariableIdentifier where liftCompare = genericLiftCompare
|
||||
instance Show1 VariableIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically VariableIdentifier
|
||||
|
||||
instance Evaluatable VariableIdentifier
|
||||
|
||||
newtype PrimitiveConstructorIdentifier a = PrimitiveConstructorIdentifier { name :: Name }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 PrimitiveConstructorIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 PrimitiveConstructorIdentifier where liftCompare = genericLiftCompare
|
||||
instance Show1 PrimitiveConstructorIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically PrimitiveConstructorIdentifier
|
||||
|
||||
instance Evaluatable PrimitiveConstructorIdentifier
|
||||
|
||||
newtype PrimitiveVariableIdentifier a = PrimitiveVariableIdentifier { name :: Name }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 PrimitiveVariableIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 PrimitiveVariableIdentifier where liftCompare = genericLiftCompare
|
||||
instance Show1 PrimitiveVariableIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically PrimitiveVariableIdentifier
|
||||
|
||||
instance Evaluatable PrimitiveVariableIdentifier
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE DeriveAnyClass, DuplicateRecordFields #-}
|
||||
{-# LANGUAGE DeriveAnyClass, DerivingVia, DuplicateRecordFields #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
|
||||
module Language.Haskell.Syntax.Pattern where
|
||||
@ -12,115 +12,79 @@ import Proto3.Suite.Class
|
||||
|
||||
newtype StrictPattern a = StrictPattern { value :: a}
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 StrictPattern where liftEq = genericLiftEq
|
||||
instance Ord1 StrictPattern where liftCompare = genericLiftCompare
|
||||
instance Show1 StrictPattern where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically StrictPattern
|
||||
|
||||
instance Evaluatable StrictPattern
|
||||
|
||||
newtype ListPattern a = ListPattern { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ListPattern where liftEq = genericLiftEq
|
||||
instance Ord1 ListPattern where liftCompare = genericLiftCompare
|
||||
instance Show1 ListPattern where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically ListPattern
|
||||
|
||||
instance Evaluatable ListPattern
|
||||
|
||||
-- e.g. The `n@num1` in `f n@num1 x@num2 = x`
|
||||
data AsPattern a = AsPattern { asPatternLeft :: a, asPatternRight :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 AsPattern where liftEq = genericLiftEq
|
||||
instance Ord1 AsPattern where liftCompare = genericLiftCompare
|
||||
instance Show1 AsPattern where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically AsPattern
|
||||
|
||||
instance Evaluatable AsPattern
|
||||
|
||||
newtype TypePattern a = TypePattern { typePatternContent :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 TypePattern where liftEq = genericLiftEq
|
||||
instance Ord1 TypePattern where liftCompare = genericLiftCompare
|
||||
instance Show1 TypePattern where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically TypePattern
|
||||
|
||||
instance Evaluatable TypePattern
|
||||
|
||||
-- e.g. The `a = 1` in `foo Bar{ a = 1 } = baz`.
|
||||
data FieldPattern a = FieldPattern { fieldPatternLeft :: a, fieldPatternRight :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 FieldPattern where liftEq = genericLiftEq
|
||||
instance Ord1 FieldPattern where liftCompare = genericLiftCompare
|
||||
instance Show1 FieldPattern where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically FieldPattern
|
||||
|
||||
instance Evaluatable FieldPattern
|
||||
|
||||
-- e.g. The `~a` in `f ~a = 1`
|
||||
newtype IrrefutablePattern a = IrrefutablePattern { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 IrrefutablePattern where liftEq = genericLiftEq
|
||||
instance Ord1 IrrefutablePattern where liftCompare = genericLiftCompare
|
||||
instance Show1 IrrefutablePattern where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically IrrefutablePattern
|
||||
|
||||
instance Evaluatable IrrefutablePattern
|
||||
|
||||
-- For handling guards in case alternative expressions.
|
||||
newtype CaseGuardPattern a = CaseGuardPattern { values :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 CaseGuardPattern where liftEq = genericLiftEq
|
||||
instance Ord1 CaseGuardPattern where liftCompare = genericLiftCompare
|
||||
instance Show1 CaseGuardPattern where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically CaseGuardPattern
|
||||
|
||||
instance Evaluatable CaseGuardPattern
|
||||
|
||||
-- For handling guards in function declarations.
|
||||
newtype FunctionGuardPattern a = FunctionGuardPattern { values :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 FunctionGuardPattern where liftEq = genericLiftEq
|
||||
instance Ord1 FunctionGuardPattern where liftCompare = genericLiftCompare
|
||||
instance Show1 FunctionGuardPattern where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically FunctionGuardPattern
|
||||
|
||||
instance Evaluatable FunctionGuardPattern
|
||||
|
||||
data ViewPattern a = ViewPattern { viewPatternLeft :: a, viewPatternRight :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ViewPattern where liftEq = genericLiftEq
|
||||
instance Ord1 ViewPattern where liftCompare = genericLiftCompare
|
||||
instance Show1 ViewPattern where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically ViewPattern
|
||||
|
||||
instance Evaluatable ViewPattern
|
||||
|
||||
-- e.g. The `Bar{..}` in `foo Bar{..} = baz`.
|
||||
newtype LabeledPattern a = LabeledPattern { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 LabeledPattern where liftEq = genericLiftEq
|
||||
instance Ord1 LabeledPattern where liftCompare = genericLiftCompare
|
||||
instance Show1 LabeledPattern where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically LabeledPattern
|
||||
|
||||
instance Evaluatable LabeledPattern
|
||||
|
||||
-- The `a <- b` in `f a | a <- b = c` of a function declaration.
|
||||
data PatternGuard a = PatternGuard { patternGuardPattern :: a, patternGuardExpression :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 PatternGuard where liftEq = genericLiftEq
|
||||
instance Ord1 PatternGuard where liftCompare = genericLiftCompare
|
||||
instance Show1 PatternGuard where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically PatternGuard
|
||||
|
||||
instance Evaluatable PatternGuard
|
||||
|
||||
newtype Guard a = Guard { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Guard where liftEq = genericLiftEq
|
||||
instance Ord1 Guard where liftCompare = genericLiftCompare
|
||||
instance Show1 Guard where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Guard
|
||||
|
||||
instance Evaluatable Guard
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE DeriveAnyClass, DuplicateRecordFields #-}
|
||||
{-# LANGUAGE DeriveAnyClass, DerivingVia, DuplicateRecordFields #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
|
||||
module Language.Haskell.Syntax.QuasiQuote where
|
||||
@ -12,72 +12,48 @@ import Proto3.Suite.Class
|
||||
|
||||
data QuasiQuotation a = QuasiQuotation { quasiQuotationHead :: a, quasiQuotationBody :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 QuasiQuotation where liftEq = genericLiftEq
|
||||
instance Ord1 QuasiQuotation where liftCompare = genericLiftCompare
|
||||
instance Show1 QuasiQuotation where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically QuasiQuotation
|
||||
|
||||
instance Evaluatable QuasiQuotation
|
||||
|
||||
newtype QuasiQuotationExpressionBody a = QuasiQuotationExpressionBody { name :: Name }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 QuasiQuotationExpressionBody where liftEq = genericLiftEq
|
||||
instance Ord1 QuasiQuotationExpressionBody where liftCompare = genericLiftCompare
|
||||
instance Show1 QuasiQuotationExpressionBody where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically QuasiQuotationExpressionBody
|
||||
|
||||
instance Evaluatable QuasiQuotationExpressionBody
|
||||
|
||||
data QuasiQuotationPattern a = QuasiQuotationPattern
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 QuasiQuotationPattern where liftEq = genericLiftEq
|
||||
instance Ord1 QuasiQuotationPattern where liftCompare = genericLiftCompare
|
||||
instance Show1 QuasiQuotationPattern where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically QuasiQuotationPattern
|
||||
|
||||
instance Evaluatable QuasiQuotationPattern
|
||||
|
||||
data QuasiQuotationType a = QuasiQuotationType
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 QuasiQuotationType where liftEq = genericLiftEq
|
||||
instance Ord1 QuasiQuotationType where liftCompare = genericLiftCompare
|
||||
instance Show1 QuasiQuotationType where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically QuasiQuotationType
|
||||
|
||||
instance Evaluatable QuasiQuotationType
|
||||
|
||||
data QuasiQuotationDeclaration a = QuasiQuotationDeclaration
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 QuasiQuotationDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 QuasiQuotationDeclaration where liftCompare = genericLiftCompare
|
||||
instance Show1 QuasiQuotationDeclaration where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically QuasiQuotationDeclaration
|
||||
|
||||
instance Evaluatable QuasiQuotationDeclaration
|
||||
|
||||
newtype QuasiQuotationQuoter a = QuasiQuotationQuoter { name :: Name }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 QuasiQuotationQuoter where liftEq = genericLiftEq
|
||||
instance Ord1 QuasiQuotationQuoter where liftCompare = genericLiftCompare
|
||||
instance Show1 QuasiQuotationQuoter where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically QuasiQuotationQuoter
|
||||
|
||||
instance Evaluatable QuasiQuotationQuoter
|
||||
|
||||
data QuasiQuotationExpression a = QuasiQuotationExpression
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 QuasiQuotationExpression where liftEq = genericLiftEq
|
||||
instance Ord1 QuasiQuotationExpression where liftCompare = genericLiftCompare
|
||||
instance Show1 QuasiQuotationExpression where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically QuasiQuotationExpression
|
||||
|
||||
instance Evaluatable QuasiQuotationExpression
|
||||
|
||||
newtype Splice a = Splice { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Splice where liftEq = genericLiftEq
|
||||
instance Ord1 Splice where liftCompare = genericLiftCompare
|
||||
instance Show1 Splice where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Splice
|
||||
|
||||
instance Evaluatable Splice
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE DeriveAnyClass, DuplicateRecordFields #-}
|
||||
{-# LANGUAGE DeriveAnyClass, DerivingVia, DuplicateRecordFields #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
|
||||
module Language.Haskell.Syntax.Type where
|
||||
@ -12,209 +12,140 @@ import Proto3.Suite.Class
|
||||
|
||||
data StrictType a = StrictType { strictTypeIdentifier :: a, strictTypeParameters :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 StrictType where liftEq = genericLiftEq
|
||||
instance Ord1 StrictType where liftCompare = genericLiftCompare
|
||||
instance Show1 StrictType where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically StrictType
|
||||
|
||||
instance Evaluatable StrictType
|
||||
|
||||
newtype StrictTypeVariable a = StrictTypeVariable { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 StrictTypeVariable where liftEq = genericLiftEq
|
||||
instance Ord1 StrictTypeVariable where liftCompare = genericLiftCompare
|
||||
instance Show1 StrictTypeVariable where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically StrictTypeVariable
|
||||
|
||||
instance Evaluatable StrictTypeVariable
|
||||
|
||||
data Type a = Type { typeIdentifier :: a, typeParameters :: a, typeKindSignature :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Type where liftEq = genericLiftEq
|
||||
instance Ord1 Type where liftCompare = genericLiftCompare
|
||||
instance Show1 Type where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Type
|
||||
|
||||
instance Evaluatable Type
|
||||
|
||||
data TypeSynonym a = TypeSynonym { typeSynonymLeft :: a, typeSynonymContext :: [a], typeSynonymRight :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 TypeSynonym where liftEq = genericLiftEq
|
||||
instance Ord1 TypeSynonym where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeSynonym where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically TypeSynonym
|
||||
|
||||
instance Evaluatable TypeSynonym
|
||||
|
||||
data AnnotatedTypeVariable a = AnnotatedTypeVariable { annotatedTypeVariableIdentifier :: a, annotatedTypeVariableannotation :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 AnnotatedTypeVariable where liftEq = genericLiftEq
|
||||
instance Ord1 AnnotatedTypeVariable where liftCompare = genericLiftCompare
|
||||
instance Show1 AnnotatedTypeVariable where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically AnnotatedTypeVariable
|
||||
|
||||
instance Evaluatable AnnotatedTypeVariable
|
||||
|
||||
data StandaloneDerivingInstance a = StandaloneDerivingInstance { standaloneDerivingInstanceContext :: [a], standaloneDerivingInstanceClass :: a, standaloneDerivingInstanceInstance :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 StandaloneDerivingInstance where liftEq = genericLiftEq
|
||||
instance Ord1 StandaloneDerivingInstance where liftCompare = genericLiftCompare
|
||||
instance Show1 StandaloneDerivingInstance where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically StandaloneDerivingInstance
|
||||
|
||||
instance Evaluatable StandaloneDerivingInstance
|
||||
|
||||
data FunctionType a = FunctionType { functionTypeLeft :: a, functionTypeRight :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 FunctionType where liftEq = genericLiftEq
|
||||
instance Ord1 FunctionType where liftCompare = genericLiftCompare
|
||||
instance Show1 FunctionType where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically FunctionType
|
||||
|
||||
instance Evaluatable FunctionType
|
||||
|
||||
data TypeSignature a = TypeSignature { typeSignatureName :: [a], typeSignatureContext :: [a], typeSignatureContent :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 TypeSignature where liftEq = genericLiftEq
|
||||
instance Ord1 TypeSignature where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeSignature where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically TypeSignature
|
||||
|
||||
instance Evaluatable TypeSignature
|
||||
|
||||
data ExpressionTypeSignature a = ExpressionTypeSignature { expressionTypeSignatureName :: [a], expressionTypeSignatureContext :: [a], expressionTypeSignatureContent :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ExpressionTypeSignature where liftEq = genericLiftEq
|
||||
instance Ord1 ExpressionTypeSignature where liftCompare = genericLiftCompare
|
||||
instance Show1 ExpressionTypeSignature where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically ExpressionTypeSignature
|
||||
|
||||
instance Evaluatable ExpressionTypeSignature
|
||||
|
||||
newtype KindSignature a = KindSignature { kindSignatureContent :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 KindSignature where liftEq = genericLiftEq
|
||||
instance Ord1 KindSignature where liftCompare = genericLiftCompare
|
||||
instance Show1 KindSignature where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically KindSignature
|
||||
|
||||
instance Evaluatable KindSignature
|
||||
|
||||
data KindFunctionType a = KindFunctionType { kindFunctionTypeLeft :: a, kindFunctionTypeRight :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 KindFunctionType where liftEq = genericLiftEq
|
||||
instance Ord1 KindFunctionType where liftCompare = genericLiftCompare
|
||||
instance Show1 KindFunctionType where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically KindFunctionType
|
||||
|
||||
instance Evaluatable KindFunctionType
|
||||
|
||||
newtype Kind a = Kind { kindKind :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Kind where liftEq = genericLiftEq
|
||||
instance Ord1 Kind where liftCompare = genericLiftCompare
|
||||
instance Show1 Kind where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Kind
|
||||
|
||||
instance Evaluatable Kind
|
||||
|
||||
newtype KindListType a = KindListType { kindListTypeKind :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 KindListType where liftEq = genericLiftEq
|
||||
instance Ord1 KindListType where liftCompare = genericLiftCompare
|
||||
instance Show1 KindListType where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically KindListType
|
||||
|
||||
instance Evaluatable KindListType
|
||||
|
||||
data Star a = Star
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Star where liftEq = genericLiftEq
|
||||
instance Ord1 Star where liftCompare = genericLiftCompare
|
||||
instance Show1 Star where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Star
|
||||
|
||||
instance Evaluatable Star
|
||||
|
||||
data EqualityConstraint a = EqualityConstraint { equalityConstraintLeft :: a, equalityConstraintRight :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 EqualityConstraint where liftEq = genericLiftEq
|
||||
instance Ord1 EqualityConstraint where liftCompare = genericLiftCompare
|
||||
instance Show1 EqualityConstraint where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically EqualityConstraint
|
||||
|
||||
instance Evaluatable EqualityConstraint
|
||||
|
||||
-- e.g. `type instance F [Int] = Int` where `F` is an open type family.
|
||||
data TypeInstance a = TypeInstance { typeInstanceType :: a, typeInstanceBody :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 TypeInstance where liftEq = genericLiftEq
|
||||
instance Ord1 TypeInstance where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeInstance where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically TypeInstance
|
||||
|
||||
instance Evaluatable TypeInstance
|
||||
|
||||
data TypeClassInstance a = TypeClassInstance { typeClassInstanceContext :: [a], typeClassInstanceIdentifier :: a, typeClassInstanceInstance :: a, typeClassInstanceBody :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 TypeClassInstance where liftEq = genericLiftEq
|
||||
instance Ord1 TypeClassInstance where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeClassInstance where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically TypeClassInstance
|
||||
|
||||
instance Evaluatable TypeClassInstance
|
||||
|
||||
newtype Instance a = Instance { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Instance where liftEq = genericLiftEq
|
||||
instance Ord1 Instance where liftCompare = genericLiftCompare
|
||||
instance Show1 Instance where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Instance
|
||||
|
||||
instance Evaluatable Instance
|
||||
|
||||
newtype KindTupleType a = KindTupleType { kindTupleType :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 KindTupleType where liftEq = genericLiftEq
|
||||
instance Ord1 KindTupleType where liftCompare = genericLiftCompare
|
||||
instance Show1 KindTupleType where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically KindTupleType
|
||||
|
||||
instance Evaluatable KindTupleType
|
||||
|
||||
data TypeClass a = TypeClass { typeClassContext :: a, typeClassIdentifier :: a, typeClassParameters :: [a], typeClassBody :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 TypeClass where liftEq = genericLiftEq
|
||||
instance Ord1 TypeClass where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeClass where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically TypeClass
|
||||
|
||||
instance Evaluatable TypeClass
|
||||
|
||||
-- The default signature of a type class. The default signature has the same shape as a TypeSignature Assignment.
|
||||
data DefaultSignature a = DefaultSignature { defaultSignatureName :: [a], defaultSignatureContext :: [a], defaultSignatureContent :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 DefaultSignature where liftEq = genericLiftEq
|
||||
instance Ord1 DefaultSignature where liftCompare = genericLiftCompare
|
||||
instance Show1 DefaultSignature where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically DefaultSignature
|
||||
|
||||
instance Evaluatable DefaultSignature
|
||||
|
||||
data TypeFamily a = TypeFamily { typeFamilyIdentifier :: a, typeFamilyParameters :: [a], typeFamilySignature :: a, typeFamilyBody :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 TypeFamily where liftEq = genericLiftEq
|
||||
instance Ord1 TypeFamily where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeFamily where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically TypeFamily
|
||||
|
||||
instance Evaluatable TypeFamily
|
||||
|
||||
newtype FunctionalDependency a = FunctionalDependency { functionalDependencyContent :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 FunctionalDependency where liftEq = genericLiftEq
|
||||
instance Ord1 FunctionalDependency where liftCompare = genericLiftCompare
|
||||
instance Show1 FunctionalDependency where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically FunctionalDependency
|
||||
|
||||
instance Evaluatable FunctionalDependency
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE DeriveAnyClass, DuplicateRecordFields #-}
|
||||
{-# LANGUAGE DeriveAnyClass, DerivingVia, DuplicateRecordFields #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
module Language.Java.Syntax where
|
||||
|
||||
@ -10,316 +10,216 @@ import Proto3.Suite.Class
|
||||
|
||||
newtype Import a = Import { imports :: [a]}
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
|
||||
instance Eq1 Import where liftEq = genericLiftEq
|
||||
instance Ord1 Import where liftCompare = genericLiftCompare
|
||||
instance Show1 Import where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Import
|
||||
|
||||
-- TODO: Implement Eval instance for ArrayType
|
||||
instance Evaluatable Import
|
||||
|
||||
data Module a = Module { moduleIdentifier :: !a, moduleStatements :: ![a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
|
||||
instance Eq1 Module where liftEq = genericLiftEq
|
||||
instance Ord1 Module where liftCompare = genericLiftCompare
|
||||
instance Show1 Module where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Module
|
||||
|
||||
instance Evaluatable Module
|
||||
|
||||
newtype Package a = Package { packages :: [a]}
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
|
||||
instance Eq1 Package where liftEq = genericLiftEq
|
||||
instance Ord1 Package where liftCompare = genericLiftCompare
|
||||
instance Show1 Package where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Package
|
||||
|
||||
-- TODO: Implement Eval instance for ArrayType
|
||||
instance Evaluatable Package
|
||||
|
||||
data EnumDeclaration a = EnumDeclaration { enumDeclarationModifier :: ![a], enumDeclarationIdentifier :: !a, enumDeclarationSuperInterfaces :: ![a], enumDeclarationConstant :: ![a], enumDeclarationBody :: ![a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically EnumDeclaration
|
||||
|
||||
instance Eq1 EnumDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 EnumDeclaration where liftCompare = genericLiftCompare
|
||||
instance Show1 EnumDeclaration where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable EnumDeclaration
|
||||
|
||||
|
||||
data Variable a = Variable { variableModifiers :: ![a], variableType :: !a, variableName :: !a}
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 Variable where liftEq = genericLiftEq
|
||||
instance Ord1 Variable where liftCompare = genericLiftCompare
|
||||
instance Show1 Variable where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Variable
|
||||
|
||||
-- TODO: Implement Eval instance for Variable
|
||||
instance Evaluatable Variable
|
||||
|
||||
data Synchronized a = Synchronized { synchronizedSubject :: !a, synchronizedBody :: !a}
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 Synchronized where liftEq = genericLiftEq
|
||||
instance Ord1 Synchronized where liftCompare = genericLiftCompare
|
||||
instance Show1 Synchronized where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Synchronized
|
||||
|
||||
-- TODO: Implement Eval instance for Synchronized
|
||||
instance Evaluatable Synchronized
|
||||
|
||||
data New a = New { newType :: !a, newArgs :: ![a], newClassBody :: Maybe a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 New where liftEq = genericLiftEq
|
||||
instance Ord1 New where liftCompare = genericLiftCompare
|
||||
instance Show1 New where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically New
|
||||
|
||||
-- TODO: Implement Eval instance for New
|
||||
instance Evaluatable New
|
||||
|
||||
data Asterisk a = Asterisk
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 Asterisk where liftEq = genericLiftEq
|
||||
instance Ord1 Asterisk where liftCompare = genericLiftCompare
|
||||
instance Show1 Asterisk where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Asterisk
|
||||
|
||||
-- TODO: Implement Eval instance for New
|
||||
instance Evaluatable Asterisk
|
||||
|
||||
|
||||
data Constructor a = Constructor { constructorModifiers :: ![a], constructorTypeParams :: ![a], constructorIdentifier :: !a, constructorParams :: ![a], constructorThrows :: ![a], constructorBody :: a}
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 Constructor where liftEq = genericLiftEq
|
||||
instance Ord1 Constructor where liftCompare = genericLiftCompare
|
||||
instance Show1 Constructor where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Constructor
|
||||
|
||||
-- TODO: Implement Eval instance for Constructor
|
||||
instance Evaluatable Constructor
|
||||
|
||||
data TypeParameter a = TypeParameter { typeParamAnnotation :: ![a], typeParamIdentifier :: !a, typeParamTypeBound :: ![a]}
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 TypeParameter where liftEq = genericLiftEq
|
||||
instance Ord1 TypeParameter where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeParameter where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically TypeParameter
|
||||
|
||||
-- TODO: Implement Eval instance for TypeParameter
|
||||
instance Evaluatable TypeParameter
|
||||
|
||||
data Annotation a = Annotation { annotationName :: !a, annotationField :: [a]}
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Message1, NFData1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Annotation
|
||||
|
||||
instance Named1 Annotation where nameOf1 _ = "JavaAnnotation"
|
||||
instance Eq1 Annotation where liftEq = genericLiftEq
|
||||
instance Ord1 Annotation where liftCompare = genericLiftCompare
|
||||
instance Show1 Annotation where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for Annotation
|
||||
instance Evaluatable Annotation
|
||||
|
||||
data AnnotationField a = AnnotationField { annotationFieldName :: a, annotationFieldValue :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 AnnotationField where liftEq = genericLiftEq
|
||||
instance Ord1 AnnotationField where liftCompare = genericLiftCompare
|
||||
instance Show1 AnnotationField where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically AnnotationField
|
||||
|
||||
-- TODO: Implement Eval instance for AnnotationField
|
||||
instance Evaluatable AnnotationField
|
||||
|
||||
data GenericType a = GenericType { genericTypeIdentifier :: a, genericTypeArguments :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 GenericType where liftEq = genericLiftEq
|
||||
instance Ord1 GenericType where liftCompare = genericLiftCompare
|
||||
instance Show1 GenericType where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically GenericType
|
||||
|
||||
-- TODO: Implement Eval instance for GenericType
|
||||
instance Evaluatable GenericType
|
||||
|
||||
data AnnotatedType a = AnnotatedType { annotationes :: [a], annotatedType :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 AnnotatedType where liftEq = genericLiftEq
|
||||
instance Ord1 AnnotatedType where liftCompare = genericLiftCompare
|
||||
instance Show1 AnnotatedType where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically AnnotatedType
|
||||
|
||||
-- TODO: Implement Eval instance for AnnotatedType
|
||||
instance Evaluatable AnnotatedType
|
||||
|
||||
newtype CatchType a = CatchType { types :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 CatchType where liftEq = genericLiftEq
|
||||
instance Ord1 CatchType where liftCompare = genericLiftCompare
|
||||
instance Show1 CatchType where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically CatchType
|
||||
|
||||
-- TODO: Implement Eval instance for CatchType
|
||||
instance Evaluatable CatchType
|
||||
|
||||
data TypeWithModifiers a = TypeWithModifiers { types :: [a], modifier :: a}
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 TypeWithModifiers where liftEq = genericLiftEq
|
||||
instance Ord1 TypeWithModifiers where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeWithModifiers where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically TypeWithModifiers
|
||||
|
||||
-- TODO: Implement Eval instance for TypeWithModifiers
|
||||
instance Evaluatable TypeWithModifiers
|
||||
|
||||
data Wildcard a = Wildcard { wildcardAnnotation :: [a], wildcardBounds :: Maybe a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 Wildcard where liftEq = genericLiftEq
|
||||
instance Ord1 Wildcard where liftCompare = genericLiftCompare
|
||||
instance Show1 Wildcard where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Wildcard
|
||||
|
||||
-- TODO: Implement Eval instance for TypeWithModifiers
|
||||
instance Evaluatable Wildcard
|
||||
|
||||
data WildcardBounds a = WildcardBoundExtends { wildcardBoundExtendsType :: a} | WildcardBoundSuper { wildcardBoundSuperType :: a}
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 WildcardBounds where liftEq = genericLiftEq
|
||||
instance Ord1 WildcardBounds where liftCompare = genericLiftCompare
|
||||
instance Show1 WildcardBounds where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically WildcardBounds
|
||||
|
||||
-- TODO: Implement Eval instance for TypeWithModifiers
|
||||
instance Evaluatable WildcardBounds
|
||||
|
||||
newtype SpreadParameter a = SpreadParameter { spreadParameterVariableDeclarator :: a}
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 SpreadParameter where liftEq = genericLiftEq
|
||||
instance Ord1 SpreadParameter where liftCompare = genericLiftCompare
|
||||
instance Show1 SpreadParameter where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically SpreadParameter
|
||||
|
||||
-- TODO: Implement Eval instance for SpreadParameter
|
||||
instance Evaluatable SpreadParameter
|
||||
|
||||
newtype StaticInitializer a = StaticInitializer { staticInitializerBlock :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
|
||||
instance Eq1 StaticInitializer where liftEq = genericLiftEq
|
||||
instance Ord1 StaticInitializer where liftCompare = genericLiftCompare
|
||||
instance Show1 StaticInitializer where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically StaticInitializer
|
||||
|
||||
instance Evaluatable StaticInitializer
|
||||
|
||||
data MethodReference a = MethodReference { methodReferenceType :: !a, methodReferenceTypeArgs :: ![a], methodReferenceIdentifier :: !a}
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 MethodReference where liftEq = genericLiftEq
|
||||
instance Ord1 MethodReference where liftCompare = genericLiftCompare
|
||||
instance Show1 MethodReference where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically MethodReference
|
||||
|
||||
-- TODO: Implement Eval instance for TypeWithModifiers
|
||||
instance Evaluatable MethodReference
|
||||
|
||||
data NewKeyword a = NewKeyword
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 NewKeyword where liftEq = genericLiftEq
|
||||
instance Ord1 NewKeyword where liftCompare = genericLiftCompare
|
||||
instance Show1 NewKeyword where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically NewKeyword
|
||||
|
||||
-- TODO: Implement Eval instance for TypeWithModifiers
|
||||
instance Evaluatable NewKeyword
|
||||
|
||||
data Lambda a = Lambda { lambdaParams :: ![a], lambdaBody :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 Lambda where liftEq = genericLiftEq
|
||||
instance Ord1 Lambda where liftCompare = genericLiftCompare
|
||||
instance Show1 Lambda where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Lambda
|
||||
|
||||
instance Evaluatable Lambda
|
||||
|
||||
newtype LambdaBody a = LambdaBody { lambdaBodyExpression :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 LambdaBody where liftEq = genericLiftEq
|
||||
instance Ord1 LambdaBody where liftCompare = genericLiftCompare
|
||||
instance Show1 LambdaBody where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically LambdaBody
|
||||
|
||||
instance Evaluatable LambdaBody
|
||||
|
||||
data ArrayCreationExpression a = ArrayCreationExpression { arrayCreationExpressionType :: !a, arrayCreationExpressionDims :: ![a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 ArrayCreationExpression where liftEq = genericLiftEq
|
||||
instance Ord1 ArrayCreationExpression where liftCompare = genericLiftCompare
|
||||
instance Show1 ArrayCreationExpression where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically ArrayCreationExpression
|
||||
|
||||
instance Evaluatable ArrayCreationExpression
|
||||
|
||||
data DimsExpr a = DimsExpr { dimsExprAnnotation :: ![a], dimsExprExpression :: ![a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 DimsExpr where liftEq = genericLiftEq
|
||||
instance Ord1 DimsExpr where liftCompare = genericLiftCompare
|
||||
instance Show1 DimsExpr where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically DimsExpr
|
||||
|
||||
instance Evaluatable DimsExpr
|
||||
|
||||
newtype ClassBody a = ClassBody { classBodyExpression :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 ClassBody where liftEq = genericLiftEq
|
||||
instance Ord1 ClassBody where liftCompare = genericLiftCompare
|
||||
instance Show1 ClassBody where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically ClassBody
|
||||
|
||||
instance Evaluatable ClassBody
|
||||
|
||||
newtype ClassLiteral a = ClassLiteral { classLiteralType :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 ClassLiteral where liftEq = genericLiftEq
|
||||
instance Ord1 ClassLiteral where liftCompare = genericLiftCompare
|
||||
instance Show1 ClassLiteral where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically ClassLiteral
|
||||
|
||||
instance Evaluatable ClassLiteral
|
||||
|
||||
data TryWithResources a = TryWithResources { tryResources :: ![a], tryBody :: !a, tryCatch :: ![a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 TryWithResources where liftEq = genericLiftEq
|
||||
instance Ord1 TryWithResources where liftCompare = genericLiftCompare
|
||||
instance Show1 TryWithResources where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically TryWithResources
|
||||
|
||||
-- TODO: Implement Eval instance for TryWithResources
|
||||
instance Evaluatable TryWithResources
|
||||
|
||||
data AssertStatement a = AssertStatement { assertLHS :: !a, assertRHS :: !(Maybe a) }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 AssertStatement where liftEq = genericLiftEq
|
||||
instance Ord1 AssertStatement where liftCompare = genericLiftCompare
|
||||
instance Show1 AssertStatement where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically AssertStatement
|
||||
|
||||
-- TODO: Implement Eval instance for AssertStatement
|
||||
instance Evaluatable AssertStatement
|
||||
|
||||
newtype DefaultValue a = DefaultValue { defaultValueElement :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 DefaultValue where liftEq = genericLiftEq
|
||||
instance Ord1 DefaultValue where liftCompare = genericLiftCompare
|
||||
instance Show1 DefaultValue where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically DefaultValue
|
||||
|
||||
instance Evaluatable DefaultValue
|
||||
|
||||
data AnnotationTypeElement a = AnnotationTypeElement { modifiers :: ![a], annotationType :: a, identifier :: !a, dims :: ![a], defaultValue :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Named1, Message1, NFData1, Traversable)
|
||||
|
||||
instance Eq1 AnnotationTypeElement where liftEq = genericLiftEq
|
||||
instance Ord1 AnnotationTypeElement where liftCompare = genericLiftCompare
|
||||
instance Show1 AnnotationTypeElement where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically AnnotationTypeElement
|
||||
|
||||
-- TODO: Implement Eval instance for AnnotationTypeElement
|
||||
instance Evaluatable AnnotationTypeElement
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE DeriveAnyClass, DuplicateRecordFields #-}
|
||||
{-# LANGUAGE DeriveAnyClass, DerivingVia, DuplicateRecordFields #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
module Language.Markdown.Syntax where
|
||||
|
||||
@ -12,110 +12,69 @@ import qualified Proto3.Suite as PB
|
||||
|
||||
newtype Document a = Document { values :: [a] }
|
||||
deriving (Eq, Ord, Show, Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Document where liftEq = genericLiftEq
|
||||
instance Ord1 Document where liftCompare = genericLiftCompare
|
||||
instance Show1 Document where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Document
|
||||
|
||||
|
||||
-- Block elements
|
||||
|
||||
newtype Paragraph a = Paragraph { values :: [a] }
|
||||
deriving (Eq, Ord, Show, Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Paragraph where liftEq = genericLiftEq
|
||||
instance Ord1 Paragraph where liftCompare = genericLiftCompare
|
||||
instance Show1 Paragraph where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Paragraph
|
||||
|
||||
data Heading a = Heading { headingLevel :: Int, headingContent :: [a], sectionContent :: [a] }
|
||||
deriving (Eq, Ord, Show, Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Heading where liftEq = genericLiftEq
|
||||
instance Ord1 Heading where liftCompare = genericLiftCompare
|
||||
instance Show1 Heading where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Heading
|
||||
|
||||
newtype UnorderedList a = UnorderedList { values :: [a] }
|
||||
deriving (Eq, Ord, Show, Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 UnorderedList where liftEq = genericLiftEq
|
||||
instance Ord1 UnorderedList where liftCompare = genericLiftCompare
|
||||
instance Show1 UnorderedList where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically UnorderedList
|
||||
|
||||
newtype OrderedList a = OrderedList { values :: [a] }
|
||||
deriving (Eq, Ord, Show, Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 OrderedList where liftEq = genericLiftEq
|
||||
instance Ord1 OrderedList where liftCompare = genericLiftCompare
|
||||
instance Show1 OrderedList where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically OrderedList
|
||||
|
||||
newtype BlockQuote a = BlockQuote { values :: [a] }
|
||||
deriving (Eq, Ord, Show, Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 BlockQuote where liftEq = genericLiftEq
|
||||
instance Ord1 BlockQuote where liftCompare = genericLiftCompare
|
||||
instance Show1 BlockQuote where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically BlockQuote
|
||||
|
||||
data ThematicBreak a = ThematicBreak
|
||||
deriving (Eq, Ord, Show, Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ThematicBreak where liftEq = genericLiftEq
|
||||
instance Ord1 ThematicBreak where liftCompare = genericLiftCompare
|
||||
instance Show1 ThematicBreak where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically ThematicBreak
|
||||
|
||||
newtype HTMLBlock a = HTMLBlock { value :: T.Text }
|
||||
deriving (Eq, Ord, Show, Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 HTMLBlock where liftEq = genericLiftEq
|
||||
instance Ord1 HTMLBlock where liftCompare = genericLiftCompare
|
||||
instance Show1 HTMLBlock where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically HTMLBlock
|
||||
|
||||
newtype Table a = Table { values :: [a] }
|
||||
deriving (Eq, Ord, Show, Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Table where liftEq = genericLiftEq
|
||||
instance Ord1 Table where liftCompare = genericLiftCompare
|
||||
instance Show1 Table where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Table
|
||||
|
||||
newtype TableRow a = TableRow { values :: [a] }
|
||||
deriving (Eq, Ord, Show, Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 TableRow where liftEq = genericLiftEq
|
||||
instance Ord1 TableRow where liftCompare = genericLiftCompare
|
||||
instance Show1 TableRow where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically TableRow
|
||||
|
||||
newtype TableCell a = TableCell { values :: [a] }
|
||||
deriving (Eq, Ord, Show, Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 TableCell where liftEq = genericLiftEq
|
||||
instance Ord1 TableCell where liftCompare = genericLiftCompare
|
||||
instance Show1 TableCell where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically TableCell
|
||||
|
||||
|
||||
-- Inline elements
|
||||
|
||||
newtype Strong a = Strong { values :: [a] }
|
||||
deriving (Eq, Ord, Show, Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Strong where liftEq = genericLiftEq
|
||||
instance Ord1 Strong where liftCompare = genericLiftCompare
|
||||
instance Show1 Strong where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Strong
|
||||
|
||||
newtype Emphasis a = Emphasis { values :: [a] }
|
||||
deriving (Eq, Ord, Show, Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Emphasis where liftEq = genericLiftEq
|
||||
instance Ord1 Emphasis where liftCompare = genericLiftCompare
|
||||
instance Show1 Emphasis where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Emphasis
|
||||
|
||||
newtype Text a = Text { value :: T.Text}
|
||||
deriving (Eq, Ord, Show, Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Text where liftEq = genericLiftEq
|
||||
instance Ord1 Text where liftCompare = genericLiftCompare
|
||||
instance Show1 Text where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Text
|
||||
|
||||
data Link a = Link { linkURL :: T.Text, linkTitle :: Maybe T.Text }
|
||||
deriving (Eq, Ord, Show, Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, Named1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Link
|
||||
|
||||
instance Message1 Link where
|
||||
liftEncodeMessage _ _ Link{..} = encodeMessageField 1 linkURL <> maybe mempty (encodeMessageField 2) linkTitle
|
||||
@ -125,12 +84,9 @@ instance Message1 Link where
|
||||
, DotProtoMessageField $ DotProtoField 2 (Prim PB.String) (Single "linkTitle") [] Nothing
|
||||
]
|
||||
|
||||
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, Named1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Image
|
||||
|
||||
instance Message1 Image where
|
||||
liftEncodeMessage _ _ Image{..} = encodeMessageField 1 imageURL <> maybe mempty (encodeMessageField 2) imageTitle
|
||||
@ -140,12 +96,9 @@ instance Message1 Image where
|
||||
, DotProtoMessageField $ DotProtoField 2 (Prim PB.String) (Single "imageTitle") [] Nothing
|
||||
]
|
||||
|
||||
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, Named1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Code
|
||||
|
||||
instance Message1 Code where
|
||||
liftEncodeMessage _ _ Code{..} = maybe mempty (encodeMessageField 1) codeLanguage <> encodeMessageField 2 codeContent
|
||||
@ -155,21 +108,10 @@ instance Message1 Code where
|
||||
, DotProtoMessageField $ DotProtoField 2 (Prim PB.String) (Single "codeContent") [] Nothing
|
||||
]
|
||||
|
||||
|
||||
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, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 LineBreak where liftEq = genericLiftEq
|
||||
instance Ord1 LineBreak where liftCompare = genericLiftCompare
|
||||
instance Show1 LineBreak where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically LineBreak
|
||||
|
||||
newtype Strikethrough a = Strikethrough { values :: [a] }
|
||||
deriving (Eq, Ord, Show, Declarations1, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, ToJSONFields1, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Strikethrough where liftEq = genericLiftEq
|
||||
instance Ord1 Strikethrough where liftCompare = genericLiftCompare
|
||||
instance Show1 Strikethrough where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Strikethrough
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE DeriveAnyClass, DuplicateRecordFields #-}
|
||||
{-# LANGUAGE DeriveAnyClass, DerivingVia, DuplicateRecordFields #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
module Language.PHP.Syntax where
|
||||
|
||||
@ -18,19 +18,14 @@ import qualified Data.Map.Strict as Map
|
||||
|
||||
newtype Text a = Text { value :: T.Text }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Text
|
||||
|
||||
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, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically VariableName
|
||||
|
||||
instance Eq1 VariableName where liftEq = genericLiftEq
|
||||
instance Ord1 VariableName where liftCompare = genericLiftCompare
|
||||
instance Show1 VariableName where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable VariableName
|
||||
|
||||
-- TODO: Variables defined in an included file take on scope of the source line
|
||||
@ -84,10 +79,7 @@ include eval pathTerm f = do
|
||||
|
||||
newtype Require a = Require { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Require where liftEq = genericLiftEq
|
||||
instance Ord1 Require where liftCompare = genericLiftCompare
|
||||
instance Show1 Require where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Require
|
||||
|
||||
instance Evaluatable Require where
|
||||
eval eval _ (Require path) = include eval path load
|
||||
@ -95,126 +87,89 @@ instance Evaluatable Require where
|
||||
|
||||
newtype RequireOnce a = RequireOnce { value :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 RequireOnce where liftEq = genericLiftEq
|
||||
instance Ord1 RequireOnce where liftCompare = genericLiftCompare
|
||||
instance Show1 RequireOnce where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically RequireOnce
|
||||
|
||||
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, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Include where liftEq = genericLiftEq
|
||||
instance Ord1 Include where liftCompare = genericLiftCompare
|
||||
instance Show1 Include where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Include
|
||||
|
||||
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, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 IncludeOnce where liftEq = genericLiftEq
|
||||
instance Ord1 IncludeOnce where liftCompare = genericLiftCompare
|
||||
instance Show1 IncludeOnce where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically IncludeOnce
|
||||
|
||||
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, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ArrayElement
|
||||
|
||||
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, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically GlobalDeclaration
|
||||
|
||||
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, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically SimpleVariable
|
||||
|
||||
instance Eq1 SimpleVariable where liftEq = genericLiftEq
|
||||
instance Ord1 SimpleVariable where liftCompare = genericLiftCompare
|
||||
instance Show1 SimpleVariable where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable SimpleVariable
|
||||
|
||||
|
||||
-- | TODO: Unify with TypeScript's PredefinedType
|
||||
newtype CastType a = CastType { _castType :: T.Text }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically CastType
|
||||
|
||||
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, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ErrorControl
|
||||
|
||||
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, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Clone
|
||||
|
||||
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, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ShellCommand
|
||||
|
||||
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, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Update where liftEq = genericLiftEq
|
||||
instance Ord1 Update where liftCompare = genericLiftCompare
|
||||
instance Show1 Update where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Update
|
||||
instance Evaluatable Update
|
||||
|
||||
newtype NewVariable a = NewVariable { values :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically NewVariable
|
||||
|
||||
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, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically RelativeScope
|
||||
|
||||
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, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 QualifiedName where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedName where liftCompare = genericLiftCompare
|
||||
instance Show1 QualifiedName where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically QualifiedName
|
||||
|
||||
instance Evaluatable QualifiedName where
|
||||
eval _ _ (QualifiedName obj iden) = do
|
||||
@ -238,308 +193,227 @@ instance Evaluatable QualifiedName where
|
||||
|
||||
newtype NamespaceName a = NamespaceName { names :: NonEmpty a }
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Diffable, FreeVariables1, Declarations1, ToJSONFields1, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically NamespaceName
|
||||
|
||||
instance Hashable1 NamespaceName where liftHashWithSalt = foldl
|
||||
instance Eq1 NamespaceName where liftEq = genericLiftEq
|
||||
instance Ord1 NamespaceName where liftCompare = genericLiftCompare
|
||||
instance Show1 NamespaceName where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable NamespaceName
|
||||
|
||||
newtype ConstDeclaration a = ConstDeclaration { values :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ConstDeclaration
|
||||
|
||||
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, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ClassConstDeclaration
|
||||
|
||||
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, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ClassInterfaceClause
|
||||
|
||||
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, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ClassBaseClause
|
||||
|
||||
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, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically UseClause
|
||||
|
||||
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, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ReturnType
|
||||
|
||||
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, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically TypeDeclaration
|
||||
|
||||
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, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 BaseTypeDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 BaseTypeDeclaration where liftCompare = genericLiftCompare
|
||||
instance Show1 BaseTypeDeclaration where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically BaseTypeDeclaration
|
||||
instance Evaluatable BaseTypeDeclaration
|
||||
|
||||
newtype ScalarType a = ScalarType { value :: T.Text }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ScalarType
|
||||
|
||||
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, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically EmptyIntrinsic
|
||||
|
||||
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, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ExitIntrinsic
|
||||
|
||||
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, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically IssetIntrinsic
|
||||
|
||||
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, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically EvalIntrinsic
|
||||
|
||||
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, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically PrintIntrinsic
|
||||
|
||||
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, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 NamespaceAliasingClause where liftEq = genericLiftEq
|
||||
instance Ord1 NamespaceAliasingClause where liftCompare = genericLiftCompare
|
||||
instance Show1 NamespaceAliasingClause where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically NamespaceAliasingClause
|
||||
instance Evaluatable NamespaceAliasingClause
|
||||
|
||||
newtype NamespaceUseDeclaration a = NamespaceUseDeclaration { values :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically NamespaceUseDeclaration
|
||||
|
||||
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, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically NamespaceUseClause
|
||||
|
||||
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, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically NamespaceUseGroupClause
|
||||
|
||||
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, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Namespace where liftEq = genericLiftEq
|
||||
instance Ord1 Namespace where liftCompare = genericLiftCompare
|
||||
instance Show1 Namespace where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Namespace
|
||||
|
||||
instance Evaluatable Namespace
|
||||
|
||||
data TraitDeclaration a = TraitDeclaration { traitName :: a, traitStatements :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically TraitDeclaration
|
||||
|
||||
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, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically AliasAs
|
||||
|
||||
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, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically InsteadOf
|
||||
|
||||
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, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically TraitUseSpecification
|
||||
|
||||
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, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically TraitUseClause
|
||||
|
||||
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, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically DestructorDeclaration
|
||||
|
||||
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, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Static
|
||||
|
||||
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, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ClassModifier
|
||||
|
||||
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, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 ConstructorDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 ConstructorDeclaration where liftCompare = genericLiftCompare
|
||||
instance Show1 ConstructorDeclaration where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically ConstructorDeclaration
|
||||
instance Evaluatable ConstructorDeclaration
|
||||
|
||||
data PropertyDeclaration a = PropertyDeclaration { modifier :: a, elements :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically PropertyDeclaration
|
||||
|
||||
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, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically PropertyModifier
|
||||
|
||||
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, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically InterfaceDeclaration
|
||||
|
||||
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, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically InterfaceBaseClause
|
||||
|
||||
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, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Echo
|
||||
|
||||
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, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Unset
|
||||
|
||||
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, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Declare
|
||||
|
||||
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, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically DeclareDirective
|
||||
|
||||
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, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically LabeledStatement
|
||||
|
||||
instance Eq1 LabeledStatement where liftEq = genericLiftEq
|
||||
instance Ord1 LabeledStatement where liftCompare = genericLiftCompare
|
||||
instance Show1 LabeledStatement where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable LabeledStatement
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE DeriveAnyClass #-}
|
||||
{-# LANGUAGE DeriveAnyClass, DerivingVia #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
{-# OPTIONS_GHC -fno-warn-orphans #-} -- FIXME
|
||||
module Language.Python.Syntax where
|
||||
@ -109,17 +109,11 @@ resolvePythonModules q = do
|
||||
-- If the list of symbols is empty copy everything to the calling environment.
|
||||
data Import a = Import { importFrom :: QualifiedName, importSymbols :: ![Alias] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
|
||||
instance Eq1 Import where liftEq = genericLiftEq
|
||||
instance Ord1 Import where liftCompare = genericLiftCompare
|
||||
instance Show1 Import where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Import
|
||||
|
||||
newtype FutureImport a = FutureImport { futureImportSymbols :: [Alias] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
|
||||
instance Eq1 FutureImport where liftEq = genericLiftEq
|
||||
instance Ord1 FutureImport where liftCompare = genericLiftCompare
|
||||
instance Show1 FutureImport where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically FutureImport
|
||||
|
||||
instance Evaluatable FutureImport where
|
||||
|
||||
@ -189,6 +183,7 @@ instance Evaluatable Import where
|
||||
|
||||
newtype QualifiedImport a = QualifiedImport { qualifiedImportFrom :: NonEmpty String }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Named1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically QualifiedImport
|
||||
|
||||
instance Message1 QualifiedImport where
|
||||
liftEncodeMessage _ _ QualifiedImport{..} = encodeMessageField 1 qualifiedImportFrom
|
||||
@ -202,10 +197,6 @@ instance Message Prelude.String where
|
||||
decodeMessage _ = Decode.at (Decode.one decodePrimitive mempty) 1
|
||||
dotProto = undefined
|
||||
|
||||
instance Eq1 QualifiedImport where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedImport where liftCompare = genericLiftCompare
|
||||
instance Show1 QualifiedImport where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- import a.b.c
|
||||
instance Evaluatable QualifiedImport where
|
||||
eval _ _ (QualifiedImport qualifiedName) = do
|
||||
@ -242,10 +233,7 @@ instance Evaluatable QualifiedImport where
|
||||
|
||||
data QualifiedAliasedImport a = QualifiedAliasedImport { qualifiedAliasedImportFrom :: QualifiedName, qualifiedAliasedImportAlias :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
|
||||
instance Eq1 QualifiedAliasedImport where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedAliasedImport where liftCompare = genericLiftCompare
|
||||
instance Show1 QualifiedAliasedImport where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically QualifiedAliasedImport
|
||||
|
||||
-- import a.b.c as e
|
||||
instance Evaluatable QualifiedAliasedImport where
|
||||
@ -272,21 +260,14 @@ instance Evaluatable QualifiedAliasedImport where
|
||||
-- | Ellipsis (used in splice expressions and alternatively can be used as a fill in expression, like `undefined` in Haskell)
|
||||
data Ellipsis a = Ellipsis
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
|
||||
instance Eq1 Ellipsis where liftEq = genericLiftEq
|
||||
instance Ord1 Ellipsis where liftCompare = genericLiftCompare
|
||||
instance Show1 Ellipsis where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Ellipsis
|
||||
|
||||
-- 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, Message1, Named1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
|
||||
instance Eq1 Redirect where liftEq = genericLiftEq
|
||||
instance Ord1 Redirect where liftCompare = genericLiftCompare
|
||||
instance Show1 Redirect where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Redirect
|
||||
|
||||
-- TODO: Implement Eval instance for Redirect
|
||||
instance Evaluatable Redirect
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE DeriveAnyClass, DuplicateRecordFields, TupleSections #-}
|
||||
{-# LANGUAGE DeriveAnyClass, DerivingVia, DuplicateRecordFields, TupleSections #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
module Language.Ruby.Syntax where
|
||||
|
||||
@ -64,10 +64,7 @@ cleanNameOrPath = T.unpack . dropRelativePrefix . stripQuotes
|
||||
|
||||
data Send a = Send { sendReceiver :: Maybe a, sendSelector :: Maybe a, sendArgs :: [a], sendBlock :: Maybe a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Send where liftEq = genericLiftEq
|
||||
instance Ord1 Send where liftCompare = genericLiftCompare
|
||||
instance Show1 Send where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Send
|
||||
|
||||
instance Evaluatable Send where
|
||||
eval eval _ Send{..} = do
|
||||
@ -97,10 +94,7 @@ instance Tokenize Send where
|
||||
|
||||
data Require a = Require { requireRelative :: Bool, requirePath :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Require where liftEq = genericLiftEq
|
||||
instance Ord1 Require where liftCompare = genericLiftCompare
|
||||
instance Show1 Require where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Require
|
||||
|
||||
instance Evaluatable Require where
|
||||
eval eval _ (Require _ x) = do
|
||||
@ -134,10 +128,7 @@ doRequire path = do
|
||||
|
||||
data Load a = Load { loadPath :: a, loadWrap :: Maybe a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Load where liftEq = genericLiftEq
|
||||
instance Ord1 Load where liftCompare = genericLiftCompare
|
||||
instance Show1 Load where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Load
|
||||
|
||||
instance Tokenize Load where
|
||||
tokenize Load{..} = do
|
||||
@ -183,14 +174,11 @@ doLoad path shouldWrap = do
|
||||
|
||||
data Class a = Class { classIdentifier :: !a, classSuperClass :: !(Maybe a), classBody :: !a }
|
||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, FreeVariables1, ToJSONFields1, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Class
|
||||
|
||||
instance Diffable Class where
|
||||
equivalentBySubterm = Just . classIdentifier
|
||||
|
||||
instance Eq1 Class where liftEq = genericLiftEq
|
||||
instance Ord1 Class where liftCompare = genericLiftCompare
|
||||
instance Show1 Class where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Class where
|
||||
eval eval _ Class{..} = do
|
||||
name <- maybeM (throwNoNameError classIdentifier) (declaredName classIdentifier)
|
||||
@ -249,10 +237,7 @@ instance Tokenize Class where
|
||||
|
||||
data Module a = Module { moduleIdentifier :: !a, moduleStatements :: ![a] }
|
||||
deriving (Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
|
||||
instance Eq1 Module where liftEq = genericLiftEq
|
||||
instance Ord1 Module where liftCompare = genericLiftCompare
|
||||
instance Show1 Module where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Module
|
||||
|
||||
instance Evaluatable Module where
|
||||
eval eval _ Module{..} = do
|
||||
@ -300,6 +285,7 @@ instance Tokenize Module where
|
||||
|
||||
data LowPrecedenceAnd a = LowPrecedenceAnd { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically LowPrecedenceAnd
|
||||
|
||||
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
|
||||
@ -308,19 +294,15 @@ instance Evaluatable LowPrecedenceAnd where
|
||||
cond <- a
|
||||
ifthenelse cond b (pure cond)
|
||||
|
||||
instance Eq1 LowPrecedenceAnd where liftEq = genericLiftEq
|
||||
instance Ord1 LowPrecedenceAnd where liftCompare = genericLiftCompare
|
||||
instance Show1 LowPrecedenceAnd where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: These should probably be expressed with a new context/token,
|
||||
-- rather than a literal run, and need to take surrounding precedence
|
||||
-- into account.
|
||||
instance Tokenize LowPrecedenceAnd where
|
||||
tokenize LowPrecedenceAnd{..} = lhs *> yield (Token.Run "and") <* rhs
|
||||
|
||||
|
||||
data LowPrecedenceOr a = LowPrecedenceOr { lhs :: a, rhs :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically LowPrecedenceOr
|
||||
|
||||
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
|
||||
@ -329,23 +311,16 @@ instance Evaluatable LowPrecedenceOr where
|
||||
cond <- a
|
||||
ifthenelse cond (pure cond) b
|
||||
|
||||
instance Eq1 LowPrecedenceOr where liftEq = genericLiftEq
|
||||
instance Ord1 LowPrecedenceOr where liftCompare = genericLiftCompare
|
||||
instance Show1 LowPrecedenceOr where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Tokenize LowPrecedenceOr where
|
||||
tokenize LowPrecedenceOr{..} = lhs *> yield (Token.Run "or") <* rhs
|
||||
|
||||
data Assignment a = Assignment { assignmentContext :: ![a], assignmentTarget :: !a, assignmentValue :: !a }
|
||||
deriving (Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Assignment
|
||||
|
||||
instance Declarations1 Assignment where
|
||||
liftDeclaredName declaredName Assignment{..} = declaredName assignmentTarget
|
||||
|
||||
instance Eq1 Assignment where liftEq = genericLiftEq
|
||||
instance Ord1 Assignment where liftCompare = genericLiftCompare
|
||||
instance Show1 Assignment where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Assignment where
|
||||
eval eval ref Assignment{..} = do
|
||||
lhsName <- maybeM (throwNoNameError assignmentTarget) (declaredName assignmentTarget)
|
||||
@ -379,12 +354,9 @@ instance Tokenize Assignment where
|
||||
-- arguments to the @super()@ invocation.
|
||||
data ZSuper a = ZSuper
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ZSuper
|
||||
|
||||
instance Evaluatable ZSuper
|
||||
|
||||
instance Eq1 ZSuper where liftEq = genericLiftEq
|
||||
instance Ord1 ZSuper where liftCompare = genericLiftCompare
|
||||
instance Show1 ZSuper where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Tokenize ZSuper where
|
||||
tokenize _ = yield $ Run "super"
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE DeriveAnyClass, DerivingStrategies, DuplicateRecordFields #-}
|
||||
{-# LANGUAGE DeriveAnyClass, DerivingStrategies, DerivingVia, DuplicateRecordFields #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
module Language.TypeScript.Syntax.Import where
|
||||
|
||||
@ -18,10 +18,7 @@ import Language.TypeScript.Resolution
|
||||
|
||||
data Import a = Import { importSymbols :: ![Alias], importFrom :: ImportPath }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Import where liftEq = genericLiftEq
|
||||
instance Ord1 Import where liftCompare = genericLiftCompare
|
||||
instance Show1 Import where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Import
|
||||
|
||||
-- http://www.typescriptlang.org/docs/handbook/module-resolution.html
|
||||
instance Evaluatable Import where
|
||||
@ -49,10 +46,7 @@ instance Evaluatable Import where
|
||||
|
||||
data QualifiedAliasedImport a = QualifiedAliasedImport { qualifiedAliasedImportAlias :: !a, qualifiedAliasedImportFrom :: ImportPath }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 QualifiedAliasedImport where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedAliasedImport where liftCompare = genericLiftCompare
|
||||
instance Show1 QualifiedAliasedImport where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically QualifiedAliasedImport
|
||||
|
||||
instance Evaluatable QualifiedAliasedImport where
|
||||
eval _ _ (QualifiedAliasedImport aliasTerm importPath) = do
|
||||
@ -71,13 +65,9 @@ instance Evaluatable QualifiedAliasedImport where
|
||||
|
||||
pure unit
|
||||
|
||||
|
||||
newtype SideEffectImport a = SideEffectImport { sideEffectImportFrom :: ImportPath }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 SideEffectImport where liftEq = genericLiftEq
|
||||
instance Ord1 SideEffectImport where liftCompare = genericLiftCompare
|
||||
instance Show1 SideEffectImport where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically SideEffectImport
|
||||
|
||||
instance Evaluatable SideEffectImport where
|
||||
eval _ _ (SideEffectImport importPath) = do
|
||||
@ -85,14 +75,10 @@ instance Evaluatable SideEffectImport where
|
||||
void $ require modulePath
|
||||
pure unit
|
||||
|
||||
|
||||
-- | Qualified Export declarations
|
||||
newtype QualifiedExport a = QualifiedExport { qualifiedExportSymbols :: [Alias] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 QualifiedExport where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedExport where liftCompare = genericLiftCompare
|
||||
instance Show1 QualifiedExport where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically QualifiedExport
|
||||
|
||||
instance Evaluatable QualifiedExport where
|
||||
eval _ _ (QualifiedExport exportSymbols) = do
|
||||
@ -117,10 +103,7 @@ toTuple Alias{..} = (aliasValue, aliasName)
|
||||
-- | Qualified Export declarations that export from another module.
|
||||
data QualifiedExportFrom a = QualifiedExportFrom { qualifiedExportFrom :: ImportPath, qualifiedExportFromSymbols :: ![Alias]}
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 QualifiedExportFrom where liftEq = genericLiftEq
|
||||
instance Ord1 QualifiedExportFrom where liftCompare = genericLiftCompare
|
||||
instance Show1 QualifiedExportFrom where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically QualifiedExportFrom
|
||||
|
||||
instance Evaluatable QualifiedExportFrom where
|
||||
eval _ _ (QualifiedExportFrom importPath exportSymbols) = do
|
||||
@ -141,10 +124,7 @@ instance Evaluatable QualifiedExportFrom where
|
||||
|
||||
newtype DefaultExport a = DefaultExport { defaultExport :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 DefaultExport where liftEq = genericLiftEq
|
||||
instance Ord1 DefaultExport where liftCompare = genericLiftCompare
|
||||
instance Show1 DefaultExport where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically DefaultExport
|
||||
|
||||
instance Evaluatable DefaultExport where
|
||||
eval eval _ (DefaultExport term) = do
|
||||
@ -167,24 +147,18 @@ instance Evaluatable DefaultExport where
|
||||
|
||||
data ImportRequireClause a = ImportRequireClause { importRequireIdentifier :: !a, importRequireSubject :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ImportRequireClause
|
||||
|
||||
instance Eq1 ImportRequireClause where liftEq = genericLiftEq
|
||||
instance Ord1 ImportRequireClause where liftCompare = genericLiftCompare
|
||||
instance Show1 ImportRequireClause where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ImportRequireClause
|
||||
|
||||
newtype ImportClause a = ImportClause { importClauseElements :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ImportClause
|
||||
|
||||
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, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ImportAlias
|
||||
|
||||
instance Eq1 ImportAlias where liftEq = genericLiftEq
|
||||
instance Ord1 ImportAlias where liftCompare = genericLiftCompare
|
||||
instance Show1 ImportAlias where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ImportAlias
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE DeriveAnyClass, DuplicateRecordFields #-}
|
||||
{-# LANGUAGE DeriveAnyClass, DerivingVia, DuplicateRecordFields #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
module Language.TypeScript.Syntax.JSX where
|
||||
|
||||
@ -15,85 +15,65 @@ import Control.Abstract as Abstract
|
||||
|
||||
data JsxElement a = JsxElement { jsxOpeningElement :: !a, jsxElements :: ![a], jsxClosingElement :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically JsxElement
|
||||
|
||||
instance Eq1 JsxElement where liftEq = genericLiftEq
|
||||
instance Ord1 JsxElement where liftCompare = genericLiftCompare
|
||||
instance Show1 JsxElement where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable JsxElement
|
||||
|
||||
newtype JsxText a = JsxText { contents :: T.Text }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically JsxText
|
||||
|
||||
instance Eq1 JsxText where liftEq = genericLiftEq
|
||||
instance Ord1 JsxText where liftCompare = genericLiftCompare
|
||||
instance Show1 JsxText where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable JsxText
|
||||
|
||||
newtype JsxExpression a = JsxExpression { jsxExpression :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically JsxExpression
|
||||
|
||||
instance Eq1 JsxExpression where liftEq = genericLiftEq
|
||||
instance Ord1 JsxExpression where liftCompare = genericLiftCompare
|
||||
instance Show1 JsxExpression where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable JsxExpression
|
||||
|
||||
data JsxOpeningElement a = JsxOpeningElement { jsxOpeningElementIdentifier :: !a, jsxAttributes :: ![a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically JsxOpeningElement
|
||||
|
||||
instance Eq1 JsxOpeningElement where liftEq = genericLiftEq
|
||||
instance Ord1 JsxOpeningElement where liftCompare = genericLiftCompare
|
||||
instance Show1 JsxOpeningElement where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable JsxOpeningElement
|
||||
|
||||
newtype JsxClosingElement a = JsxClosingElement { jsxClosingElementIdentifier :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically JsxClosingElement
|
||||
|
||||
instance Eq1 JsxClosingElement where liftEq = genericLiftEq
|
||||
instance Ord1 JsxClosingElement where liftCompare = genericLiftCompare
|
||||
instance Show1 JsxClosingElement where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable JsxClosingElement
|
||||
|
||||
data JsxSelfClosingElement a = JsxSelfClosingElement { jsxSelfClosingElementIdentifier :: !a, jsxSelfClosingElementAttributes :: ![a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically JsxSelfClosingElement
|
||||
|
||||
instance Eq1 JsxSelfClosingElement where liftEq = genericLiftEq
|
||||
instance Ord1 JsxSelfClosingElement where liftCompare = genericLiftCompare
|
||||
instance Show1 JsxSelfClosingElement where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable JsxSelfClosingElement
|
||||
|
||||
data JsxAttribute a = JsxAttribute { jsxAttributeTarget :: !a, jsxAttributeValue :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically JsxAttribute
|
||||
|
||||
instance Eq1 JsxAttribute where liftEq = genericLiftEq
|
||||
instance Ord1 JsxAttribute where liftCompare = genericLiftCompare
|
||||
instance Show1 JsxAttribute where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable JsxAttribute
|
||||
|
||||
newtype ImplementsClause a = ImplementsClause { implementsClauseTypes :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ImplementsClause
|
||||
|
||||
instance Eq1 ImplementsClause where liftEq = genericLiftEq
|
||||
instance Ord1 ImplementsClause where liftCompare = genericLiftCompare
|
||||
instance Show1 ImplementsClause where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ImplementsClause
|
||||
|
||||
data OptionalParameter a = OptionalParameter { optionalParameterContext :: ![a], optionalParameterSubject :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically OptionalParameter
|
||||
|
||||
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 }
|
||||
deriving (Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically RequiredParameter
|
||||
|
||||
instance Declarations1 RequiredParameter where
|
||||
liftDeclaredName declaredName RequiredParameter{..} = declaredName requiredParameterSubject
|
||||
|
||||
instance Eq1 RequiredParameter where liftEq = genericLiftEq
|
||||
instance Ord1 RequiredParameter where liftCompare = genericLiftCompare
|
||||
instance Show1 RequiredParameter where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable RequiredParameter where
|
||||
eval eval ref RequiredParameter{..} = do
|
||||
name <- maybeM (throwNoNameError requiredParameterSubject) (declaredName requiredParameterSubject)
|
||||
@ -119,24 +99,18 @@ instance Evaluatable RequiredParameter where
|
||||
|
||||
data RestParameter a = RestParameter { restParameterContext :: ![a], restParameterSubject :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically RestParameter
|
||||
|
||||
instance Eq1 RestParameter where liftEq = genericLiftEq
|
||||
instance Ord1 RestParameter where liftCompare = genericLiftCompare
|
||||
instance Show1 RestParameter where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable RestParameter
|
||||
|
||||
newtype JsxFragment a = JsxFragment { terms :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically JsxFragment
|
||||
|
||||
instance Eq1 JsxFragment where liftEq = genericLiftEq
|
||||
instance Ord1 JsxFragment where liftCompare = genericLiftCompare
|
||||
instance Show1 JsxFragment where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable JsxFragment
|
||||
|
||||
data JsxNamespaceName a = JsxNamespaceName { left :: a, right :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically JsxNamespaceName
|
||||
|
||||
instance Eq1 JsxNamespaceName where liftEq = genericLiftEq
|
||||
instance Ord1 JsxNamespaceName where liftCompare = genericLiftCompare
|
||||
instance Show1 JsxNamespaceName where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable JsxNamespaceName
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE DeriveAnyClass, DuplicateRecordFields #-}
|
||||
{-# LANGUAGE DeriveAnyClass, DerivingVia, DuplicateRecordFields #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
module Language.TypeScript.Syntax.JavaScript where
|
||||
|
||||
@ -17,10 +17,7 @@ import qualified Data.Map.Strict as Map
|
||||
|
||||
data JavaScriptRequire a = JavaScriptRequire { javascriptRequireIden :: !a, javascriptRequireFrom :: ImportPath }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 JavaScriptRequire where liftEq = genericLiftEq
|
||||
instance Ord1 JavaScriptRequire where liftCompare = genericLiftCompare
|
||||
instance Show1 JavaScriptRequire where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically JavaScriptRequire
|
||||
|
||||
instance Evaluatable JavaScriptRequire where
|
||||
eval _ _ (JavaScriptRequire aliasTerm importPath) = do
|
||||
@ -43,32 +40,24 @@ instance Evaluatable JavaScriptRequire where
|
||||
|
||||
data Debugger a = Debugger
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Debugger
|
||||
|
||||
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, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Super
|
||||
|
||||
instance Eq1 Super where liftEq = genericLiftEq
|
||||
instance Ord1 Super where liftCompare = genericLiftCompare
|
||||
instance Show1 Super where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable Super
|
||||
|
||||
data Undefined a = Undefined
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Undefined
|
||||
|
||||
instance Eq1 Undefined where liftEq = genericLiftEq
|
||||
instance Ord1 Undefined where liftCompare = genericLiftCompare
|
||||
instance Show1 Undefined where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable Undefined
|
||||
|
||||
data With a = With { withExpression :: !a, withBody :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically With
|
||||
|
||||
instance Eq1 With where liftEq = genericLiftEq
|
||||
instance Ord1 With where liftCompare = genericLiftCompare
|
||||
instance Show1 With where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable With
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE DeriveAnyClass, DuplicateRecordFields, TupleSections #-}
|
||||
{-# LANGUAGE DeriveAnyClass, DerivingVia, DuplicateRecordFields, TupleSections #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
module Language.TypeScript.Syntax.TypeScript where
|
||||
|
||||
@ -18,111 +18,83 @@ import Diffing.Algorithm
|
||||
-- | ShorthandPropertyIdentifier used in object patterns such as var baz = { foo } to mean var baz = { foo: foo }
|
||||
newtype ShorthandPropertyIdentifier a = ShorthandPropertyIdentifier { contents :: T.Text }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ShorthandPropertyIdentifier
|
||||
|
||||
instance Eq1 ShorthandPropertyIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 ShorthandPropertyIdentifier where liftCompare = genericLiftCompare
|
||||
instance Show1 ShorthandPropertyIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ShorthandPropertyIdentifier
|
||||
|
||||
data Union a = Union { unionLeft :: !a, unionRight :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Union
|
||||
|
||||
instance Eq1 Language.TypeScript.Syntax.TypeScript.Union where liftEq = genericLiftEq
|
||||
instance Ord1 Language.TypeScript.Syntax.TypeScript.Union where liftCompare = genericLiftCompare
|
||||
instance Show1 Language.TypeScript.Syntax.TypeScript.Union where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable Language.TypeScript.Syntax.TypeScript.Union
|
||||
|
||||
data Intersection a = Intersection { intersectionLeft :: !a, intersectionRight :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Intersection
|
||||
|
||||
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, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically AmbientFunction
|
||||
|
||||
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, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Tuple where liftEq = genericLiftEq
|
||||
instance Ord1 Tuple where liftCompare = genericLiftCompare
|
||||
instance Show1 Tuple where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Tuple
|
||||
|
||||
-- This is a tuple type, not a tuple value, so we can't lean on the shared Tuple value
|
||||
instance Evaluatable Tuple
|
||||
|
||||
data Constructor a = Constructor { constructorTypeParameters :: !a, constructorFormalParameters :: ![a], constructorType :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Constructor
|
||||
|
||||
instance Eq1 Language.TypeScript.Syntax.TypeScript.Constructor where liftEq = genericLiftEq
|
||||
instance Ord1 Language.TypeScript.Syntax.TypeScript.Constructor where liftCompare = genericLiftCompare
|
||||
instance Show1 Language.TypeScript.Syntax.TypeScript.Constructor where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable Language.TypeScript.Syntax.TypeScript.Constructor
|
||||
|
||||
|
||||
newtype Annotation a = Annotation { annotationType :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Annotation
|
||||
|
||||
instance Eq1 Annotation where liftEq = genericLiftEq
|
||||
instance Ord1 Annotation where liftCompare = genericLiftCompare
|
||||
instance Show1 Annotation where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable Annotation
|
||||
|
||||
newtype Decorator a = Decorator { decoratorTerm :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Decorator
|
||||
|
||||
instance Eq1 Decorator where liftEq = genericLiftEq
|
||||
instance Ord1 Decorator where liftCompare = genericLiftCompare
|
||||
instance Show1 Decorator where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable Decorator
|
||||
|
||||
newtype ComputedPropertyName a = ComputedPropertyName { propertyName :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ComputedPropertyName
|
||||
|
||||
instance Eq1 ComputedPropertyName where liftEq = genericLiftEq
|
||||
instance Ord1 ComputedPropertyName where liftCompare = genericLiftCompare
|
||||
instance Show1 ComputedPropertyName where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ComputedPropertyName
|
||||
|
||||
newtype Constraint a = Constraint { constraintType :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Constraint
|
||||
|
||||
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, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically NestedIdentifier
|
||||
|
||||
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, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 AmbientDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 AmbientDeclaration where liftCompare = genericLiftCompare
|
||||
instance Show1 AmbientDeclaration where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically AmbientDeclaration
|
||||
|
||||
instance Evaluatable AmbientDeclaration where
|
||||
eval eval _ (AmbientDeclaration body) = eval body
|
||||
|
||||
data EnumDeclaration a = EnumDeclaration { enumDeclarationIdentifier :: !a, enumDeclarationBody :: ![a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically EnumDeclaration
|
||||
|
||||
instance Eq1 EnumDeclaration where liftEq = genericLiftEq
|
||||
instance Ord1 EnumDeclaration where liftCompare = genericLiftCompare
|
||||
instance Show1 EnumDeclaration where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable EnumDeclaration
|
||||
|
||||
instance Declarations a => Declarations (EnumDeclaration a) where
|
||||
@ -130,14 +102,12 @@ instance Declarations a => Declarations (EnumDeclaration a) where
|
||||
|
||||
newtype ExtendsClause a = ExtendsClause { extendsClauses :: [a] }
|
||||
deriving (Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ExtendsClause
|
||||
|
||||
instance Declarations1 ExtendsClause where
|
||||
liftDeclaredName _ (ExtendsClause []) = Nothing
|
||||
liftDeclaredName declaredName (ExtendsClause (x : _)) = declaredName x
|
||||
|
||||
instance Eq1 ExtendsClause where liftEq = genericLiftEq
|
||||
instance Ord1 ExtendsClause where liftCompare = genericLiftCompare
|
||||
instance Show1 ExtendsClause where liftShowsPrec = genericLiftShowsPrec
|
||||
-- TODO: ExtendsClause shouldn't evaluate to an address in the heap?
|
||||
instance Evaluatable ExtendsClause where
|
||||
eval eval _ ExtendsClause{..} = do
|
||||
@ -147,75 +117,56 @@ instance Evaluatable ExtendsClause where
|
||||
|
||||
data PropertySignature a = PropertySignature { modifiers :: ![a], propertySignaturePropertyName :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically PropertySignature
|
||||
|
||||
instance Eq1 PropertySignature where liftEq = genericLiftEq
|
||||
instance Ord1 PropertySignature where liftCompare = genericLiftCompare
|
||||
instance Show1 PropertySignature where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable PropertySignature
|
||||
|
||||
data CallSignature a = CallSignature { callSignatureTypeParameters :: !a, callSignatureParameters :: ![a], callSignatureType :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically CallSignature
|
||||
|
||||
instance Eq1 CallSignature where liftEq = genericLiftEq
|
||||
instance Ord1 CallSignature where liftCompare = genericLiftCompare
|
||||
instance Show1 CallSignature where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable CallSignature
|
||||
|
||||
-- | Todo: Move type params and type to context
|
||||
data ConstructSignature a = ConstructSignature { constructSignatureTypeParameters :: !a, constructSignatureParameters :: ![a], constructSignatureType :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ConstructSignature
|
||||
|
||||
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, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically IndexSignature
|
||||
|
||||
instance Eq1 IndexSignature where liftEq = genericLiftEq
|
||||
instance Ord1 IndexSignature where liftCompare = genericLiftCompare
|
||||
instance Show1 IndexSignature where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable IndexSignature
|
||||
|
||||
data AbstractMethodSignature a = AbstractMethodSignature { abstractMethodSignatureContext :: ![a], abstractMethodSignatureName :: !a, abstractMethodSignatureParameters :: ![a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically AbstractMethodSignature
|
||||
|
||||
instance Eq1 AbstractMethodSignature where liftEq = genericLiftEq
|
||||
instance Ord1 AbstractMethodSignature where liftCompare = genericLiftCompare
|
||||
instance Show1 AbstractMethodSignature where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable AbstractMethodSignature
|
||||
|
||||
data ForOf a = ForOf { forOfBinding :: !a, forOfSubject :: !a, forOfBody :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ForOf
|
||||
|
||||
instance Eq1 ForOf where liftEq = genericLiftEq
|
||||
instance Ord1 ForOf where liftCompare = genericLiftCompare
|
||||
instance Show1 ForOf where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ForOf
|
||||
|
||||
data LabeledStatement a = LabeledStatement { labeledStatementIdentifier :: !a, labeledStatementSubject :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically LabeledStatement
|
||||
|
||||
instance Eq1 LabeledStatement where liftEq = genericLiftEq
|
||||
instance Ord1 LabeledStatement where liftCompare = genericLiftCompare
|
||||
instance Show1 LabeledStatement where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable LabeledStatement
|
||||
|
||||
newtype Update a = Update { updateSubject :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Update
|
||||
|
||||
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, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Module where liftEq = genericLiftEq
|
||||
instance Ord1 Module where liftCompare = genericLiftCompare
|
||||
instance Show1 Module where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically Module
|
||||
|
||||
declareModule :: ( AbstractValue term address value m
|
||||
, Carrier sig m
|
||||
@ -280,10 +231,7 @@ instance Declarations1 Module where
|
||||
|
||||
data InternalModule a = InternalModule { internalModuleIdentifier :: !a, internalModuleStatements :: ![a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 InternalModule where liftEq = genericLiftEq
|
||||
instance Ord1 InternalModule where liftCompare = genericLiftCompare
|
||||
instance Show1 InternalModule where liftShowsPrec = genericLiftShowsPrec
|
||||
deriving (Eq1, Show1, Ord1) via Generically InternalModule
|
||||
|
||||
instance Evaluatable InternalModule where
|
||||
eval eval _ InternalModule{..} =
|
||||
@ -294,18 +242,14 @@ instance Declarations a => Declarations (InternalModule a) where
|
||||
|
||||
data ClassHeritage a = ClassHeritage { classHeritageExtendsClause :: !a, implementsClause :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ClassHeritage
|
||||
|
||||
instance Eq1 ClassHeritage where liftEq = genericLiftEq
|
||||
instance Ord1 ClassHeritage where liftCompare = genericLiftCompare
|
||||
instance Show1 ClassHeritage where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ClassHeritage
|
||||
|
||||
data AbstractClass a = AbstractClass { abstractClassIdentifier :: !a, abstractClassTypeParameters :: !a, classHeritage :: ![a], classBody :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically AbstractClass
|
||||
|
||||
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
|
||||
|
||||
@ -343,8 +287,6 @@ instance Evaluatable AbstractClass where
|
||||
|
||||
data MetaProperty a = MetaProperty
|
||||
deriving (Diffable, Eq, Foldable, Functor, Generic1, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically MetaProperty
|
||||
|
||||
instance Eq1 MetaProperty where liftEq = genericLiftEq
|
||||
instance Ord1 MetaProperty where liftCompare = genericLiftCompare
|
||||
instance Show1 MetaProperty where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable MetaProperty
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE DeriveAnyClass, DuplicateRecordFields #-}
|
||||
{-# LANGUAGE DeriveAnyClass, DerivingVia, DuplicateRecordFields #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
module Language.TypeScript.Syntax.Types where
|
||||
|
||||
@ -15,70 +15,54 @@ import Diffing.Algorithm
|
||||
-- | Lookup type for a type-level key in a typescript map.
|
||||
data LookupType a = LookupType { lookupTypeIdentifier :: a, lookupTypeKey :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically LookupType
|
||||
|
||||
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, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically FunctionType
|
||||
|
||||
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, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically TypeParameter
|
||||
|
||||
instance Eq1 TypeParameter where liftEq = genericLiftEq
|
||||
instance Ord1 TypeParameter where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeParameter where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable TypeParameter
|
||||
|
||||
data TypeAssertion a = TypeAssertion { typeAssertionParameters :: !a, typeAssertionExpression :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically TypeAssertion
|
||||
|
||||
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, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically DefaultType
|
||||
|
||||
instance Eq1 DefaultType where liftEq = genericLiftEq
|
||||
instance Ord1 DefaultType where liftCompare = genericLiftCompare
|
||||
instance Show1 DefaultType where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable DefaultType
|
||||
|
||||
newtype ParenthesizedType a = ParenthesizedType { parenthesizedType :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ParenthesizedType
|
||||
|
||||
instance Eq1 ParenthesizedType where liftEq = genericLiftEq
|
||||
instance Ord1 ParenthesizedType where liftCompare = genericLiftCompare
|
||||
instance Show1 ParenthesizedType where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ParenthesizedType
|
||||
|
||||
newtype PredefinedType a = PredefinedType { predefinedType :: T.Text }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically PredefinedType
|
||||
|
||||
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, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically TypeIdentifier
|
||||
|
||||
instance Declarations1 TypeIdentifier where
|
||||
liftDeclaredName _ (TypeIdentifier identifier) = Just (Evaluatable.name identifier)
|
||||
|
||||
instance Eq1 TypeIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 TypeIdentifier where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
-- TODO: TypeIdentifier shouldn't evaluate to an address in the heap?
|
||||
instance Evaluatable TypeIdentifier where
|
||||
eval _ _ TypeIdentifier{..} = do
|
||||
@ -88,97 +72,72 @@ instance Evaluatable TypeIdentifier where
|
||||
|
||||
data NestedTypeIdentifier a = NestedTypeIdentifier { left :: !a, right :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically NestedTypeIdentifier
|
||||
|
||||
instance Eq1 NestedTypeIdentifier where liftEq = genericLiftEq
|
||||
instance Ord1 NestedTypeIdentifier where liftCompare = genericLiftCompare
|
||||
instance Show1 NestedTypeIdentifier where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable NestedTypeIdentifier
|
||||
|
||||
data GenericType a = GenericType { genericTypeIdentifier :: !a, genericTypeArguments :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically GenericType
|
||||
|
||||
instance Eq1 GenericType where liftEq = genericLiftEq
|
||||
instance Ord1 GenericType where liftCompare = genericLiftCompare
|
||||
instance Show1 GenericType where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable GenericType
|
||||
|
||||
data TypePredicate a = TypePredicate { typePredicateIdentifier :: !a, typePredicateType :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically TypePredicate
|
||||
|
||||
instance Eq1 TypePredicate where liftEq = genericLiftEq
|
||||
instance Ord1 TypePredicate where liftCompare = genericLiftCompare
|
||||
instance Show1 TypePredicate where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable TypePredicate
|
||||
|
||||
newtype ObjectType a = ObjectType { objectTypeElements :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ObjectType
|
||||
|
||||
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, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ArrayType
|
||||
|
||||
instance Eq1 ArrayType where liftEq = genericLiftEq
|
||||
instance Ord1 ArrayType where liftCompare = genericLiftCompare
|
||||
instance Show1 ArrayType where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ArrayType
|
||||
|
||||
newtype FlowMaybeType a = FlowMaybeType { flowMaybeType :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically FlowMaybeType
|
||||
|
||||
instance Eq1 FlowMaybeType where liftEq = genericLiftEq
|
||||
instance Ord1 FlowMaybeType where liftCompare = genericLiftCompare
|
||||
instance Show1 FlowMaybeType where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable FlowMaybeType
|
||||
|
||||
newtype TypeQuery a = TypeQuery { typeQuerySubject :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically TypeQuery
|
||||
|
||||
instance Eq1 TypeQuery where liftEq = genericLiftEq
|
||||
instance Ord1 TypeQuery where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeQuery where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable TypeQuery
|
||||
|
||||
newtype IndexTypeQuery a = IndexTypeQuery { indexTypeQuerySubject :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically IndexTypeQuery
|
||||
|
||||
instance Eq1 IndexTypeQuery where liftEq = genericLiftEq
|
||||
instance Ord1 IndexTypeQuery where liftCompare = genericLiftCompare
|
||||
instance Show1 IndexTypeQuery where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable IndexTypeQuery
|
||||
|
||||
newtype TypeArguments a = TypeArguments { typeArguments :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically TypeArguments
|
||||
|
||||
instance Eq1 TypeArguments where liftEq = genericLiftEq
|
||||
instance Ord1 TypeArguments where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeArguments where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable TypeArguments
|
||||
|
||||
newtype ThisType a = ThisType { contents :: T.Text }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ThisType
|
||||
|
||||
instance Eq1 ThisType where liftEq = genericLiftEq
|
||||
instance Ord1 ThisType where liftCompare = genericLiftCompare
|
||||
instance Show1 ThisType where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ThisType
|
||||
|
||||
newtype ExistentialType a = ExistentialType { contents :: T.Text }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically ExistentialType
|
||||
|
||||
instance Eq1 ExistentialType where liftEq = genericLiftEq
|
||||
instance Ord1 ExistentialType where liftCompare = genericLiftCompare
|
||||
instance Show1 ExistentialType where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable ExistentialType
|
||||
|
||||
|
||||
newtype LiteralType a = LiteralType { literalTypeSubject :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, NFData1, Named1, Ord, Show, ToJSONFields1, Traversable)
|
||||
deriving (Eq1, Show1, Ord1) via Generically LiteralType
|
||||
|
||||
instance Eq1 LiteralType where liftEq = genericLiftEq
|
||||
instance Ord1 LiteralType where liftCompare = genericLiftCompare
|
||||
instance Show1 LiteralType where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable LiteralType
|
||||
|
@ -51,6 +51,7 @@ import Data.Functor.Foldable as X (Base, Corecursive (..), Recursive (..))
|
||||
import Data.Hashable as X (Hashable, hash, hashUsing, hashWithSalt)
|
||||
import Data.Hashable.Lifted as X (Hashable1(..), hashWithSalt1)
|
||||
import Data.Monoid as X (First (..), Last (..), Monoid (..))
|
||||
import Data.Monoid.Generic as X
|
||||
import Data.Proxy as X (Proxy (..))
|
||||
import Data.Semigroup as X (Semigroup (..))
|
||||
import Data.Traversable as X
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE RankNTypes, ScopedTypeVariables #-}
|
||||
{-# LANGUAGE DerivingVia, RankNTypes, ScopedTypeVariables #-}
|
||||
module Rendering.TOC
|
||||
( renderToCDiff
|
||||
, renderRPCToCDiff
|
||||
@ -26,7 +26,7 @@ import Data.Diff
|
||||
import Data.Language as Language
|
||||
import Data.List (sortOn)
|
||||
import qualified Data.List as List
|
||||
import qualified Data.Map as Map
|
||||
import qualified Data.Map.Monoidal as Map
|
||||
import Data.Patch
|
||||
import Data.Location
|
||||
import Data.Term
|
||||
@ -36,15 +36,10 @@ renderJSONSummaryError :: BlobPair -> String -> Summaries
|
||||
renderJSONSummaryError pair e = Summaries mempty (Map.singleton path [object ["error" .= e]])
|
||||
where path = T.pack (pathKeyForBlobPair pair)
|
||||
|
||||
data Summaries = Summaries { changes, errors :: !(Map.Map T.Text [Value]) }
|
||||
deriving (Eq, Show)
|
||||
|
||||
instance Semigroup Summaries where
|
||||
(<>) (Summaries c1 e1) (Summaries c2 e2) = Summaries (Map.unionWith (<>) c1 c2) (Map.unionWith (<>) e1 e2)
|
||||
|
||||
instance Monoid Summaries where
|
||||
mempty = Summaries mempty mempty
|
||||
mappend = (<>)
|
||||
data Summaries = Summaries { changes, errors :: Map.Map T.Text [Value] }
|
||||
deriving (Eq, Show, Generic)
|
||||
deriving Semigroup via GenericSemigroup Summaries
|
||||
deriving Monoid via GenericMonoid Summaries
|
||||
|
||||
instance ToJSON Summaries where
|
||||
toJSON Summaries{..} = object [ "changes" .= changes, "errors" .= errors ]
|
||||
|
Loading…
Reference in New Issue
Block a user