-- For GHC version 7.10 or higher {-# LANGUAGE GADTs, KindSignatures, DataKinds #-} {-# LANGUAGE LambdaCase #-} {-# OPTIONS_GHC -fno-warn-unused-binds #-} {-# OPTIONS_GHC -fno-warn-unused-imports #-} {-# OPTIONS_GHC -fno-warn-unused-matches #-} {-# OPTIONS_GHC -fno-warn-incomplete-patterns #-} {-# OPTIONS_GHC -fno-warn-overlapping-patterns #-} module AbsAlfa ( Tree(..) , Decl , Def , Exp , Arrow , Typing , VarDecl , Bound , FieldDecl , Branch , Constructor , IndConstructor , Binding , PackageBody , OpenArg , DefAttr , Import , AIdent , Comment , Infix , PIdent , johnMajorEq , module ComposOpAlfa ) where import Prelude ((.), (>), (&&), (==)) import Prelude (Int, (.), (>), (&&), (==)) import qualified Prelude as P import ComposOpAlfa data Tag = Decl_ | Def_ | Exp_ | Arrow_ | Typing_ | VarDecl_ | Bound_ | FieldDecl_ | Branch_ | Constructor_ | IndConstructor_ | Binding_ | PackageBody_ | OpenArg_ | DefAttr_ | Import_ | AIdent_ | Comment_ | Infix_ | PIdent_ type Decl = Tree 'Decl_ type Def = Tree 'Def_ type Exp = Tree 'Exp_ type Arrow = Tree 'Arrow_ type Typing = Tree 'Typing_ type VarDecl = Tree 'VarDecl_ type Bound = Tree 'Bound_ type FieldDecl = Tree 'FieldDecl_ type Branch = Tree 'Branch_ type Constructor = Tree 'Constructor_ type IndConstructor = Tree 'IndConstructor_ type Binding = Tree 'Binding_ type PackageBody = Tree 'PackageBody_ type OpenArg = Tree 'OpenArg_ type DefAttr = Tree 'DefAttr_ type Import = Tree 'Import_ type AIdent = Tree 'AIdent_ type Comment = Tree 'Comment_ type Infix = Tree 'Infix_ type PIdent = Tree 'PIdent_ data Tree (a :: Tag) where DDef :: [DefAttr] -> Def -> Tree 'Decl_ DImp :: Import -> Tree 'Decl_ Axiom :: AIdent -> [Typing] -> Exp -> Tree 'Def_ Binding :: AIdent -> Exp -> Tree 'Def_ Commt :: Comment -> Tree 'Def_ Data :: AIdent -> [Typing] -> [Constructor] -> Tree 'Def_ Mutual :: [Def] -> Tree 'Def_ Open :: Exp -> [OpenArg] -> Tree 'Def_ Package :: AIdent -> [Typing] -> PackageBody -> Tree 'Def_ Type :: AIdent -> [Typing] -> Exp -> Tree 'Def_ Value :: AIdent -> [VarDecl] -> Exp -> Exp -> Tree 'Def_ EAbs :: VarDecl -> Arrow -> Exp -> Tree 'Exp_ EAbsUnt :: [AIdent] -> Arrow -> Exp -> Tree 'Exp_ EApp :: Exp -> Exp -> Tree 'Exp_ ECase :: Exp -> [Branch] -> Tree 'Exp_ EChar :: P.Char -> Tree 'Exp_ ECommL :: Comment -> Exp -> Tree 'Exp_ ECommR :: Exp -> Comment -> Tree 'Exp_ ECon :: AIdent -> Tree 'Exp_ EConst :: AIdent -> Tree 'Exp_ EDouble :: P.Double -> Tree 'Exp_ EFun :: Exp -> Arrow -> Exp -> Tree 'Exp_ EIData :: [VarDecl] -> [IndConstructor] -> Tree 'Exp_ EInfix :: Exp -> Infix -> Exp -> Tree 'Exp_ EInt :: P.Integer -> Tree 'Exp_ ELet :: [Decl] -> Exp -> Tree 'Exp_ EMeta :: Tree 'Exp_ EMetaN :: P.Integer -> Tree 'Exp_ EMetaU :: Tree 'Exp_ EOpen :: Exp -> [OpenArg] -> Exp -> Tree 'Exp_ EPi :: VarDecl -> Arrow -> Exp -> Tree 'Exp_ EProj :: Exp -> AIdent -> Tree 'Exp_ ESet :: Tree 'Exp_ ESig :: [FieldDecl] -> Tree 'Exp_ EStar :: P.Integer -> Tree 'Exp_ EStr :: [Binding] -> Tree 'Exp_ EString :: P.String -> Tree 'Exp_ ESum :: [Constructor] -> Tree 'Exp_ EType :: Tree 'Exp_ EVar :: AIdent -> Tree 'Exp_ AHide :: Tree 'Arrow_ AShow :: Tree 'Arrow_ TDecl :: VarDecl -> Tree 'Typing_ TExp :: Exp -> Tree 'Typing_ VDecl :: [Bound] -> Exp -> Tree 'VarDecl_ BHide :: AIdent -> Tree 'Bound_ BVar :: AIdent -> Tree 'Bound_ FDecl :: AIdent -> Exp -> Tree 'FieldDecl_ BranchCon :: AIdent -> [AIdent] -> Exp -> Tree 'Branch_ BranchInf :: AIdent -> Infix -> AIdent -> Exp -> Tree 'Branch_ BranchVar :: AIdent -> Exp -> Tree 'Branch_ Cnstr :: AIdent -> [Typing] -> Tree 'Constructor_ ICnstr :: AIdent -> [Typing] -> [Exp] -> Tree 'IndConstructor_ Bind :: AIdent -> Exp -> Tree 'Binding_ PackageDef :: [Decl] -> Tree 'PackageBody_ PackageInst :: Exp -> Tree 'PackageBody_ OArg :: [DefAttr] -> AIdent -> Tree 'OpenArg_ OArgD :: [DefAttr] -> AIdent -> Exp -> Tree 'OpenArg_ OArgT :: [DefAttr] -> AIdent -> Exp -> Tree 'OpenArg_ OArgTD :: [DefAttr] -> AIdent -> Exp -> Exp -> Tree 'OpenArg_ Abstract :: Tree 'DefAttr_ Concrete :: Tree 'DefAttr_ Private :: Tree 'DefAttr_ Public :: Tree 'DefAttr_ Import :: P.String -> Tree 'Import_ F :: PIdent -> Tree 'AIdent_ I :: Infix -> Tree 'AIdent_ Comment ::P.String -> Tree 'Comment_ Infix ::P.String -> Tree 'Infix_ PIdent :: ((Int,Int),P.String) -> Tree 'PIdent_ instance Compos Tree where compos r a f = \case DDef defAttrs def -> r DDef `a` P.foldr (\ x z -> r (:) `a` f x `a` z) (r []) defAttrs `a` f def DImp import_ -> r DImp `a` f import_ Axiom aIdent typings exp -> r Axiom `a` f aIdent `a` P.foldr (\ x z -> r (:) `a` f x `a` z) (r []) typings `a` f exp Binding aIdent exp -> r Binding `a` f aIdent `a` f exp Commt comment -> r Commt `a` f comment Data aIdent typings constructors -> r Data `a` f aIdent `a` P.foldr (\ x z -> r (:) `a` f x `a` z) (r []) typings `a` P.foldr (\ x z -> r (:) `a` f x `a` z) (r []) constructors Mutual defs -> r Mutual `a` P.foldr (\ x z -> r (:) `a` f x `a` z) (r []) defs Open exp openArgs -> r Open `a` f exp `a` P.foldr (\ x z -> r (:) `a` f x `a` z) (r []) openArgs Package aIdent typings packageBody -> r Package `a` f aIdent `a` P.foldr (\ x z -> r (:) `a` f x `a` z) (r []) typings `a` f packageBody Type aIdent typings exp -> r Type `a` f aIdent `a` P.foldr (\ x z -> r (:) `a` f x `a` z) (r []) typings `a` f exp Value aIdent varDecls exp1 exp2 -> r Value `a` f aIdent `a` P.foldr (\ x z -> r (:) `a` f x `a` z) (r []) varDecls `a` f exp1 `a` f exp2 EAbs varDecl arrow exp -> r EAbs `a` f varDecl `a` f arrow `a` f exp EAbsUnt aIdents arrow exp -> r EAbsUnt `a` P.foldr (\ x z -> r (:) `a` f x `a` z) (r []) aIdents `a` f arrow `a` f exp EApp exp1 exp2 -> r EApp `a` f exp1 `a` f exp2 ECase exp branchs -> r ECase `a` f exp `a` P.foldr (\ x z -> r (:) `a` f x `a` z) (r []) branchs ECommL comment exp -> r ECommL `a` f comment `a` f exp ECommR exp comment -> r ECommR `a` f exp `a` f comment ECon aIdent -> r ECon `a` f aIdent EConst aIdent -> r EConst `a` f aIdent EFun exp1 arrow exp2 -> r EFun `a` f exp1 `a` f arrow `a` f exp2 EIData varDecls indConstructors -> r EIData `a` P.foldr (\ x z -> r (:) `a` f x `a` z) (r []) varDecls `a` P.foldr (\ x z -> r (:) `a` f x `a` z) (r []) indConstructors EInfix exp1 infix_ exp2 -> r EInfix `a` f exp1 `a` f infix_ `a` f exp2 ELet decls exp -> r ELet `a` P.foldr (\ x z -> r (:) `a` f x `a` z) (r []) decls `a` f exp EOpen exp1 openArgs exp2 -> r EOpen `a` f exp1 `a` P.foldr (\ x z -> r (:) `a` f x `a` z) (r []) openArgs `a` f exp2 EPi varDecl arrow exp -> r EPi `a` f varDecl `a` f arrow `a` f exp EProj exp aIdent -> r EProj `a` f exp `a` f aIdent ESig fieldDecls -> r ESig `a` P.foldr (\ x z -> r (:) `a` f x `a` z) (r []) fieldDecls EStr bindings -> r EStr `a` P.foldr (\ x z -> r (:) `a` f x `a` z) (r []) bindings ESum constructors -> r ESum `a` P.foldr (\ x z -> r (:) `a` f x `a` z) (r []) constructors EVar aIdent -> r EVar `a` f aIdent TDecl varDecl -> r TDecl `a` f varDecl TExp exp -> r TExp `a` f exp VDecl bounds exp -> r VDecl `a` P.foldr (\ x z -> r (:) `a` f x `a` z) (r []) bounds `a` f exp BHide aIdent -> r BHide `a` f aIdent BVar aIdent -> r BVar `a` f aIdent FDecl aIdent exp -> r FDecl `a` f aIdent `a` f exp BranchCon aIdent aIdents exp -> r BranchCon `a` f aIdent `a` P.foldr (\ x z -> r (:) `a` f x `a` z) (r []) aIdents `a` f exp BranchInf aIdent1 infix_ aIdent2 exp -> r BranchInf `a` f aIdent1 `a` f infix_ `a` f aIdent2 `a` f exp BranchVar aIdent exp -> r BranchVar `a` f aIdent `a` f exp Cnstr aIdent typings -> r Cnstr `a` f aIdent `a` P.foldr (\ x z -> r (:) `a` f x `a` z) (r []) typings ICnstr aIdent typings exps -> r ICnstr `a` f aIdent `a` P.foldr (\ x z -> r (:) `a` f x `a` z) (r []) typings `a` P.foldr (\ x z -> r (:) `a` f x `a` z) (r []) exps Bind aIdent exp -> r Bind `a` f aIdent `a` f exp PackageDef decls -> r PackageDef `a` P.foldr (\ x z -> r (:) `a` f x `a` z) (r []) decls PackageInst exp -> r PackageInst `a` f exp OArg defAttrs aIdent -> r OArg `a` P.foldr (\ x z -> r (:) `a` f x `a` z) (r []) defAttrs `a` f aIdent OArgD defAttrs aIdent exp -> r OArgD `a` P.foldr (\ x z -> r (:) `a` f x `a` z) (r []) defAttrs `a` f aIdent `a` f exp OArgT defAttrs aIdent exp -> r OArgT `a` P.foldr (\ x z -> r (:) `a` f x `a` z) (r []) defAttrs `a` f aIdent `a` f exp OArgTD defAttrs aIdent exp1 exp2 -> r OArgTD `a` P.foldr (\ x z -> r (:) `a` f x `a` z) (r []) defAttrs `a` f aIdent `a` f exp1 `a` f exp2 F pIdent -> r F `a` f pIdent I infix_ -> r I `a` f infix_ t -> r t instance P.Show (Tree c) where showsPrec n = \case Comment str -> opar . P.showString "Comment" . P.showChar ' ' . P.showsPrec 1 str . cpar Infix str -> opar . P.showString "Infix" . P.showChar ' ' . P.showsPrec 1 str . cpar PIdent str -> opar . P.showString "PIdent" . P.showChar ' ' . P.showsPrec 1 str . cpar DDef defAttrs def -> opar . P.showString "DDef" . P.showChar ' ' . P.showsPrec 1 defAttrs . P.showChar ' ' . P.showsPrec 1 def . cpar DImp import_ -> opar . P.showString "DImp" . P.showChar ' ' . P.showsPrec 1 import_ . cpar Axiom aIdent typings exp -> opar . P.showString "Axiom" . P.showChar ' ' . P.showsPrec 1 aIdent . P.showChar ' ' . P.showsPrec 1 typings . P.showChar ' ' . P.showsPrec 1 exp . cpar Binding aIdent exp -> opar . P.showString "Binding" . P.showChar ' ' . P.showsPrec 1 aIdent . P.showChar ' ' . P.showsPrec 1 exp . cpar Commt comment -> opar . P.showString "Commt" . P.showChar ' ' . P.showsPrec 1 comment . cpar Data aIdent typings constructors -> opar . P.showString "Data" . P.showChar ' ' . P.showsPrec 1 aIdent . P.showChar ' ' . P.showsPrec 1 typings . P.showChar ' ' . P.showsPrec 1 constructors . cpar Mutual defs -> opar . P.showString "Mutual" . P.showChar ' ' . P.showsPrec 1 defs . cpar Open exp openArgs -> opar . P.showString "Open" . P.showChar ' ' . P.showsPrec 1 exp . P.showChar ' ' . P.showsPrec 1 openArgs . cpar Package aIdent typings packageBody -> opar . P.showString "Package" . P.showChar ' ' . P.showsPrec 1 aIdent . P.showChar ' ' . P.showsPrec 1 typings . P.showChar ' ' . P.showsPrec 1 packageBody . cpar Type aIdent typings exp -> opar . P.showString "Type" . P.showChar ' ' . P.showsPrec 1 aIdent . P.showChar ' ' . P.showsPrec 1 typings . P.showChar ' ' . P.showsPrec 1 exp . cpar Value aIdent varDecls exp1 exp2 -> opar . P.showString "Value" . P.showChar ' ' . P.showsPrec 1 aIdent . P.showChar ' ' . P.showsPrec 1 varDecls . P.showChar ' ' . P.showsPrec 1 exp1 . P.showChar ' ' . P.showsPrec 1 exp2 . cpar EAbs varDecl arrow exp -> opar . P.showString "EAbs" . P.showChar ' ' . P.showsPrec 1 varDecl . P.showChar ' ' . P.showsPrec 1 arrow . P.showChar ' ' . P.showsPrec 1 exp . cpar EAbsUnt aIdents arrow exp -> opar . P.showString "EAbsUnt" . P.showChar ' ' . P.showsPrec 1 aIdents . P.showChar ' ' . P.showsPrec 1 arrow . P.showChar ' ' . P.showsPrec 1 exp . cpar EApp exp1 exp2 -> opar . P.showString "EApp" . P.showChar ' ' . P.showsPrec 1 exp1 . P.showChar ' ' . P.showsPrec 1 exp2 . cpar ECase exp branchs -> opar . P.showString "ECase" . P.showChar ' ' . P.showsPrec 1 exp . P.showChar ' ' . P.showsPrec 1 branchs . cpar EChar c -> opar . P.showString "EChar" . P.showChar ' ' . P.showsPrec 1 c . cpar ECommL comment exp -> opar . P.showString "ECommL" . P.showChar ' ' . P.showsPrec 1 comment . P.showChar ' ' . P.showsPrec 1 exp . cpar ECommR exp comment -> opar . P.showString "ECommR" . P.showChar ' ' . P.showsPrec 1 exp . P.showChar ' ' . P.showsPrec 1 comment . cpar ECon aIdent -> opar . P.showString "ECon" . P.showChar ' ' . P.showsPrec 1 aIdent . cpar EConst aIdent -> opar . P.showString "EConst" . P.showChar ' ' . P.showsPrec 1 aIdent . cpar EDouble d -> opar . P.showString "EDouble" . P.showChar ' ' . P.showsPrec 1 d . cpar EFun exp1 arrow exp2 -> opar . P.showString "EFun" . P.showChar ' ' . P.showsPrec 1 exp1 . P.showChar ' ' . P.showsPrec 1 arrow . P.showChar ' ' . P.showsPrec 1 exp2 . cpar EIData varDecls indConstructors -> opar . P.showString "EIData" . P.showChar ' ' . P.showsPrec 1 varDecls . P.showChar ' ' . P.showsPrec 1 indConstructors . cpar EInfix exp1 infix_ exp2 -> opar . P.showString "EInfix" . P.showChar ' ' . P.showsPrec 1 exp1 . P.showChar ' ' . P.showsPrec 1 infix_ . P.showChar ' ' . P.showsPrec 1 exp2 . cpar EInt n -> opar . P.showString "EInt" . P.showChar ' ' . P.showsPrec 1 n . cpar ELet decls exp -> opar . P.showString "ELet" . P.showChar ' ' . P.showsPrec 1 decls . P.showChar ' ' . P.showsPrec 1 exp . cpar EMeta -> P.showString "EMeta" EMetaN n -> opar . P.showString "EMetaN" . P.showChar ' ' . P.showsPrec 1 n . cpar EMetaU -> P.showString "EMetaU" EOpen exp1 openArgs exp2 -> opar . P.showString "EOpen" . P.showChar ' ' . P.showsPrec 1 exp1 . P.showChar ' ' . P.showsPrec 1 openArgs . P.showChar ' ' . P.showsPrec 1 exp2 . cpar EPi varDecl arrow exp -> opar . P.showString "EPi" . P.showChar ' ' . P.showsPrec 1 varDecl . P.showChar ' ' . P.showsPrec 1 arrow . P.showChar ' ' . P.showsPrec 1 exp . cpar EProj exp aIdent -> opar . P.showString "EProj" . P.showChar ' ' . P.showsPrec 1 exp . P.showChar ' ' . P.showsPrec 1 aIdent . cpar ESet -> P.showString "ESet" ESig fieldDecls -> opar . P.showString "ESig" . P.showChar ' ' . P.showsPrec 1 fieldDecls . cpar EStar n -> opar . P.showString "EStar" . P.showChar ' ' . P.showsPrec 1 n . cpar EStr bindings -> opar . P.showString "EStr" . P.showChar ' ' . P.showsPrec 1 bindings . cpar EString str -> opar . P.showString "EString" . P.showChar ' ' . P.showsPrec 1 str . cpar ESum constructors -> opar . P.showString "ESum" . P.showChar ' ' . P.showsPrec 1 constructors . cpar EType -> P.showString "EType" EVar aIdent -> opar . P.showString "EVar" . P.showChar ' ' . P.showsPrec 1 aIdent . cpar AHide -> P.showString "AHide" AShow -> P.showString "AShow" TDecl varDecl -> opar . P.showString "TDecl" . P.showChar ' ' . P.showsPrec 1 varDecl . cpar TExp exp -> opar . P.showString "TExp" . P.showChar ' ' . P.showsPrec 1 exp . cpar VDecl bounds exp -> opar . P.showString "VDecl" . P.showChar ' ' . P.showsPrec 1 bounds . P.showChar ' ' . P.showsPrec 1 exp . cpar BHide aIdent -> opar . P.showString "BHide" . P.showChar ' ' . P.showsPrec 1 aIdent . cpar BVar aIdent -> opar . P.showString "BVar" . P.showChar ' ' . P.showsPrec 1 aIdent . cpar FDecl aIdent exp -> opar . P.showString "FDecl" . P.showChar ' ' . P.showsPrec 1 aIdent . P.showChar ' ' . P.showsPrec 1 exp . cpar BranchCon aIdent aIdents exp -> opar . P.showString "BranchCon" . P.showChar ' ' . P.showsPrec 1 aIdent . P.showChar ' ' . P.showsPrec 1 aIdents . P.showChar ' ' . P.showsPrec 1 exp . cpar BranchInf aIdent1 infix_ aIdent2 exp -> opar . P.showString "BranchInf" . P.showChar ' ' . P.showsPrec 1 aIdent1 . P.showChar ' ' . P.showsPrec 1 infix_ . P.showChar ' ' . P.showsPrec 1 aIdent2 . P.showChar ' ' . P.showsPrec 1 exp . cpar BranchVar aIdent exp -> opar . P.showString "BranchVar" . P.showChar ' ' . P.showsPrec 1 aIdent . P.showChar ' ' . P.showsPrec 1 exp . cpar Cnstr aIdent typings -> opar . P.showString "Cnstr" . P.showChar ' ' . P.showsPrec 1 aIdent . P.showChar ' ' . P.showsPrec 1 typings . cpar ICnstr aIdent typings exps -> opar . P.showString "ICnstr" . P.showChar ' ' . P.showsPrec 1 aIdent . P.showChar ' ' . P.showsPrec 1 typings . P.showChar ' ' . P.showsPrec 1 exps . cpar Bind aIdent exp -> opar . P.showString "Bind" . P.showChar ' ' . P.showsPrec 1 aIdent . P.showChar ' ' . P.showsPrec 1 exp . cpar PackageDef decls -> opar . P.showString "PackageDef" . P.showChar ' ' . P.showsPrec 1 decls . cpar PackageInst exp -> opar . P.showString "PackageInst" . P.showChar ' ' . P.showsPrec 1 exp . cpar OArg defAttrs aIdent -> opar . P.showString "OArg" . P.showChar ' ' . P.showsPrec 1 defAttrs . P.showChar ' ' . P.showsPrec 1 aIdent . cpar OArgD defAttrs aIdent exp -> opar . P.showString "OArgD" . P.showChar ' ' . P.showsPrec 1 defAttrs . P.showChar ' ' . P.showsPrec 1 aIdent . P.showChar ' ' . P.showsPrec 1 exp . cpar OArgT defAttrs aIdent exp -> opar . P.showString "OArgT" . P.showChar ' ' . P.showsPrec 1 defAttrs . P.showChar ' ' . P.showsPrec 1 aIdent . P.showChar ' ' . P.showsPrec 1 exp . cpar OArgTD defAttrs aIdent exp1 exp2 -> opar . P.showString "OArgTD" . P.showChar ' ' . P.showsPrec 1 defAttrs . P.showChar ' ' . P.showsPrec 1 aIdent . P.showChar ' ' . P.showsPrec 1 exp1 . P.showChar ' ' . P.showsPrec 1 exp2 . cpar Abstract -> P.showString "Abstract" Concrete -> P.showString "Concrete" Private -> P.showString "Private" Public -> P.showString "Public" Import str -> opar . P.showString "Import" . P.showChar ' ' . P.showsPrec 1 str . cpar F pIdent -> opar . P.showString "F" . P.showChar ' ' . P.showsPrec 1 pIdent . cpar I infix_ -> opar . P.showString "I" . P.showChar ' ' . P.showsPrec 1 infix_ . cpar where opar = if n > 0 then P.showChar '(' else P.id cpar = if n > 0 then P.showChar ')' else P.id instance P.Eq (Tree c) where (==) = johnMajorEq instance P.Ord (Tree c) where compare x y = P.compare (index x) (index y) `P.mappend` compareSame x y index :: Tree c -> P.Int index (DDef _ _) = 1 index (DImp _) = 2 index (Axiom _ _ _) = 3 index (Binding _ _) = 4 index (Commt _) = 5 index (Data _ _ _) = 6 index (Mutual _) = 7 index (Open _ _) = 8 index (Package _ _ _) = 9 index (Type _ _ _) = 10 index (Value _ _ _ _) = 11 index (EAbs _ _ _) = 12 index (EAbsUnt _ _ _) = 13 index (EApp _ _) = 14 index (ECase _ _) = 15 index (EChar _) = 16 index (ECommL _ _) = 17 index (ECommR _ _) = 18 index (ECon _) = 19 index (EConst _) = 20 index (EDouble _) = 21 index (EFun _ _ _) = 22 index (EIData _ _) = 23 index (EInfix _ _ _) = 24 index (EInt _) = 25 index (ELet _ _) = 26 index (EMeta ) = 27 index (EMetaN _) = 28 index (EMetaU ) = 29 index (EOpen _ _ _) = 30 index (EPi _ _ _) = 31 index (EProj _ _) = 32 index (ESet ) = 33 index (ESig _) = 34 index (EStar _) = 35 index (EStr _) = 36 index (EString _) = 37 index (ESum _) = 38 index (EType ) = 39 index (EVar _) = 40 index (AHide ) = 41 index (AShow ) = 42 index (TDecl _) = 43 index (TExp _) = 44 index (VDecl _ _) = 45 index (BHide _) = 46 index (BVar _) = 47 index (FDecl _ _) = 48 index (BranchCon _ _ _) = 49 index (BranchInf _ _ _ _) = 50 index (BranchVar _ _) = 51 index (Cnstr _ _) = 52 index (ICnstr _ _ _) = 53 index (Bind _ _) = 54 index (PackageDef _) = 55 index (PackageInst _) = 56 index (OArg _ _) = 57 index (OArgD _ _ _) = 58 index (OArgT _ _ _) = 59 index (OArgTD _ _ _ _) = 60 index (Abstract ) = 61 index (Concrete ) = 62 index (Private ) = 63 index (Public ) = 64 index (Import _) = 65 index (F _) = 66 index (I _) = 67 index (Comment _) = 68 index (Infix _) = 69 index (PIdent _) = 70 johnMajorEq :: Tree a -> Tree b -> P.Bool johnMajorEq (DDef defAttrs def) (DDef defAttrs_ def_) = defAttrs == defAttrs_ && def == def_ johnMajorEq (DImp import_) (DImp import__) = import_ == import__ johnMajorEq (Axiom aIdent typings exp) (Axiom aIdent_ typings_ exp_) = aIdent == aIdent_ && typings == typings_ && exp == exp_ johnMajorEq (Binding aIdent exp) (Binding aIdent_ exp_) = aIdent == aIdent_ && exp == exp_ johnMajorEq (Commt comment) (Commt comment_) = comment == comment_ johnMajorEq (Data aIdent typings constructors) (Data aIdent_ typings_ constructors_) = aIdent == aIdent_ && typings == typings_ && constructors == constructors_ johnMajorEq (Mutual defs) (Mutual defs_) = defs == defs_ johnMajorEq (Open exp openArgs) (Open exp_ openArgs_) = exp == exp_ && openArgs == openArgs_ johnMajorEq (Package aIdent typings packageBody) (Package aIdent_ typings_ packageBody_) = aIdent == aIdent_ && typings == typings_ && packageBody == packageBody_ johnMajorEq (Type aIdent typings exp) (Type aIdent_ typings_ exp_) = aIdent == aIdent_ && typings == typings_ && exp == exp_ johnMajorEq (Value aIdent varDecls exp1 exp2) (Value aIdent_ varDecls_ exp1_ exp2_) = aIdent == aIdent_ && varDecls == varDecls_ && exp1 == exp1_ && exp2 == exp2_ johnMajorEq (EAbs varDecl arrow exp) (EAbs varDecl_ arrow_ exp_) = varDecl == varDecl_ && arrow == arrow_ && exp == exp_ johnMajorEq (EAbsUnt aIdents arrow exp) (EAbsUnt aIdents_ arrow_ exp_) = aIdents == aIdents_ && arrow == arrow_ && exp == exp_ johnMajorEq (EApp exp1 exp2) (EApp exp1_ exp2_) = exp1 == exp1_ && exp2 == exp2_ johnMajorEq (ECase exp branchs) (ECase exp_ branchs_) = exp == exp_ && branchs == branchs_ johnMajorEq (EChar c) (EChar c_) = c == c_ johnMajorEq (ECommL comment exp) (ECommL comment_ exp_) = comment == comment_ && exp == exp_ johnMajorEq (ECommR exp comment) (ECommR exp_ comment_) = exp == exp_ && comment == comment_ johnMajorEq (ECon aIdent) (ECon aIdent_) = aIdent == aIdent_ johnMajorEq (EConst aIdent) (EConst aIdent_) = aIdent == aIdent_ johnMajorEq (EDouble d) (EDouble d_) = d == d_ johnMajorEq (EFun exp1 arrow exp2) (EFun exp1_ arrow_ exp2_) = exp1 == exp1_ && arrow == arrow_ && exp2 == exp2_ johnMajorEq (EIData varDecls indConstructors) (EIData varDecls_ indConstructors_) = varDecls == varDecls_ && indConstructors == indConstructors_ johnMajorEq (EInfix exp1 infix_ exp2) (EInfix exp1_ infix__ exp2_) = exp1 == exp1_ && infix_ == infix__ && exp2 == exp2_ johnMajorEq (EInt n) (EInt n_) = n == n_ johnMajorEq (ELet decls exp) (ELet decls_ exp_) = decls == decls_ && exp == exp_ johnMajorEq EMeta EMeta = P.True johnMajorEq (EMetaN n) (EMetaN n_) = n == n_ johnMajorEq EMetaU EMetaU = P.True johnMajorEq (EOpen exp1 openArgs exp2) (EOpen exp1_ openArgs_ exp2_) = exp1 == exp1_ && openArgs == openArgs_ && exp2 == exp2_ johnMajorEq (EPi varDecl arrow exp) (EPi varDecl_ arrow_ exp_) = varDecl == varDecl_ && arrow == arrow_ && exp == exp_ johnMajorEq (EProj exp aIdent) (EProj exp_ aIdent_) = exp == exp_ && aIdent == aIdent_ johnMajorEq ESet ESet = P.True johnMajorEq (ESig fieldDecls) (ESig fieldDecls_) = fieldDecls == fieldDecls_ johnMajorEq (EStar n) (EStar n_) = n == n_ johnMajorEq (EStr bindings) (EStr bindings_) = bindings == bindings_ johnMajorEq (EString str) (EString str_) = str == str_ johnMajorEq (ESum constructors) (ESum constructors_) = constructors == constructors_ johnMajorEq EType EType = P.True johnMajorEq (EVar aIdent) (EVar aIdent_) = aIdent == aIdent_ johnMajorEq AHide AHide = P.True johnMajorEq AShow AShow = P.True johnMajorEq (TDecl varDecl) (TDecl varDecl_) = varDecl == varDecl_ johnMajorEq (TExp exp) (TExp exp_) = exp == exp_ johnMajorEq (VDecl bounds exp) (VDecl bounds_ exp_) = bounds == bounds_ && exp == exp_ johnMajorEq (BHide aIdent) (BHide aIdent_) = aIdent == aIdent_ johnMajorEq (BVar aIdent) (BVar aIdent_) = aIdent == aIdent_ johnMajorEq (FDecl aIdent exp) (FDecl aIdent_ exp_) = aIdent == aIdent_ && exp == exp_ johnMajorEq (BranchCon aIdent aIdents exp) (BranchCon aIdent_ aIdents_ exp_) = aIdent == aIdent_ && aIdents == aIdents_ && exp == exp_ johnMajorEq (BranchInf aIdent1 infix_ aIdent2 exp) (BranchInf aIdent1_ infix__ aIdent2_ exp_) = aIdent1 == aIdent1_ && infix_ == infix__ && aIdent2 == aIdent2_ && exp == exp_ johnMajorEq (BranchVar aIdent exp) (BranchVar aIdent_ exp_) = aIdent == aIdent_ && exp == exp_ johnMajorEq (Cnstr aIdent typings) (Cnstr aIdent_ typings_) = aIdent == aIdent_ && typings == typings_ johnMajorEq (ICnstr aIdent typings exps) (ICnstr aIdent_ typings_ exps_) = aIdent == aIdent_ && typings == typings_ && exps == exps_ johnMajorEq (Bind aIdent exp) (Bind aIdent_ exp_) = aIdent == aIdent_ && exp == exp_ johnMajorEq (PackageDef decls) (PackageDef decls_) = decls == decls_ johnMajorEq (PackageInst exp) (PackageInst exp_) = exp == exp_ johnMajorEq (OArg defAttrs aIdent) (OArg defAttrs_ aIdent_) = defAttrs == defAttrs_ && aIdent == aIdent_ johnMajorEq (OArgD defAttrs aIdent exp) (OArgD defAttrs_ aIdent_ exp_) = defAttrs == defAttrs_ && aIdent == aIdent_ && exp == exp_ johnMajorEq (OArgT defAttrs aIdent exp) (OArgT defAttrs_ aIdent_ exp_) = defAttrs == defAttrs_ && aIdent == aIdent_ && exp == exp_ johnMajorEq (OArgTD defAttrs aIdent exp1 exp2) (OArgTD defAttrs_ aIdent_ exp1_ exp2_) = defAttrs == defAttrs_ && aIdent == aIdent_ && exp1 == exp1_ && exp2 == exp2_ johnMajorEq Abstract Abstract = P.True johnMajorEq Concrete Concrete = P.True johnMajorEq Private Private = P.True johnMajorEq Public Public = P.True johnMajorEq (Import str) (Import str_) = str == str_ johnMajorEq (F pIdent) (F pIdent_) = pIdent == pIdent_ johnMajorEq (I infix_) (I infix__) = infix_ == infix__ johnMajorEq (Comment str) (Comment str_) = str == str_ johnMajorEq (Infix str) (Infix str_) = str == str_ johnMajorEq (PIdent str) (PIdent str_) = str == str_ johnMajorEq _ _ = P.False compareSame :: Tree c -> Tree c -> P.Ordering compareSame (DDef defAttrs def) (DDef defAttrs_ def_) = P.mappend (P.compare defAttrs defAttrs_) (P.compare def def_) compareSame (DImp import_) (DImp import__) = P.compare import_ import__ compareSame (Axiom aIdent typings exp) (Axiom aIdent_ typings_ exp_) = P.mappend (P.compare aIdent aIdent_) (P.mappend (P.compare typings typings_) (P.compare exp exp_)) compareSame (Binding aIdent exp) (Binding aIdent_ exp_) = P.mappend (P.compare aIdent aIdent_) (P.compare exp exp_) compareSame (Commt comment) (Commt comment_) = P.compare comment comment_ compareSame (Data aIdent typings constructors) (Data aIdent_ typings_ constructors_) = P.mappend (P.compare aIdent aIdent_) (P.mappend (P.compare typings typings_) (P.compare constructors constructors_)) compareSame (Mutual defs) (Mutual defs_) = P.compare defs defs_ compareSame (Open exp openArgs) (Open exp_ openArgs_) = P.mappend (P.compare exp exp_) (P.compare openArgs openArgs_) compareSame (Package aIdent typings packageBody) (Package aIdent_ typings_ packageBody_) = P.mappend (P.compare aIdent aIdent_) (P.mappend (P.compare typings typings_) (P.compare packageBody packageBody_)) compareSame (Type aIdent typings exp) (Type aIdent_ typings_ exp_) = P.mappend (P.compare aIdent aIdent_) (P.mappend (P.compare typings typings_) (P.compare exp exp_)) compareSame (Value aIdent varDecls exp1 exp2) (Value aIdent_ varDecls_ exp1_ exp2_) = P.mappend (P.compare aIdent aIdent_) (P.mappend (P.compare varDecls varDecls_) (P.mappend (P.compare exp1 exp1_) (P.compare exp2 exp2_))) compareSame (EAbs varDecl arrow exp) (EAbs varDecl_ arrow_ exp_) = P.mappend (P.compare varDecl varDecl_) (P.mappend (P.compare arrow arrow_) (P.compare exp exp_)) compareSame (EAbsUnt aIdents arrow exp) (EAbsUnt aIdents_ arrow_ exp_) = P.mappend (P.compare aIdents aIdents_) (P.mappend (P.compare arrow arrow_) (P.compare exp exp_)) compareSame (EApp exp1 exp2) (EApp exp1_ exp2_) = P.mappend (P.compare exp1 exp1_) (P.compare exp2 exp2_) compareSame (ECase exp branchs) (ECase exp_ branchs_) = P.mappend (P.compare exp exp_) (P.compare branchs branchs_) compareSame (EChar c) (EChar c_) = P.compare c c_ compareSame (ECommL comment exp) (ECommL comment_ exp_) = P.mappend (P.compare comment comment_) (P.compare exp exp_) compareSame (ECommR exp comment) (ECommR exp_ comment_) = P.mappend (P.compare exp exp_) (P.compare comment comment_) compareSame (ECon aIdent) (ECon aIdent_) = P.compare aIdent aIdent_ compareSame (EConst aIdent) (EConst aIdent_) = P.compare aIdent aIdent_ compareSame (EDouble d) (EDouble d_) = P.compare d d_ compareSame (EFun exp1 arrow exp2) (EFun exp1_ arrow_ exp2_) = P.mappend (P.compare exp1 exp1_) (P.mappend (P.compare arrow arrow_) (P.compare exp2 exp2_)) compareSame (EIData varDecls indConstructors) (EIData varDecls_ indConstructors_) = P.mappend (P.compare varDecls varDecls_) (P.compare indConstructors indConstructors_) compareSame (EInfix exp1 infix_ exp2) (EInfix exp1_ infix__ exp2_) = P.mappend (P.compare exp1 exp1_) (P.mappend (P.compare infix_ infix__) (P.compare exp2 exp2_)) compareSame (EInt n) (EInt n_) = P.compare n n_ compareSame (ELet decls exp) (ELet decls_ exp_) = P.mappend (P.compare decls decls_) (P.compare exp exp_) compareSame EMeta EMeta = P.EQ compareSame (EMetaN n) (EMetaN n_) = P.compare n n_ compareSame EMetaU EMetaU = P.EQ compareSame (EOpen exp1 openArgs exp2) (EOpen exp1_ openArgs_ exp2_) = P.mappend (P.compare exp1 exp1_) (P.mappend (P.compare openArgs openArgs_) (P.compare exp2 exp2_)) compareSame (EPi varDecl arrow exp) (EPi varDecl_ arrow_ exp_) = P.mappend (P.compare varDecl varDecl_) (P.mappend (P.compare arrow arrow_) (P.compare exp exp_)) compareSame (EProj exp aIdent) (EProj exp_ aIdent_) = P.mappend (P.compare exp exp_) (P.compare aIdent aIdent_) compareSame ESet ESet = P.EQ compareSame (ESig fieldDecls) (ESig fieldDecls_) = P.compare fieldDecls fieldDecls_ compareSame (EStar n) (EStar n_) = P.compare n n_ compareSame (EStr bindings) (EStr bindings_) = P.compare bindings bindings_ compareSame (EString str) (EString str_) = P.compare str str_ compareSame (ESum constructors) (ESum constructors_) = P.compare constructors constructors_ compareSame EType EType = P.EQ compareSame (EVar aIdent) (EVar aIdent_) = P.compare aIdent aIdent_ compareSame AHide AHide = P.EQ compareSame AShow AShow = P.EQ compareSame (TDecl varDecl) (TDecl varDecl_) = P.compare varDecl varDecl_ compareSame (TExp exp) (TExp exp_) = P.compare exp exp_ compareSame (VDecl bounds exp) (VDecl bounds_ exp_) = P.mappend (P.compare bounds bounds_) (P.compare exp exp_) compareSame (BHide aIdent) (BHide aIdent_) = P.compare aIdent aIdent_ compareSame (BVar aIdent) (BVar aIdent_) = P.compare aIdent aIdent_ compareSame (FDecl aIdent exp) (FDecl aIdent_ exp_) = P.mappend (P.compare aIdent aIdent_) (P.compare exp exp_) compareSame (BranchCon aIdent aIdents exp) (BranchCon aIdent_ aIdents_ exp_) = P.mappend (P.compare aIdent aIdent_) (P.mappend (P.compare aIdents aIdents_) (P.compare exp exp_)) compareSame (BranchInf aIdent1 infix_ aIdent2 exp) (BranchInf aIdent1_ infix__ aIdent2_ exp_) = P.mappend (P.compare aIdent1 aIdent1_) (P.mappend (P.compare infix_ infix__) (P.mappend (P.compare aIdent2 aIdent2_) (P.compare exp exp_))) compareSame (BranchVar aIdent exp) (BranchVar aIdent_ exp_) = P.mappend (P.compare aIdent aIdent_) (P.compare exp exp_) compareSame (Cnstr aIdent typings) (Cnstr aIdent_ typings_) = P.mappend (P.compare aIdent aIdent_) (P.compare typings typings_) compareSame (ICnstr aIdent typings exps) (ICnstr aIdent_ typings_ exps_) = P.mappend (P.compare aIdent aIdent_) (P.mappend (P.compare typings typings_) (P.compare exps exps_)) compareSame (Bind aIdent exp) (Bind aIdent_ exp_) = P.mappend (P.compare aIdent aIdent_) (P.compare exp exp_) compareSame (PackageDef decls) (PackageDef decls_) = P.compare decls decls_ compareSame (PackageInst exp) (PackageInst exp_) = P.compare exp exp_ compareSame (OArg defAttrs aIdent) (OArg defAttrs_ aIdent_) = P.mappend (P.compare defAttrs defAttrs_) (P.compare aIdent aIdent_) compareSame (OArgD defAttrs aIdent exp) (OArgD defAttrs_ aIdent_ exp_) = P.mappend (P.compare defAttrs defAttrs_) (P.mappend (P.compare aIdent aIdent_) (P.compare exp exp_)) compareSame (OArgT defAttrs aIdent exp) (OArgT defAttrs_ aIdent_ exp_) = P.mappend (P.compare defAttrs defAttrs_) (P.mappend (P.compare aIdent aIdent_) (P.compare exp exp_)) compareSame (OArgTD defAttrs aIdent exp1 exp2) (OArgTD defAttrs_ aIdent_ exp1_ exp2_) = P.mappend (P.compare defAttrs defAttrs_) (P.mappend (P.compare aIdent aIdent_) (P.mappend (P.compare exp1 exp1_) (P.compare exp2 exp2_))) compareSame Abstract Abstract = P.EQ compareSame Concrete Concrete = P.EQ compareSame Private Private = P.EQ compareSame Public Public = P.EQ compareSame (Import str) (Import str_) = P.compare str str_ compareSame (F pIdent) (F pIdent_) = P.compare pIdent pIdent_ compareSame (I infix_) (I infix__) = P.compare infix_ infix__ compareSame (Comment str) (Comment str_) = P.compare str str_ compareSame (Infix str) (Infix str_) = P.compare str str_ compareSame (PIdent str) (PIdent str_) = P.compare str str_ compareSame _ _ = P.error "BNFC error: compareSame"