mirror of
https://github.com/github/semantic.git
synced 2025-01-03 04:51:57 +03:00
add typeclasses to deal with recent merge
This commit is contained in:
parent
8aad81b775
commit
9bd78b4123
@ -340,7 +340,7 @@ instance ToJSONFields1 Cast
|
|||||||
instance Evaluatable Cast
|
instance Evaluatable Cast
|
||||||
|
|
||||||
data Super a = Super
|
data Super a = Super
|
||||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1)
|
||||||
|
|
||||||
instance Eq1 Super where liftEq = genericLiftEq
|
instance Eq1 Super where liftEq = genericLiftEq
|
||||||
instance Ord1 Super where liftCompare = genericLiftCompare
|
instance Ord1 Super where liftCompare = genericLiftCompare
|
||||||
@ -348,7 +348,7 @@ instance Show1 Super where liftShowsPrec = genericLiftShowsPrec
|
|||||||
instance Evaluatable Super
|
instance Evaluatable Super
|
||||||
|
|
||||||
data This a = This
|
data This a = This
|
||||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1)
|
||||||
|
|
||||||
instance Eq1 This where liftEq = genericLiftEq
|
instance Eq1 This where liftEq = genericLiftEq
|
||||||
instance Ord1 This where liftCompare = genericLiftCompare
|
instance Ord1 This where liftCompare = genericLiftCompare
|
||||||
|
@ -159,7 +159,7 @@ instance Evaluatable PostDecrement
|
|||||||
|
|
||||||
-- | Pre increment operator (e.g. ++1 in C or Java).
|
-- | Pre increment operator (e.g. ++1 in C or Java).
|
||||||
newtype PreIncrement a = PreIncrement a
|
newtype PreIncrement a = PreIncrement a
|
||||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1)
|
||||||
|
|
||||||
instance Eq1 PreIncrement where liftEq = genericLiftEq
|
instance Eq1 PreIncrement where liftEq = genericLiftEq
|
||||||
instance Ord1 PreIncrement where liftCompare = genericLiftCompare
|
instance Ord1 PreIncrement where liftCompare = genericLiftCompare
|
||||||
@ -171,7 +171,7 @@ instance Evaluatable PreIncrement
|
|||||||
|
|
||||||
-- | Pre decrement operator (e.g. --1 in C or Java).
|
-- | Pre decrement operator (e.g. --1 in C or Java).
|
||||||
newtype PreDecrement a = PreDecrement a
|
newtype PreDecrement a = PreDecrement a
|
||||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1)
|
||||||
|
|
||||||
instance Eq1 PreDecrement where liftEq = genericLiftEq
|
instance Eq1 PreDecrement where liftEq = genericLiftEq
|
||||||
instance Ord1 PreDecrement where liftCompare = genericLiftCompare
|
instance Ord1 PreDecrement where liftCompare = genericLiftCompare
|
||||||
|
@ -153,7 +153,7 @@ instance Evaluatable TypeParameters
|
|||||||
|
|
||||||
-- data instead of newtype because no payload
|
-- data instead of newtype because no payload
|
||||||
data Void a = Void
|
data Void a = Void
|
||||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1)
|
||||||
|
|
||||||
instance Eq1 Void where liftEq = genericLiftEq
|
instance Eq1 Void where liftEq = genericLiftEq
|
||||||
instance Ord1 Void where liftCompare = genericLiftCompare
|
instance Ord1 Void where liftCompare = genericLiftCompare
|
||||||
@ -164,7 +164,7 @@ instance Evaluatable Void
|
|||||||
|
|
||||||
-- data instead of newtype because no payload
|
-- data instead of newtype because no payload
|
||||||
data Int a = Int
|
data Int a = Int
|
||||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1)
|
||||||
|
|
||||||
instance Eq1 Int where liftEq = genericLiftEq
|
instance Eq1 Int where liftEq = genericLiftEq
|
||||||
instance Ord1 Int where liftCompare = genericLiftCompare
|
instance Ord1 Int where liftCompare = genericLiftCompare
|
||||||
@ -174,7 +174,7 @@ instance Show1 Int where liftShowsPrec = genericLiftShowsPrec
|
|||||||
instance Evaluatable Int
|
instance Evaluatable Int
|
||||||
|
|
||||||
data Float a = Float | Double
|
data Float a = Float | Double
|
||||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1)
|
||||||
|
|
||||||
instance Eq1 Float where liftEq = genericLiftEq
|
instance Eq1 Float where liftEq = genericLiftEq
|
||||||
instance Ord1 Float where liftCompare = genericLiftCompare
|
instance Ord1 Float where liftCompare = genericLiftCompare
|
||||||
@ -184,7 +184,7 @@ instance Show1 Float where liftShowsPrec = genericLiftShowsPrec
|
|||||||
instance Evaluatable Float
|
instance Evaluatable Float
|
||||||
|
|
||||||
data Bool a = Bool
|
data Bool a = Bool
|
||||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1)
|
||||||
|
|
||||||
instance Eq1 Bool where liftEq = genericLiftEq
|
instance Eq1 Bool where liftEq = genericLiftEq
|
||||||
instance Ord1 Bool where liftCompare = genericLiftCompare
|
instance Ord1 Bool where liftCompare = genericLiftCompare
|
||||||
|
@ -11,9 +11,8 @@ import Data.Abstract.FreeVariables
|
|||||||
import Data.Functor (($>))
|
import Data.Functor (($>))
|
||||||
import Data.List.NonEmpty (some1)
|
import Data.List.NonEmpty (some1)
|
||||||
import Data.Record
|
import Data.Record
|
||||||
import Data.Semigroup
|
|
||||||
import Data.Syntax (contextualize, emptyTerm, handleError, infixContext, makeTerm, makeTerm', makeTerm'', makeTerm1, parseError, postContextualize)
|
import Data.Syntax (contextualize, emptyTerm, handleError, infixContext, makeTerm, makeTerm', makeTerm'', makeTerm1, parseError, postContextualize)
|
||||||
import Data.Union
|
import Data.Sum
|
||||||
import GHC.Stack
|
import GHC.Stack
|
||||||
import Language.Java.Grammar as Grammar
|
import Language.Java.Grammar as Grammar
|
||||||
import Language.Java.Syntax as Java.Syntax
|
import Language.Java.Syntax as Java.Syntax
|
||||||
@ -102,7 +101,7 @@ type Syntax =
|
|||||||
, []
|
, []
|
||||||
]
|
]
|
||||||
|
|
||||||
type Term = Term.Term (Union Syntax) (Record Location)
|
type Term = Term.Term (Sum Syntax) (Record Location)
|
||||||
type Assignment = HasCallStack => Assignment.Assignment [] Grammar Term
|
type Assignment = HasCallStack => Assignment.Assignment [] Grammar Term
|
||||||
|
|
||||||
-- | Assignment from AST in Java's grammar onto a program in Java's syntax.
|
-- | Assignment from AST in Java's grammar onto a program in Java's syntax.
|
||||||
@ -403,26 +402,26 @@ enhancedFor = makeTerm <$> symbol EnhancedForStatement <*> children (Statement.F
|
|||||||
-- TODO: instanceOf
|
-- TODO: instanceOf
|
||||||
binary :: Assignment
|
binary :: Assignment
|
||||||
binary = makeTerm' <$> symbol BinaryExpression <*> children (infixTerm expression expression
|
binary = makeTerm' <$> symbol BinaryExpression <*> children (infixTerm expression expression
|
||||||
[ (inj .) . Expression.LessThan <$ symbol AnonLAngle
|
[ (injectSum .) . Expression.LessThan <$ symbol AnonLAngle
|
||||||
, (inj .) . Expression.GreaterThan <$ symbol AnonRAngle
|
, (injectSum .) . Expression.GreaterThan <$ symbol AnonRAngle
|
||||||
, (inj .) . Expression.Equal <$ symbol AnonEqualEqual
|
, (injectSum .) . Expression.Equal <$ symbol AnonEqualEqual
|
||||||
, (inj .) . Expression.GreaterThanEqual <$ symbol AnonRAngleEqual
|
, (injectSum .) . Expression.GreaterThanEqual <$ symbol AnonRAngleEqual
|
||||||
, (inj .) . Expression.LessThanEqual <$ symbol AnonLAngleEqual
|
, (injectSum .) . Expression.LessThanEqual <$ symbol AnonLAngleEqual
|
||||||
, (inj .) . invert Expression.Equal <$ symbol AnonBangEqual
|
, (injectSum .) . invert Expression.Equal <$ symbol AnonBangEqual
|
||||||
, (inj .) . Expression.And <$ symbol AnonAmpersandAmpersand
|
, (injectSum .) . Expression.And <$ symbol AnonAmpersandAmpersand
|
||||||
, (inj .) . Expression.Or <$ symbol AnonPipePipe
|
, (injectSum .) . Expression.Or <$ symbol AnonPipePipe
|
||||||
, (inj .) . Expression.BAnd <$ symbol AnonAmpersand
|
, (injectSum .) . Expression.BAnd <$ symbol AnonAmpersand
|
||||||
, (inj .) . Expression.BOr <$ symbol AnonPipe
|
, (injectSum .) . Expression.BOr <$ symbol AnonPipe
|
||||||
, (inj .) . Expression.BXOr <$ symbol AnonCaret
|
, (injectSum .) . Expression.BXOr <$ symbol AnonCaret
|
||||||
, (inj .) . Expression.Modulo <$ symbol AnonPercent
|
, (injectSum .) . Expression.Modulo <$ symbol AnonPercent
|
||||||
, (inj .) . Expression.LShift <$ symbol AnonLAngleLAngle
|
, (injectSum .) . Expression.LShift <$ symbol AnonLAngleLAngle
|
||||||
, (inj .) . Expression.RShift <$ symbol AnonRAngleRAngle
|
, (injectSum .) . Expression.RShift <$ symbol AnonRAngleRAngle
|
||||||
, (inj .) . Expression.UnsignedRShift <$ symbol AnonRAngleRAngleRAngle
|
, (injectSum .) . Expression.UnsignedRShift <$ symbol AnonRAngleRAngleRAngle
|
||||||
, (inj .) . Expression.Plus <$ symbol AnonPlus
|
, (injectSum .) . Expression.Plus <$ symbol AnonPlus
|
||||||
, (inj .) . Expression.Minus <$ symbol AnonMinus
|
, (injectSum .) . Expression.Minus <$ symbol AnonMinus
|
||||||
, (inj .) . Expression.Times <$ symbol AnonStar
|
, (injectSum .) . Expression.Times <$ symbol AnonStar
|
||||||
, (inj .) . Expression.DividedBy <$ symbol AnonSlash
|
, (injectSum .) . Expression.DividedBy <$ symbol AnonSlash
|
||||||
, (inj .) . Expression.InstanceOf <$ symbol AnonInstanceof
|
, (injectSum .) . Expression.InstanceOf <$ symbol AnonInstanceof
|
||||||
])
|
])
|
||||||
where invert cons a b = Expression.Not (makeTerm1 (cons a b))
|
where invert cons a b = Expression.Not (makeTerm1 (cons a b))
|
||||||
|
|
||||||
@ -430,13 +429,13 @@ binary = makeTerm' <$> symbol BinaryExpression <*> children (infixTerm expressio
|
|||||||
infixTerm :: HasCallStack
|
infixTerm :: HasCallStack
|
||||||
=> Assignment
|
=> Assignment
|
||||||
-> Assignment
|
-> Assignment
|
||||||
-> [Assignment.Assignment [] Grammar (Term -> Term -> Union Syntax Term)]
|
-> [Assignment.Assignment [] Grammar (Term -> Term -> Sum Syntax Term)]
|
||||||
-> Assignment.Assignment [] Grammar (Union Syntax Term)
|
-> Assignment.Assignment [] Grammar (Sum Syntax Term)
|
||||||
infixTerm = infixContext comment
|
infixTerm = infixContext comment
|
||||||
|
|
||||||
assignment' :: Assignment
|
assignment' :: Assignment
|
||||||
assignment' = makeTerm' <$> symbol AssignmentExpression <*> children (infixTerm lhs expression
|
assignment' = makeTerm' <$> symbol AssignmentExpression <*> children (infixTerm lhs expression
|
||||||
[ (inj .) . Statement.Assignment [] <$ symbol AnonEqual
|
[ (injectSum .) . Statement.Assignment [] <$ symbol AnonEqual
|
||||||
, assign Expression.Plus <$ symbol AnonPlusEqual
|
, assign Expression.Plus <$ symbol AnonPlusEqual
|
||||||
, assign Expression.Minus <$ symbol AnonMinusEqual
|
, assign Expression.Minus <$ symbol AnonMinusEqual
|
||||||
, assign Expression.Times <$ symbol AnonStarEqual
|
, assign Expression.Times <$ symbol AnonStarEqual
|
||||||
@ -450,8 +449,8 @@ assignment' = makeTerm' <$> symbol AssignmentExpression <*> children (infixTerm
|
|||||||
, assign Expression.BXOr <$ symbol AnonCaretEqual
|
, assign Expression.BXOr <$ symbol AnonCaretEqual
|
||||||
])
|
])
|
||||||
where
|
where
|
||||||
assign :: (f :< Syntax) => (Term -> Term -> f Term) -> Term -> Term -> Union Syntax Term
|
assign :: (f :< Syntax) => (Term -> Term -> f Term) -> Term -> Term -> Sum Syntax Term
|
||||||
assign c l r = inj (Statement.Assignment [] l (makeTerm1 (c l r)))
|
assign c l r = injectSum (Statement.Assignment [] l (makeTerm1 (c l r)))
|
||||||
lhs = symbol Lhs *> children (term expression)
|
lhs = symbol Lhs *> children (term expression)
|
||||||
|
|
||||||
data UnaryType
|
data UnaryType
|
||||||
@ -474,10 +473,10 @@ unary = make <$> symbol UnaryExpression <*> children ((,) <$> operator <*> term
|
|||||||
|
|
||||||
update :: Assignment
|
update :: Assignment
|
||||||
update = makeTerm' <$> symbol UpdateExpression <*> children (
|
update = makeTerm' <$> symbol UpdateExpression <*> children (
|
||||||
inj . Statement.PreIncrement <$ token AnonPlusPlus <*> term expression
|
injectSum . Statement.PreIncrement <$ token AnonPlusPlus <*> term expression
|
||||||
<|> inj . Statement.PreDecrement <$ token AnonMinusMinus <*> term expression
|
<|> injectSum . Statement.PreDecrement <$ token AnonMinusMinus <*> term expression
|
||||||
<|> inj . Statement.PostIncrement <$> term expression <* token AnonPlusPlus
|
<|> injectSum . Statement.PostIncrement <$> term expression <* token AnonPlusPlus
|
||||||
<|> inj . Statement.PostDecrement <$> term expression <* token AnonMinusMinus)
|
<|> injectSum . Statement.PostDecrement <$> term expression <* token AnonMinusMinus)
|
||||||
|
|
||||||
ternary :: Assignment
|
ternary :: Assignment
|
||||||
ternary = makeTerm <$> symbol TernaryExpression <*> children (Statement.If <$> term expression <*> term expression <*> term expression)
|
ternary = makeTerm <$> symbol TernaryExpression <*> children (Statement.If <$> term expression <*> term expression <*> term expression)
|
||||||
|
@ -4,9 +4,10 @@ module Language.Java.Syntax where
|
|||||||
import Data.Abstract.Evaluatable hiding (Label)
|
import Data.Abstract.Evaluatable hiding (Label)
|
||||||
import Diffing.Algorithm
|
import Diffing.Algorithm
|
||||||
import Prologue hiding (Constructor)
|
import Prologue hiding (Constructor)
|
||||||
|
import Data.JSON.Fields
|
||||||
|
|
||||||
newtype Import a = Import [a]
|
newtype Import a = Import [a]
|
||||||
deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, Declarations1)
|
deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1)
|
||||||
|
|
||||||
instance Eq1 Import where liftEq = genericLiftEq
|
instance Eq1 Import where liftEq = genericLiftEq
|
||||||
instance Ord1 Import where liftCompare = genericLiftCompare
|
instance Ord1 Import where liftCompare = genericLiftCompare
|
||||||
@ -16,7 +17,7 @@ instance Show1 Import where liftShowsPrec = genericLiftShowsPrec
|
|||||||
instance Evaluatable Import
|
instance Evaluatable Import
|
||||||
|
|
||||||
data Module a = Module { moduleIdentifier :: !a, moduleStatements :: ![a] }
|
data Module a = Module { moduleIdentifier :: !a, moduleStatements :: ![a] }
|
||||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1)
|
||||||
|
|
||||||
instance Eq1 Module where liftEq = genericLiftEq
|
instance Eq1 Module where liftEq = genericLiftEq
|
||||||
instance Ord1 Module where liftCompare = genericLiftCompare
|
instance Ord1 Module where liftCompare = genericLiftCompare
|
||||||
@ -25,7 +26,7 @@ instance Show1 Module where liftShowsPrec = genericLiftShowsPrec
|
|||||||
instance Evaluatable Module
|
instance Evaluatable Module
|
||||||
|
|
||||||
newtype Package a = Package [a]
|
newtype Package a = Package [a]
|
||||||
deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, Declarations1)
|
deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1)
|
||||||
|
|
||||||
instance Eq1 Package where liftEq = genericLiftEq
|
instance Eq1 Package where liftEq = genericLiftEq
|
||||||
instance Ord1 Package where liftCompare = genericLiftCompare
|
instance Ord1 Package where liftCompare = genericLiftCompare
|
||||||
@ -35,7 +36,7 @@ instance Show1 Package where liftShowsPrec = genericLiftShowsPrec
|
|||||||
instance Evaluatable Package
|
instance Evaluatable Package
|
||||||
|
|
||||||
data EnumDeclaration a = EnumDeclaration { _enumDeclarationIdentifier :: !a, _enumDeclarationBody :: ![a] }
|
data EnumDeclaration a = EnumDeclaration { _enumDeclarationIdentifier :: !a, _enumDeclarationBody :: ![a] }
|
||||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1)
|
||||||
|
|
||||||
instance Eq1 EnumDeclaration where liftEq = genericLiftEq
|
instance Eq1 EnumDeclaration where liftEq = genericLiftEq
|
||||||
instance Ord1 EnumDeclaration where liftCompare = genericLiftCompare
|
instance Ord1 EnumDeclaration where liftCompare = genericLiftCompare
|
||||||
@ -44,7 +45,7 @@ instance Evaluatable EnumDeclaration
|
|||||||
|
|
||||||
|
|
||||||
data Variable a = Variable { variableModifiers :: ![a], variableType :: !a, variableName :: !a}
|
data Variable a = Variable { variableModifiers :: ![a], variableType :: !a, variableName :: !a}
|
||||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1)
|
||||||
|
|
||||||
instance Eq1 Variable where liftEq = genericLiftEq
|
instance Eq1 Variable where liftEq = genericLiftEq
|
||||||
instance Ord1 Variable where liftCompare = genericLiftCompare
|
instance Ord1 Variable where liftCompare = genericLiftCompare
|
||||||
@ -54,7 +55,7 @@ instance Show1 Variable where liftShowsPrec = genericLiftShowsPrec
|
|||||||
instance Evaluatable Variable
|
instance Evaluatable Variable
|
||||||
|
|
||||||
data Synchronized a = Synchronized { synchronizedSubject :: !a, synchronizedBody :: !a}
|
data Synchronized a = Synchronized { synchronizedSubject :: !a, synchronizedBody :: !a}
|
||||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1)
|
||||||
|
|
||||||
instance Eq1 Synchronized where liftEq = genericLiftEq
|
instance Eq1 Synchronized where liftEq = genericLiftEq
|
||||||
instance Ord1 Synchronized where liftCompare = genericLiftCompare
|
instance Ord1 Synchronized where liftCompare = genericLiftCompare
|
||||||
@ -64,7 +65,7 @@ instance Show1 Synchronized where liftShowsPrec = genericLiftShowsPrec
|
|||||||
instance Evaluatable Synchronized
|
instance Evaluatable Synchronized
|
||||||
|
|
||||||
data New a = New { newType :: !a, newArgs :: ![a] }
|
data New a = New { newType :: !a, newArgs :: ![a] }
|
||||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1)
|
||||||
|
|
||||||
instance Eq1 New where liftEq = genericLiftEq
|
instance Eq1 New where liftEq = genericLiftEq
|
||||||
instance Ord1 New where liftCompare = genericLiftCompare
|
instance Ord1 New where liftCompare = genericLiftCompare
|
||||||
@ -74,7 +75,7 @@ instance Show1 New where liftShowsPrec = genericLiftShowsPrec
|
|||||||
instance Evaluatable New
|
instance Evaluatable New
|
||||||
|
|
||||||
data Asterisk a = Asterisk
|
data Asterisk a = Asterisk
|
||||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1)
|
||||||
|
|
||||||
instance Eq1 Asterisk where liftEq = genericLiftEq
|
instance Eq1 Asterisk where liftEq = genericLiftEq
|
||||||
instance Ord1 Asterisk where liftCompare = genericLiftCompare
|
instance Ord1 Asterisk where liftCompare = genericLiftCompare
|
||||||
@ -85,7 +86,7 @@ instance Evaluatable Asterisk
|
|||||||
|
|
||||||
|
|
||||||
data Constructor a = Constructor { constructorModifiers :: ![a], constructorTypeParams :: ![a], constructorIdentifier :: !a, constructorParams :: ![a], constructorThrows :: ![a], constructorBody :: a}
|
data Constructor a = Constructor { constructorModifiers :: ![a], constructorTypeParams :: ![a], constructorIdentifier :: !a, constructorParams :: ![a], constructorThrows :: ![a], constructorBody :: a}
|
||||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1)
|
||||||
|
|
||||||
instance Eq1 Constructor where liftEq = genericLiftEq
|
instance Eq1 Constructor where liftEq = genericLiftEq
|
||||||
instance Ord1 Constructor where liftCompare = genericLiftCompare
|
instance Ord1 Constructor where liftCompare = genericLiftCompare
|
||||||
@ -95,7 +96,7 @@ instance Show1 Constructor where liftShowsPrec = genericLiftShowsPrec
|
|||||||
instance Evaluatable Constructor
|
instance Evaluatable Constructor
|
||||||
|
|
||||||
data TypeParameter a = TypeParameter { typeParamAnnotation :: ![a], typeParamIdentifier :: !a, typeParamTypeBound :: ![a]}
|
data TypeParameter a = TypeParameter { typeParamAnnotation :: ![a], typeParamIdentifier :: !a, typeParamTypeBound :: ![a]}
|
||||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1)
|
||||||
|
|
||||||
instance Eq1 TypeParameter where liftEq = genericLiftEq
|
instance Eq1 TypeParameter where liftEq = genericLiftEq
|
||||||
instance Ord1 TypeParameter where liftCompare = genericLiftCompare
|
instance Ord1 TypeParameter where liftCompare = genericLiftCompare
|
||||||
@ -105,7 +106,7 @@ instance Show1 TypeParameter where liftShowsPrec = genericLiftShowsPrec
|
|||||||
instance Evaluatable TypeParameter
|
instance Evaluatable TypeParameter
|
||||||
|
|
||||||
data Annotation a = Annotation { annotationName :: !a, annotationField :: [a]}
|
data Annotation a = Annotation { annotationName :: !a, annotationField :: [a]}
|
||||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1)
|
||||||
|
|
||||||
instance Eq1 Annotation where liftEq = genericLiftEq
|
instance Eq1 Annotation where liftEq = genericLiftEq
|
||||||
instance Ord1 Annotation where liftCompare = genericLiftCompare
|
instance Ord1 Annotation where liftCompare = genericLiftCompare
|
||||||
@ -115,7 +116,7 @@ instance Show1 Annotation where liftShowsPrec = genericLiftShowsPrec
|
|||||||
instance Evaluatable Annotation
|
instance Evaluatable Annotation
|
||||||
|
|
||||||
data AnnotationField a = AnnotationField { annotationFieldName :: a, annotationFieldValue :: a }
|
data AnnotationField a = AnnotationField { annotationFieldName :: a, annotationFieldValue :: a }
|
||||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1)
|
||||||
|
|
||||||
instance Eq1 AnnotationField where liftEq = genericLiftEq
|
instance Eq1 AnnotationField where liftEq = genericLiftEq
|
||||||
instance Ord1 AnnotationField where liftCompare = genericLiftCompare
|
instance Ord1 AnnotationField where liftCompare = genericLiftCompare
|
||||||
@ -125,7 +126,7 @@ instance Show1 AnnotationField where liftShowsPrec = genericLiftShowsPrec
|
|||||||
instance Evaluatable AnnotationField
|
instance Evaluatable AnnotationField
|
||||||
|
|
||||||
data GenericType a = GenericType { genericTypeIdentifier :: a, genericTypeArguments :: [a] }
|
data GenericType a = GenericType { genericTypeIdentifier :: a, genericTypeArguments :: [a] }
|
||||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1)
|
||||||
|
|
||||||
instance Eq1 GenericType where liftEq = genericLiftEq
|
instance Eq1 GenericType where liftEq = genericLiftEq
|
||||||
instance Ord1 GenericType where liftCompare = genericLiftCompare
|
instance Ord1 GenericType where liftCompare = genericLiftCompare
|
||||||
@ -135,7 +136,7 @@ instance Show1 GenericType where liftShowsPrec = genericLiftShowsPrec
|
|||||||
instance Evaluatable GenericType
|
instance Evaluatable GenericType
|
||||||
|
|
||||||
data TypeWithModifiers a = TypeWithModifiers [a] a
|
data TypeWithModifiers a = TypeWithModifiers [a] a
|
||||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1)
|
||||||
|
|
||||||
instance Eq1 TypeWithModifiers where liftEq = genericLiftEq
|
instance Eq1 TypeWithModifiers where liftEq = genericLiftEq
|
||||||
instance Ord1 TypeWithModifiers where liftCompare = genericLiftCompare
|
instance Ord1 TypeWithModifiers where liftCompare = genericLiftCompare
|
||||||
|
@ -111,7 +111,7 @@ type family ApplyAll (typeclasses :: [(* -> *) -> Constraint]) (syntax :: * -> *
|
|||||||
--
|
--
|
||||||
-- > runTask (parse (someParser @'[Show1] language) blob) >>= putStrLn . withSomeTerm show
|
-- > runTask (parse (someParser @'[Show1] language) blob) >>= putStrLn . withSomeTerm show
|
||||||
someParser :: ( ApplyAll typeclasses (Sum Go.Syntax)
|
someParser :: ( ApplyAll typeclasses (Sum Go.Syntax)
|
||||||
, ApplyAll typeclasses (Union Java.Syntax)
|
, ApplyAll typeclasses (Sum Java.Syntax)
|
||||||
, ApplyAll typeclasses (Sum JSON.Syntax)
|
, ApplyAll typeclasses (Sum JSON.Syntax)
|
||||||
, ApplyAll typeclasses (Sum Markdown.Syntax)
|
, ApplyAll typeclasses (Sum Markdown.Syntax)
|
||||||
, ApplyAll typeclasses (Sum Python.Syntax)
|
, ApplyAll typeclasses (Sum Python.Syntax)
|
||||||
|
Loading…
Reference in New Issue
Block a user