-- Haskel data types for the abstract syntax. -- Generated by the BNF converter. {-# LANGUAGE DeriveTraversable #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE PatternSynonyms #-} -- | The abstract syntax of language OCL. module AbsOCL where import qualified Prelude as T (Double, Integer, String) import qualified Prelude as C ( Eq , Ord , Show , Read , Functor , Foldable , Traversable , Int, Maybe(..) ) import Data.String type OCLfile = OCLfile' BNFC'Position data OCLfile' a = OCLf a [OCLPackage' a] -- ^ OCLfile ::= OCLPackage deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type OCLPackage = OCLPackage' BNFC'Position data OCLPackage' a = Pack a (PackageName' a) (OCLExpressions' a) -- ^ OCLPackage ::= "package" PackageName OCLExpressions "endpackage" deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type PackageName = PackageName' BNFC'Position data PackageName' a = PackName a (PathName' a) -- ^ PackageName ::= PathName deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type OCLExpressions = OCLExpressions' BNFC'Position data OCLExpressions' a = Constraints a [Constrnt' a] -- ^ OCLExpressions ::= Constrnt deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Constrnt = Constrnt' BNFC'Position data Constrnt' a = Constr a (ContextDeclaration' a) [ConstrBody' a] -- ^ Constrnt ::= ContextDeclaration ConstrBody deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type ConstrBody = ConstrBody' BNFC'Position data ConstrBody' a = CB a (Stereotype' a) (OCLExpression' a) -- ^ ConstrBody ::= Stereotype ":" OCLExpression | CBDef a [LetExpression' a] -- ^ ConstrBody ::= "def" ":" LetExpression | CBDefNamed a Ident [LetExpression' a] -- ^ ConstrBody ::= "def" Ident ":" LetExpression | CBNamed a (Stereotype' a) Ident (OCLExpression' a) -- ^ ConstrBody ::= Stereotype Ident ":" OCLExpression deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type ContextDeclaration = ContextDeclaration' BNFC'Position data ContextDeclaration' a = CDClassif a (ClassifierContext' a) -- ^ ContextDeclaration ::= "context" ClassifierContext | CDOper a (OperationContext' a) -- ^ ContextDeclaration ::= "context" OperationContext deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type ClassifierContext = ClassifierContext' BNFC'Position data ClassifierContext' a = CC a Ident -- ^ ClassifierContext ::= Ident | CCType a Ident Ident -- ^ ClassifierContext ::= Ident ":" Ident deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type OperationContext = OperationContext' BNFC'Position data OperationContext' a = OpC a Ident (OperationName' a) [FormalParameter' a] -- ^ OperationContext ::= Ident "::" OperationName "(" FormalParameter ")" | OpCRT a Ident (OperationName' a) [FormalParameter' a] (ReturnType' a) -- ^ OperationContext ::= Ident "::" OperationName "(" FormalParameter ")" ":" ReturnType deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Stereotype = Stereotype' BNFC'Position data Stereotype' a = Inv a -- ^ Stereotype ::= "inv" | Post a -- ^ Stereotype ::= "post" | Pre a -- ^ Stereotype ::= "pre" deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type OperationName = OperationName' BNFC'Position data OperationName' a = Add a -- ^ OperationName ::= "+" | And a -- ^ OperationName ::= "and" | Div a -- ^ OperationName ::= "/" | Eq a -- ^ OperationName ::= "=" | GRT a -- ^ OperationName ::= ">" | GRTE a -- ^ OperationName ::= ">=" | Impl a -- ^ OperationName ::= "implies" | LST a -- ^ OperationName ::= "<" | LSTE a -- ^ OperationName ::= "<=" | Mult a -- ^ OperationName ::= "*" | NEq a -- ^ OperationName ::= "<>" | Not a -- ^ OperationName ::= "not" | OpName a Ident -- ^ OperationName ::= Ident | Or a -- ^ OperationName ::= "or" | Sub a -- ^ OperationName ::= "-" | Xor a -- ^ OperationName ::= "xor" deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type FormalParameter = FormalParameter' BNFC'Position data FormalParameter' a = FP a Ident (TypeSpecifier' a) -- ^ FormalParameter ::= Ident ":" TypeSpecifier deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type TypeSpecifier = TypeSpecifier' BNFC'Position data TypeSpecifier' a = TScoll a (CollectionType' a) -- ^ TypeSpecifier ::= CollectionType | TSsimple a (SimpleTypeSpecifier' a) -- ^ TypeSpecifier ::= SimpleTypeSpecifier deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type CollectionType = CollectionType' BNFC'Position data CollectionType' a = CT a (CollectionKind' a) (SimpleTypeSpecifier' a) -- ^ CollectionType ::= CollectionKind "(" SimpleTypeSpecifier ")" deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type ReturnType = ReturnType' BNFC'Position data ReturnType' a = RT a (TypeSpecifier' a) -- ^ ReturnType ::= TypeSpecifier deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type OCLExpression = OCLExpression' BNFC'Position data OCLExpression' a = OCLExp a (Expression' a) -- ^ OCLExpression ::= Expression | OCLExpLet a [LetExpression' a] (Expression' a) -- ^ OCLExpression ::= LetExpression "in" Expression deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type LetExpression = LetExpression' BNFC'Position data LetExpression' a = LE a Ident [FormalParameter' a] (Expression' a) -- ^ LetExpression ::= "let" Ident "(" FormalParameter ")" "=" Expression | LENoParam a Ident (Expression' a) -- ^ LetExpression ::= "let" Ident "=" Expression | LENoParamType a Ident (TypeSpecifier' a) (Expression' a) -- ^ LetExpression ::= "let" Ident ":" TypeSpecifier "=" Expression | LEType a Ident [FormalParameter' a] (TypeSpecifier' a) (Expression' a) -- ^ LetExpression ::= "let" Ident "(" FormalParameter ")" ":" TypeSpecifier "=" Expression deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type IfExpression = IfExpression' BNFC'Position data IfExpression' a = IfExp a (Expression' a) (Expression' a) (Expression' a) -- ^ IfExpression ::= "if" Expression "then" Expression "else" Expression "endif" deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Expression = Expression' BNFC'Position data Expression' a = EExplPropCall a (Expression' a) (PostfixOperator' a) (PropertyCall' a) -- ^ Expression ::= Expression7 PostfixOperator PropertyCall | EIfExp a (IfExpression' a) -- ^ Expression ::= IfExpression | EImplPropCall a (PropertyCall' a) -- ^ Expression ::= PropertyCall | ELit a (OCLLiteral' a) -- ^ Expression ::= OCLLiteral | ELitColl a (LiteralCollection' a) -- ^ Expression ::= LiteralCollection | EMessage a (Expression' a) (PathName' a) [MessageArg' a] -- ^ Expression ::= Expression7 "^" PathName "(" MessageArg ")" | ENull a -- ^ Expression ::= "null" | EOpAdd a (Expression' a) (AddOperator' a) (Expression' a) -- ^ Expression ::= Expression4 AddOperator Expression5 | EOpEq a (Expression' a) (EqualityOperator' a) (Expression' a) -- ^ Expression ::= Expression2 EqualityOperator Expression3 | EOpImpl a (Expression' a) (Expression' a) -- ^ Expression ::= Expression "implies" Expression1 | EOpLog a (Expression' a) (LogicalOperator' a) (Expression' a) -- ^ Expression ::= Expression1 LogicalOperator Expression2 | EOpMul a (Expression' a) (MultiplyOperator' a) (Expression' a) -- ^ Expression ::= Expression5 MultiplyOperator Expression6 | EOpRel a (Expression' a) (RelationalOperator' a) (Expression' a) -- ^ Expression ::= Expression3 RelationalOperator Expression4 | EOpUn a (UnaryOperator' a) (Expression' a) -- ^ Expression ::= UnaryOperator Expression7 deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type MessageArg = MessageArg' BNFC'Position data MessageArg' a = MAExpr a (Expression' a) -- ^ MessageArg ::= Expression | MAUnspec a -- ^ MessageArg ::= "?" | MAUnspecTyped a (TypeSpecifier' a) -- ^ MessageArg ::= "?" ":" TypeSpecifier deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type PropertyCall = PropertyCall' BNFC'Position data PropertyCall' a = PCall a (PathName' a) (PossTimeExpression' a) (PossQualifiers' a) (PossPropCallParam' a) -- ^ PropertyCall ::= PathName PossTimeExpression PossQualifiers PossPropCallParam deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type PathName = PathName' BNFC'Position data PathName' a = PathN a [PName' a] -- ^ PathName ::= PName deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type PName = PName' BNFC'Position data PName' a = PN a Ident -- ^ PName ::= Ident deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type PossQualifiers = PossQualifiers' BNFC'Position data PossQualifiers' a = NoQual a -- ^ PossQualifiers ::= | Qual a (Qualifiers' a) -- ^ PossQualifiers ::= Qualifiers deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Qualifiers = Qualifiers' BNFC'Position data Qualifiers' a = Quals a [Expression' a] -- ^ Qualifiers ::= "[" Expression "]" deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type PossTimeExpression = PossTimeExpression' BNFC'Position data PossTimeExpression' a = AtPre a -- ^ PossTimeExpression ::= "@" "pre" | NoTE a -- ^ PossTimeExpression ::= deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type PossPropCallParam = PossPropCallParam' BNFC'Position data PossPropCallParam' a = NoPCP a -- ^ PossPropCallParam ::= | PCPs a (PropertyCallParameters' a) -- ^ PossPropCallParam ::= PropertyCallParameters deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Declarator = Declarator' BNFC'Position data Declarator' a = Decl a (DeclaratorVarList' a) -- ^ Declarator ::= DeclaratorVarList "|" | DeclAcc a (DeclaratorVarList' a) Ident (TypeSpecifier' a) (Expression' a) -- ^ Declarator ::= DeclaratorVarList ";" Ident ":" TypeSpecifier "=" Expression "|" deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type DeclaratorVarList = DeclaratorVarList' BNFC'Position data DeclaratorVarList' a = DVL a [Ident] -- ^ DeclaratorVarList ::= Ident | DVLType a [Ident] (SimpleTypeSpecifier' a) -- ^ DeclaratorVarList ::= Ident ":" SimpleTypeSpecifier deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type PropertyCallParameters = PropertyCallParameters' BNFC'Position data PropertyCallParameters' a = PCP a [Expression' a] -- ^ PropertyCallParameters ::= "(" Expression ")" | PCPConcrete a (Expression' a) [PCPHelper' a] -- ^ PropertyCallParameters ::= "(" Expression PCPHelper ")" | PCPDecl a (Declarator' a) [Expression' a] -- ^ PropertyCallParameters ::= "(" Declarator Expression ")" | PCPNoDeclNoParam a -- ^ PropertyCallParameters ::= "(" ")" deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type PCPHelper = PCPHelper' BNFC'Position data PCPHelper' a = PCPBar a (Expression' a) -- ^ PCPHelper ::= "|" Expression | PCPColon a (SimpleTypeSpecifier' a) -- ^ PCPHelper ::= ":" SimpleTypeSpecifier | PCPComma a (Expression' a) -- ^ PCPHelper ::= "," Expression | PCPIterate a Ident (TypeSpecifier' a) (Expression' a) -- ^ PCPHelper ::= ";" Ident ":" TypeSpecifier "=" Expression deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type OCLLiteral = OCLLiteral' BNFC'Position data OCLLiteral' a = LitBoolFalse a -- ^ OCLLiteral ::= "false" | LitBoolTrue a -- ^ OCLLiteral ::= "true" | LitNum a (OCLNumber' a) -- ^ OCLLiteral ::= OCLNumber | LitStr a T.String -- ^ OCLLiteral ::= String deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type SimpleTypeSpecifier = SimpleTypeSpecifier' BNFC'Position data SimpleTypeSpecifier' a = STSpec a (PathName' a) -- ^ SimpleTypeSpecifier ::= PathName deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type LiteralCollection = LiteralCollection' BNFC'Position data LiteralCollection' a = LCollection a (CollectionKind' a) [CollectionItem' a] -- ^ LiteralCollection ::= CollectionKind "{" CollectionItem "}" | LCollectionEmpty a (CollectionKind' a) -- ^ LiteralCollection ::= CollectionKind "{" "}" deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type CollectionItem = CollectionItem' BNFC'Position data CollectionItem' a = CI a (Expression' a) -- ^ CollectionItem ::= Expression | CIRange a (Expression' a) (Expression' a) -- ^ CollectionItem ::= Expression ".." Expression deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type OCLNumber = OCLNumber' BNFC'Position data OCLNumber' a = NumDouble a T.Double -- ^ OCLNumber ::= Double | NumInt a T.Integer -- ^ OCLNumber ::= Integer deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type LogicalOperator = LogicalOperator' BNFC'Position data LogicalOperator' a = LAnd a -- ^ LogicalOperator ::= "and" | LOr a -- ^ LogicalOperator ::= "or" | LXor a -- ^ LogicalOperator ::= "xor" deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type CollectionKind = CollectionKind' BNFC'Position data CollectionKind' a = Bag a -- ^ CollectionKind ::= "Bag" | Collection a -- ^ CollectionKind ::= "Collection" | Sequence a -- ^ CollectionKind ::= "Sequence" | Set a -- ^ CollectionKind ::= "Set" deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type EqualityOperator = EqualityOperator' BNFC'Position data EqualityOperator' a = EEq a -- ^ EqualityOperator ::= "=" | ENEq a -- ^ EqualityOperator ::= "<>" deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type RelationalOperator = RelationalOperator' BNFC'Position data RelationalOperator' a = RGT a -- ^ RelationalOperator ::= ">" | RGTE a -- ^ RelationalOperator ::= ">=" | RLT a -- ^ RelationalOperator ::= "<" | RLTE a -- ^ RelationalOperator ::= "<=" deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type AddOperator = AddOperator' BNFC'Position data AddOperator' a = AAdd a -- ^ AddOperator ::= "+" | ASub a -- ^ AddOperator ::= "-" deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type MultiplyOperator = MultiplyOperator' BNFC'Position data MultiplyOperator' a = MDiv a -- ^ MultiplyOperator ::= "/" | MMult a -- ^ MultiplyOperator ::= "*" deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type UnaryOperator = UnaryOperator' BNFC'Position data UnaryOperator' a = UMin a -- ^ UnaryOperator ::= "-" | UNot a -- ^ UnaryOperator ::= "not" deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type PostfixOperator = PostfixOperator' BNFC'Position data PostfixOperator' a = PArrow a -- ^ PostfixOperator ::= "->" | PDot a -- ^ PostfixOperator ::= "." deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) newtype Ident = Ident T.String deriving (C.Eq, C.Ord, C.Show, C.Read, Data.String.IsString) -- | Start position (line, column) of something. type BNFC'Position = C.Maybe (C.Int, C.Int) pattern BNFC'NoPosition :: BNFC'Position pattern BNFC'NoPosition = C.Nothing pattern BNFC'Position :: C.Int -> C.Int -> BNFC'Position pattern BNFC'Position line col = C.Just (line, col) -- | Get the start position of something. class HasPosition a where hasPosition :: a -> BNFC'Position instance HasPosition OCLfile where hasPosition = \case OCLf p _ -> p instance HasPosition OCLPackage where hasPosition = \case Pack p _ _ -> p instance HasPosition PackageName where hasPosition = \case PackName p _ -> p instance HasPosition OCLExpressions where hasPosition = \case Constraints p _ -> p instance HasPosition Constrnt where hasPosition = \case Constr p _ _ -> p instance HasPosition ConstrBody where hasPosition = \case CB p _ _ -> p CBDef p _ -> p CBDefNamed p _ _ -> p CBNamed p _ _ _ -> p instance HasPosition ContextDeclaration where hasPosition = \case CDClassif p _ -> p CDOper p _ -> p instance HasPosition ClassifierContext where hasPosition = \case CC p _ -> p CCType p _ _ -> p instance HasPosition OperationContext where hasPosition = \case OpC p _ _ _ -> p OpCRT p _ _ _ _ -> p instance HasPosition Stereotype where hasPosition = \case Inv p -> p Post p -> p Pre p -> p instance HasPosition OperationName where hasPosition = \case Add p -> p And p -> p Div p -> p Eq p -> p GRT p -> p GRTE p -> p Impl p -> p LST p -> p LSTE p -> p Mult p -> p NEq p -> p Not p -> p OpName p _ -> p Or p -> p Sub p -> p Xor p -> p instance HasPosition FormalParameter where hasPosition = \case FP p _ _ -> p instance HasPosition TypeSpecifier where hasPosition = \case TScoll p _ -> p TSsimple p _ -> p instance HasPosition CollectionType where hasPosition = \case CT p _ _ -> p instance HasPosition ReturnType where hasPosition = \case RT p _ -> p instance HasPosition OCLExpression where hasPosition = \case OCLExp p _ -> p OCLExpLet p _ _ -> p instance HasPosition LetExpression where hasPosition = \case LE p _ _ _ -> p LENoParam p _ _ -> p LENoParamType p _ _ _ -> p LEType p _ _ _ _ -> p instance HasPosition IfExpression where hasPosition = \case IfExp p _ _ _ -> p instance HasPosition Expression where hasPosition = \case EExplPropCall p _ _ _ -> p EIfExp p _ -> p EImplPropCall p _ -> p ELit p _ -> p ELitColl p _ -> p EMessage p _ _ _ -> p ENull p -> p EOpAdd p _ _ _ -> p EOpEq p _ _ _ -> p EOpImpl p _ _ -> p EOpLog p _ _ _ -> p EOpMul p _ _ _ -> p EOpRel p _ _ _ -> p EOpUn p _ _ -> p instance HasPosition MessageArg where hasPosition = \case MAExpr p _ -> p MAUnspec p -> p MAUnspecTyped p _ -> p instance HasPosition PropertyCall where hasPosition = \case PCall p _ _ _ _ -> p instance HasPosition PathName where hasPosition = \case PathN p _ -> p instance HasPosition PName where hasPosition = \case PN p _ -> p instance HasPosition PossQualifiers where hasPosition = \case NoQual p -> p Qual p _ -> p instance HasPosition Qualifiers where hasPosition = \case Quals p _ -> p instance HasPosition PossTimeExpression where hasPosition = \case AtPre p -> p NoTE p -> p instance HasPosition PossPropCallParam where hasPosition = \case NoPCP p -> p PCPs p _ -> p instance HasPosition Declarator where hasPosition = \case Decl p _ -> p DeclAcc p _ _ _ _ -> p instance HasPosition DeclaratorVarList where hasPosition = \case DVL p _ -> p DVLType p _ _ -> p instance HasPosition PropertyCallParameters where hasPosition = \case PCP p _ -> p PCPConcrete p _ _ -> p PCPDecl p _ _ -> p PCPNoDeclNoParam p -> p instance HasPosition PCPHelper where hasPosition = \case PCPBar p _ -> p PCPColon p _ -> p PCPComma p _ -> p PCPIterate p _ _ _ -> p instance HasPosition OCLLiteral where hasPosition = \case LitBoolFalse p -> p LitBoolTrue p -> p LitNum p _ -> p LitStr p _ -> p instance HasPosition SimpleTypeSpecifier where hasPosition = \case STSpec p _ -> p instance HasPosition LiteralCollection where hasPosition = \case LCollection p _ _ -> p LCollectionEmpty p _ -> p instance HasPosition CollectionItem where hasPosition = \case CI p _ -> p CIRange p _ _ -> p instance HasPosition OCLNumber where hasPosition = \case NumDouble p _ -> p NumInt p _ -> p instance HasPosition LogicalOperator where hasPosition = \case LAnd p -> p LOr p -> p LXor p -> p instance HasPosition CollectionKind where hasPosition = \case Bag p -> p Collection p -> p Sequence p -> p Set p -> p instance HasPosition EqualityOperator where hasPosition = \case EEq p -> p ENEq p -> p instance HasPosition RelationalOperator where hasPosition = \case RGT p -> p RGTE p -> p RLT p -> p RLTE p -> p instance HasPosition AddOperator where hasPosition = \case AAdd p -> p ASub p -> p instance HasPosition MultiplyOperator where hasPosition = \case MDiv p -> p MMult p -> p instance HasPosition UnaryOperator where hasPosition = \case UMin p -> p UNot p -> p instance HasPosition PostfixOperator where hasPosition = \case PArrow p -> p PDot p -> p