-- 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 GF. module AbsGF where import qualified Prelude as T (Integer, String) import qualified Prelude as C ( Eq , Ord , Show , Read , Functor , Foldable , Traversable , Int, Maybe(..) ) import Data.String type Grammar = Grammar' BNFC'Position data Grammar' a = Gr a [ModDef' a] -- ^ Grammar ::= ModDef deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type ModDef = ModDef' BNFC'Position data ModDef' a = MMain a Ident Ident [ConcSpec' a] -- ^ ModDef ::= "grammar" Ident "=" "{" "abstract" "=" Ident ";" ConcSpec "}" | MModule a (ComplMod' a) (ModType' a) (ModBody' a) -- ^ ModDef ::= ComplMod ModType "=" ModBody deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type ConcSpec = ConcSpec' BNFC'Position data ConcSpec' a = ConcSpecC a Ident (ConcExp' a) -- ^ ConcSpec ::= Ident "=" ConcExp deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type ConcExp = ConcExp' BNFC'Position data ConcExp' a = ConcExpC a Ident [Transfer' a] -- ^ ConcExp ::= Ident Transfer deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Transfer = Transfer' BNFC'Position data Transfer' a = TransferIn a (OpenDecl' a) -- ^ Transfer ::= "(" "transfer" "in" OpenDecl ")" | TransferOut a (OpenDecl' a) -- ^ Transfer ::= "(" "transfer" "out" OpenDecl ")" deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type ModType = ModType' BNFC'Position data ModType' a = MTAbstract a Ident -- ^ ModType ::= "abstract" Ident | MTConcrete a Ident Ident -- ^ ModType ::= "concrete" Ident "of" Ident | MTInstance a Ident Ident -- ^ ModType ::= "instance" Ident "of" Ident | MTInterface a Ident -- ^ ModType ::= "interface" Ident | MTResource a Ident -- ^ ModType ::= "resource" Ident | MTTransfer a Ident (OpenDecl' a) (OpenDecl' a) -- ^ ModType ::= "transfer" Ident ":" OpenDecl "->" OpenDecl deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type ModBody = ModBody' BNFC'Position data ModBody' a = MBody a (Extend' a) (Opens' a) [TopDef' a] -- ^ ModBody ::= Extend Opens "{" TopDef "}" | MReuse a Ident -- ^ ModBody ::= "reuse" Ident | MUnion a [Included' a] -- ^ ModBody ::= "union" Included | MWith a Ident [OpenDecl' a] -- ^ ModBody ::= Ident "with" OpenDecl | MWithE a [Included' a] Ident [OpenDecl' a] -- ^ ModBody ::= Included "**" Ident "with" OpenDecl deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Extend = Extend' BNFC'Position data Extend' a = Ext a [Included' a] -- ^ Extend ::= Included "**" | NoExt a -- ^ Extend ::= deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Opens = Opens' BNFC'Position data Opens' a = NoOpens a -- ^ Opens ::= | OpenIn a [OpenDecl' a] -- ^ Opens ::= "open" OpenDecl "in" deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type OpenDecl = OpenDecl' BNFC'Position data OpenDecl' a = OName a Ident -- ^ OpenDecl ::= Ident | OQual a (QualOpen' a) Ident Ident -- ^ OpenDecl ::= "(" QualOpen Ident "=" Ident ")" | OQualQO a (QualOpen' a) Ident -- ^ OpenDecl ::= "(" QualOpen Ident ")" deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type ComplMod = ComplMod' BNFC'Position data ComplMod' a = CMCompl a -- ^ ComplMod ::= | CMIncompl a -- ^ ComplMod ::= "incomplete" deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type QualOpen = QualOpen' BNFC'Position data QualOpen' a = QOCompl a -- ^ QualOpen ::= | QOIncompl a -- ^ QualOpen ::= "incomplete" | QOInterface a -- ^ QualOpen ::= "interface" deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Included = Included' BNFC'Position data Included' a = IAll a Ident -- ^ Included ::= Ident | IMinus a Ident [Ident] -- ^ Included ::= Ident "-" "[" Ident "]" | ISome a Ident [Ident] -- ^ Included ::= Ident "[" Ident "]" deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Def = Def' BNFC'Position data Def' a = DDeclC a [Name' a] (Exp' a) -- ^ Def ::= Name ":" Exp | DDef a [Name' a] (Exp' a) -- ^ Def ::= Name "=" Exp | DFull a [Name' a] (Exp' a) (Exp' a) -- ^ Def ::= Name ":" Exp "=" Exp | DPatt a (Name' a) [Patt' a] (Exp' a) -- ^ Def ::= Name Patt "=" Exp deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type TopDef = TopDef' BNFC'Position data TopDef' a = DefCat a [CatDef' a] -- ^ TopDef ::= "cat" CatDef | DefData a [DataDef' a] -- ^ TopDef ::= "data" DataDef | DefDef a [Def' a] -- ^ TopDef ::= "def" Def | DefFlag a [FlagDef' a] -- ^ TopDef ::= "flags" FlagDef | DefFun a [FunDef' a] -- ^ TopDef ::= "fun" FunDef | DefFunData a [FunDef' a] -- ^ TopDef ::= "data" FunDef | DefLin a [Def' a] -- ^ TopDef ::= "lin" Def | DefLincat a [PrintDef' a] -- ^ TopDef ::= "lincat" PrintDef | DefLindef a [Def' a] -- ^ TopDef ::= "lindef" Def | DefLintype a [Def' a] -- ^ TopDef ::= "lintype" Def | DefOper a [Def' a] -- ^ TopDef ::= "oper" Def | DefPackage a Ident [TopDef' a] -- ^ TopDef ::= "package" Ident "=" "{" TopDef "}" ";" | DefPar a [ParDef' a] -- ^ TopDef ::= "param" ParDef | DefPattern a [Def' a] -- ^ TopDef ::= "pattern" Def | DefPrintCat a [PrintDef' a] -- ^ TopDef ::= "printname" "cat" PrintDef | DefPrintFun a [PrintDef' a] -- ^ TopDef ::= "printname" "fun" PrintDef | DefPrintOld a [PrintDef' a] -- ^ TopDef ::= "printname" PrintDef | DefTokenizer a Ident -- ^ TopDef ::= "tokenizer" Ident ";" | DefTrans a [Def' a] -- ^ TopDef ::= "transfer" Def | DefVars a [Def' a] -- ^ TopDef ::= "var" Def deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type CatDef = CatDef' BNFC'Position data CatDef' a = ListCatDefC a Ident [DDecl' a] -- ^ CatDef ::= "[" Ident DDecl "]" | ListSizeCatDef a Ident [DDecl' a] T.Integer -- ^ CatDef ::= "[" Ident DDecl "]" "{" Integer "}" | SimpleCatDef a Ident [DDecl' a] -- ^ CatDef ::= Ident DDecl deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type FunDef = FunDef' BNFC'Position data FunDef' a = FunDefC a [Ident] (Exp' a) -- ^ FunDef ::= Ident ":" Exp deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type DataDef = DataDef' BNFC'Position data DataDef' a = DataDefC a Ident [DataConstr' a] -- ^ DataDef ::= Ident "=" DataConstr deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type DataConstr = DataConstr' BNFC'Position data DataConstr' a = DataId a Ident -- ^ DataConstr ::= Ident | DataQId a Ident Ident -- ^ DataConstr ::= Ident "." Ident deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type ParDef = ParDef' BNFC'Position data ParDef' a = ParDefAbs a Ident -- ^ ParDef ::= Ident | ParDefDir a Ident [ParConstr' a] -- ^ ParDef ::= Ident "=" ParConstr | ParDefIndir a Ident Ident -- ^ ParDef ::= Ident "=" "(" "in" Ident ")" deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type ParConstr = ParConstr' BNFC'Position data ParConstr' a = ParConstrC a Ident [DDecl' a] -- ^ ParConstr ::= Ident DDecl deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type PrintDef = PrintDef' BNFC'Position data PrintDef' a = PrintDefC a [Name' a] (Exp' a) -- ^ PrintDef ::= Name "=" Exp deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type FlagDef = FlagDef' BNFC'Position data FlagDef' a = FlagDefC a Ident Ident -- ^ FlagDef ::= Ident "=" Ident deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Name = Name' BNFC'Position data Name' a = IdentName a Ident -- ^ Name ::= Ident | ListNameC a Ident -- ^ Name ::= "[" Ident "]" deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type LocDef = LocDef' BNFC'Position data LocDef' a = LDDecl a [Ident] (Exp' a) -- ^ LocDef ::= Ident ":" Exp | LDDef a [Ident] (Exp' a) -- ^ LocDef ::= Ident "=" Exp | LDFull a [Ident] (Exp' a) (Exp' a) -- ^ LocDef ::= Ident ":" Exp "=" Exp deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Exp = Exp' BNFC'Position data Exp' a = EAbstr a [Bind' a] (Exp' a) -- ^ Exp ::= "\\" Bind "->" Exp | EApp a (Exp' a) (Exp' a) -- ^ Exp ::= Exp2 Exp3 | ECTable a [Bind' a] (Exp' a) -- ^ Exp ::= "\\" "\\" Bind "=>" Exp | ECase a (Exp' a) [Case' a] -- ^ Exp ::= "case" Exp "of" "{" Case "}" | EConAt a Ident (Exp' a) -- ^ Exp ::= Ident "@" Exp4 | EConcat a (Exp' a) (Exp' a) -- ^ Exp ::= Exp1 "++" Exp | ECons a Ident -- ^ Exp ::= "%" Ident "%" | EConstr a Ident -- ^ Exp ::= "{" Ident "}" | EData a -- ^ Exp ::= "data" | EEmpty a -- ^ Exp ::= "[" "]" | EEqs a [Equation' a] -- ^ Exp ::= "fn" "{" Equation "}" | EExtend a (Exp' a) (Exp' a) -- ^ Exp ::= Exp1 "**" Exp2 | EGlue a (Exp' a) (Exp' a) -- ^ Exp ::= Exp1 "+" Exp | EIdent a Ident -- ^ Exp ::= Ident | EIndir a Ident -- ^ Exp ::= "(" "in" Ident ")" | EInt a T.Integer -- ^ Exp ::= Integer | ELString a LString -- ^ Exp ::= LString | ELet a [LocDef' a] (Exp' a) -- ^ Exp ::= "let" "{" LocDef "}" "in" Exp | ELetb a [LocDef' a] (Exp' a) -- ^ Exp ::= "let" LocDef "in" Exp | ELin a Ident -- ^ Exp ::= "Lin" Ident | EList a Ident (Exps' a) -- ^ Exp ::= "[" Ident Exps "]" | EMeta a -- ^ Exp ::= "?" | EPre a (Exp' a) [Altern' a] -- ^ Exp ::= "pre" "{" Exp ";" Altern "}" | EProd a (Decl' a) (Exp' a) -- ^ Exp ::= Decl "->" Exp | EProj a (Exp' a) (Label' a) -- ^ Exp ::= Exp3 "." Label | EQCons a Ident Ident -- ^ Exp ::= "%" Ident "." Ident | EQConstr a Ident Ident -- ^ Exp ::= "{" Ident "." Ident "}" | ERecord a [LocDef' a] -- ^ Exp ::= "{" LocDef "}" | ESelect a (Exp' a) (Exp' a) -- ^ Exp ::= Exp1 "!" Exp2 | ESort a (Sort' a) -- ^ Exp ::= Sort | EString a T.String -- ^ Exp ::= String | EStrings a T.String -- ^ Exp ::= "[" String "]" | EStrs a [Exp' a] -- ^ Exp ::= "strs" "{" Exp "}" | ETTable a (Exp' a) [Case' a] -- ^ Exp ::= "table" Exp4 "{" Case "}" | ETType a (Exp' a) (Exp' a) -- ^ Exp ::= Exp1 "=>" Exp | ETable a [Case' a] -- ^ Exp ::= "table" "{" Case "}" | ETupTyp a (Exp' a) (Exp' a) -- ^ Exp ::= Exp1 "*" Exp2 | ETuple a [TupleComp' a] -- ^ Exp ::= "<" TupleComp ">" | ETyped a (Exp' a) (Exp' a) -- ^ Exp ::= "<" Exp ":" Exp ">" | EVTable a (Exp' a) [Exp' a] -- ^ Exp ::= "table" Exp4 "[" Exp "]" | EVariants a [Exp' a] -- ^ Exp ::= "variants" "{" Exp "}" | EWhere a (Exp' a) [LocDef' a] -- ^ Exp ::= Exp1 "where" "{" LocDef "}" deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Exps = Exps' BNFC'Position data Exps' a = ConsExp a (Exp' a) (Exps' a) -- ^ Exps ::= Exp4 Exps | NilExp a -- ^ Exps ::= deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Patt = Patt' BNFC'Position data Patt' a = PC a Ident [Patt' a] -- ^ Patt ::= Ident Patt | PCon a Ident -- ^ Patt ::= "{" Ident "}" | PInt a T.Integer -- ^ Patt ::= Integer | PQ a Ident Ident -- ^ Patt ::= Ident "." Ident | PQC a Ident Ident [Patt' a] -- ^ Patt ::= Ident "." Ident Patt | PR a [PattAss' a] -- ^ Patt ::= "{" PattAss "}" | PStr a T.String -- ^ Patt ::= String | PTup a [PattTupleComp' a] -- ^ Patt ::= "<" PattTupleComp ">" | PV a Ident -- ^ Patt ::= Ident | PW a -- ^ Patt ::= "_" deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type PattAss = PattAss' BNFC'Position data PattAss' a = PA a [Ident] (Patt' a) -- ^ PattAss ::= Ident "=" Patt deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Label = Label' BNFC'Position data Label' a = LIdent a Ident -- ^ Label ::= Ident | LVar a T.Integer -- ^ Label ::= "$" Integer deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Sort = Sort' BNFC'Position data Sort' a = Sort_PType a -- ^ Sort ::= "PType" | Sort_Str a -- ^ Sort ::= "Str" | Sort_Strs a -- ^ Sort ::= "Strs" | Sort_Tok a -- ^ Sort ::= "Tok" | Sort_Type a -- ^ Sort ::= "Type" deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type PattAlt = PattAlt' BNFC'Position data PattAlt' a = AltP a (Patt' a) -- ^ PattAlt ::= Patt deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Bind = Bind' BNFC'Position data Bind' a = BIdent a Ident -- ^ Bind ::= Ident | BWild a -- ^ Bind ::= "_" deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Decl = Decl' BNFC'Position data Decl' a = DDec a [Bind' a] (Exp' a) -- ^ Decl ::= "(" Bind ":" Exp ")" | DExp a (Exp' a) -- ^ Decl ::= Exp2 deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type TupleComp = TupleComp' BNFC'Position data TupleComp' a = TComp a (Exp' a) -- ^ TupleComp ::= Exp deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type PattTupleComp = PattTupleComp' BNFC'Position data PattTupleComp' a = PTComp a (Patt' a) -- ^ PattTupleComp ::= Patt deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Case = Case' BNFC'Position data Case' a = CaseC a [PattAlt' a] (Exp' a) -- ^ Case ::= PattAlt "=>" Exp deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Equation = Equation' BNFC'Position data Equation' a = Equ a [Patt' a] (Exp' a) -- ^ Equation ::= Patt "->" Exp deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Altern = Altern' BNFC'Position data Altern' a = Alt a (Exp' a) (Exp' a) -- ^ Altern ::= Exp "/" Exp deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type DDecl = DDecl' BNFC'Position data DDecl' a = DDDec a [Bind' a] (Exp' a) -- ^ DDecl ::= "(" Bind ":" Exp ")" | DDExp a (Exp' a) -- ^ DDecl ::= Exp4 deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type OldGrammar = OldGrammar' BNFC'Position data OldGrammar' a = OldGr a (IncludeDecl' a) [TopDef' a] -- ^ OldGrammar ::= IncludeDecl TopDef deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type IncludeDecl = IncludeDecl' BNFC'Position data IncludeDecl' a = Incl a [FileName' a] -- ^ IncludeDecl ::= "include" FileName | NoIncl a -- ^ IncludeDecl ::= deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type FileName = FileName' BNFC'Position data FileName' a = FAddId a Ident (FileName' a) -- ^ FileName ::= Ident FileName | FDot a (FileName' a) -- ^ FileName ::= "." FileName | FIdent a Ident -- ^ FileName ::= Ident | FMinus a (FileName' a) -- ^ FileName ::= "-" FileName | FSlash a (FileName' a) -- ^ FileName ::= "/" FileName | FString a T.String -- ^ FileName ::= String 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) newtype LString = LString 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 Grammar where hasPosition = \case Gr p _ -> p instance HasPosition ModDef where hasPosition = \case MMain p _ _ _ -> p MModule p _ _ _ -> p instance HasPosition ConcSpec where hasPosition = \case ConcSpecC p _ _ -> p instance HasPosition ConcExp where hasPosition = \case ConcExpC p _ _ -> p instance HasPosition Transfer where hasPosition = \case TransferIn p _ -> p TransferOut p _ -> p instance HasPosition ModType where hasPosition = \case MTAbstract p _ -> p MTConcrete p _ _ -> p MTInstance p _ _ -> p MTInterface p _ -> p MTResource p _ -> p MTTransfer p _ _ _ -> p instance HasPosition ModBody where hasPosition = \case MBody p _ _ _ -> p MReuse p _ -> p MUnion p _ -> p MWith p _ _ -> p MWithE p _ _ _ -> p instance HasPosition Extend where hasPosition = \case Ext p _ -> p NoExt p -> p instance HasPosition Opens where hasPosition = \case NoOpens p -> p OpenIn p _ -> p instance HasPosition OpenDecl where hasPosition = \case OName p _ -> p OQual p _ _ _ -> p OQualQO p _ _ -> p instance HasPosition ComplMod where hasPosition = \case CMCompl p -> p CMIncompl p -> p instance HasPosition QualOpen where hasPosition = \case QOCompl p -> p QOIncompl p -> p QOInterface p -> p instance HasPosition Included where hasPosition = \case IAll p _ -> p IMinus p _ _ -> p ISome p _ _ -> p instance HasPosition Def where hasPosition = \case DDeclC p _ _ -> p DDef p _ _ -> p DFull p _ _ _ -> p DPatt p _ _ _ -> p instance HasPosition TopDef where hasPosition = \case DefCat p _ -> p DefData p _ -> p DefDef p _ -> p DefFlag p _ -> p DefFun p _ -> p DefFunData p _ -> p DefLin p _ -> p DefLincat p _ -> p DefLindef p _ -> p DefLintype p _ -> p DefOper p _ -> p DefPackage p _ _ -> p DefPar p _ -> p DefPattern p _ -> p DefPrintCat p _ -> p DefPrintFun p _ -> p DefPrintOld p _ -> p DefTokenizer p _ -> p DefTrans p _ -> p DefVars p _ -> p instance HasPosition CatDef where hasPosition = \case ListCatDefC p _ _ -> p ListSizeCatDef p _ _ _ -> p SimpleCatDef p _ _ -> p instance HasPosition FunDef where hasPosition = \case FunDefC p _ _ -> p instance HasPosition DataDef where hasPosition = \case DataDefC p _ _ -> p instance HasPosition DataConstr where hasPosition = \case DataId p _ -> p DataQId p _ _ -> p instance HasPosition ParDef where hasPosition = \case ParDefAbs p _ -> p ParDefDir p _ _ -> p ParDefIndir p _ _ -> p instance HasPosition ParConstr where hasPosition = \case ParConstrC p _ _ -> p instance HasPosition PrintDef where hasPosition = \case PrintDefC p _ _ -> p instance HasPosition FlagDef where hasPosition = \case FlagDefC p _ _ -> p instance HasPosition Name where hasPosition = \case IdentName p _ -> p ListNameC p _ -> p instance HasPosition LocDef where hasPosition = \case LDDecl p _ _ -> p LDDef p _ _ -> p LDFull p _ _ _ -> p instance HasPosition Exp where hasPosition = \case EAbstr p _ _ -> p EApp p _ _ -> p ECTable p _ _ -> p ECase p _ _ -> p EConAt p _ _ -> p EConcat p _ _ -> p ECons p _ -> p EConstr p _ -> p EData p -> p EEmpty p -> p EEqs p _ -> p EExtend p _ _ -> p EGlue p _ _ -> p EIdent p _ -> p EIndir p _ -> p EInt p _ -> p ELString p _ -> p ELet p _ _ -> p ELetb p _ _ -> p ELin p _ -> p EList p _ _ -> p EMeta p -> p EPre p _ _ -> p EProd p _ _ -> p EProj p _ _ -> p EQCons p _ _ -> p EQConstr p _ _ -> p ERecord p _ -> p ESelect p _ _ -> p ESort p _ -> p EString p _ -> p EStrings p _ -> p EStrs p _ -> p ETTable p _ _ -> p ETType p _ _ -> p ETable p _ -> p ETupTyp p _ _ -> p ETuple p _ -> p ETyped p _ _ -> p EVTable p _ _ -> p EVariants p _ -> p EWhere p _ _ -> p instance HasPosition Exps where hasPosition = \case ConsExp p _ _ -> p NilExp p -> p instance HasPosition Patt where hasPosition = \case PC p _ _ -> p PCon p _ -> p PInt p _ -> p PQ p _ _ -> p PQC p _ _ _ -> p PR p _ -> p PStr p _ -> p PTup p _ -> p PV p _ -> p PW p -> p instance HasPosition PattAss where hasPosition = \case PA p _ _ -> p instance HasPosition Label where hasPosition = \case LIdent p _ -> p LVar p _ -> p instance HasPosition Sort where hasPosition = \case Sort_PType p -> p Sort_Str p -> p Sort_Strs p -> p Sort_Tok p -> p Sort_Type p -> p instance HasPosition PattAlt where hasPosition = \case AltP p _ -> p instance HasPosition Bind where hasPosition = \case BIdent p _ -> p BWild p -> p instance HasPosition Decl where hasPosition = \case DDec p _ _ -> p DExp p _ -> p instance HasPosition TupleComp where hasPosition = \case TComp p _ -> p instance HasPosition PattTupleComp where hasPosition = \case PTComp p _ -> p instance HasPosition Case where hasPosition = \case CaseC p _ _ -> p instance HasPosition Equation where hasPosition = \case Equ p _ _ -> p instance HasPosition Altern where hasPosition = \case Alt p _ _ -> p instance HasPosition DDecl where hasPosition = \case DDDec p _ _ -> p DDExp p _ -> p instance HasPosition OldGrammar where hasPosition = \case OldGr p _ _ -> p instance HasPosition IncludeDecl where hasPosition = \case Incl p _ -> p NoIncl p -> p instance HasPosition FileName where hasPosition = \case FAddId p _ _ -> p FDot p _ -> p FIdent p _ -> p FMinus p _ -> p FSlash p _ -> p FString p _ -> p