{-# OPTIONS_GHC -fno-warn-overlapping-patterns #-}
module Language.LBNF.Grammar(Language.LBNF.Grammar.tokens
  , Language.LBNF.Grammar.pGrammar
  , Language.LBNF.Grammar.pDef
  , Language.LBNF.Grammar.pRHS
  , Language.LBNF.Grammar.pItem
  , Language.LBNF.Grammar.pCat
  , Language.LBNF.Grammar.pLabel
  , Language.LBNF.Grammar.pMIdent
  , Language.LBNF.Grammar.pHsTyp
  , Language.LBNF.Grammar.pArg
  , Language.LBNF.Grammar.pExp
  , Language.LBNF.Grammar.pMinimumSize
  , Language.LBNF.Grammar.pReg
  , Language.LBNF.Grammar.qGrammar
  , Language.LBNF.Grammar.qDef
  , Language.LBNF.Grammar.qRHS
  , Language.LBNF.Grammar.qItem
  , Language.LBNF.Grammar.qCat
  , Language.LBNF.Grammar.qLabel
  , Language.LBNF.Grammar.qMIdent
  , Language.LBNF.Grammar.qHsTyp
  , Language.LBNF.Grammar.qArg
  , Language.LBNF.Grammar.qExp
  , Language.LBNF.Grammar.qMinimumSize
  , Language.LBNF.Grammar.qReg
  , Language.LBNF.Grammar.grammar
  , Language.LBNF.Grammar.def
  , Language.LBNF.Grammar.rHS
  , Language.LBNF.Grammar.item
  , Language.LBNF.Grammar.cat
  , Language.LBNF.Grammar.label
  , Language.LBNF.Grammar.mIdent
  , Language.LBNF.Grammar.hsTyp
  , Language.LBNF.Grammar.arg
  , Language.LBNF.Grammar.exp
  , Language.LBNF.Grammar.minimumSize
  , Language.LBNF.Grammar.reg
  , Language.LBNF.Grammar.Grammar(..)
  , Language.LBNF.Grammar.Def(..)
  , Language.LBNF.Grammar.RHS(..)
  , Language.LBNF.Grammar.Item(..)
  , Language.LBNF.Grammar.Cat(..)
  , Language.LBNF.Grammar.Label(..)
  , Language.LBNF.Grammar.MIdent(..)
  , Language.LBNF.Grammar.HsTyp(..)
  , Language.LBNF.Grammar.Arg(..)
  , Language.LBNF.Grammar.Exp(..)
  , Language.LBNF.Grammar.MinimumSize(..)
  , Language.LBNF.Grammar.Reg(..)
  , Language.LBNF.Grammar.Ident(..)) where
import Language.LBNF.Compiletime

data Grammar = Grammar ([Def])
    deriving (Eq, Ord, Show)
data Def = Rule Label Cat RHS
         | Comment String
         | Comments String String
         | Internal Label Cat ([Item])
         | Token Ident Reg
         | PosToken Ident Reg
         | Entryp ([Ident])
         | Separator MinimumSize Cat String
         | Terminator MinimumSize Cat String
         | Coercions Ident Integer
         | Rules Ident ([RHS])
         | Function Ident ([Arg]) Exp
         | External Ident HsTyp
         | AntiQuote String String String
         | Layout ([String])
         | LayoutStop ([String])
         | LayoutTop
    deriving (Eq, Ord, Show)
data RHS = RHS ([Item]) | TRHS Reg
    deriving (Eq, Ord, Show)
data Item = Terminal String | NTerminal Cat
    deriving (Eq, Ord, Show)
data Cat = OptCat Cat | ListCat Cat | IdCat Ident
    deriving (Eq, Ord, Show)
data Label = Id Ident
           | Wild
           | ListE
           | ListCons
           | ListOne
           | Aq MIdent
    deriving (Eq, Ord, Show)
data MIdent = JIdent Ident | NIdent
    deriving (Eq, Ord, Show)
data HsTyp = HsApp HsTyp HsTyp
           | HsCon Ident
           | HsTup ([HsTyp])
           | HsList HsTyp
    deriving (Eq, Ord, Show)
data Arg = Arg Ident
    deriving (Eq, Ord, Show)
data Exp = Cons Exp Exp
         | App Ident ([Exp])
         | Var Ident
         | LitInt Integer
         | LitChar Char
         | LitString String
         | LitDouble Double
         | List ([Exp])
    deriving (Eq, Ord, Show)
data MinimumSize = MNonempty | MEmpty
    deriving (Eq, Ord, Show)
data Reg = RSeq Reg Reg
         | RAlt Reg Reg
         | RMinus Reg Reg
         | RStar Reg
         | RPlus Reg
         | ROpt Reg
         | REps
         | RChar Char
         | RAlts String
         | RSeqs String
         | RDigit
         | RLetter
         | RUpper
         | RLower
         | RAny
    deriving (Eq, Ord, Show)
newtype Ident = Ident String
    deriving (Eq, Ord, Show)
instance Print Ident
    where prt _ (Ident i_0) = doc (showString i_0)
instance Print Grammar
    where prt i_1 x_2 = case x_2 of
                                                  Grammar defs -> prPrec i_1 0 (concatD [prt 0 defs])
instance Print Def
    where prt i_3 x_4 = case x_4 of
                                                  Rule label
                                                       cat
                                                       rhs -> prPrec i_3 0 (concatD [prt 0 label,
                                                                                                                                 doc (showString "."),
                                                                                                                                 prt 0 cat,
                                                                                                                                 doc (showString "::="),
                                                                                                                                 prt 0 rhs])
                                                  Comment str -> prPrec i_3 0 (concatD [doc (showString "comment"),
                                                                                                                                    prt 0 str])
                                                  Comments str0
                                                           str -> prPrec i_3 0 (concatD [doc (showString "comment"),
                                                                                                                                     prt 0 str0,
                                                                                                                                     prt 0 str])
                                                  Internal label
                                                           cat
                                                           items -> prPrec i_3 0 (concatD [doc (showString "internal"),
                                                                                                                                       prt 0 label,
                                                                                                                                       doc (showString "."),
                                                                                                                                       prt 0 cat,
                                                                                                                                       doc (showString "::="),
                                                                                                                                       prt 0 items])
                                                  Token id
                                                        reg -> prPrec i_3 0 (concatD [doc (showString "token"),
                                                                                                                                  prt 0 id,
                                                                                                                                  prt 0 reg])
                                                  PosToken id
                                                           reg -> prPrec i_3 0 (concatD [doc (showString "position"),
                                                                                                                                     doc (showString "token"),
                                                                                                                                     prt 0 id,
                                                                                                                                     prt 0 reg])
                                                  Entryp ids -> prPrec i_3 0 (concatD [doc (showString "entrypoints"),
                                                                                                                                   prt 0 ids])
                                                  Separator minimumsize
                                                            cat
                                                            str -> prPrec i_3 0 (concatD [doc (showString "separator"),
                                                                                                                                      prt 0 minimumsize,
                                                                                                                                      prt 0 cat,
                                                                                                                                      prt 0 str])
                                                  Terminator minimumsize
                                                             cat
                                                             str -> prPrec i_3 0 (concatD [doc (showString "terminator"),
                                                                                                                                       prt 0 minimumsize,
                                                                                                                                       prt 0 cat,
                                                                                                                                       prt 0 str])
                                                  Coercions id
                                                            n -> prPrec i_3 0 (concatD [doc (showString "coercions"),
                                                                                                                                    prt 0 id,
                                                                                                                                    prt 0 n])
                                                  Rules id
                                                        rhss -> prPrec i_3 0 (concatD [doc (showString "rules"),
                                                                                                                                   prt 0 id,
                                                                                                                                   doc (showString "::="),
                                                                                                                                   prt 0 rhss])
                                                  Function id
                                                           args
                                                           exp -> prPrec i_3 0 (concatD [doc (showString "define"),
                                                                                                                                     prt 0 id,
                                                                                                                                     prt 0 args,
                                                                                                                                     doc (showString "="),
                                                                                                                                     prt 0 exp])
                                                  External id
                                                           hstyp -> prPrec i_3 0 (concatD [doc (showString "external"),
                                                                                                                                       prt 0 id,
                                                                                                                                       doc (showString "="),
                                                                                                                                       prt 0 hstyp])
                                                  AntiQuote str0
                                                            str1
                                                            str -> prPrec i_3 0 (concatD [doc (showString "antiquote"),
                                                                                                                                      prt 0 str0,
                                                                                                                                      prt 0 str1,
                                                                                                                                      prt 0 str])
                                                  Layout strs -> prPrec i_3 0 (concatD [doc (showString "layout"),
                                                                                                                                    prt 0 strs])
                                                  LayoutStop strs -> prPrec i_3 0 (concatD [doc (showString "layout"),
                                                                                                                                        doc (showString "stop"),
                                                                                                                                        prt 0 strs])
                                                  LayoutTop -> prPrec i_3 0 (concatD [doc (showString "layout"),
                                                                                                                                  doc (showString "toplevel")])
          prtList es_5 = case es_5 of
                                                   [] -> concatD []
                                                   [x] -> concatD [prt 0 x]
                                                   (:) x
                                                                 xs -> concatD [prt 0 x,
                                                                                                      doc (showString ";"),
                                                                                                      prt 0 xs]
instance Print RHS
    where prt i_6 x_7 = case x_7 of
                                                  RHS items -> prPrec i_6 0 (concatD [prt 0 items])
                                                  TRHS reg -> prPrec i_6 0 (concatD [doc (showString "@"),
                                                                                                                                 prt 0 reg])
          prtList es_8 = case es_8 of
                                                   [x] -> concatD [prt 0 x]
                                                   (:) x
                                                                 xs -> concatD [prt 0 x,
                                                                                                      doc (showString "|"),
                                                                                                      prt 0 xs]
instance Print Item
    where prt i_9 x_10 = case x_10 of
                                                   Terminal str -> prPrec i_9 0 (concatD [prt 0 str])
                                                   NTerminal cat -> prPrec i_9 0 (concatD [prt 0 cat])
          prtList es_11 = case es_11 of
                                                    [] -> concatD []
                                                    (:) x
                                                                  xs -> concatD [prt 0 x,
                                                                                                       prt 0 xs]
instance Print Cat
    where prt i_12 x_13 = case x_13 of
                                                    OptCat cat -> prPrec i_12 0 (concatD [doc (showString "?"),
                                                                                                                                      prt 1 cat])
                                                    ListCat cat -> prPrec i_12 1 (concatD [doc (showString "["),
                                                                                                                                       prt 0 cat,
                                                                                                                                       doc (showString "]")])
                                                    IdCat id -> prPrec i_12 1 (concatD [prt 0 id])
instance Print Label
    where prt i_14 x_15 = case x_15 of
                                                    Id id -> prPrec i_14 0 (concatD [prt 0 id])
                                                    Wild -> prPrec i_14 0 (concatD [doc (showString "_")])
                                                    ListE -> prPrec i_14 0 (concatD [doc (showString "["),
                                                                                                                                 doc (showString "]")])
                                                    ListCons -> prPrec i_14 0 (concatD [doc (showString "("),
                                                                                                                                    doc (showString ":"),
                                                                                                                                    doc (showString ")")])
                                                    ListOne -> prPrec i_14 0 (concatD [doc (showString "("),
                                                                                                                                   doc (showString ":"),
                                                                                                                                   doc (showString "["),
                                                                                                                                   doc (showString "]"),
                                                                                                                                   doc (showString ")")])
                                                    Aq mident -> prPrec i_14 0 (concatD [doc (showString "$"),
                                                                                                                                     prt 0 mident])
instance Print MIdent
    where prt i_16 x_17 = case x_17 of
                                                    JIdent id -> prPrec i_16 0 (concatD [prt 0 id])
                                                    NIdent -> prPrec i_16 0 (concatD [])
instance Print HsTyp
    where prt i_18 x_19 = case x_19 of
                                                    HsApp hstyp0
                                                          hstyp -> prPrec i_18 0 (concatD [prt 0 hstyp0,
                                                                                                                                       prt 1 hstyp])
                                                    HsCon id -> prPrec i_18 1 (concatD [prt 0 id])
                                                    HsTup hstyps -> prPrec i_18 1 (concatD [doc (showString "("),
                                                                                                                                        prt 0 hstyps,
                                                                                                                                        doc (showString ")")])
                                                    HsList hstyp -> prPrec i_18 1 (concatD [doc (showString "["),
                                                                                                                                        prt 0 hstyp,
                                                                                                                                        doc (showString "]")])
          prtList es_20 = case es_20 of
                                                    [x] -> concatD [prt 0 x]
                                                    (:) x
                                                                  xs -> concatD [prt 0 x,
                                                                                                       doc (showString ","),
                                                                                                       prt 0 xs]
instance Print Arg
    where prt i_21 x_22 = case x_22 of
                                                    Arg id -> prPrec i_21 0 (concatD [prt 0 id])
          prtList es_23 = case es_23 of
                                                    [] -> concatD []
                                                    (:) x
                                                                  xs -> concatD [prt 0 x,
                                                                                                       prt 0 xs]
instance Print Exp
    where prt i_24 x_25 = case x_25 of
                                                    Cons exp0
                                                         exp -> prPrec i_24 0 (concatD [prt 1 exp0,
                                                                                                                                    doc (showString ":"),
                                                                                                                                    prt 0 exp])
                                                    App id
                                                        exps -> prPrec i_24 1 (concatD [prt 0 id,
                                                                                                                                    prt 2 exps])
                                                    Var id -> prPrec i_24 2 (concatD [prt 0 id])
                                                    LitInt n -> prPrec i_24 2 (concatD [prt 0 n])
                                                    LitChar c -> prPrec i_24 2 (concatD [prt 0 c])
                                                    LitString str -> prPrec i_24 2 (concatD [prt 0 str])
                                                    LitDouble d -> prPrec i_24 2 (concatD [prt 0 d])
                                                    List exps -> prPrec i_24 2 (concatD [doc (showString "["),
                                                                                                                                     prt 0 exps,
                                                                                                                                     doc (showString "]")])
          prtList es_26 = case es_26 of
                                                    [] -> concatD []
                                                    [x] -> concatD [prt 2 x]
                                                    [x] -> concatD [prt 0 x]
                                                    (:) x
                                                                  xs -> concatD [prt 2 x,
                                                                                                       prt 2 xs]
                                                    (:) x
                                                                  xs -> concatD [prt 0 x,
                                                                                                       doc (showString ","),
                                                                                                       prt 0 xs]
instance Print MinimumSize
    where prt i_27 x_28 = case x_28 of
                                                    MNonempty -> prPrec i_27 0 (concatD [doc (showString "nonempty")])
                                                    MEmpty -> prPrec i_27 0 (concatD [])
instance Print Reg
    where prt i_29 x_30 = case x_30 of
                                                    RSeq reg0
                                                         reg -> prPrec i_29 2 (concatD [prt 2 reg0,
                                                                                                                                    prt 3 reg])
                                                    RAlt reg0
                                                         reg -> prPrec i_29 1 (concatD [prt 1 reg0,
                                                                                                                                    doc (showString "|"),
                                                                                                                                    prt 2 reg])
                                                    RMinus reg0
                                                           reg -> prPrec i_29 1 (concatD [prt 2 reg0,
                                                                                                                                      doc (showString "-"),
                                                                                                                                      prt 2 reg])
                                                    RStar reg -> prPrec i_29 3 (concatD [prt 3 reg,
                                                                                                                                     doc (showString "*")])
                                                    RPlus reg -> prPrec i_29 3 (concatD [prt 3 reg,
                                                                                                                                     doc (showString "+")])
                                                    ROpt reg -> prPrec i_29 3 (concatD [prt 3 reg,
                                                                                                                                    doc (showString "?")])
                                                    REps -> prPrec i_29 3 (concatD [doc (showString "eps")])
                                                    RChar c -> prPrec i_29 3 (concatD [prt 0 c])
                                                    RAlts str -> prPrec i_29 3 (concatD [doc (showString "["),
                                                                                                                                     prt 0 str,
                                                                                                                                     doc (showString "]")])
                                                    RSeqs str -> prPrec i_29 3 (concatD [doc (showString "{"),
                                                                                                                                     prt 0 str,
                                                                                                                                     doc (showString "}")])
                                                    RDigit -> prPrec i_29 3 (concatD [doc (showString "digit")])
                                                    RLetter -> prPrec i_29 3 (concatD [doc (showString "letter")])
                                                    RUpper -> prPrec i_29 3 (concatD [doc (showString "upper")])
                                                    RLower -> prPrec i_29 3 (concatD [doc (showString "lower")])
                                                    RAny -> prPrec i_29 3 (concatD [doc (showString "char")])
grammar = Language.LBNF.Compiletime.parseToQuoter (qGrammar . tokens)
def = Language.LBNF.Compiletime.parseToQuoter (qDef . tokens)
rHS = Language.LBNF.Compiletime.parseToQuoter (qRHS . tokens)
item = Language.LBNF.Compiletime.parseToQuoter (qItem . tokens)
cat = Language.LBNF.Compiletime.parseToQuoter (qCat . tokens)
label = Language.LBNF.Compiletime.parseToQuoter (qLabel . tokens)
mIdent = Language.LBNF.Compiletime.parseToQuoter (qMIdent . tokens)
hsTyp = Language.LBNF.Compiletime.parseToQuoter (qHsTyp . tokens)
arg = Language.LBNF.Compiletime.parseToQuoter (qArg . tokens)
exp = Language.LBNF.Compiletime.parseToQuoter (qExp . tokens)
minimumSize = Language.LBNF.Compiletime.parseToQuoter (qMinimumSize . tokens)
reg = Language.LBNF.Compiletime.parseToQuoter (qReg . tokens)
alex_base :: Array Int Int
alex_base = listArray (0,30) [1,56,57,23,24,0,68,69,25,26,27,66,0,15,13,156,364,0,279,487,213,0,41,157,211,53,231,33,242,285,439]

alex_table :: Array Int Int
alex_table = listArray (0,742) [0,-1,-1,-1,-1,-1,-1,-1,-1,-1,11,11,11,11,11,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,11,-1,18,-1,12,-1,-1,23,12,12,12,12,12,3,12,-1,25,25,25,25,25,25,25,25,25,25,13,12,-1,12,-1,12,12,-1,-1,1,7,7,7,8,14,12,11,11,11,11,11,21,27,27,27,27,27,27,27,27,27,27,0,12,-1,12,-1,12,-1,11,28,0,25,25,25,25,25,25,25,25,25,25,0,0,7,6,0,0,0,0,0,0,0,0,0,10,12,12,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,4,5,16,-1,0,0,0,0,0,0,0,16,16,16,16,16,16,16,16,16,16,0,0,-1,0,0,0,0,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,19,-1,24,22,16,19,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,26,26,26,26,26,26,26,26,26,26,-1,26,26,26,26,26,26,26,26,26,26,0,0,0,22,0,19,0,0,0,0,0,0,0,17,0,0,0,0,0,0,0,22,0,19,0,0,0,22,0,19,30,0,29,27,27,27,27,27,27,27,27,27,27,0,0,0,0,0,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,20,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,0,0,0,0,0,0,0,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,0,0,0,0,16,0,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,27,27,27,27,27,27,27,27,27,27,-1,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,17,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,20,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,16,0,16,16,16,16,16,16,16,16,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0]

alex_check :: Array Int Int
alex_check = listArray (0,742) [-1,0,1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20,21,22,23,24,25,26,27,28,29,30,31,32,33,34,35,36,37,38,39,40,41,42,43,44,45,46,47,48,49,50,51,52,53,54,55,56,57,58,59,60,61,62,63,64,10,10,45,45,45,45,45,58,61,9,10,11,12,13,39,48,49,50,51,52,53,54,55,56,57,-1,91,92,93,94,95,96,32,46,-1,48,49,50,51,52,53,54,55,56,57,-1,-1,45,45,-1,-1,-1,-1,-1,-1,-1,-1,-1,123,124,125,126,127,128,129,130,131,132,133,134,135,136,137,138,139,140,141,142,143,144,145,146,147,148,149,150,151,152,153,154,155,156,157,158,159,160,161,162,163,164,165,166,167,168,169,170,171,172,173,174,175,176,177,178,179,180,181,182,183,184,185,186,187,188,189,190,191,125,125,39,39,-1,-1,-1,-1,-1,-1,-1,48,49,50,51,52,53,54,55,56,57,-1,-1,215,-1,-1,-1,-1,65,66,67,68,69,70,71,72,73,74,75,76,77,78,79,80,81,82,83,84,85,86,87,88,89,90,34,247,92,39,95,39,97,98,99,100,101,102,103,104,105,106,107,108,109,110,111,112,113,114,115,116,117,118,119,120,121,122,48,49,50,51,52,53,54,55,56,57,10,48,49,50,51,52,53,54,55,56,57,-1,-1,-1,92,-1,92,-1,-1,-1,-1,-1,-1,-1,34,-1,-1,-1,-1,-1,-1,-1,110,-1,110,-1,-1,-1,116,-1,116,45,-1,101,48,49,50,51,52,53,54,55,56,57,-1,-1,-1,-1,-1,192,193,194,195,196,197,198,199,200,201,202,203,204,205,206,207,208,209,210,211,212,213,214,92,216,217,218,219,220,221,222,223,224,225,226,227,228,229,230,231,232,233,234,235,236,237,238,239,240,241,242,243,244,245,246,39,248,249,250,251,252,253,254,255,48,49,50,51,52,53,54,55,56,57,-1,-1,-1,-1,-1,-1,-1,65,66,67,68,69,70,71,72,73,74,75,76,77,78,79,80,81,82,83,84,85,86,87,88,89,90,-1,-1,-1,-1,95,-1,97,98,99,100,101,102,103,104,105,106,107,108,109,110,111,112,113,114,115,116,117,118,119,120,121,122,48,49,50,51,52,53,54,55,56,57,10,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,34,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,192,193,194,195,196,197,198,199,200,201,202,203,204,205,206,207,208,209,210,211,212,213,214,92,216,217,218,219,220,221,222,223,224,225,226,227,228,229,230,231,232,233,234,235,236,237,238,239,240,241,242,243,244,245,246,-1,248,249,250,251,252,253,254,255,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1,-1]

alex_deflt :: Array Int Int
alex_deflt = listArray (0,30) [15,2,2,-1,9,-1,9,9,9,9,-1,-1,-1,-1,-1,-1,-1,-1,19,19,-1,-1,-1,22,-1,-1,-1,-1,-1,-1,-1]

alex_accept = listArray (0::Int,30) [[],[(AlexAccSkip)],[(AlexAccSkip)],[(AlexAcc (alex_action_3))],[(AlexAccSkip)],[(AlexAccSkip)],[],[],[],[],[(AlexAcc (alex_action_3))],[(AlexAccSkip)],[(AlexAcc (alex_action_3))],[(AlexAcc (alex_action_3))],[],[(AlexAcc (alex_action_4))],[(AlexAcc (alex_action_4))],[(AlexAcc (alex_action_5))],[],[],[],[(AlexAcc (alex_action_6))],[],[],[],[(AlexAcc (alex_action_7))],[(AlexAcc (alex_action_8))],[(AlexAcc (alex_action_8))],[],[],[]]
alex_action_3 =  tok (\p s -> PT p (TS $ share s)) 
alex_action_4 =  tok (\p s -> PT p (eitherResIdent (TV . share) s)) 
alex_action_5 =  tok (\p s -> PT p (TL $ share $ unescapeInitTail s)) 
alex_action_6 =  tok (\p s -> PT p (TC $ share s))  
alex_action_7 =  tok (\p s -> PT p (TI $ share s))    
alex_action_8 =  tok (\p s -> PT p (TD $ share s)) 


tok f p s = f p s

share :: String -> String
share = id

data Tok =
   TS !String     -- reserved words and symbols
 | TL !String     -- string literals
 | TI !String     -- integer literals
 | TV !String     -- identifiers
 | TD !String     -- double precision float literals
 | TC !String     -- character literals

 deriving (Eq,Show,Ord)

data Token = 
   PT  Posn Tok
 | Err Posn
  deriving (Eq,Show,Ord)

tokenPos (PT (Pn _ l _) _ :_) = "line " ++ show l
tokenPos (Err (Pn _ l _) :_) = "line " ++ show l
tokenPos _ = "end of file"

posLineCol (Pn _ l c) = (l,c)
mkPosToken t@(PT p _) = (posLineCol p, prToken t)

prToken t = case t of
  PT _ (TS s) -> s
  PT _ (TI s) -> s
  PT _ (TV s) -> s
  PT _ (TD s) -> s
  PT _ (TC s) -> s

  _ -> show t

data BTree = N | B String Tok BTree BTree deriving (Show)

eitherResIdent :: (String -> Tok) -> String -> Tok
eitherResIdent tv s = treeFind resWords
  where
  treeFind N = tv s
  treeFind (B a t left right) | s < a  = treeFind left
                              | s > a  = treeFind right
                              | s == a = t

resWords = b "letter" (b "digit" (b "coercions" (b "char" (b "antiquote" N N) N) (b "define" (b "comment" N N) N)) (b "external" (b "eps" (b "entrypoints" N N) N) (b "layout" (b "internal" N N) N))) (b "stop" (b "position" (b "nonempty" (b "lower" N N) N) (b "separator" (b "rules" N N) N)) (b "toplevel" (b "token" (b "terminator" N N) N) (b "upper" N N)))
   where b s = B s (TS s)

unescapeInitTail :: String -> String
unescapeInitTail = unesc . tail where
  unesc s = case s of
    '\\':c:cs | elem c ['\"', '\\', '\''] -> c : unesc cs
    '\\':'n':cs  -> '\n' : unesc cs
    '\\':'t':cs  -> '\t' : unesc cs
    '"':[]    -> []
    c:cs      -> c : unesc cs
    _         -> []

-------------------------------------------------------------------
-- Alex wrapper code.
-- A modified "posn" wrapper.
-------------------------------------------------------------------

data Posn = Pn !Int !Int !Int
      deriving (Eq, Show,Ord)

alexStartPos :: Posn
alexStartPos = Pn 0 1 1

alexMove :: Posn -> Char -> Posn
alexMove (Pn a l c) '\t' = Pn (a+1)  l     (((c+7) `div` 8)*8+1)
alexMove (Pn a l c) '\n' = Pn (a+1) (l+1)   1
alexMove (Pn a l c) _    = Pn (a+1)  l     (c+1)

type AlexInput = (Posn, -- current position,
               Char,     -- previous char
               String)   -- current input string

tokens :: String -> [Token]
tokens str = go (alexStartPos, '\n', str)
    where
      go :: (Posn, Char, String) -> [Token]
      go inp@(pos, _, str) =
               case alexScan inp 0 of
                AlexEOF                -> []
                AlexError (pos, _, _)  -> [Err pos]
                AlexSkip  inp' len     -> go inp'
                AlexToken inp' len act -> act pos (take len str) : (go inp')

alexGetChar :: AlexInput -> Maybe (Char,AlexInput)
alexGetChar (p, c, [])    = Nothing
alexGetChar (p, _, (c:s)) =
    let p' = alexMove p c
     in p' `seq` Just (c, (p', c, s))

alexInputPrevChar :: AlexInput -> Char
alexInputPrevChar (p, c, s) = c

{-# LINE 1 "templates\GenericTemplate.hs" #-}
{-# LINE 1 "templates\\GenericTemplate.hs" #-}
{-# LINE 1 "<built-in>" #-}
{-# LINE 1 "<command line>" #-}
{-# LINE 1 "templates\\GenericTemplate.hs" #-}
-- -----------------------------------------------------------------------------
-- ALEX TEMPLATE
--
-- This code is in the PUBLIC DOMAIN; you may copy it freely and use
-- it for any purpose whatsoever.

-- -----------------------------------------------------------------------------
-- INTERNALS and main scanner engine

{-# LINE 37 "templates\\GenericTemplate.hs" #-}

{-# LINE 47 "templates\\GenericTemplate.hs" #-}

{-# LINE 68 "templates\\GenericTemplate.hs" #-}
alexIndexInt16OffAddr arr off = arr ! off


{-# LINE 89 "templates\\GenericTemplate.hs" #-}
alexIndexInt32OffAddr arr off = arr ! off


{-# LINE 100 "templates\\GenericTemplate.hs" #-}
quickIndex arr i = arr ! i


-- -----------------------------------------------------------------------------
-- Main lexing routines

data AlexReturn a
  = AlexEOF
  | AlexError  !AlexInput
  | AlexSkip   !AlexInput !Int
  | AlexToken  !AlexInput !Int a

-- alexScan :: AlexInput -> StartCode -> AlexReturn a
alexScan input (sc)
  = alexScanUser undefined input (sc)

alexScanUser user input (sc)
  = case alex_scan_tkn user input (0) input sc AlexNone of
	(AlexNone, input') ->
		case alexGetChar input of
			Nothing -> 



				   AlexEOF
			Just _ ->



				   AlexError input'

	(AlexLastSkip input'' len, _) ->



		AlexSkip input'' len

	(AlexLastAcc k input''' len, _) ->



		AlexToken input''' len k


-- Push the input through the DFA, remembering the most recent accepting
-- state it encountered.

alex_scan_tkn user orig_input len input s last_acc =
  input `seq` -- strict in the input
  let 
	new_acc = check_accs (alex_accept `quickIndex` (s))
  in
  new_acc `seq`
  case alexGetChar input of
     Nothing -> (new_acc, input)
     Just (c, new_input) -> 



	let
		(base) = alexIndexInt32OffAddr alex_base s
		((ord_c)) = ord c
		(offset) = (base + ord_c)
		(check)  = alexIndexInt16OffAddr alex_check offset
		
		(new_s) = if (offset >= (0)) && (check == ord_c)
			  then alexIndexInt16OffAddr alex_table offset
			  else alexIndexInt16OffAddr alex_deflt s
	in
	case new_s + 1 of 
	    (0) -> (new_acc, input)
		-- on an error, we want to keep the input *before* the
		-- character that failed, not after.
    	    _ -> alex_scan_tkn user orig_input (len + (1)) 
			new_input new_s new_acc

  where
	check_accs [] = last_acc
	check_accs (AlexAcc a : _) = AlexLastAcc a input (len)
	check_accs (AlexAccSkip : _)  = AlexLastSkip  input (len)
	check_accs (AlexAccPred a predx : rest)
	   | predx user orig_input (len) input
	   = AlexLastAcc a input (len)
	check_accs (AlexAccSkipPred predx : rest)
	   | predx user orig_input (len) input
	   = AlexLastSkip input (len)
	check_accs (_ : rest) = check_accs rest

data AlexLastAcc a
  = AlexNone
  | AlexLastAcc a !AlexInput !Int
  | AlexLastSkip  !AlexInput !Int

data AlexAcc a user
  = AlexAcc a
  | AlexAccSkip
  | AlexAccPred a (AlexAccPred user)
  | AlexAccSkipPred (AlexAccPred user)

type AlexAccPred user = user -> AlexInput -> Int -> AlexInput -> Bool

-- -----------------------------------------------------------------------------
-- Predicates on a rule

alexAndPred p1 p2 user in1 len in2
  = p1 user in1 len in2 && p2 user in1 len in2

--alexPrevCharIsPred :: Char -> AlexAccPred _ 
alexPrevCharIs c _ input _ _ = c == alexInputPrevChar input

--alexPrevCharIsOneOfPred :: Array Char Bool -> AlexAccPred _ 
alexPrevCharIsOneOf arr _ input _ _ = arr ! alexInputPrevChar input

--alexRightContext :: Int -> AlexAccPred _
alexRightContext (sc) user _ _ input = 
     case alex_scan_tkn user input (0) input sc AlexNone of
	  (AlexNone, _) -> False
	  _ -> True
	-- TODO: there's no need to find the longest
	-- match when checking the right context, just
	-- the first match will do.

-- used by wrappers
iUnbox (i) = i
{-# OPTIONS_GHC -fno-warn-overlapping-patterns #-}

-- parser produced by Happy 

data HappyAbsSyn 
	= HappyTerminal (Token)
	| HappyErrorToken Int
	| HappyAbsSyn59 (String)
	| HappyAbsSyn60 (BNFC_QQType)
	| HappyAbsSyn61 (Ident)
	| HappyAbsSyn63 (Integer)
	| HappyAbsSyn65 (Char)
	| HappyAbsSyn67 (Double)
	| HappyAbsSyn69 (Grammar)
	| HappyAbsSyn71 ([Def])
	| HappyAbsSyn73 ([Item])
	| HappyAbsSyn75 (Def)
	| HappyAbsSyn77 (RHS)
	| HappyAbsSyn79 ([RHS])
	| HappyAbsSyn81 (Item)
	| HappyAbsSyn83 (Cat)
	| HappyAbsSyn87 (Label)
	| HappyAbsSyn89 (MIdent)
	| HappyAbsSyn91 (HsTyp)
	| HappyAbsSyn95 ([HsTyp])
	| HappyAbsSyn97 (Arg)
	| HappyAbsSyn99 ([Arg])
	| HappyAbsSyn101 (Exp)
	| HappyAbsSyn107 ([Exp])
	| HappyAbsSyn111 ([String])
	| HappyAbsSyn113 (MinimumSize)
	| HappyAbsSyn115 (Reg)
	| HappyAbsSyn123 ([Ident])

{- to allow type-synonyms as our monads (likely
 - with explicitly-specified bind and return)
 - in Haskell98, it seems that with
 - /type M a = .../, then /(HappyReduction M)/
 - is not allowed.  But Happy is a
 - code-generator that can just substitute it.
type HappyReduction m = 
	   Int 
	-> (Token)
	-> HappyState (Token) (HappyStk HappyAbsSyn -> [(Token)] -> m HappyAbsSyn)
	-> [HappyState (Token) (HappyStk HappyAbsSyn -> [(Token)] -> m HappyAbsSyn)] 
	-> HappyStk HappyAbsSyn 
	-> [(Token)] -> m HappyAbsSyn
-}

action_0,
 action_1,
 action_2,
 action_3,
 action_4,
 action_5,
 action_6,
 action_7,
 action_8,
 action_9,
 action_10,
 action_11,
 action_12,
 action_13,
 action_14,
 action_15,
 action_16,
 action_17,
 action_18,
 action_19,
 action_20,
 action_21,
 action_22,
 action_23,
 action_24,
 action_25,
 action_26,
 action_27,
 action_28,
 action_29,
 action_30,
 action_31,
 action_32,
 action_33,
 action_34,
 action_35,
 action_36,
 action_37,
 action_38,
 action_39,
 action_40,
 action_41,
 action_42,
 action_43,
 action_44,
 action_45,
 action_46,
 action_47,
 action_48,
 action_49,
 action_50,
 action_51,
 action_52,
 action_53,
 action_54,
 action_55,
 action_56,
 action_57,
 action_58,
 action_59,
 action_60,
 action_61,
 action_62,
 action_63,
 action_64,
 action_65,
 action_66,
 action_67,
 action_68,
 action_69,
 action_70,
 action_71,
 action_72,
 action_73,
 action_74,
 action_75,
 action_76,
 action_77,
 action_78,
 action_79,
 action_80,
 action_81,
 action_82,
 action_83,
 action_84,
 action_85,
 action_86,
 action_87,
 action_88,
 action_89,
 action_90,
 action_91,
 action_92,
 action_93,
 action_94,
 action_95,
 action_96,
 action_97,
 action_98,
 action_99,
 action_100,
 action_101,
 action_102,
 action_103,
 action_104,
 action_105,
 action_106,
 action_107,
 action_108,
 action_109,
 action_110,
 action_111,
 action_112,
 action_113,
 action_114,
 action_115,
 action_116,
 action_117,
 action_118,
 action_119,
 action_120,
 action_121,
 action_122,
 action_123,
 action_124,
 action_125,
 action_126,
 action_127,
 action_128,
 action_129,
 action_130,
 action_131,
 action_132,
 action_133,
 action_134,
 action_135,
 action_136,
 action_137,
 action_138,
 action_139,
 action_140,
 action_141,
 action_142,
 action_143,
 action_144,
 action_145,
 action_146,
 action_147,
 action_148,
 action_149,
 action_150,
 action_151,
 action_152,
 action_153,
 action_154,
 action_155,
 action_156,
 action_157,
 action_158,
 action_159,
 action_160,
 action_161,
 action_162,
 action_163,
 action_164,
 action_165,
 action_166,
 action_167,
 action_168,
 action_169,
 action_170,
 action_171,
 action_172,
 action_173,
 action_174,
 action_175,
 action_176,
 action_177,
 action_178,
 action_179,
 action_180,
 action_181,
 action_182,
 action_183,
 action_184,
 action_185,
 action_186,
 action_187,
 action_188,
 action_189,
 action_190,
 action_191,
 action_192,
 action_193,
 action_194,
 action_195,
 action_196,
 action_197,
 action_198,
 action_199,
 action_200,
 action_201,
 action_202,
 action_203,
 action_204,
 action_205,
 action_206,
 action_207,
 action_208,
 action_209,
 action_210,
 action_211,
 action_212,
 action_213,
 action_214,
 action_215,
 action_216,
 action_217,
 action_218,
 action_219,
 action_220,
 action_221,
 action_222,
 action_223,
 action_224,
 action_225,
 action_226,
 action_227,
 action_228,
 action_229,
 action_230,
 action_231,
 action_232,
 action_233,
 action_234,
 action_235,
 action_236,
 action_237,
 action_238,
 action_239,
 action_240,
 action_241,
 action_242,
 action_243,
 action_244,
 action_245,
 action_246,
 action_247,
 action_248,
 action_249,
 action_250,
 action_251,
 action_252,
 action_253,
 action_254,
 action_255,
 action_256,
 action_257,
 action_258,
 action_259,
 action_260,
 action_261,
 action_262,
 action_263,
 action_264,
 action_265,
 action_266,
 action_267,
 action_268,
 action_269,
 action_270,
 action_271,
 action_272,
 action_273,
 action_274,
 action_275,
 action_276,
 action_277,
 action_278,
 action_279,
 action_280,
 action_281,
 action_282,
 action_283,
 action_284,
 action_285,
 action_286,
 action_287,
 action_288,
 action_289,
 action_290,
 action_291,
 action_292,
 action_293,
 action_294,
 action_295,
 action_296,
 action_297,
 action_298,
 action_299,
 action_300,
 action_301,
 action_302,
 action_303,
 action_304,
 action_305,
 action_306,
 action_307,
 action_308,
 action_309,
 action_310,
 action_311,
 action_312,
 action_313,
 action_314,
 action_315,
 action_316,
 action_317,
 action_318,
 action_319,
 action_320,
 action_321,
 action_322,
 action_323,
 action_324,
 action_325,
 action_326,
 action_327,
 action_328,
 action_329,
 action_330,
 action_331,
 action_332,
 action_333,
 action_334,
 action_335,
 action_336,
 action_337,
 action_338,
 action_339,
 action_340,
 action_341,
 action_342,
 action_343,
 action_344,
 action_345,
 action_346,
 action_347,
 action_348,
 action_349,
 action_350,
 action_351,
 action_352,
 action_353,
 action_354,
 action_355,
 action_356,
 action_357,
 action_358,
 action_359,
 action_360,
 action_361,
 action_362,
 action_363,
 action_364,
 action_365,
 action_366,
 action_367,
 action_368,
 action_369,
 action_370,
 action_371,
 action_372,
 action_373,
 action_374,
 action_375,
 action_376,
 action_377,
 action_378,
 action_379,
 action_380,
 action_381,
 action_382,
 action_383,
 action_384,
 action_385,
 action_386,
 action_387,
 action_388,
 action_389,
 action_390,
 action_391,
 action_392,
 action_393,
 action_394,
 action_395,
 action_396,
 action_397,
 action_398,
 action_399,
 action_400,
 action_401,
 action_402,
 action_403,
 action_404,
 action_405,
 action_406,
 action_407,
 action_408,
 action_409,
 action_410,
 action_411,
 action_412,
 action_413,
 action_414,
 action_415,
 action_416,
 action_417,
 action_418,
 action_419,
 action_420,
 action_421,
 action_422,
 action_423,
 action_424,
 action_425,
 action_426,
 action_427,
 action_428,
 action_429,
 action_430,
 action_431,
 action_432,
 action_433,
 action_434,
 action_435,
 action_436,
 action_437,
 action_438 :: () => Int -> ({-HappyReduction (ParseMonad) = -}
	   Int 
	-> (Token)
	-> HappyState (Token) (HappyStk HappyAbsSyn -> [(Token)] -> (ParseMonad) HappyAbsSyn)
	-> [HappyState (Token) (HappyStk HappyAbsSyn -> [(Token)] -> (ParseMonad) HappyAbsSyn)] 
	-> HappyStk HappyAbsSyn 
	-> [(Token)] -> (ParseMonad) HappyAbsSyn)

happyReduce_56,
 happyReduce_57,
 happyReduce_58,
 happyReduce_59,
 happyReduce_60,
 happyReduce_61,
 happyReduce_62,
 happyReduce_63,
 happyReduce_64,
 happyReduce_65,
 happyReduce_66,
 happyReduce_67,
 happyReduce_68,
 happyReduce_69,
 happyReduce_70,
 happyReduce_71,
 happyReduce_72,
 happyReduce_73,
 happyReduce_74,
 happyReduce_75,
 happyReduce_76,
 happyReduce_77,
 happyReduce_78,
 happyReduce_79,
 happyReduce_80,
 happyReduce_81,
 happyReduce_82,
 happyReduce_83,
 happyReduce_84,
 happyReduce_85,
 happyReduce_86,
 happyReduce_87,
 happyReduce_88,
 happyReduce_89,
 happyReduce_90,
 happyReduce_91,
 happyReduce_92,
 happyReduce_93,
 happyReduce_94,
 happyReduce_95,
 happyReduce_96,
 happyReduce_97,
 happyReduce_98,
 happyReduce_99,
 happyReduce_100,
 happyReduce_101,
 happyReduce_102,
 happyReduce_103,
 happyReduce_104,
 happyReduce_105,
 happyReduce_106,
 happyReduce_107,
 happyReduce_108,
 happyReduce_109,
 happyReduce_110,
 happyReduce_111,
 happyReduce_112,
 happyReduce_113,
 happyReduce_114,
 happyReduce_115,
 happyReduce_116,
 happyReduce_117,
 happyReduce_118,
 happyReduce_119,
 happyReduce_120,
 happyReduce_121,
 happyReduce_122,
 happyReduce_123,
 happyReduce_124,
 happyReduce_125,
 happyReduce_126,
 happyReduce_127,
 happyReduce_128,
 happyReduce_129,
 happyReduce_130,
 happyReduce_131,
 happyReduce_132,
 happyReduce_133,
 happyReduce_134,
 happyReduce_135,
 happyReduce_136,
 happyReduce_137,
 happyReduce_138,
 happyReduce_139,
 happyReduce_140,
 happyReduce_141,
 happyReduce_142,
 happyReduce_143,
 happyReduce_144,
 happyReduce_145,
 happyReduce_146,
 happyReduce_147,
 happyReduce_148,
 happyReduce_149,
 happyReduce_150,
 happyReduce_151,
 happyReduce_152,
 happyReduce_153,
 happyReduce_154,
 happyReduce_155,
 happyReduce_156,
 happyReduce_157,
 happyReduce_158,
 happyReduce_159,
 happyReduce_160,
 happyReduce_161,
 happyReduce_162,
 happyReduce_163,
 happyReduce_164,
 happyReduce_165,
 happyReduce_166,
 happyReduce_167,
 happyReduce_168,
 happyReduce_169,
 happyReduce_170,
 happyReduce_171,
 happyReduce_172,
 happyReduce_173,
 happyReduce_174,
 happyReduce_175,
 happyReduce_176,
 happyReduce_177,
 happyReduce_178,
 happyReduce_179,
 happyReduce_180,
 happyReduce_181,
 happyReduce_182,
 happyReduce_183,
 happyReduce_184,
 happyReduce_185,
 happyReduce_186,
 happyReduce_187,
 happyReduce_188,
 happyReduce_189,
 happyReduce_190,
 happyReduce_191,
 happyReduce_192,
 happyReduce_193,
 happyReduce_194,
 happyReduce_195,
 happyReduce_196,
 happyReduce_197,
 happyReduce_198,
 happyReduce_199,
 happyReduce_200,
 happyReduce_201,
 happyReduce_202,
 happyReduce_203,
 happyReduce_204,
 happyReduce_205,
 happyReduce_206,
 happyReduce_207,
 happyReduce_208,
 happyReduce_209,
 happyReduce_210,
 happyReduce_211,
 happyReduce_212,
 happyReduce_213,
 happyReduce_214,
 happyReduce_215,
 happyReduce_216,
 happyReduce_217,
 happyReduce_218,
 happyReduce_219,
 happyReduce_220,
 happyReduce_221,
 happyReduce_222,
 happyReduce_223,
 happyReduce_224,
 happyReduce_225,
 happyReduce_226,
 happyReduce_227,
 happyReduce_228,
 happyReduce_229,
 happyReduce_230,
 happyReduce_231,
 happyReduce_232,
 happyReduce_233,
 happyReduce_234,
 happyReduce_235,
 happyReduce_236,
 happyReduce_237,
 happyReduce_238,
 happyReduce_239,
 happyReduce_240,
 happyReduce_241,
 happyReduce_242,
 happyReduce_243,
 happyReduce_244,
 happyReduce_245,
 happyReduce_246,
 happyReduce_247 :: () => ({-HappyReduction (ParseMonad) = -}
	   Int 
	-> (Token)
	-> HappyState (Token) (HappyStk HappyAbsSyn -> [(Token)] -> (ParseMonad) HappyAbsSyn)
	-> [HappyState (Token) (HappyStk HappyAbsSyn -> [(Token)] -> (ParseMonad) HappyAbsSyn)] 
	-> HappyStk HappyAbsSyn 
	-> [(Token)] -> (ParseMonad) HappyAbsSyn)

action_0 (131) = happyShift action_179
action_0 (133) = happyShift action_180
action_0 (134) = happyShift action_181
action_0 (137) = happyShift action_182
action_0 (145) = happyShift action_228
action_0 (147) = happyShift action_229
action_0 (148) = happyShift action_230
action_0 (149) = happyShift action_231
action_0 (151) = happyShift action_232
action_0 (153) = happyShift action_233
action_0 (154) = happyShift action_234
action_0 (155) = happyShift action_235
action_0 (159) = happyShift action_236
action_0 (160) = happyShift action_237
action_0 (161) = happyShift action_238
action_0 (163) = happyShift action_239
action_0 (164) = happyShift action_240
action_0 (168) = happyShift action_63
action_0 (61) = happyGoto action_177
action_0 (69) = happyGoto action_249
action_0 (71) = happyGoto action_250
action_0 (75) = happyGoto action_246
action_0 (87) = happyGoto action_227
action_0 _ = happyReduce_68

action_1 (131) = happyShift action_173
action_1 (133) = happyShift action_174
action_1 (134) = happyShift action_175
action_1 (137) = happyShift action_176
action_1 (145) = happyShift action_213
action_1 (147) = happyShift action_214
action_1 (148) = happyShift action_215
action_1 (149) = happyShift action_216
action_1 (151) = happyShift action_217
action_1 (153) = happyShift action_218
action_1 (154) = happyShift action_219
action_1 (155) = happyShift action_220
action_1 (159) = happyShift action_221
action_1 (160) = happyShift action_222
action_1 (161) = happyShift action_223
action_1 (163) = happyShift action_224
action_1 (164) = happyShift action_225
action_1 (168) = happyShift action_60
action_1 (62) = happyGoto action_171
action_1 (70) = happyGoto action_247
action_1 (72) = happyGoto action_248
action_1 (76) = happyGoto action_244
action_1 (88) = happyGoto action_212
action_1 _ = happyReduce_71

action_2 (131) = happyShift action_179
action_2 (133) = happyShift action_180
action_2 (134) = happyShift action_181
action_2 (137) = happyShift action_182
action_2 (145) = happyShift action_228
action_2 (147) = happyShift action_229
action_2 (148) = happyShift action_230
action_2 (149) = happyShift action_231
action_2 (151) = happyShift action_232
action_2 (153) = happyShift action_233
action_2 (154) = happyShift action_234
action_2 (155) = happyShift action_235
action_2 (159) = happyShift action_236
action_2 (160) = happyShift action_237
action_2 (161) = happyShift action_238
action_2 (163) = happyShift action_239
action_2 (164) = happyShift action_240
action_2 (168) = happyShift action_63
action_2 (61) = happyGoto action_177
action_2 (71) = happyGoto action_245
action_2 (75) = happyGoto action_246
action_2 (87) = happyGoto action_227
action_2 _ = happyReduce_68

action_3 (131) = happyShift action_173
action_3 (133) = happyShift action_174
action_3 (134) = happyShift action_175
action_3 (137) = happyShift action_176
action_3 (145) = happyShift action_213
action_3 (147) = happyShift action_214
action_3 (148) = happyShift action_215
action_3 (149) = happyShift action_216
action_3 (151) = happyShift action_217
action_3 (153) = happyShift action_218
action_3 (154) = happyShift action_219
action_3 (155) = happyShift action_220
action_3 (159) = happyShift action_221
action_3 (160) = happyShift action_222
action_3 (161) = happyShift action_223
action_3 (163) = happyShift action_224
action_3 (164) = happyShift action_225
action_3 (168) = happyShift action_60
action_3 (62) = happyGoto action_171
action_3 (72) = happyGoto action_243
action_3 (76) = happyGoto action_244
action_3 (88) = happyGoto action_212
action_3 _ = happyReduce_71

action_4 (73) = happyGoto action_242
action_4 _ = happyReduce_74

action_5 (74) = happyGoto action_241
action_5 _ = happyReduce_76

action_6 (131) = happyShift action_179
action_6 (133) = happyShift action_180
action_6 (134) = happyShift action_181
action_6 (137) = happyShift action_182
action_6 (145) = happyShift action_228
action_6 (147) = happyShift action_229
action_6 (148) = happyShift action_230
action_6 (149) = happyShift action_231
action_6 (151) = happyShift action_232
action_6 (153) = happyShift action_233
action_6 (154) = happyShift action_234
action_6 (155) = happyShift action_235
action_6 (159) = happyShift action_236
action_6 (160) = happyShift action_237
action_6 (161) = happyShift action_238
action_6 (163) = happyShift action_239
action_6 (164) = happyShift action_240
action_6 (168) = happyShift action_63
action_6 (61) = happyGoto action_177
action_6 (75) = happyGoto action_226
action_6 (87) = happyGoto action_227
action_6 _ = happyFail

action_7 (131) = happyShift action_173
action_7 (133) = happyShift action_174
action_7 (134) = happyShift action_175
action_7 (137) = happyShift action_176
action_7 (145) = happyShift action_213
action_7 (147) = happyShift action_214
action_7 (148) = happyShift action_215
action_7 (149) = happyShift action_216
action_7 (151) = happyShift action_217
action_7 (153) = happyShift action_218
action_7 (154) = happyShift action_219
action_7 (155) = happyShift action_220
action_7 (159) = happyShift action_221
action_7 (160) = happyShift action_222
action_7 (161) = happyShift action_223
action_7 (163) = happyShift action_224
action_7 (164) = happyShift action_225
action_7 (168) = happyShift action_60
action_7 (62) = happyGoto action_171
action_7 (76) = happyGoto action_211
action_7 (88) = happyGoto action_212
action_7 _ = happyFail

action_8 (128) = happyShift action_208
action_8 (73) = happyGoto action_205
action_8 (77) = happyGoto action_210
action_8 _ = happyReduce_74

action_9 (128) = happyShift action_204
action_9 (74) = happyGoto action_201
action_9 (78) = happyGoto action_209
action_9 _ = happyReduce_76

action_10 (128) = happyShift action_208
action_10 (73) = happyGoto action_205
action_10 (77) = happyGoto action_206
action_10 (79) = happyGoto action_207
action_10 _ = happyReduce_74

action_11 (128) = happyShift action_204
action_11 (74) = happyGoto action_201
action_11 (78) = happyGoto action_202
action_11 (80) = happyGoto action_203
action_11 _ = happyReduce_76

action_12 (130) = happyShift action_194
action_12 (131) = happyShift action_188
action_12 (167) = happyShift action_57
action_12 (168) = happyShift action_63
action_12 (59) = happyGoto action_198
action_12 (61) = happyGoto action_186
action_12 (81) = happyGoto action_199
action_12 (83) = happyGoto action_200
action_12 (85) = happyGoto action_193
action_12 _ = happyFail

action_13 (130) = happyShift action_191
action_13 (131) = happyShift action_185
action_13 (167) = happyShift action_106
action_13 (168) = happyShift action_60
action_13 (60) = happyGoto action_195
action_13 (62) = happyGoto action_183
action_13 (82) = happyGoto action_196
action_13 (84) = happyGoto action_197
action_13 (86) = happyGoto action_190
action_13 _ = happyFail

action_14 (130) = happyShift action_194
action_14 (131) = happyShift action_188
action_14 (168) = happyShift action_63
action_14 (61) = happyGoto action_186
action_14 (83) = happyGoto action_192
action_14 (85) = happyGoto action_193
action_14 _ = happyFail

action_15 (130) = happyShift action_191
action_15 (131) = happyShift action_185
action_15 (168) = happyShift action_60
action_15 (62) = happyGoto action_183
action_15 (84) = happyGoto action_189
action_15 (86) = happyGoto action_190
action_15 _ = happyFail

action_16 (131) = happyShift action_188
action_16 (168) = happyShift action_63
action_16 (61) = happyGoto action_186
action_16 (85) = happyGoto action_187
action_16 _ = happyFail

action_17 (131) = happyShift action_185
action_17 (168) = happyShift action_60
action_17 (62) = happyGoto action_183
action_17 (86) = happyGoto action_184
action_17 _ = happyFail

action_18 (131) = happyShift action_179
action_18 (133) = happyShift action_180
action_18 (134) = happyShift action_181
action_18 (137) = happyShift action_182
action_18 (168) = happyShift action_63
action_18 (61) = happyGoto action_177
action_18 (87) = happyGoto action_178
action_18 _ = happyFail

action_19 (131) = happyShift action_173
action_19 (133) = happyShift action_174
action_19 (134) = happyShift action_175
action_19 (137) = happyShift action_176
action_19 (168) = happyShift action_60
action_19 (62) = happyGoto action_171
action_19 (88) = happyGoto action_172
action_19 _ = happyFail

action_20 (168) = happyShift action_63
action_20 (61) = happyGoto action_169
action_20 (89) = happyGoto action_170
action_20 _ = happyReduce_145

action_21 (168) = happyShift action_60
action_21 (62) = happyGoto action_167
action_21 (90) = happyGoto action_168
action_21 _ = happyReduce_147

action_22 (91) = happyGoto action_166
action_22 _ = happyFail

action_23 (92) = happyGoto action_165
action_23 _ = happyFail

action_24 (131) = happyShift action_163
action_24 (134) = happyShift action_164
action_24 (168) = happyShift action_63
action_24 (61) = happyGoto action_161
action_24 (93) = happyGoto action_162
action_24 _ = happyFail

action_25 (131) = happyShift action_159
action_25 (134) = happyShift action_160
action_25 (168) = happyShift action_60
action_25 (62) = happyGoto action_157
action_25 (94) = happyGoto action_158
action_25 _ = happyFail

action_26 (91) = happyGoto action_155
action_26 (95) = happyGoto action_156
action_26 _ = happyFail

action_27 (92) = happyGoto action_153
action_27 (96) = happyGoto action_154
action_27 _ = happyFail

action_28 (168) = happyShift action_63
action_28 (61) = happyGoto action_151
action_28 (97) = happyGoto action_152
action_28 _ = happyFail

action_29 (168) = happyShift action_60
action_29 (62) = happyGoto action_149
action_29 (98) = happyGoto action_150
action_29 _ = happyFail

action_30 (99) = happyGoto action_148
action_30 _ = happyReduce_162

action_31 (100) = happyGoto action_147
action_31 _ = happyReduce_164

action_32 (131) = happyShift action_131
action_32 (134) = happyShift action_132
action_32 (167) = happyShift action_57
action_32 (168) = happyShift action_63
action_32 (169) = happyShift action_133
action_32 (170) = happyShift action_93
action_32 (171) = happyShift action_134
action_32 (59) = happyGoto action_122
action_32 (61) = happyGoto action_123
action_32 (63) = happyGoto action_124
action_32 (65) = happyGoto action_125
action_32 (67) = happyGoto action_126
action_32 (101) = happyGoto action_146
action_32 (103) = happyGoto action_128
action_32 (105) = happyGoto action_129
action_32 _ = happyFail

action_33 (131) = happyShift action_118
action_33 (134) = happyShift action_119
action_33 (167) = happyShift action_106
action_33 (168) = happyShift action_60
action_33 (169) = happyShift action_120
action_33 (170) = happyShift action_78
action_33 (171) = happyShift action_121
action_33 (60) = happyGoto action_109
action_33 (62) = happyGoto action_110
action_33 (64) = happyGoto action_111
action_33 (66) = happyGoto action_112
action_33 (68) = happyGoto action_113
action_33 (102) = happyGoto action_145
action_33 (104) = happyGoto action_115
action_33 (106) = happyGoto action_116
action_33 _ = happyFail

action_34 (131) = happyShift action_131
action_34 (134) = happyShift action_132
action_34 (167) = happyShift action_57
action_34 (168) = happyShift action_63
action_34 (169) = happyShift action_133
action_34 (170) = happyShift action_93
action_34 (171) = happyShift action_134
action_34 (59) = happyGoto action_122
action_34 (61) = happyGoto action_123
action_34 (63) = happyGoto action_124
action_34 (65) = happyGoto action_125
action_34 (67) = happyGoto action_126
action_34 (103) = happyGoto action_144
action_34 (105) = happyGoto action_129
action_34 _ = happyFail

action_35 (131) = happyShift action_118
action_35 (134) = happyShift action_119
action_35 (167) = happyShift action_106
action_35 (168) = happyShift action_60
action_35 (169) = happyShift action_120
action_35 (170) = happyShift action_78
action_35 (171) = happyShift action_121
action_35 (60) = happyGoto action_109
action_35 (62) = happyGoto action_110
action_35 (64) = happyGoto action_111
action_35 (66) = happyGoto action_112
action_35 (68) = happyGoto action_113
action_35 (104) = happyGoto action_143
action_35 (106) = happyGoto action_116
action_35 _ = happyFail

action_36 (131) = happyShift action_131
action_36 (134) = happyShift action_132
action_36 (167) = happyShift action_57
action_36 (168) = happyShift action_63
action_36 (169) = happyShift action_133
action_36 (170) = happyShift action_93
action_36 (171) = happyShift action_134
action_36 (59) = happyGoto action_122
action_36 (61) = happyGoto action_138
action_36 (63) = happyGoto action_124
action_36 (65) = happyGoto action_125
action_36 (67) = happyGoto action_126
action_36 (105) = happyGoto action_142
action_36 _ = happyFail

action_37 (131) = happyShift action_118
action_37 (134) = happyShift action_119
action_37 (167) = happyShift action_106
action_37 (168) = happyShift action_60
action_37 (169) = happyShift action_120
action_37 (170) = happyShift action_78
action_37 (171) = happyShift action_121
action_37 (60) = happyGoto action_109
action_37 (62) = happyGoto action_135
action_37 (64) = happyGoto action_111
action_37 (66) = happyGoto action_112
action_37 (68) = happyGoto action_113
action_37 (106) = happyGoto action_141
action_37 _ = happyFail

action_38 (131) = happyShift action_131
action_38 (134) = happyShift action_132
action_38 (167) = happyShift action_57
action_38 (168) = happyShift action_63
action_38 (169) = happyShift action_133
action_38 (170) = happyShift action_93
action_38 (171) = happyShift action_134
action_38 (59) = happyGoto action_122
action_38 (61) = happyGoto action_138
action_38 (63) = happyGoto action_124
action_38 (65) = happyGoto action_125
action_38 (67) = happyGoto action_126
action_38 (105) = happyGoto action_139
action_38 (107) = happyGoto action_140
action_38 _ = happyFail

action_39 (131) = happyShift action_118
action_39 (134) = happyShift action_119
action_39 (167) = happyShift action_106
action_39 (168) = happyShift action_60
action_39 (169) = happyShift action_120
action_39 (170) = happyShift action_78
action_39 (171) = happyShift action_121
action_39 (60) = happyGoto action_109
action_39 (62) = happyGoto action_135
action_39 (64) = happyGoto action_111
action_39 (66) = happyGoto action_112
action_39 (68) = happyGoto action_113
action_39 (106) = happyGoto action_136
action_39 (108) = happyGoto action_137
action_39 _ = happyFail

action_40 (131) = happyShift action_131
action_40 (134) = happyShift action_132
action_40 (167) = happyShift action_57
action_40 (168) = happyShift action_63
action_40 (169) = happyShift action_133
action_40 (170) = happyShift action_93
action_40 (171) = happyShift action_134
action_40 (59) = happyGoto action_122
action_40 (61) = happyGoto action_123
action_40 (63) = happyGoto action_124
action_40 (65) = happyGoto action_125
action_40 (67) = happyGoto action_126
action_40 (101) = happyGoto action_127
action_40 (103) = happyGoto action_128
action_40 (105) = happyGoto action_129
action_40 (109) = happyGoto action_130
action_40 _ = happyReduce_192

action_41 (131) = happyShift action_118
action_41 (134) = happyShift action_119
action_41 (167) = happyShift action_106
action_41 (168) = happyShift action_60
action_41 (169) = happyShift action_120
action_41 (170) = happyShift action_78
action_41 (171) = happyShift action_121
action_41 (60) = happyGoto action_109
action_41 (62) = happyGoto action_110
action_41 (64) = happyGoto action_111
action_41 (66) = happyGoto action_112
action_41 (68) = happyGoto action_113
action_41 (102) = happyGoto action_114
action_41 (104) = happyGoto action_115
action_41 (106) = happyGoto action_116
action_41 (110) = happyGoto action_117
action_41 _ = happyReduce_195

action_42 (167) = happyShift action_57
action_42 (59) = happyGoto action_107
action_42 (111) = happyGoto action_108
action_42 _ = happyFail

action_43 (167) = happyShift action_106
action_43 (60) = happyGoto action_104
action_43 (112) = happyGoto action_105
action_43 _ = happyFail

action_44 (158) = happyShift action_103
action_44 (113) = happyGoto action_102
action_44 _ = happyReduce_203

action_45 (158) = happyShift action_101
action_45 (114) = happyGoto action_100
action_45 _ = happyReduce_205

action_46 (131) = happyShift action_84
action_46 (134) = happyShift action_85
action_46 (143) = happyShift action_86
action_46 (146) = happyShift action_87
action_46 (150) = happyShift action_88
action_46 (152) = happyShift action_89
action_46 (156) = happyShift action_90
action_46 (157) = happyShift action_91
action_46 (166) = happyShift action_92
action_46 (170) = happyShift action_93
action_46 (65) = happyGoto action_79
action_46 (115) = happyGoto action_99
action_46 (119) = happyGoto action_82
action_46 _ = happyFail

action_47 (131) = happyShift action_69
action_47 (134) = happyShift action_70
action_47 (143) = happyShift action_71
action_47 (146) = happyShift action_72
action_47 (150) = happyShift action_73
action_47 (152) = happyShift action_74
action_47 (156) = happyShift action_75
action_47 (157) = happyShift action_76
action_47 (166) = happyShift action_77
action_47 (170) = happyShift action_78
action_47 (66) = happyGoto action_64
action_47 (116) = happyGoto action_98
action_47 (120) = happyGoto action_67
action_47 _ = happyFail

action_48 (131) = happyShift action_84
action_48 (134) = happyShift action_85
action_48 (143) = happyShift action_86
action_48 (146) = happyShift action_87
action_48 (150) = happyShift action_88
action_48 (152) = happyShift action_89
action_48 (156) = happyShift action_90
action_48 (157) = happyShift action_91
action_48 (166) = happyShift action_92
action_48 (170) = happyShift action_93
action_48 (65) = happyGoto action_79
action_48 (115) = happyGoto action_80
action_48 (117) = happyGoto action_97
action_48 (119) = happyGoto action_82
action_48 _ = happyFail

action_49 (131) = happyShift action_69
action_49 (134) = happyShift action_70
action_49 (143) = happyShift action_71
action_49 (146) = happyShift action_72
action_49 (150) = happyShift action_73
action_49 (152) = happyShift action_74
action_49 (156) = happyShift action_75
action_49 (157) = happyShift action_76
action_49 (166) = happyShift action_77
action_49 (170) = happyShift action_78
action_49 (66) = happyGoto action_64
action_49 (116) = happyGoto action_65
action_49 (118) = happyGoto action_96
action_49 (120) = happyGoto action_67
action_49 _ = happyFail

action_50 (131) = happyShift action_84
action_50 (134) = happyShift action_85
action_50 (143) = happyShift action_86
action_50 (146) = happyShift action_87
action_50 (150) = happyShift action_88
action_50 (152) = happyShift action_89
action_50 (156) = happyShift action_90
action_50 (157) = happyShift action_91
action_50 (166) = happyShift action_92
action_50 (170) = happyShift action_93
action_50 (65) = happyGoto action_79
action_50 (119) = happyGoto action_95
action_50 _ = happyFail

action_51 (131) = happyShift action_69
action_51 (134) = happyShift action_70
action_51 (143) = happyShift action_71
action_51 (146) = happyShift action_72
action_51 (150) = happyShift action_73
action_51 (152) = happyShift action_74
action_51 (156) = happyShift action_75
action_51 (157) = happyShift action_76
action_51 (166) = happyShift action_77
action_51 (170) = happyShift action_78
action_51 (66) = happyGoto action_64
action_51 (120) = happyGoto action_94
action_51 _ = happyFail

action_52 (131) = happyShift action_84
action_52 (134) = happyShift action_85
action_52 (143) = happyShift action_86
action_52 (146) = happyShift action_87
action_52 (150) = happyShift action_88
action_52 (152) = happyShift action_89
action_52 (156) = happyShift action_90
action_52 (157) = happyShift action_91
action_52 (166) = happyShift action_92
action_52 (170) = happyShift action_93
action_52 (65) = happyGoto action_79
action_52 (115) = happyGoto action_80
action_52 (117) = happyGoto action_81
action_52 (119) = happyGoto action_82
action_52 (121) = happyGoto action_83
action_52 _ = happyFail

action_53 (131) = happyShift action_69
action_53 (134) = happyShift action_70
action_53 (143) = happyShift action_71
action_53 (146) = happyShift action_72
action_53 (150) = happyShift action_73
action_53 (152) = happyShift action_74
action_53 (156) = happyShift action_75
action_53 (157) = happyShift action_76
action_53 (166) = happyShift action_77
action_53 (170) = happyShift action_78
action_53 (66) = happyGoto action_64
action_53 (116) = happyGoto action_65
action_53 (118) = happyGoto action_66
action_53 (120) = happyGoto action_67
action_53 (122) = happyGoto action_68
action_53 _ = happyFail

action_54 (168) = happyShift action_63
action_54 (61) = happyGoto action_61
action_54 (123) = happyGoto action_62
action_54 _ = happyFail

action_55 (168) = happyShift action_60
action_55 (62) = happyGoto action_58
action_55 (124) = happyGoto action_59
action_55 _ = happyFail

action_56 (167) = happyShift action_57
action_56 _ = happyFail

action_57 _ = happyReduce_56

action_58 (139) = happyShift action_344
action_58 _ = happyReduce_246

action_59 (173) = happyAccept
action_59 _ = happyFail

action_60 _ = happyReduce_59

action_61 (139) = happyShift action_343
action_61 _ = happyReduce_244

action_62 (173) = happyAccept
action_62 _ = happyFail

action_63 _ = happyReduce_58

action_64 _ = happyReduce_233

action_65 (131) = happyShift action_69
action_65 (134) = happyShift action_70
action_65 (140) = happyShift action_342
action_65 (143) = happyShift action_71
action_65 (146) = happyShift action_72
action_65 (150) = happyShift action_73
action_65 (152) = happyShift action_74
action_65 (156) = happyShift action_75
action_65 (157) = happyShift action_76
action_65 (166) = happyShift action_77
action_65 (170) = happyShift action_78
action_65 (66) = happyGoto action_64
action_65 (120) = happyGoto action_326
action_65 _ = happyReduce_215

action_66 (129) = happyShift action_328
action_66 _ = happyReduce_243

action_67 (130) = happyShift action_332
action_67 (141) = happyShift action_333
action_67 (142) = happyShift action_334
action_67 _ = happyReduce_209

action_68 (173) = happyAccept
action_68 _ = happyFail

action_69 (167) = happyShift action_106
action_69 (60) = happyGoto action_341
action_69 _ = happyFail

action_70 (131) = happyShift action_69
action_70 (134) = happyShift action_70
action_70 (143) = happyShift action_71
action_70 (146) = happyShift action_72
action_70 (150) = happyShift action_73
action_70 (152) = happyShift action_74
action_70 (156) = happyShift action_75
action_70 (157) = happyShift action_76
action_70 (166) = happyShift action_77
action_70 (170) = happyShift action_78
action_70 (66) = happyGoto action_64
action_70 (116) = happyGoto action_65
action_70 (118) = happyGoto action_66
action_70 (120) = happyGoto action_67
action_70 (122) = happyGoto action_340
action_70 _ = happyFail

action_71 (167) = happyShift action_106
action_71 (60) = happyGoto action_339
action_71 _ = happyFail

action_72 _ = happyReduce_240

action_73 _ = happyReduce_236

action_74 _ = happyReduce_232

action_75 _ = happyReduce_237

action_76 _ = happyReduce_239

action_77 _ = happyReduce_238

action_78 _ = happyReduce_63

action_79 _ = happyReduce_220

action_80 (131) = happyShift action_84
action_80 (134) = happyShift action_85
action_80 (140) = happyShift action_338
action_80 (143) = happyShift action_86
action_80 (146) = happyShift action_87
action_80 (150) = happyShift action_88
action_80 (152) = happyShift action_89
action_80 (156) = happyShift action_90
action_80 (157) = happyShift action_91
action_80 (166) = happyShift action_92
action_80 (170) = happyShift action_93
action_80 (65) = happyGoto action_79
action_80 (119) = happyGoto action_325
action_80 _ = happyReduce_212

action_81 (129) = happyShift action_327
action_81 _ = happyReduce_242

action_82 (130) = happyShift action_329
action_82 (141) = happyShift action_330
action_82 (142) = happyShift action_331
action_82 _ = happyReduce_207

action_83 (173) = happyAccept
action_83 _ = happyFail

action_84 (167) = happyShift action_57
action_84 (59) = happyGoto action_337
action_84 _ = happyFail

action_85 (131) = happyShift action_84
action_85 (134) = happyShift action_85
action_85 (143) = happyShift action_86
action_85 (146) = happyShift action_87
action_85 (150) = happyShift action_88
action_85 (152) = happyShift action_89
action_85 (156) = happyShift action_90
action_85 (157) = happyShift action_91
action_85 (166) = happyShift action_92
action_85 (170) = happyShift action_93
action_85 (65) = happyGoto action_79
action_85 (115) = happyGoto action_80
action_85 (117) = happyGoto action_81
action_85 (119) = happyGoto action_82
action_85 (121) = happyGoto action_336
action_85 _ = happyFail

action_86 (167) = happyShift action_57
action_86 (59) = happyGoto action_335
action_86 _ = happyFail

action_87 _ = happyReduce_227

action_88 _ = happyReduce_223

action_89 _ = happyReduce_219

action_90 _ = happyReduce_224

action_91 _ = happyReduce_226

action_92 _ = happyReduce_225

action_93 _ = happyReduce_62

action_94 (130) = happyShift action_332
action_94 (141) = happyShift action_333
action_94 (142) = happyShift action_334
action_94 (173) = happyAccept
action_94 _ = happyFail

action_95 (130) = happyShift action_329
action_95 (141) = happyShift action_330
action_95 (142) = happyShift action_331
action_95 (173) = happyAccept
action_95 _ = happyFail

action_96 (129) = happyShift action_328
action_96 (173) = happyAccept
action_96 _ = happyFail

action_97 (129) = happyShift action_327
action_97 (173) = happyAccept
action_97 _ = happyFail

action_98 (131) = happyShift action_69
action_98 (134) = happyShift action_70
action_98 (143) = happyShift action_71
action_98 (146) = happyShift action_72
action_98 (150) = happyShift action_73
action_98 (152) = happyShift action_74
action_98 (156) = happyShift action_75
action_98 (157) = happyShift action_76
action_98 (166) = happyShift action_77
action_98 (170) = happyShift action_78
action_98 (173) = happyAccept
action_98 (66) = happyGoto action_64
action_98 (120) = happyGoto action_326
action_98 _ = happyFail

action_99 (131) = happyShift action_84
action_99 (134) = happyShift action_85
action_99 (143) = happyShift action_86
action_99 (146) = happyShift action_87
action_99 (150) = happyShift action_88
action_99 (152) = happyShift action_89
action_99 (156) = happyShift action_90
action_99 (157) = happyShift action_91
action_99 (166) = happyShift action_92
action_99 (170) = happyShift action_93
action_99 (173) = happyAccept
action_99 (65) = happyGoto action_79
action_99 (119) = happyGoto action_325
action_99 _ = happyFail

action_100 (173) = happyAccept
action_100 _ = happyFail

action_101 _ = happyReduce_204

action_102 (173) = happyAccept
action_102 _ = happyFail

action_103 _ = happyReduce_202

action_104 (139) = happyShift action_324
action_104 _ = happyReduce_200

action_105 (173) = happyAccept
action_105 _ = happyFail

action_106 _ = happyReduce_57

action_107 (139) = happyShift action_323
action_107 _ = happyReduce_198

action_108 (173) = happyAccept
action_108 _ = happyFail

action_109 _ = happyReduce_184

action_110 (131) = happyShift action_118
action_110 (134) = happyShift action_119
action_110 (167) = happyShift action_106
action_110 (168) = happyShift action_60
action_110 (169) = happyShift action_120
action_110 (170) = happyShift action_78
action_110 (171) = happyShift action_121
action_110 (60) = happyGoto action_109
action_110 (62) = happyGoto action_135
action_110 (64) = happyGoto action_111
action_110 (66) = happyGoto action_112
action_110 (68) = happyGoto action_113
action_110 (106) = happyGoto action_136
action_110 (108) = happyGoto action_322
action_110 _ = happyReduce_181

action_111 _ = happyReduce_182

action_112 _ = happyReduce_183

action_113 _ = happyReduce_185

action_114 (139) = happyShift action_321
action_114 _ = happyReduce_196

action_115 (135) = happyShift action_320
action_115 _ = happyReduce_169

action_116 _ = happyReduce_173

action_117 (173) = happyAccept
action_117 _ = happyFail

action_118 (131) = happyShift action_118
action_118 (134) = happyShift action_119
action_118 (167) = happyShift action_106
action_118 (168) = happyShift action_60
action_118 (169) = happyShift action_120
action_118 (170) = happyShift action_78
action_118 (171) = happyShift action_121
action_118 (60) = happyGoto action_109
action_118 (62) = happyGoto action_110
action_118 (64) = happyGoto action_111
action_118 (66) = happyGoto action_112
action_118 (68) = happyGoto action_113
action_118 (102) = happyGoto action_114
action_118 (104) = happyGoto action_115
action_118 (106) = happyGoto action_116
action_118 (110) = happyGoto action_319
action_118 _ = happyReduce_195

action_119 (131) = happyShift action_118
action_119 (134) = happyShift action_119
action_119 (167) = happyShift action_106
action_119 (168) = happyShift action_60
action_119 (169) = happyShift action_120
action_119 (170) = happyShift action_78
action_119 (171) = happyShift action_121
action_119 (60) = happyGoto action_109
action_119 (62) = happyGoto action_110
action_119 (64) = happyGoto action_111
action_119 (66) = happyGoto action_112
action_119 (68) = happyGoto action_113
action_119 (102) = happyGoto action_318
action_119 (104) = happyGoto action_115
action_119 (106) = happyGoto action_116
action_119 _ = happyFail

action_120 _ = happyReduce_61

action_121 _ = happyReduce_65

action_122 _ = happyReduce_177

action_123 (131) = happyShift action_131
action_123 (134) = happyShift action_132
action_123 (167) = happyShift action_57
action_123 (168) = happyShift action_63
action_123 (169) = happyShift action_133
action_123 (170) = happyShift action_93
action_123 (171) = happyShift action_134
action_123 (59) = happyGoto action_122
action_123 (61) = happyGoto action_138
action_123 (63) = happyGoto action_124
action_123 (65) = happyGoto action_125
action_123 (67) = happyGoto action_126
action_123 (105) = happyGoto action_139
action_123 (107) = happyGoto action_317
action_123 _ = happyReduce_174

action_124 _ = happyReduce_175

action_125 _ = happyReduce_176

action_126 _ = happyReduce_178

action_127 (139) = happyShift action_316
action_127 _ = happyReduce_193

action_128 (135) = happyShift action_315
action_128 _ = happyReduce_167

action_129 _ = happyReduce_171

action_130 (173) = happyAccept
action_130 _ = happyFail

action_131 (131) = happyShift action_131
action_131 (134) = happyShift action_132
action_131 (167) = happyShift action_57
action_131 (168) = happyShift action_63
action_131 (169) = happyShift action_133
action_131 (170) = happyShift action_93
action_131 (171) = happyShift action_134
action_131 (59) = happyGoto action_122
action_131 (61) = happyGoto action_123
action_131 (63) = happyGoto action_124
action_131 (65) = happyGoto action_125
action_131 (67) = happyGoto action_126
action_131 (101) = happyGoto action_127
action_131 (103) = happyGoto action_128
action_131 (105) = happyGoto action_129
action_131 (109) = happyGoto action_314
action_131 _ = happyReduce_192

action_132 (131) = happyShift action_131
action_132 (134) = happyShift action_132
action_132 (167) = happyShift action_57
action_132 (168) = happyShift action_63
action_132 (169) = happyShift action_133
action_132 (170) = happyShift action_93
action_132 (171) = happyShift action_134
action_132 (59) = happyGoto action_122
action_132 (61) = happyGoto action_123
action_132 (63) = happyGoto action_124
action_132 (65) = happyGoto action_125
action_132 (67) = happyGoto action_126
action_132 (101) = happyGoto action_313
action_132 (103) = happyGoto action_128
action_132 (105) = happyGoto action_129
action_132 _ = happyFail

action_133 _ = happyReduce_60

action_134 _ = happyReduce_64

action_135 _ = happyReduce_181

action_136 (131) = happyShift action_118
action_136 (134) = happyShift action_119
action_136 (167) = happyShift action_106
action_136 (168) = happyShift action_60
action_136 (169) = happyShift action_120
action_136 (170) = happyShift action_78
action_136 (171) = happyShift action_121
action_136 (60) = happyGoto action_109
action_136 (62) = happyGoto action_135
action_136 (64) = happyGoto action_111
action_136 (66) = happyGoto action_112
action_136 (68) = happyGoto action_113
action_136 (106) = happyGoto action_136
action_136 (108) = happyGoto action_312
action_136 _ = happyReduce_190

action_137 (173) = happyAccept
action_137 _ = happyFail

action_138 _ = happyReduce_174

action_139 (131) = happyShift action_131
action_139 (134) = happyShift action_132
action_139 (167) = happyShift action_57
action_139 (168) = happyShift action_63
action_139 (169) = happyShift action_133
action_139 (170) = happyShift action_93
action_139 (171) = happyShift action_134
action_139 (59) = happyGoto action_122
action_139 (61) = happyGoto action_138
action_139 (63) = happyGoto action_124
action_139 (65) = happyGoto action_125
action_139 (67) = happyGoto action_126
action_139 (105) = happyGoto action_139
action_139 (107) = happyGoto action_311
action_139 _ = happyReduce_188

action_140 (173) = happyAccept
action_140 _ = happyFail

action_141 (173) = happyAccept
action_141 _ = happyFail

action_142 (173) = happyAccept
action_142 _ = happyFail

action_143 (173) = happyAccept
action_143 _ = happyFail

action_144 (173) = happyAccept
action_144 _ = happyFail

action_145 (173) = happyAccept
action_145 _ = happyFail

action_146 (173) = happyAccept
action_146 _ = happyFail

action_147 (168) = happyShift action_60
action_147 (173) = happyAccept
action_147 (62) = happyGoto action_149
action_147 (98) = happyGoto action_310
action_147 _ = happyFail

action_148 (168) = happyShift action_63
action_148 (173) = happyAccept
action_148 (61) = happyGoto action_151
action_148 (97) = happyGoto action_309
action_148 _ = happyFail

action_149 _ = happyReduce_161

action_150 (173) = happyAccept
action_150 _ = happyFail

action_151 _ = happyReduce_160

action_152 (173) = happyAccept
action_152 _ = happyFail

action_153 (131) = happyShift action_159
action_153 (134) = happyShift action_160
action_153 (139) = happyShift action_308
action_153 (168) = happyShift action_60
action_153 (62) = happyGoto action_157
action_153 (94) = happyGoto action_302
action_153 _ = happyReduce_158

action_154 (173) = happyAccept
action_154 _ = happyFail

action_155 (131) = happyShift action_163
action_155 (134) = happyShift action_164
action_155 (139) = happyShift action_307
action_155 (168) = happyShift action_63
action_155 (61) = happyGoto action_161
action_155 (93) = happyGoto action_301
action_155 _ = happyReduce_156

action_156 (173) = happyAccept
action_156 _ = happyFail

action_157 _ = happyReduce_153

action_158 (173) = happyAccept
action_158 _ = happyFail

action_159 (92) = happyGoto action_306
action_159 _ = happyFail

action_160 (92) = happyGoto action_153
action_160 (96) = happyGoto action_305
action_160 _ = happyFail

action_161 _ = happyReduce_150

action_162 (173) = happyAccept
action_162 _ = happyFail

action_163 (91) = happyGoto action_304
action_163 _ = happyFail

action_164 (91) = happyGoto action_155
action_164 (95) = happyGoto action_303
action_164 _ = happyFail

action_165 (131) = happyShift action_159
action_165 (134) = happyShift action_160
action_165 (168) = happyShift action_60
action_165 (173) = happyAccept
action_165 (62) = happyGoto action_157
action_165 (94) = happyGoto action_302
action_165 _ = happyFail

action_166 (131) = happyShift action_163
action_166 (134) = happyShift action_164
action_166 (168) = happyShift action_63
action_166 (173) = happyAccept
action_166 (61) = happyGoto action_161
action_166 (93) = happyGoto action_301
action_166 _ = happyFail

action_167 _ = happyReduce_146

action_168 (173) = happyAccept
action_168 _ = happyFail

action_169 _ = happyReduce_144

action_170 (173) = happyAccept
action_170 _ = happyFail

action_171 _ = happyReduce_138

action_172 (173) = happyAccept
action_172 _ = happyFail

action_173 (132) = happyShift action_300
action_173 _ = happyFail

action_174 _ = happyReduce_139

action_175 (135) = happyShift action_299
action_175 _ = happyFail

action_176 (168) = happyShift action_60
action_176 (62) = happyGoto action_167
action_176 (90) = happyGoto action_298
action_176 _ = happyReduce_147

action_177 _ = happyReduce_132

action_178 (173) = happyAccept
action_178 _ = happyFail

action_179 (132) = happyShift action_297
action_179 _ = happyFail

action_180 _ = happyReduce_133

action_181 (135) = happyShift action_296
action_181 _ = happyFail

action_182 (168) = happyShift action_63
action_182 (61) = happyGoto action_169
action_182 (89) = happyGoto action_295
action_182 _ = happyReduce_145

action_183 _ = happyReduce_131

action_184 (173) = happyAccept
action_184 _ = happyFail

action_185 (130) = happyShift action_191
action_185 (131) = happyShift action_185
action_185 (168) = happyShift action_60
action_185 (62) = happyGoto action_183
action_185 (84) = happyGoto action_294
action_185 (86) = happyGoto action_190
action_185 _ = happyFail

action_186 _ = happyReduce_129

action_187 (173) = happyAccept
action_187 _ = happyFail

action_188 (130) = happyShift action_194
action_188 (131) = happyShift action_188
action_188 (168) = happyShift action_63
action_188 (61) = happyGoto action_186
action_188 (83) = happyGoto action_293
action_188 (85) = happyGoto action_193
action_188 _ = happyFail

action_189 (173) = happyAccept
action_189 _ = happyFail

action_190 _ = happyReduce_127

action_191 (131) = happyShift action_185
action_191 (168) = happyShift action_60
action_191 (62) = happyGoto action_183
action_191 (86) = happyGoto action_292
action_191 _ = happyFail

action_192 (173) = happyAccept
action_192 _ = happyFail

action_193 _ = happyReduce_125

action_194 (131) = happyShift action_188
action_194 (168) = happyShift action_63
action_194 (61) = happyGoto action_186
action_194 (85) = happyGoto action_291
action_194 _ = happyFail

action_195 _ = happyReduce_122

action_196 (173) = happyAccept
action_196 _ = happyFail

action_197 _ = happyReduce_123

action_198 _ = happyReduce_120

action_199 (173) = happyAccept
action_199 _ = happyFail

action_200 _ = happyReduce_121

action_201 (130) = happyShift action_191
action_201 (131) = happyShift action_185
action_201 (167) = happyShift action_106
action_201 (168) = happyShift action_60
action_201 (60) = happyGoto action_195
action_201 (62) = happyGoto action_183
action_201 (82) = happyGoto action_254
action_201 (84) = happyGoto action_197
action_201 (86) = happyGoto action_190
action_201 _ = happyReduce_114

action_202 (129) = happyShift action_290
action_202 _ = happyReduce_118

action_203 (173) = happyAccept
action_203 _ = happyFail

action_204 (131) = happyShift action_69
action_204 (134) = happyShift action_70
action_204 (143) = happyShift action_71
action_204 (146) = happyShift action_72
action_204 (150) = happyShift action_73
action_204 (152) = happyShift action_74
action_204 (156) = happyShift action_75
action_204 (157) = happyShift action_76
action_204 (166) = happyShift action_77
action_204 (170) = happyShift action_78
action_204 (66) = happyGoto action_64
action_204 (116) = happyGoto action_65
action_204 (118) = happyGoto action_66
action_204 (120) = happyGoto action_67
action_204 (122) = happyGoto action_289
action_204 _ = happyFail

action_205 (130) = happyShift action_194
action_205 (131) = happyShift action_188
action_205 (167) = happyShift action_57
action_205 (168) = happyShift action_63
action_205 (59) = happyGoto action_198
action_205 (61) = happyGoto action_186
action_205 (81) = happyGoto action_253
action_205 (83) = happyGoto action_200
action_205 (85) = happyGoto action_193
action_205 _ = happyReduce_112

action_206 (129) = happyShift action_288
action_206 _ = happyReduce_116

action_207 (173) = happyAccept
action_207 _ = happyFail

action_208 (131) = happyShift action_84
action_208 (134) = happyShift action_85
action_208 (143) = happyShift action_86
action_208 (146) = happyShift action_87
action_208 (150) = happyShift action_88
action_208 (152) = happyShift action_89
action_208 (156) = happyShift action_90
action_208 (157) = happyShift action_91
action_208 (166) = happyShift action_92
action_208 (170) = happyShift action_93
action_208 (65) = happyGoto action_79
action_208 (115) = happyGoto action_80
action_208 (117) = happyGoto action_81
action_208 (119) = happyGoto action_82
action_208 (121) = happyGoto action_287
action_208 _ = happyFail

action_209 (173) = happyAccept
action_209 _ = happyFail

action_210 (173) = happyAccept
action_210 _ = happyFail

action_211 (173) = happyAccept
action_211 _ = happyFail

action_212 (126) = happyShift action_286
action_212 _ = happyFail

action_213 (167) = happyShift action_106
action_213 (60) = happyGoto action_285
action_213 _ = happyFail

action_214 (168) = happyShift action_60
action_214 (62) = happyGoto action_284
action_214 _ = happyFail

action_215 (167) = happyShift action_106
action_215 (60) = happyGoto action_283
action_215 _ = happyFail

action_216 (168) = happyShift action_60
action_216 (62) = happyGoto action_282
action_216 _ = happyFail

action_217 (168) = happyShift action_60
action_217 (62) = happyGoto action_58
action_217 (124) = happyGoto action_281
action_217 _ = happyFail

action_218 (168) = happyShift action_60
action_218 (62) = happyGoto action_280
action_218 _ = happyFail

action_219 (131) = happyShift action_173
action_219 (133) = happyShift action_174
action_219 (134) = happyShift action_175
action_219 (137) = happyShift action_176
action_219 (168) = happyShift action_60
action_219 (62) = happyGoto action_171
action_219 (88) = happyGoto action_279
action_219 _ = happyFail

action_220 (162) = happyShift action_277
action_220 (165) = happyShift action_278
action_220 (167) = happyShift action_106
action_220 (60) = happyGoto action_104
action_220 (112) = happyGoto action_276
action_220 _ = happyFail

action_221 (164) = happyShift action_275
action_221 _ = happyFail

action_222 (168) = happyShift action_60
action_222 (62) = happyGoto action_274
action_222 _ = happyFail

action_223 (158) = happyShift action_101
action_223 (114) = happyGoto action_273
action_223 _ = happyReduce_205

action_224 (158) = happyShift action_101
action_224 (114) = happyGoto action_272
action_224 _ = happyReduce_205

action_225 (168) = happyShift action_60
action_225 (62) = happyGoto action_271
action_225 _ = happyFail

action_226 (173) = happyAccept
action_226 _ = happyFail

action_227 (126) = happyShift action_270
action_227 _ = happyFail

action_228 (167) = happyShift action_57
action_228 (59) = happyGoto action_269
action_228 _ = happyFail

action_229 (168) = happyShift action_63
action_229 (61) = happyGoto action_268
action_229 _ = happyFail

action_230 (167) = happyShift action_57
action_230 (59) = happyGoto action_267
action_230 _ = happyFail

action_231 (168) = happyShift action_63
action_231 (61) = happyGoto action_266
action_231 _ = happyFail

action_232 (168) = happyShift action_63
action_232 (61) = happyGoto action_61
action_232 (123) = happyGoto action_265
action_232 _ = happyFail

action_233 (168) = happyShift action_63
action_233 (61) = happyGoto action_264
action_233 _ = happyFail

action_234 (131) = happyShift action_179
action_234 (133) = happyShift action_180
action_234 (134) = happyShift action_181
action_234 (137) = happyShift action_182
action_234 (168) = happyShift action_63
action_234 (61) = happyGoto action_177
action_234 (87) = happyGoto action_263
action_234 _ = happyFail

action_235 (162) = happyShift action_261
action_235 (165) = happyShift action_262
action_235 (167) = happyShift action_57
action_235 (59) = happyGoto action_107
action_235 (111) = happyGoto action_260
action_235 _ = happyFail

action_236 (164) = happyShift action_259
action_236 _ = happyFail

action_237 (168) = happyShift action_63
action_237 (61) = happyGoto action_258
action_237 _ = happyFail

action_238 (158) = happyShift action_103
action_238 (113) = happyGoto action_257
action_238 _ = happyReduce_203

action_239 (158) = happyShift action_103
action_239 (113) = happyGoto action_256
action_239 _ = happyReduce_203

action_240 (168) = happyShift action_63
action_240 (61) = happyGoto action_255
action_240 _ = happyFail

action_241 (130) = happyShift action_191
action_241 (131) = happyShift action_185
action_241 (167) = happyShift action_106
action_241 (168) = happyShift action_60
action_241 (173) = happyAccept
action_241 (60) = happyGoto action_195
action_241 (62) = happyGoto action_183
action_241 (82) = happyGoto action_254
action_241 (84) = happyGoto action_197
action_241 (86) = happyGoto action_190
action_241 _ = happyFail

action_242 (130) = happyShift action_194
action_242 (131) = happyShift action_188
action_242 (167) = happyShift action_57
action_242 (168) = happyShift action_63
action_242 (173) = happyAccept
action_242 (59) = happyGoto action_198
action_242 (61) = happyGoto action_186
action_242 (81) = happyGoto action_253
action_242 (83) = happyGoto action_200
action_242 (85) = happyGoto action_193
action_242 _ = happyFail

action_243 (173) = happyAccept
action_243 _ = happyFail

action_244 (125) = happyShift action_252
action_244 _ = happyReduce_72

action_245 (173) = happyAccept
action_245 _ = happyFail

action_246 (125) = happyShift action_251
action_246 _ = happyReduce_69

action_247 (173) = happyAccept
action_247 _ = happyFail

action_248 _ = happyReduce_67

action_249 (173) = happyAccept
action_249 _ = happyFail

action_250 _ = happyReduce_66

action_251 (131) = happyShift action_179
action_251 (133) = happyShift action_180
action_251 (134) = happyShift action_181
action_251 (137) = happyShift action_182
action_251 (145) = happyShift action_228
action_251 (147) = happyShift action_229
action_251 (148) = happyShift action_230
action_251 (149) = happyShift action_231
action_251 (151) = happyShift action_232
action_251 (153) = happyShift action_233
action_251 (154) = happyShift action_234
action_251 (155) = happyShift action_235
action_251 (159) = happyShift action_236
action_251 (160) = happyShift action_237
action_251 (161) = happyShift action_238
action_251 (163) = happyShift action_239
action_251 (164) = happyShift action_240
action_251 (168) = happyShift action_63
action_251 (61) = happyGoto action_177
action_251 (71) = happyGoto action_408
action_251 (75) = happyGoto action_246
action_251 (87) = happyGoto action_227
action_251 _ = happyReduce_68

action_252 (131) = happyShift action_173
action_252 (133) = happyShift action_174
action_252 (134) = happyShift action_175
action_252 (137) = happyShift action_176
action_252 (145) = happyShift action_213
action_252 (147) = happyShift action_214
action_252 (148) = happyShift action_215
action_252 (149) = happyShift action_216
action_252 (151) = happyShift action_217
action_252 (153) = happyShift action_218
action_252 (154) = happyShift action_219
action_252 (155) = happyShift action_220
action_252 (159) = happyShift action_221
action_252 (160) = happyShift action_222
action_252 (161) = happyShift action_223
action_252 (163) = happyShift action_224
action_252 (164) = happyShift action_225
action_252 (168) = happyShift action_60
action_252 (62) = happyGoto action_171
action_252 (72) = happyGoto action_407
action_252 (76) = happyGoto action_244
action_252 (88) = happyGoto action_212
action_252 _ = happyReduce_71

action_253 _ = happyReduce_75

action_254 _ = happyReduce_77

action_255 (131) = happyShift action_84
action_255 (134) = happyShift action_85
action_255 (143) = happyShift action_86
action_255 (146) = happyShift action_87
action_255 (150) = happyShift action_88
action_255 (152) = happyShift action_89
action_255 (156) = happyShift action_90
action_255 (157) = happyShift action_91
action_255 (166) = happyShift action_92
action_255 (170) = happyShift action_93
action_255 (65) = happyGoto action_79
action_255 (115) = happyGoto action_80
action_255 (117) = happyGoto action_81
action_255 (119) = happyGoto action_82
action_255 (121) = happyGoto action_406
action_255 _ = happyFail

action_256 (130) = happyShift action_194
action_256 (131) = happyShift action_188
action_256 (168) = happyShift action_63
action_256 (61) = happyGoto action_186
action_256 (83) = happyGoto action_405
action_256 (85) = happyGoto action_193
action_256 _ = happyFail

action_257 (130) = happyShift action_194
action_257 (131) = happyShift action_188
action_257 (168) = happyShift action_63
action_257 (61) = happyGoto action_186
action_257 (83) = happyGoto action_404
action_257 (85) = happyGoto action_193
action_257 _ = happyFail

action_258 (127) = happyShift action_403
action_258 _ = happyFail

action_259 (168) = happyShift action_63
action_259 (61) = happyGoto action_402
action_259 _ = happyFail

action_260 _ = happyReduce_92

action_261 (167) = happyShift action_57
action_261 (59) = happyGoto action_107
action_261 (111) = happyGoto action_401
action_261 _ = happyFail

action_262 _ = happyReduce_94

action_263 (126) = happyShift action_400
action_263 _ = happyFail

action_264 (138) = happyShift action_399
action_264 _ = happyFail

action_265 _ = happyReduce_84

action_266 (99) = happyGoto action_398
action_266 _ = happyReduce_162

action_267 (167) = happyShift action_57
action_267 (59) = happyGoto action_397
action_267 _ = happyReduce_79

action_268 (169) = happyShift action_133
action_268 (63) = happyGoto action_396
action_268 _ = happyFail

action_269 (167) = happyShift action_57
action_269 (59) = happyGoto action_395
action_269 _ = happyFail

action_270 (130) = happyShift action_194
action_270 (131) = happyShift action_188
action_270 (168) = happyShift action_63
action_270 (61) = happyGoto action_186
action_270 (83) = happyGoto action_394
action_270 (85) = happyGoto action_193
action_270 _ = happyFail

action_271 (131) = happyShift action_69
action_271 (134) = happyShift action_70
action_271 (143) = happyShift action_71
action_271 (146) = happyShift action_72
action_271 (150) = happyShift action_73
action_271 (152) = happyShift action_74
action_271 (156) = happyShift action_75
action_271 (157) = happyShift action_76
action_271 (166) = happyShift action_77
action_271 (170) = happyShift action_78
action_271 (66) = happyGoto action_64
action_271 (116) = happyGoto action_65
action_271 (118) = happyGoto action_66
action_271 (120) = happyGoto action_67
action_271 (122) = happyGoto action_393
action_271 _ = happyFail

action_272 (130) = happyShift action_191
action_272 (131) = happyShift action_185
action_272 (168) = happyShift action_60
action_272 (62) = happyGoto action_183
action_272 (84) = happyGoto action_392
action_272 (86) = happyGoto action_190
action_272 _ = happyFail

action_273 (130) = happyShift action_191
action_273 (131) = happyShift action_185
action_273 (168) = happyShift action_60
action_273 (62) = happyGoto action_183
action_273 (84) = happyGoto action_391
action_273 (86) = happyGoto action_190
action_273 _ = happyFail

action_274 (127) = happyShift action_390
action_274 _ = happyFail

action_275 (168) = happyShift action_60
action_275 (62) = happyGoto action_389
action_275 _ = happyFail

action_276 _ = happyReduce_109

action_277 (167) = happyShift action_106
action_277 (60) = happyGoto action_104
action_277 (112) = happyGoto action_388
action_277 _ = happyFail

action_278 _ = happyReduce_111

action_279 (126) = happyShift action_387
action_279 _ = happyFail

action_280 (138) = happyShift action_386
action_280 _ = happyFail

action_281 _ = happyReduce_101

action_282 (100) = happyGoto action_385
action_282 _ = happyReduce_164

action_283 (167) = happyShift action_106
action_283 (60) = happyGoto action_384
action_283 _ = happyReduce_96

action_284 (169) = happyShift action_120
action_284 (64) = happyGoto action_383
action_284 _ = happyFail

action_285 (167) = happyShift action_106
action_285 (60) = happyGoto action_382
action_285 _ = happyFail

action_286 (130) = happyShift action_191
action_286 (131) = happyShift action_185
action_286 (168) = happyShift action_60
action_286 (62) = happyGoto action_183
action_286 (84) = happyGoto action_381
action_286 (86) = happyGoto action_190
action_286 _ = happyFail

action_287 _ = happyReduce_113

action_288 (128) = happyShift action_208
action_288 (73) = happyGoto action_205
action_288 (77) = happyGoto action_206
action_288 (79) = happyGoto action_380
action_288 _ = happyReduce_74

action_289 _ = happyReduce_115

action_290 (128) = happyShift action_204
action_290 (74) = happyGoto action_201
action_290 (78) = happyGoto action_202
action_290 (80) = happyGoto action_379
action_290 _ = happyReduce_76

action_291 _ = happyReduce_124

action_292 _ = happyReduce_126

action_293 (132) = happyShift action_378
action_293 _ = happyFail

action_294 (132) = happyShift action_377
action_294 _ = happyFail

action_295 _ = happyReduce_137

action_296 (131) = happyShift action_375
action_296 (136) = happyShift action_376
action_296 _ = happyFail

action_297 _ = happyReduce_134

action_298 _ = happyReduce_143

action_299 (131) = happyShift action_373
action_299 (136) = happyShift action_374
action_299 _ = happyFail

action_300 _ = happyReduce_140

action_301 _ = happyReduce_148

action_302 _ = happyReduce_149

action_303 (136) = happyShift action_372
action_303 _ = happyFail

action_304 (131) = happyShift action_163
action_304 (132) = happyShift action_371
action_304 (134) = happyShift action_164
action_304 (168) = happyShift action_63
action_304 (61) = happyGoto action_161
action_304 (93) = happyGoto action_301
action_304 _ = happyFail

action_305 (136) = happyShift action_370
action_305 _ = happyFail

action_306 (131) = happyShift action_159
action_306 (132) = happyShift action_369
action_306 (134) = happyShift action_160
action_306 (168) = happyShift action_60
action_306 (62) = happyGoto action_157
action_306 (94) = happyGoto action_302
action_306 _ = happyFail

action_307 (91) = happyGoto action_155
action_307 (95) = happyGoto action_368
action_307 _ = happyFail

action_308 (92) = happyGoto action_153
action_308 (96) = happyGoto action_367
action_308 _ = happyFail

action_309 _ = happyReduce_163

action_310 _ = happyReduce_165

action_311 _ = happyReduce_189

action_312 _ = happyReduce_191

action_313 (136) = happyShift action_366
action_313 _ = happyFail

action_314 (132) = happyShift action_365
action_314 _ = happyFail

action_315 (131) = happyShift action_131
action_315 (134) = happyShift action_132
action_315 (167) = happyShift action_57
action_315 (168) = happyShift action_63
action_315 (169) = happyShift action_133
action_315 (170) = happyShift action_93
action_315 (171) = happyShift action_134
action_315 (59) = happyGoto action_122
action_315 (61) = happyGoto action_123
action_315 (63) = happyGoto action_124
action_315 (65) = happyGoto action_125
action_315 (67) = happyGoto action_126
action_315 (101) = happyGoto action_364
action_315 (103) = happyGoto action_128
action_315 (105) = happyGoto action_129
action_315 _ = happyFail

action_316 (131) = happyShift action_131
action_316 (134) = happyShift action_132
action_316 (167) = happyShift action_57
action_316 (168) = happyShift action_63
action_316 (169) = happyShift action_133
action_316 (170) = happyShift action_93
action_316 (171) = happyShift action_134
action_316 (59) = happyGoto action_122
action_316 (61) = happyGoto action_123
action_316 (63) = happyGoto action_124
action_316 (65) = happyGoto action_125
action_316 (67) = happyGoto action_126
action_316 (101) = happyGoto action_127
action_316 (103) = happyGoto action_128
action_316 (105) = happyGoto action_129
action_316 (109) = happyGoto action_363
action_316 _ = happyReduce_192

action_317 _ = happyReduce_170

action_318 (136) = happyShift action_362
action_318 _ = happyFail

action_319 (132) = happyShift action_361
action_319 _ = happyFail

action_320 (131) = happyShift action_118
action_320 (134) = happyShift action_119
action_320 (167) = happyShift action_106
action_320 (168) = happyShift action_60
action_320 (169) = happyShift action_120
action_320 (170) = happyShift action_78
action_320 (171) = happyShift action_121
action_320 (60) = happyGoto action_109
action_320 (62) = happyGoto action_110
action_320 (64) = happyGoto action_111
action_320 (66) = happyGoto action_112
action_320 (68) = happyGoto action_113
action_320 (102) = happyGoto action_360
action_320 (104) = happyGoto action_115
action_320 (106) = happyGoto action_116
action_320 _ = happyFail

action_321 (131) = happyShift action_118
action_321 (134) = happyShift action_119
action_321 (167) = happyShift action_106
action_321 (168) = happyShift action_60
action_321 (169) = happyShift action_120
action_321 (170) = happyShift action_78
action_321 (171) = happyShift action_121
action_321 (60) = happyGoto action_109
action_321 (62) = happyGoto action_110
action_321 (64) = happyGoto action_111
action_321 (66) = happyGoto action_112
action_321 (68) = happyGoto action_113
action_321 (102) = happyGoto action_114
action_321 (104) = happyGoto action_115
action_321 (106) = happyGoto action_116
action_321 (110) = happyGoto action_359
action_321 _ = happyReduce_195

action_322 _ = happyReduce_172

action_323 (167) = happyShift action_57
action_323 (59) = happyGoto action_107
action_323 (111) = happyGoto action_358
action_323 _ = happyFail

action_324 (167) = happyShift action_106
action_324 (60) = happyGoto action_104
action_324 (112) = happyGoto action_357
action_324 _ = happyFail

action_325 (130) = happyShift action_329
action_325 (141) = happyShift action_330
action_325 (142) = happyShift action_331
action_325 _ = happyReduce_206

action_326 (130) = happyShift action_332
action_326 (141) = happyShift action_333
action_326 (142) = happyShift action_334
action_326 _ = happyReduce_208

action_327 (131) = happyShift action_84
action_327 (134) = happyShift action_85
action_327 (143) = happyShift action_86
action_327 (146) = happyShift action_87
action_327 (150) = happyShift action_88
action_327 (152) = happyShift action_89
action_327 (156) = happyShift action_90
action_327 (157) = happyShift action_91
action_327 (166) = happyShift action_92
action_327 (170) = happyShift action_93
action_327 (65) = happyGoto action_79
action_327 (115) = happyGoto action_356
action_327 (119) = happyGoto action_82
action_327 _ = happyFail

action_328 (131) = happyShift action_69
action_328 (134) = happyShift action_70
action_328 (143) = happyShift action_71
action_328 (146) = happyShift action_72
action_328 (150) = happyShift action_73
action_328 (152) = happyShift action_74
action_328 (156) = happyShift action_75
action_328 (157) = happyShift action_76
action_328 (166) = happyShift action_77
action_328 (170) = happyShift action_78
action_328 (66) = happyGoto action_64
action_328 (116) = happyGoto action_355
action_328 (120) = happyGoto action_67
action_328 _ = happyFail

action_329 _ = happyReduce_218

action_330 _ = happyReduce_216

action_331 _ = happyReduce_217

action_332 _ = happyReduce_231

action_333 _ = happyReduce_229

action_334 _ = happyReduce_230

action_335 (144) = happyShift action_354
action_335 _ = happyFail

action_336 (136) = happyShift action_353
action_336 _ = happyFail

action_337 (132) = happyShift action_352
action_337 _ = happyFail

action_338 (131) = happyShift action_84
action_338 (134) = happyShift action_85
action_338 (143) = happyShift action_86
action_338 (146) = happyShift action_87
action_338 (150) = happyShift action_88
action_338 (152) = happyShift action_89
action_338 (156) = happyShift action_90
action_338 (157) = happyShift action_91
action_338 (166) = happyShift action_92
action_338 (170) = happyShift action_93
action_338 (65) = happyGoto action_79
action_338 (115) = happyGoto action_351
action_338 (119) = happyGoto action_82
action_338 _ = happyFail

action_339 (144) = happyShift action_350
action_339 _ = happyFail

action_340 (136) = happyShift action_349
action_340 _ = happyFail

action_341 (132) = happyShift action_348
action_341 _ = happyFail

action_342 (131) = happyShift action_69
action_342 (134) = happyShift action_70
action_342 (143) = happyShift action_71
action_342 (146) = happyShift action_72
action_342 (150) = happyShift action_73
action_342 (152) = happyShift action_74
action_342 (156) = happyShift action_75
action_342 (157) = happyShift action_76
action_342 (166) = happyShift action_77
action_342 (170) = happyShift action_78
action_342 (66) = happyGoto action_64
action_342 (116) = happyGoto action_347
action_342 (120) = happyGoto action_67
action_342 _ = happyFail

action_343 (168) = happyShift action_63
action_343 (61) = happyGoto action_61
action_343 (123) = happyGoto action_346
action_343 _ = happyFail

action_344 (168) = happyShift action_60
action_344 (62) = happyGoto action_58
action_344 (124) = happyGoto action_345
action_344 _ = happyFail

action_345 _ = happyReduce_247

action_346 _ = happyReduce_245

action_347 (131) = happyShift action_69
action_347 (134) = happyShift action_70
action_347 (143) = happyShift action_71
action_347 (146) = happyShift action_72
action_347 (150) = happyShift action_73
action_347 (152) = happyShift action_74
action_347 (156) = happyShift action_75
action_347 (157) = happyShift action_76
action_347 (166) = happyShift action_77
action_347 (170) = happyShift action_78
action_347 (66) = happyGoto action_64
action_347 (120) = happyGoto action_326
action_347 _ = happyReduce_214

action_348 _ = happyReduce_234

action_349 _ = happyReduce_241

action_350 _ = happyReduce_235

action_351 (131) = happyShift action_84
action_351 (134) = happyShift action_85
action_351 (143) = happyShift action_86
action_351 (146) = happyShift action_87
action_351 (150) = happyShift action_88
action_351 (152) = happyShift action_89
action_351 (156) = happyShift action_90
action_351 (157) = happyShift action_91
action_351 (166) = happyShift action_92
action_351 (170) = happyShift action_93
action_351 (65) = happyGoto action_79
action_351 (119) = happyGoto action_325
action_351 _ = happyReduce_211

action_352 _ = happyReduce_221

action_353 _ = happyReduce_228

action_354 _ = happyReduce_222

action_355 (131) = happyShift action_69
action_355 (134) = happyShift action_70
action_355 (143) = happyShift action_71
action_355 (146) = happyShift action_72
action_355 (150) = happyShift action_73
action_355 (152) = happyShift action_74
action_355 (156) = happyShift action_75
action_355 (157) = happyShift action_76
action_355 (166) = happyShift action_77
action_355 (170) = happyShift action_78
action_355 (66) = happyGoto action_64
action_355 (120) = happyGoto action_326
action_355 _ = happyReduce_213

action_356 (131) = happyShift action_84
action_356 (134) = happyShift action_85
action_356 (143) = happyShift action_86
action_356 (146) = happyShift action_87
action_356 (150) = happyShift action_88
action_356 (152) = happyShift action_89
action_356 (156) = happyShift action_90
action_356 (157) = happyShift action_91
action_356 (166) = happyShift action_92
action_356 (170) = happyShift action_93
action_356 (65) = happyGoto action_79
action_356 (119) = happyGoto action_325
action_356 _ = happyReduce_210

action_357 _ = happyReduce_201

action_358 _ = happyReduce_199

action_359 _ = happyReduce_197

action_360 _ = happyReduce_168

action_361 _ = happyReduce_186

action_362 _ = happyReduce_187

action_363 _ = happyReduce_194

action_364 _ = happyReduce_166

action_365 _ = happyReduce_179

action_366 _ = happyReduce_180

action_367 _ = happyReduce_159

action_368 _ = happyReduce_157

action_369 _ = happyReduce_155

action_370 _ = happyReduce_154

action_371 _ = happyReduce_152

action_372 _ = happyReduce_151

action_373 (132) = happyShift action_428
action_373 _ = happyFail

action_374 _ = happyReduce_141

action_375 (132) = happyShift action_427
action_375 _ = happyFail

action_376 _ = happyReduce_135

action_377 _ = happyReduce_130

action_378 _ = happyReduce_128

action_379 _ = happyReduce_119

action_380 _ = happyReduce_117

action_381 (127) = happyShift action_426
action_381 _ = happyFail

action_382 (167) = happyShift action_106
action_382 (60) = happyGoto action_425
action_382 _ = happyFail

action_383 _ = happyReduce_104

action_384 _ = happyReduce_97

action_385 (138) = happyShift action_424
action_385 (168) = happyShift action_60
action_385 (62) = happyGoto action_149
action_385 (98) = happyGoto action_310
action_385 _ = happyFail

action_386 (92) = happyGoto action_423
action_386 _ = happyFail

action_387 (130) = happyShift action_191
action_387 (131) = happyShift action_185
action_387 (168) = happyShift action_60
action_387 (62) = happyGoto action_183
action_387 (84) = happyGoto action_422
action_387 (86) = happyGoto action_190
action_387 _ = happyFail

action_388 _ = happyReduce_110

action_389 (131) = happyShift action_69
action_389 (134) = happyShift action_70
action_389 (143) = happyShift action_71
action_389 (146) = happyShift action_72
action_389 (150) = happyShift action_73
action_389 (152) = happyShift action_74
action_389 (156) = happyShift action_75
action_389 (157) = happyShift action_76
action_389 (166) = happyShift action_77
action_389 (170) = happyShift action_78
action_389 (66) = happyGoto action_64
action_389 (116) = happyGoto action_65
action_389 (118) = happyGoto action_66
action_389 (120) = happyGoto action_67
action_389 (122) = happyGoto action_421
action_389 _ = happyFail

action_390 (128) = happyShift action_204
action_390 (74) = happyGoto action_201
action_390 (78) = happyGoto action_202
action_390 (80) = happyGoto action_420
action_390 _ = happyReduce_76

action_391 (167) = happyShift action_106
action_391 (60) = happyGoto action_419
action_391 _ = happyFail

action_392 (167) = happyShift action_106
action_392 (60) = happyGoto action_418
action_392 _ = happyFail

action_393 _ = happyReduce_99

action_394 (127) = happyShift action_417
action_394 _ = happyFail

action_395 (167) = happyShift action_57
action_395 (59) = happyGoto action_416
action_395 _ = happyFail

action_396 _ = happyReduce_87

action_397 _ = happyReduce_80

action_398 (138) = happyShift action_415
action_398 (168) = happyShift action_63
action_398 (61) = happyGoto action_151
action_398 (97) = happyGoto action_309
action_398 _ = happyFail

action_399 (91) = happyGoto action_414
action_399 _ = happyFail

action_400 (130) = happyShift action_194
action_400 (131) = happyShift action_188
action_400 (168) = happyShift action_63
action_400 (61) = happyGoto action_186
action_400 (83) = happyGoto action_413
action_400 (85) = happyGoto action_193
action_400 _ = happyFail

action_401 _ = happyReduce_93

action_402 (131) = happyShift action_84
action_402 (134) = happyShift action_85
action_402 (143) = happyShift action_86
action_402 (146) = happyShift action_87
action_402 (150) = happyShift action_88
action_402 (152) = happyShift action_89
action_402 (156) = happyShift action_90
action_402 (157) = happyShift action_91
action_402 (166) = happyShift action_92
action_402 (170) = happyShift action_93
action_402 (65) = happyGoto action_79
action_402 (115) = happyGoto action_80
action_402 (117) = happyGoto action_81
action_402 (119) = happyGoto action_82
action_402 (121) = happyGoto action_412
action_402 _ = happyFail

action_403 (128) = happyShift action_208
action_403 (73) = happyGoto action_205
action_403 (77) = happyGoto action_206
action_403 (79) = happyGoto action_411
action_403 _ = happyReduce_74

action_404 (167) = happyShift action_57
action_404 (59) = happyGoto action_410
action_404 _ = happyFail

action_405 (167) = happyShift action_57
action_405 (59) = happyGoto action_409
action_405 _ = happyFail

action_406 _ = happyReduce_82

action_407 _ = happyReduce_73

action_408 _ = happyReduce_70

action_409 _ = happyReduce_86

action_410 _ = happyReduce_85

action_411 _ = happyReduce_88

action_412 _ = happyReduce_83

action_413 (127) = happyShift action_436
action_413 _ = happyFail

action_414 (131) = happyShift action_163
action_414 (134) = happyShift action_164
action_414 (168) = happyShift action_63
action_414 (61) = happyGoto action_161
action_414 (93) = happyGoto action_301
action_414 _ = happyReduce_90

action_415 (131) = happyShift action_131
action_415 (134) = happyShift action_132
action_415 (167) = happyShift action_57
action_415 (168) = happyShift action_63
action_415 (169) = happyShift action_133
action_415 (170) = happyShift action_93
action_415 (171) = happyShift action_134
action_415 (59) = happyGoto action_122
action_415 (61) = happyGoto action_123
action_415 (63) = happyGoto action_124
action_415 (65) = happyGoto action_125
action_415 (67) = happyGoto action_126
action_415 (101) = happyGoto action_435
action_415 (103) = happyGoto action_128
action_415 (105) = happyGoto action_129
action_415 _ = happyFail

action_416 _ = happyReduce_91

action_417 (128) = happyShift action_208
action_417 (73) = happyGoto action_205
action_417 (77) = happyGoto action_434
action_417 _ = happyReduce_74

action_418 _ = happyReduce_103

action_419 _ = happyReduce_102

action_420 _ = happyReduce_105

action_421 _ = happyReduce_100

action_422 (127) = happyShift action_433
action_422 _ = happyFail

action_423 (131) = happyShift action_159
action_423 (134) = happyShift action_160
action_423 (168) = happyShift action_60
action_423 (62) = happyGoto action_157
action_423 (94) = happyGoto action_302
action_423 _ = happyReduce_107

action_424 (131) = happyShift action_118
action_424 (134) = happyShift action_119
action_424 (167) = happyShift action_106
action_424 (168) = happyShift action_60
action_424 (169) = happyShift action_120
action_424 (170) = happyShift action_78
action_424 (171) = happyShift action_121
action_424 (60) = happyGoto action_109
action_424 (62) = happyGoto action_110
action_424 (64) = happyGoto action_111
action_424 (66) = happyGoto action_112
action_424 (68) = happyGoto action_113
action_424 (102) = happyGoto action_432
action_424 (104) = happyGoto action_115
action_424 (106) = happyGoto action_116
action_424 _ = happyFail

action_425 _ = happyReduce_108

action_426 (128) = happyShift action_204
action_426 (74) = happyGoto action_201
action_426 (78) = happyGoto action_431
action_426 _ = happyReduce_76

action_427 (136) = happyShift action_430
action_427 _ = happyFail

action_428 (136) = happyShift action_429
action_428 _ = happyFail

action_429 _ = happyReduce_142

action_430 _ = happyReduce_136

action_431 _ = happyReduce_95

action_432 _ = happyReduce_106

action_433 (74) = happyGoto action_438
action_433 _ = happyReduce_76

action_434 _ = happyReduce_78

action_435 _ = happyReduce_89

action_436 (73) = happyGoto action_437
action_436 _ = happyReduce_74

action_437 (130) = happyShift action_194
action_437 (131) = happyShift action_188
action_437 (167) = happyShift action_57
action_437 (168) = happyShift action_63
action_437 (59) = happyGoto action_198
action_437 (61) = happyGoto action_186
action_437 (81) = happyGoto action_253
action_437 (83) = happyGoto action_200
action_437 (85) = happyGoto action_193
action_437 _ = happyReduce_81

action_438 (130) = happyShift action_191
action_438 (131) = happyShift action_185
action_438 (167) = happyShift action_106
action_438 (168) = happyShift action_60
action_438 (60) = happyGoto action_195
action_438 (62) = happyGoto action_183
action_438 (82) = happyGoto action_254
action_438 (84) = happyGoto action_197
action_438 (86) = happyGoto action_190
action_438 _ = happyReduce_98

happyReduce_56 = happySpecReduce_1  59 happyReduction_56
happyReduction_56 (HappyTerminal (PT _ (TL happy_var_1)))
	 =  HappyAbsSyn59
		 (happy_var_1
	)
happyReduction_56 _  = notHappyAtAll 

happyReduce_57 = happySpecReduce_1  60 happyReduction_57
happyReduction_57 (HappyTerminal (PT _ (TL happy_var_1)))
	 =  HappyAbsSyn60
		 (fromString myLocation happy_var_1
	)
happyReduction_57 _  = notHappyAtAll 

happyReduce_58 = happySpecReduce_1  61 happyReduction_58
happyReduction_58 (HappyTerminal (PT _ (TV happy_var_1)))
	 =  HappyAbsSyn61
		 (Ident happy_var_1
	)
happyReduction_58 _  = notHappyAtAll 

happyReduce_59 = happySpecReduce_1  62 happyReduction_59
happyReduction_59 (HappyTerminal (PT _ (TV happy_var_1)))
	 =  HappyAbsSyn60
		 (fromToken myLocation "Ident" happy_var_1
	)
happyReduction_59 _  = notHappyAtAll 

happyReduce_60 = happySpecReduce_1  63 happyReduction_60
happyReduction_60 (HappyTerminal (PT _ (TI happy_var_1)))
	 =  HappyAbsSyn63
		 ((read happy_var_1) :: Integer
	)
happyReduction_60 _  = notHappyAtAll 

happyReduce_61 = happySpecReduce_1  64 happyReduction_61
happyReduction_61 (HappyTerminal (PT _ (TI happy_var_1)))
	 =  HappyAbsSyn60
		 (fromLit myLocation (read happy_var_1 :: Integer)
	)
happyReduction_61 _  = notHappyAtAll 

happyReduce_62 = happySpecReduce_1  65 happyReduction_62
happyReduction_62 (HappyTerminal (PT _ (TC happy_var_1)))
	 =  HappyAbsSyn65
		 ((read happy_var_1) :: Char
	)
happyReduction_62 _  = notHappyAtAll 

happyReduce_63 = happySpecReduce_1  66 happyReduction_63
happyReduction_63 (HappyTerminal (PT _ (TC happy_var_1)))
	 =  HappyAbsSyn60
		 (fromLit myLocation  (read happy_var_1 :: Char)
	)
happyReduction_63 _  = notHappyAtAll 

happyReduce_64 = happySpecReduce_1  67 happyReduction_64
happyReduction_64 (HappyTerminal (PT _ (TD happy_var_1)))
	 =  HappyAbsSyn67
		 ((read happy_var_1) :: Double
	)
happyReduction_64 _  = notHappyAtAll 

happyReduce_65 = happySpecReduce_1  68 happyReduction_65
happyReduction_65 (HappyTerminal (PT _ (TD happy_var_1)))
	 =  HappyAbsSyn60
		 (fromLit myLocation  (read happy_var_1 :: Double)
	)
happyReduction_65 _  = notHappyAtAll 

happyReduce_66 = happySpecReduce_1  69 happyReduction_66
happyReduction_66 (HappyAbsSyn71  happy_var_1)
	 =  HappyAbsSyn69
		 (Grammar (happy_var_1)
	)
happyReduction_66 _  = notHappyAtAll 

happyReduce_67 = happySpecReduce_1  70 happyReduction_67
happyReduction_67 (HappyAbsSyn60  happy_var_1)
	 =  HappyAbsSyn60
		 (appEPAll myLocation "Grammar"  [happy_var_1]
	)
happyReduction_67 _  = notHappyAtAll 

happyReduce_68 = happySpecReduce_0  71 happyReduction_68
happyReduction_68  =  HappyAbsSyn71
		 ([]
	)

happyReduce_69 = happySpecReduce_1  71 happyReduction_69
happyReduction_69 (HappyAbsSyn75  happy_var_1)
	 =  HappyAbsSyn71
		 ((:[]) (happy_var_1)
	)
happyReduction_69 _  = notHappyAtAll 

happyReduce_70 = happySpecReduce_3  71 happyReduction_70
happyReduction_70 (HappyAbsSyn71  happy_var_3)
	_
	(HappyAbsSyn75  happy_var_1)
	 =  HappyAbsSyn71
		 ((:) (happy_var_1) (happy_var_3)
	)
happyReduction_70 _ _ _  = notHappyAtAll 

happyReduce_71 = happySpecReduce_0  72 happyReduction_71
happyReduction_71  =  HappyAbsSyn60
		 (appEPAll myLocation  "[]" []
	)

happyReduce_72 = happySpecReduce_1  72 happyReduction_72
happyReduction_72 (HappyAbsSyn60  happy_var_1)
	 =  HappyAbsSyn60
		 (appEPAllL myLocation  [happy_var_1]
	)
happyReduction_72 _  = notHappyAtAll 

happyReduce_73 = happySpecReduce_3  72 happyReduction_73
happyReduction_73 (HappyAbsSyn60  happy_var_3)
	_
	(HappyAbsSyn60  happy_var_1)
	 =  HappyAbsSyn60
		 (appEPAll myLocation ":"  [happy_var_1,happy_var_3]
	)
happyReduction_73 _ _ _  = notHappyAtAll 

happyReduce_74 = happySpecReduce_0  73 happyReduction_74
happyReduction_74  =  HappyAbsSyn73
		 ([]
	)

happyReduce_75 = happySpecReduce_2  73 happyReduction_75
happyReduction_75 (HappyAbsSyn81  happy_var_2)
	(HappyAbsSyn73  happy_var_1)
	 =  HappyAbsSyn73
		 (flip (:) (happy_var_1) (happy_var_2)
	)
happyReduction_75 _ _  = notHappyAtAll 

happyReduce_76 = happySpecReduce_0  74 happyReduction_76
happyReduction_76  =  HappyAbsSyn60
		 (appEPAll myLocation  "[]" []
	)

happyReduce_77 = happySpecReduce_2  74 happyReduction_77
happyReduction_77 (HappyAbsSyn60  happy_var_2)
	(HappyAbsSyn60  happy_var_1)
	 =  HappyAbsSyn60
		 (appEPAllL myLocation  [happy_var_1,happy_var_2]
	)
happyReduction_77 _ _  = notHappyAtAll 

happyReduce_78 = happyReduce 5 75 happyReduction_78
happyReduction_78 ((HappyAbsSyn77  happy_var_5) `HappyStk`
	_ `HappyStk`
	(HappyAbsSyn83  happy_var_3) `HappyStk`
	_ `HappyStk`
	(HappyAbsSyn87  happy_var_1) `HappyStk`
	happyRest)
	 = HappyAbsSyn75
		 (Rule (happy_var_1) (happy_var_3) (happy_var_5)
	) `HappyStk` happyRest

happyReduce_79 = happySpecReduce_2  75 happyReduction_79
happyReduction_79 (HappyAbsSyn59  happy_var_2)
	_
	 =  HappyAbsSyn75
		 (Comment (happy_var_2)
	)
happyReduction_79 _ _  = notHappyAtAll 

happyReduce_80 = happySpecReduce_3  75 happyReduction_80
happyReduction_80 (HappyAbsSyn59  happy_var_3)
	(HappyAbsSyn59  happy_var_2)
	_
	 =  HappyAbsSyn75
		 (Comments (happy_var_2) (happy_var_3)
	)
happyReduction_80 _ _ _  = notHappyAtAll 

happyReduce_81 = happyReduce 6 75 happyReduction_81
happyReduction_81 ((HappyAbsSyn73  happy_var_6) `HappyStk`
	_ `HappyStk`
	(HappyAbsSyn83  happy_var_4) `HappyStk`
	_ `HappyStk`
	(HappyAbsSyn87  happy_var_2) `HappyStk`
	_ `HappyStk`
	happyRest)
	 = HappyAbsSyn75
		 (Internal (happy_var_2) (happy_var_4) (reverse $ happy_var_6)
	) `HappyStk` happyRest

happyReduce_82 = happySpecReduce_3  75 happyReduction_82
happyReduction_82 (HappyAbsSyn115  happy_var_3)
	(HappyAbsSyn61  happy_var_2)
	_
	 =  HappyAbsSyn75
		 (Token (happy_var_2) (happy_var_3)
	)
happyReduction_82 _ _ _  = notHappyAtAll 

happyReduce_83 = happyReduce 4 75 happyReduction_83
happyReduction_83 ((HappyAbsSyn115  happy_var_4) `HappyStk`
	(HappyAbsSyn61  happy_var_3) `HappyStk`
	_ `HappyStk`
	_ `HappyStk`
	happyRest)
	 = HappyAbsSyn75
		 (PosToken (happy_var_3) (happy_var_4)
	) `HappyStk` happyRest

happyReduce_84 = happySpecReduce_2  75 happyReduction_84
happyReduction_84 (HappyAbsSyn123  happy_var_2)
	_
	 =  HappyAbsSyn75
		 (Entryp (happy_var_2)
	)
happyReduction_84 _ _  = notHappyAtAll 

happyReduce_85 = happyReduce 4 75 happyReduction_85
happyReduction_85 ((HappyAbsSyn59  happy_var_4) `HappyStk`
	(HappyAbsSyn83  happy_var_3) `HappyStk`
	(HappyAbsSyn113  happy_var_2) `HappyStk`
	_ `HappyStk`
	happyRest)
	 = HappyAbsSyn75
		 (Separator (happy_var_2) (happy_var_3) (happy_var_4)
	) `HappyStk` happyRest

happyReduce_86 = happyReduce 4 75 happyReduction_86
happyReduction_86 ((HappyAbsSyn59  happy_var_4) `HappyStk`
	(HappyAbsSyn83  happy_var_3) `HappyStk`
	(HappyAbsSyn113  happy_var_2) `HappyStk`
	_ `HappyStk`
	happyRest)
	 = HappyAbsSyn75
		 (Terminator (happy_var_2) (happy_var_3) (happy_var_4)
	) `HappyStk` happyRest

happyReduce_87 = happySpecReduce_3  75 happyReduction_87
happyReduction_87 (HappyAbsSyn63  happy_var_3)
	(HappyAbsSyn61  happy_var_2)
	_
	 =  HappyAbsSyn75
		 (Coercions (happy_var_2) (happy_var_3)
	)
happyReduction_87 _ _ _  = notHappyAtAll 

happyReduce_88 = happyReduce 4 75 happyReduction_88
happyReduction_88 ((HappyAbsSyn79  happy_var_4) `HappyStk`
	_ `HappyStk`
	(HappyAbsSyn61  happy_var_2) `HappyStk`
	_ `HappyStk`
	happyRest)
	 = HappyAbsSyn75
		 (Rules (happy_var_2) (happy_var_4)
	) `HappyStk` happyRest

happyReduce_89 = happyReduce 5 75 happyReduction_89
happyReduction_89 ((HappyAbsSyn101  happy_var_5) `HappyStk`
	_ `HappyStk`
	(HappyAbsSyn99  happy_var_3) `HappyStk`
	(HappyAbsSyn61  happy_var_2) `HappyStk`
	_ `HappyStk`
	happyRest)
	 = HappyAbsSyn75
		 (Function (happy_var_2) (reverse $ happy_var_3) (happy_var_5)
	) `HappyStk` happyRest

happyReduce_90 = happyReduce 4 75 happyReduction_90
happyReduction_90 ((HappyAbsSyn91  happy_var_4) `HappyStk`
	_ `HappyStk`
	(HappyAbsSyn61  happy_var_2) `HappyStk`
	_ `HappyStk`
	happyRest)
	 = HappyAbsSyn75
		 (External (happy_var_2) (happy_var_4)
	) `HappyStk` happyRest

happyReduce_91 = happyReduce 4 75 happyReduction_91
happyReduction_91 ((HappyAbsSyn59  happy_var_4) `HappyStk`
	(HappyAbsSyn59  happy_var_3) `HappyStk`
	(HappyAbsSyn59  happy_var_2) `HappyStk`
	_ `HappyStk`
	happyRest)
	 = HappyAbsSyn75
		 (AntiQuote (happy_var_2) (happy_var_3) (happy_var_4)
	) `HappyStk` happyRest

happyReduce_92 = happySpecReduce_2  75 happyReduction_92
happyReduction_92 (HappyAbsSyn111  happy_var_2)
	_
	 =  HappyAbsSyn75
		 (Layout (happy_var_2)
	)
happyReduction_92 _ _  = notHappyAtAll 

happyReduce_93 = happySpecReduce_3  75 happyReduction_93
happyReduction_93 (HappyAbsSyn111  happy_var_3)
	_
	_
	 =  HappyAbsSyn75
		 (LayoutStop (happy_var_3)
	)
happyReduction_93 _ _ _  = notHappyAtAll 

happyReduce_94 = happySpecReduce_2  75 happyReduction_94
happyReduction_94 _
	_
	 =  HappyAbsSyn75
		 (LayoutTop
	)

happyReduce_95 = happyReduce 5 76 happyReduction_95
happyReduction_95 ((HappyAbsSyn60  happy_var_5) `HappyStk`
	_ `HappyStk`
	(HappyAbsSyn60  happy_var_3) `HappyStk`
	_ `HappyStk`
	(HappyAbsSyn60  happy_var_1) `HappyStk`
	happyRest)
	 = HappyAbsSyn60
		 (appEPAll myLocation "Rule"  [happy_var_1,happy_var_3,happy_var_5]
	) `HappyStk` happyRest

happyReduce_96 = happySpecReduce_2  76 happyReduction_96
happyReduction_96 (HappyAbsSyn60  happy_var_2)
	_
	 =  HappyAbsSyn60
		 (appEPAll myLocation "Comment"  [happy_var_2]
	)
happyReduction_96 _ _  = notHappyAtAll 

happyReduce_97 = happySpecReduce_3  76 happyReduction_97
happyReduction_97 (HappyAbsSyn60  happy_var_3)
	(HappyAbsSyn60  happy_var_2)
	_
	 =  HappyAbsSyn60
		 (appEPAll myLocation "Comments"  [happy_var_2,happy_var_3]
	)
happyReduction_97 _ _ _  = notHappyAtAll 

happyReduce_98 = happyReduce 6 76 happyReduction_98
happyReduction_98 ((HappyAbsSyn60  happy_var_6) `HappyStk`
	_ `HappyStk`
	(HappyAbsSyn60  happy_var_4) `HappyStk`
	_ `HappyStk`
	(HappyAbsSyn60  happy_var_2) `HappyStk`
	_ `HappyStk`
	happyRest)
	 = HappyAbsSyn60
		 (appEPAll myLocation "Internal"  [happy_var_2,happy_var_4,happy_var_6]
	) `HappyStk` happyRest

happyReduce_99 = happySpecReduce_3  76 happyReduction_99
happyReduction_99 (HappyAbsSyn60  happy_var_3)
	(HappyAbsSyn60  happy_var_2)
	_
	 =  HappyAbsSyn60
		 (appEPAll myLocation "Token"  [happy_var_2,happy_var_3]
	)
happyReduction_99 _ _ _  = notHappyAtAll 

happyReduce_100 = happyReduce 4 76 happyReduction_100
happyReduction_100 ((HappyAbsSyn60  happy_var_4) `HappyStk`
	(HappyAbsSyn60  happy_var_3) `HappyStk`
	_ `HappyStk`
	_ `HappyStk`
	happyRest)
	 = HappyAbsSyn60
		 (appEPAll myLocation "PosToken"  [happy_var_3,happy_var_4]
	) `HappyStk` happyRest

happyReduce_101 = happySpecReduce_2  76 happyReduction_101
happyReduction_101 (HappyAbsSyn60  happy_var_2)
	_
	 =  HappyAbsSyn60
		 (appEPAll myLocation "Entryp"  [happy_var_2]
	)
happyReduction_101 _ _  = notHappyAtAll 

happyReduce_102 = happyReduce 4 76 happyReduction_102
happyReduction_102 ((HappyAbsSyn60  happy_var_4) `HappyStk`
	(HappyAbsSyn60  happy_var_3) `HappyStk`
	(HappyAbsSyn60  happy_var_2) `HappyStk`
	_ `HappyStk`
	happyRest)
	 = HappyAbsSyn60
		 (appEPAll myLocation "Separator"  [happy_var_2,happy_var_3,happy_var_4]
	) `HappyStk` happyRest

happyReduce_103 = happyReduce 4 76 happyReduction_103
happyReduction_103 ((HappyAbsSyn60  happy_var_4) `HappyStk`
	(HappyAbsSyn60  happy_var_3) `HappyStk`
	(HappyAbsSyn60  happy_var_2) `HappyStk`
	_ `HappyStk`
	happyRest)
	 = HappyAbsSyn60
		 (appEPAll myLocation "Terminator"  [happy_var_2,happy_var_3,happy_var_4]
	) `HappyStk` happyRest

happyReduce_104 = happySpecReduce_3  76 happyReduction_104
happyReduction_104 (HappyAbsSyn60  happy_var_3)
	(HappyAbsSyn60  happy_var_2)
	_
	 =  HappyAbsSyn60
		 (appEPAll myLocation "Coercions"  [happy_var_2,happy_var_3]
	)
happyReduction_104 _ _ _  = notHappyAtAll 

happyReduce_105 = happyReduce 4 76 happyReduction_105
happyReduction_105 ((HappyAbsSyn60  happy_var_4) `HappyStk`
	_ `HappyStk`
	(HappyAbsSyn60  happy_var_2) `HappyStk`
	_ `HappyStk`
	happyRest)
	 = HappyAbsSyn60
		 (appEPAll myLocation "Rules"  [happy_var_2,happy_var_4]
	) `HappyStk` happyRest

happyReduce_106 = happyReduce 5 76 happyReduction_106
happyReduction_106 ((HappyAbsSyn60  happy_var_5) `HappyStk`
	_ `HappyStk`
	(HappyAbsSyn60  happy_var_3) `HappyStk`
	(HappyAbsSyn60  happy_var_2) `HappyStk`
	_ `HappyStk`
	happyRest)
	 = HappyAbsSyn60
		 (appEPAll myLocation "Function"  [happy_var_2,happy_var_3,happy_var_5]
	) `HappyStk` happyRest

happyReduce_107 = happyReduce 4 76 happyReduction_107
happyReduction_107 ((HappyAbsSyn60  happy_var_4) `HappyStk`
	_ `HappyStk`
	(HappyAbsSyn60  happy_var_2) `HappyStk`
	_ `HappyStk`
	happyRest)
	 = HappyAbsSyn60
		 (appEPAll myLocation "External"  [happy_var_2,happy_var_4]
	) `HappyStk` happyRest

happyReduce_108 = happyReduce 4 76 happyReduction_108
happyReduction_108 ((HappyAbsSyn60  happy_var_4) `HappyStk`
	(HappyAbsSyn60  happy_var_3) `HappyStk`
	(HappyAbsSyn60  happy_var_2) `HappyStk`
	_ `HappyStk`
	happyRest)
	 = HappyAbsSyn60
		 (appEPAll myLocation "AntiQuote"  [happy_var_2,happy_var_3,happy_var_4]
	) `HappyStk` happyRest

happyReduce_109 = happySpecReduce_2  76 happyReduction_109
happyReduction_109 (HappyAbsSyn60  happy_var_2)
	_
	 =  HappyAbsSyn60
		 (appEPAll myLocation "Layout"  [happy_var_2]
	)
happyReduction_109 _ _  = notHappyAtAll 

happyReduce_110 = happySpecReduce_3  76 happyReduction_110
happyReduction_110 (HappyAbsSyn60  happy_var_3)
	_
	_
	 =  HappyAbsSyn60
		 (appEPAll myLocation "LayoutStop"  [happy_var_3]
	)
happyReduction_110 _ _ _  = notHappyAtAll 

happyReduce_111 = happySpecReduce_2  76 happyReduction_111
happyReduction_111 _
	_
	 =  HappyAbsSyn60
		 (appEPAll myLocation  "LayoutTop" []
	)

happyReduce_112 = happySpecReduce_1  77 happyReduction_112
happyReduction_112 (HappyAbsSyn73  happy_var_1)
	 =  HappyAbsSyn77
		 (RHS (reverse $ happy_var_1)
	)
happyReduction_112 _  = notHappyAtAll 

happyReduce_113 = happySpecReduce_2  77 happyReduction_113
happyReduction_113 (HappyAbsSyn115  happy_var_2)
	_
	 =  HappyAbsSyn77
		 (TRHS (happy_var_2)
	)
happyReduction_113 _ _  = notHappyAtAll 

happyReduce_114 = happySpecReduce_1  78 happyReduction_114
happyReduction_114 (HappyAbsSyn60  happy_var_1)
	 =  HappyAbsSyn60
		 (appEPAll myLocation "RHS"  [happy_var_1]
	)
happyReduction_114 _  = notHappyAtAll 

happyReduce_115 = happySpecReduce_2  78 happyReduction_115
happyReduction_115 (HappyAbsSyn60  happy_var_2)
	_
	 =  HappyAbsSyn60
		 (appEPAll myLocation "TRHS"  [happy_var_2]
	)
happyReduction_115 _ _  = notHappyAtAll 

happyReduce_116 = happySpecReduce_1  79 happyReduction_116
happyReduction_116 (HappyAbsSyn77  happy_var_1)
	 =  HappyAbsSyn79
		 ((:[]) (happy_var_1)
	)
happyReduction_116 _  = notHappyAtAll 

happyReduce_117 = happySpecReduce_3  79 happyReduction_117
happyReduction_117 (HappyAbsSyn79  happy_var_3)
	_
	(HappyAbsSyn77  happy_var_1)
	 =  HappyAbsSyn79
		 ((:) (happy_var_1) (happy_var_3)
	)
happyReduction_117 _ _ _  = notHappyAtAll 

happyReduce_118 = happySpecReduce_1  80 happyReduction_118
happyReduction_118 (HappyAbsSyn60  happy_var_1)
	 =  HappyAbsSyn60
		 (appEPAllL myLocation  [happy_var_1]
	)
happyReduction_118 _  = notHappyAtAll 

happyReduce_119 = happySpecReduce_3  80 happyReduction_119
happyReduction_119 (HappyAbsSyn60  happy_var_3)
	_
	(HappyAbsSyn60  happy_var_1)
	 =  HappyAbsSyn60
		 (appEPAll myLocation ":"  [happy_var_1,happy_var_3]
	)
happyReduction_119 _ _ _  = notHappyAtAll 

happyReduce_120 = happySpecReduce_1  81 happyReduction_120
happyReduction_120 (HappyAbsSyn59  happy_var_1)
	 =  HappyAbsSyn81
		 (Terminal (happy_var_1)
	)
happyReduction_120 _  = notHappyAtAll 

happyReduce_121 = happySpecReduce_1  81 happyReduction_121
happyReduction_121 (HappyAbsSyn83  happy_var_1)
	 =  HappyAbsSyn81
		 (NTerminal (happy_var_1)
	)
happyReduction_121 _  = notHappyAtAll 

happyReduce_122 = happySpecReduce_1  82 happyReduction_122
happyReduction_122 (HappyAbsSyn60  happy_var_1)
	 =  HappyAbsSyn60
		 (appEPAll myLocation "Terminal"  [happy_var_1]
	)
happyReduction_122 _  = notHappyAtAll 

happyReduce_123 = happySpecReduce_1  82 happyReduction_123
happyReduction_123 (HappyAbsSyn60  happy_var_1)
	 =  HappyAbsSyn60
		 (appEPAll myLocation "NTerminal"  [happy_var_1]
	)
happyReduction_123 _  = notHappyAtAll 

happyReduce_124 = happySpecReduce_2  83 happyReduction_124
happyReduction_124 (HappyAbsSyn83  happy_var_2)
	_
	 =  HappyAbsSyn83
		 (OptCat (happy_var_2)
	)
happyReduction_124 _ _  = notHappyAtAll 

happyReduce_125 = happySpecReduce_1  83 happyReduction_125
happyReduction_125 (HappyAbsSyn83  happy_var_1)
	 =  HappyAbsSyn83
		 (happy_var_1
	)
happyReduction_125 _  = notHappyAtAll 

happyReduce_126 = happySpecReduce_2  84 happyReduction_126
happyReduction_126 (HappyAbsSyn60  happy_var_2)
	_
	 =  HappyAbsSyn60
		 (appEPAll myLocation "OptCat"  [happy_var_2]
	)
happyReduction_126 _ _  = notHappyAtAll 

happyReduce_127 = happySpecReduce_1  84 happyReduction_127
happyReduction_127 (HappyAbsSyn60  happy_var_1)
	 =  HappyAbsSyn60
		 (happy_var_1
	)
happyReduction_127 _  = notHappyAtAll 

happyReduce_128 = happySpecReduce_3  85 happyReduction_128
happyReduction_128 _
	(HappyAbsSyn83  happy_var_2)
	_
	 =  HappyAbsSyn83
		 (ListCat (happy_var_2)
	)
happyReduction_128 _ _ _  = notHappyAtAll 

happyReduce_129 = happySpecReduce_1  85 happyReduction_129
happyReduction_129 (HappyAbsSyn61  happy_var_1)
	 =  HappyAbsSyn83
		 (IdCat (happy_var_1)
	)
happyReduction_129 _  = notHappyAtAll 

happyReduce_130 = happySpecReduce_3  86 happyReduction_130
happyReduction_130 _
	(HappyAbsSyn60  happy_var_2)
	_
	 =  HappyAbsSyn60
		 (appEPAll myLocation "ListCat"  [happy_var_2]
	)
happyReduction_130 _ _ _  = notHappyAtAll 

happyReduce_131 = happySpecReduce_1  86 happyReduction_131
happyReduction_131 (HappyAbsSyn60  happy_var_1)
	 =  HappyAbsSyn60
		 (appEPAll myLocation "IdCat"  [happy_var_1]
	)
happyReduction_131 _  = notHappyAtAll 

happyReduce_132 = happySpecReduce_1  87 happyReduction_132
happyReduction_132 (HappyAbsSyn61  happy_var_1)
	 =  HappyAbsSyn87
		 (Id (happy_var_1)
	)
happyReduction_132 _  = notHappyAtAll 

happyReduce_133 = happySpecReduce_1  87 happyReduction_133
happyReduction_133 _
	 =  HappyAbsSyn87
		 (Wild
	)

happyReduce_134 = happySpecReduce_2  87 happyReduction_134
happyReduction_134 _
	_
	 =  HappyAbsSyn87
		 (ListE
	)

happyReduce_135 = happySpecReduce_3  87 happyReduction_135
happyReduction_135 _
	_
	_
	 =  HappyAbsSyn87
		 (ListCons
	)

happyReduce_136 = happyReduce 5 87 happyReduction_136
happyReduction_136 (_ `HappyStk`
	_ `HappyStk`
	_ `HappyStk`
	_ `HappyStk`
	_ `HappyStk`
	happyRest)
	 = HappyAbsSyn87
		 (ListOne
	) `HappyStk` happyRest

happyReduce_137 = happySpecReduce_2  87 happyReduction_137
happyReduction_137 (HappyAbsSyn89  happy_var_2)
	_
	 =  HappyAbsSyn87
		 (Aq (happy_var_2)
	)
happyReduction_137 _ _  = notHappyAtAll 

happyReduce_138 = happySpecReduce_1  88 happyReduction_138
happyReduction_138 (HappyAbsSyn60  happy_var_1)
	 =  HappyAbsSyn60
		 (appEPAll myLocation "Id"  [happy_var_1]
	)
happyReduction_138 _  = notHappyAtAll 

happyReduce_139 = happySpecReduce_1  88 happyReduction_139
happyReduction_139 _
	 =  HappyAbsSyn60
		 (appEPAll myLocation  "Wild" []
	)

happyReduce_140 = happySpecReduce_2  88 happyReduction_140
happyReduction_140 _
	_
	 =  HappyAbsSyn60
		 (appEPAll myLocation  "ListE" []
	)

happyReduce_141 = happySpecReduce_3  88 happyReduction_141
happyReduction_141 _
	_
	_
	 =  HappyAbsSyn60
		 (appEPAll myLocation  "ListCons" []
	)

happyReduce_142 = happyReduce 5 88 happyReduction_142
happyReduction_142 (_ `HappyStk`
	_ `HappyStk`
	_ `HappyStk`
	_ `HappyStk`
	_ `HappyStk`
	happyRest)
	 = HappyAbsSyn60
		 (appEPAll myLocation  "ListOne" []
	) `HappyStk` happyRest

happyReduce_143 = happySpecReduce_2  88 happyReduction_143
happyReduction_143 (HappyAbsSyn60  happy_var_2)
	_
	 =  HappyAbsSyn60
		 (appEPAll myLocation "Aq"  [happy_var_2]
	)
happyReduction_143 _ _  = notHappyAtAll 

happyReduce_144 = happySpecReduce_1  89 happyReduction_144
happyReduction_144 (HappyAbsSyn61  happy_var_1)
	 =  HappyAbsSyn89
		 (JIdent (happy_var_1)
	)
happyReduction_144 _  = notHappyAtAll 

happyReduce_145 = happySpecReduce_0  89 happyReduction_145
happyReduction_145  =  HappyAbsSyn89
		 (NIdent
	)

happyReduce_146 = happySpecReduce_1  90 happyReduction_146
happyReduction_146 (HappyAbsSyn60  happy_var_1)
	 =  HappyAbsSyn60
		 (appEPAll myLocation "JIdent"  [happy_var_1]
	)
happyReduction_146 _  = notHappyAtAll 

happyReduce_147 = happySpecReduce_0  90 happyReduction_147
happyReduction_147  =  HappyAbsSyn60
		 (appEPAll myLocation  "NIdent" []
	)

happyReduce_148 = happySpecReduce_2  91 happyReduction_148
happyReduction_148 (HappyAbsSyn91  happy_var_2)
	(HappyAbsSyn91  happy_var_1)
	 =  HappyAbsSyn91
		 (HsApp (happy_var_1) (happy_var_2)
	)
happyReduction_148 _ _  = notHappyAtAll 

happyReduce_149 = happySpecReduce_2  92 happyReduction_149
happyReduction_149 (HappyAbsSyn60  happy_var_2)
	(HappyAbsSyn60  happy_var_1)
	 =  HappyAbsSyn60
		 (appEPAll myLocation "HsApp"  [happy_var_1,happy_var_2]
	)
happyReduction_149 _ _  = notHappyAtAll 

happyReduce_150 = happySpecReduce_1  93 happyReduction_150
happyReduction_150 (HappyAbsSyn61  happy_var_1)
	 =  HappyAbsSyn91
		 (HsCon (happy_var_1)
	)
happyReduction_150 _  = notHappyAtAll 

happyReduce_151 = happySpecReduce_3  93 happyReduction_151
happyReduction_151 _
	(HappyAbsSyn95  happy_var_2)
	_
	 =  HappyAbsSyn91
		 (HsTup (happy_var_2)
	)
happyReduction_151 _ _ _  = notHappyAtAll 

happyReduce_152 = happySpecReduce_3  93 happyReduction_152
happyReduction_152 _
	(HappyAbsSyn91  happy_var_2)
	_
	 =  HappyAbsSyn91
		 (HsList (happy_var_2)
	)
happyReduction_152 _ _ _  = notHappyAtAll 

happyReduce_153 = happySpecReduce_1  94 happyReduction_153
happyReduction_153 (HappyAbsSyn60  happy_var_1)
	 =  HappyAbsSyn60
		 (appEPAll myLocation "HsCon"  [happy_var_1]
	)
happyReduction_153 _  = notHappyAtAll 

happyReduce_154 = happySpecReduce_3  94 happyReduction_154
happyReduction_154 _
	(HappyAbsSyn60  happy_var_2)
	_
	 =  HappyAbsSyn60
		 (appEPAll myLocation "HsTup"  [happy_var_2]
	)
happyReduction_154 _ _ _  = notHappyAtAll 

happyReduce_155 = happySpecReduce_3  94 happyReduction_155
happyReduction_155 _
	(HappyAbsSyn60  happy_var_2)
	_
	 =  HappyAbsSyn60
		 (appEPAll myLocation "HsList"  [happy_var_2]
	)
happyReduction_155 _ _ _  = notHappyAtAll 

happyReduce_156 = happySpecReduce_1  95 happyReduction_156
happyReduction_156 (HappyAbsSyn91  happy_var_1)
	 =  HappyAbsSyn95
		 ((:[]) (happy_var_1)
	)
happyReduction_156 _  = notHappyAtAll 

happyReduce_157 = happySpecReduce_3  95 happyReduction_157
happyReduction_157 (HappyAbsSyn95  happy_var_3)
	_
	(HappyAbsSyn91  happy_var_1)
	 =  HappyAbsSyn95
		 ((:) (happy_var_1) (happy_var_3)
	)
happyReduction_157 _ _ _  = notHappyAtAll 

happyReduce_158 = happySpecReduce_1  96 happyReduction_158
happyReduction_158 (HappyAbsSyn60  happy_var_1)
	 =  HappyAbsSyn60
		 (appEPAllL myLocation  [happy_var_1]
	)
happyReduction_158 _  = notHappyAtAll 

happyReduce_159 = happySpecReduce_3  96 happyReduction_159
happyReduction_159 (HappyAbsSyn60  happy_var_3)
	_
	(HappyAbsSyn60  happy_var_1)
	 =  HappyAbsSyn60
		 (appEPAll myLocation ":"  [happy_var_1,happy_var_3]
	)
happyReduction_159 _ _ _  = notHappyAtAll 

happyReduce_160 = happySpecReduce_1  97 happyReduction_160
happyReduction_160 (HappyAbsSyn61  happy_var_1)
	 =  HappyAbsSyn97
		 (Arg (happy_var_1)
	)
happyReduction_160 _  = notHappyAtAll 

happyReduce_161 = happySpecReduce_1  98 happyReduction_161
happyReduction_161 (HappyAbsSyn60  happy_var_1)
	 =  HappyAbsSyn60
		 (appEPAll myLocation "Arg"  [happy_var_1]
	)
happyReduction_161 _  = notHappyAtAll 

happyReduce_162 = happySpecReduce_0  99 happyReduction_162
happyReduction_162  =  HappyAbsSyn99
		 ([]
	)

happyReduce_163 = happySpecReduce_2  99 happyReduction_163
happyReduction_163 (HappyAbsSyn97  happy_var_2)
	(HappyAbsSyn99  happy_var_1)
	 =  HappyAbsSyn99
		 (flip (:) (happy_var_1) (happy_var_2)
	)
happyReduction_163 _ _  = notHappyAtAll 

happyReduce_164 = happySpecReduce_0  100 happyReduction_164
happyReduction_164  =  HappyAbsSyn60
		 (appEPAll myLocation  "[]" []
	)

happyReduce_165 = happySpecReduce_2  100 happyReduction_165
happyReduction_165 (HappyAbsSyn60  happy_var_2)
	(HappyAbsSyn60  happy_var_1)
	 =  HappyAbsSyn60
		 (appEPAllL myLocation  [happy_var_1,happy_var_2]
	)
happyReduction_165 _ _  = notHappyAtAll 

happyReduce_166 = happySpecReduce_3  101 happyReduction_166
happyReduction_166 (HappyAbsSyn101  happy_var_3)
	_
	(HappyAbsSyn101  happy_var_1)
	 =  HappyAbsSyn101
		 (Cons (happy_var_1) (happy_var_3)
	)
happyReduction_166 _ _ _  = notHappyAtAll 

happyReduce_167 = happySpecReduce_1  101 happyReduction_167
happyReduction_167 (HappyAbsSyn101  happy_var_1)
	 =  HappyAbsSyn101
		 (happy_var_1
	)
happyReduction_167 _  = notHappyAtAll 

happyReduce_168 = happySpecReduce_3  102 happyReduction_168
happyReduction_168 (HappyAbsSyn60  happy_var_3)
	_
	(HappyAbsSyn60  happy_var_1)
	 =  HappyAbsSyn60
		 (appEPAll myLocation "Cons"  [happy_var_1,happy_var_3]
	)
happyReduction_168 _ _ _  = notHappyAtAll 

happyReduce_169 = happySpecReduce_1  102 happyReduction_169
happyReduction_169 (HappyAbsSyn60  happy_var_1)
	 =  HappyAbsSyn60
		 (happy_var_1
	)
happyReduction_169 _  = notHappyAtAll 

happyReduce_170 = happySpecReduce_2  103 happyReduction_170
happyReduction_170 (HappyAbsSyn107  happy_var_2)
	(HappyAbsSyn61  happy_var_1)
	 =  HappyAbsSyn101
		 (App (happy_var_1) (happy_var_2)
	)
happyReduction_170 _ _  = notHappyAtAll 

happyReduce_171 = happySpecReduce_1  103 happyReduction_171
happyReduction_171 (HappyAbsSyn101  happy_var_1)
	 =  HappyAbsSyn101
		 (happy_var_1
	)
happyReduction_171 _  = notHappyAtAll 

happyReduce_172 = happySpecReduce_2  104 happyReduction_172
happyReduction_172 (HappyAbsSyn60  happy_var_2)
	(HappyAbsSyn60  happy_var_1)
	 =  HappyAbsSyn60
		 (appEPAll myLocation "App"  [happy_var_1,happy_var_2]
	)
happyReduction_172 _ _  = notHappyAtAll 

happyReduce_173 = happySpecReduce_1  104 happyReduction_173
happyReduction_173 (HappyAbsSyn60  happy_var_1)
	 =  HappyAbsSyn60
		 (happy_var_1
	)
happyReduction_173 _  = notHappyAtAll 

happyReduce_174 = happySpecReduce_1  105 happyReduction_174
happyReduction_174 (HappyAbsSyn61  happy_var_1)
	 =  HappyAbsSyn101
		 (Var (happy_var_1)
	)
happyReduction_174 _  = notHappyAtAll 

happyReduce_175 = happySpecReduce_1  105 happyReduction_175
happyReduction_175 (HappyAbsSyn63  happy_var_1)
	 =  HappyAbsSyn101
		 (LitInt (happy_var_1)
	)
happyReduction_175 _  = notHappyAtAll 

happyReduce_176 = happySpecReduce_1  105 happyReduction_176
happyReduction_176 (HappyAbsSyn65  happy_var_1)
	 =  HappyAbsSyn101
		 (LitChar (happy_var_1)
	)
happyReduction_176 _  = notHappyAtAll 

happyReduce_177 = happySpecReduce_1  105 happyReduction_177
happyReduction_177 (HappyAbsSyn59  happy_var_1)
	 =  HappyAbsSyn101
		 (LitString (happy_var_1)
	)
happyReduction_177 _  = notHappyAtAll 

happyReduce_178 = happySpecReduce_1  105 happyReduction_178
happyReduction_178 (HappyAbsSyn67  happy_var_1)
	 =  HappyAbsSyn101
		 (LitDouble (happy_var_1)
	)
happyReduction_178 _  = notHappyAtAll 

happyReduce_179 = happySpecReduce_3  105 happyReduction_179
happyReduction_179 _
	(HappyAbsSyn107  happy_var_2)
	_
	 =  HappyAbsSyn101
		 (List (happy_var_2)
	)
happyReduction_179 _ _ _  = notHappyAtAll 

happyReduce_180 = happySpecReduce_3  105 happyReduction_180
happyReduction_180 _
	(HappyAbsSyn101  happy_var_2)
	_
	 =  HappyAbsSyn101
		 (happy_var_2
	)
happyReduction_180 _ _ _  = notHappyAtAll 

happyReduce_181 = happySpecReduce_1  106 happyReduction_181
happyReduction_181 (HappyAbsSyn60  happy_var_1)
	 =  HappyAbsSyn60
		 (appEPAll myLocation "Var"  [happy_var_1]
	)
happyReduction_181 _  = notHappyAtAll 

happyReduce_182 = happySpecReduce_1  106 happyReduction_182
happyReduction_182 (HappyAbsSyn60  happy_var_1)
	 =  HappyAbsSyn60
		 (appEPAll myLocation "LitInt"  [happy_var_1]
	)
happyReduction_182 _  = notHappyAtAll 

happyReduce_183 = happySpecReduce_1  106 happyReduction_183
happyReduction_183 (HappyAbsSyn60  happy_var_1)
	 =  HappyAbsSyn60
		 (appEPAll myLocation "LitChar"  [happy_var_1]
	)
happyReduction_183 _  = notHappyAtAll 

happyReduce_184 = happySpecReduce_1  106 happyReduction_184
happyReduction_184 (HappyAbsSyn60  happy_var_1)
	 =  HappyAbsSyn60
		 (appEPAll myLocation "LitString"  [happy_var_1]
	)
happyReduction_184 _  = notHappyAtAll 

happyReduce_185 = happySpecReduce_1  106 happyReduction_185
happyReduction_185 (HappyAbsSyn60  happy_var_1)
	 =  HappyAbsSyn60
		 (appEPAll myLocation "LitDouble"  [happy_var_1]
	)
happyReduction_185 _  = notHappyAtAll 

happyReduce_186 = happySpecReduce_3  106 happyReduction_186
happyReduction_186 _
	(HappyAbsSyn60  happy_var_2)
	_
	 =  HappyAbsSyn60
		 (appEPAll myLocation "List"  [happy_var_2]
	)
happyReduction_186 _ _ _  = notHappyAtAll 

happyReduce_187 = happySpecReduce_3  106 happyReduction_187
happyReduction_187 _
	(HappyAbsSyn60  happy_var_2)
	_
	 =  HappyAbsSyn60
		 (happy_var_2
	)
happyReduction_187 _ _ _  = notHappyAtAll 

happyReduce_188 = happySpecReduce_1  107 happyReduction_188
happyReduction_188 (HappyAbsSyn101  happy_var_1)
	 =  HappyAbsSyn107
		 ((:[]) (happy_var_1)
	)
happyReduction_188 _  = notHappyAtAll 

happyReduce_189 = happySpecReduce_2  107 happyReduction_189
happyReduction_189 (HappyAbsSyn107  happy_var_2)
	(HappyAbsSyn101  happy_var_1)
	 =  HappyAbsSyn107
		 ((:) (happy_var_1) (happy_var_2)
	)
happyReduction_189 _ _  = notHappyAtAll 

happyReduce_190 = happySpecReduce_1  108 happyReduction_190
happyReduction_190 (HappyAbsSyn60  happy_var_1)
	 =  HappyAbsSyn60
		 (appEPAllL myLocation  [happy_var_1]
	)
happyReduction_190 _  = notHappyAtAll 

happyReduce_191 = happySpecReduce_2  108 happyReduction_191
happyReduction_191 (HappyAbsSyn60  happy_var_2)
	(HappyAbsSyn60  happy_var_1)
	 =  HappyAbsSyn60
		 (appEPAll myLocation ":"  [happy_var_1,happy_var_2]
	)
happyReduction_191 _ _  = notHappyAtAll 

happyReduce_192 = happySpecReduce_0  109 happyReduction_192
happyReduction_192  =  HappyAbsSyn107
		 ([]
	)

happyReduce_193 = happySpecReduce_1  109 happyReduction_193
happyReduction_193 (HappyAbsSyn101  happy_var_1)
	 =  HappyAbsSyn107
		 ((:[]) (happy_var_1)
	)
happyReduction_193 _  = notHappyAtAll 

happyReduce_194 = happySpecReduce_3  109 happyReduction_194
happyReduction_194 (HappyAbsSyn107  happy_var_3)
	_
	(HappyAbsSyn101  happy_var_1)
	 =  HappyAbsSyn107
		 ((:) (happy_var_1) (happy_var_3)
	)
happyReduction_194 _ _ _  = notHappyAtAll 

happyReduce_195 = happySpecReduce_0  110 happyReduction_195
happyReduction_195  =  HappyAbsSyn60
		 (appEPAll myLocation  "[]" []
	)

happyReduce_196 = happySpecReduce_1  110 happyReduction_196
happyReduction_196 (HappyAbsSyn60  happy_var_1)
	 =  HappyAbsSyn60
		 (appEPAllL myLocation  [happy_var_1]
	)
happyReduction_196 _  = notHappyAtAll 

happyReduce_197 = happySpecReduce_3  110 happyReduction_197
happyReduction_197 (HappyAbsSyn60  happy_var_3)
	_
	(HappyAbsSyn60  happy_var_1)
	 =  HappyAbsSyn60
		 (appEPAll myLocation ":"  [happy_var_1,happy_var_3]
	)
happyReduction_197 _ _ _  = notHappyAtAll 

happyReduce_198 = happySpecReduce_1  111 happyReduction_198
happyReduction_198 (HappyAbsSyn59  happy_var_1)
	 =  HappyAbsSyn111
		 ((:[]) (happy_var_1)
	)
happyReduction_198 _  = notHappyAtAll 

happyReduce_199 = happySpecReduce_3  111 happyReduction_199
happyReduction_199 (HappyAbsSyn111  happy_var_3)
	_
	(HappyAbsSyn59  happy_var_1)
	 =  HappyAbsSyn111
		 ((:) (happy_var_1) (happy_var_3)
	)
happyReduction_199 _ _ _  = notHappyAtAll 

happyReduce_200 = happySpecReduce_1  112 happyReduction_200
happyReduction_200 (HappyAbsSyn60  happy_var_1)
	 =  HappyAbsSyn60
		 (appEPAllL myLocation  [happy_var_1]
	)
happyReduction_200 _  = notHappyAtAll 

happyReduce_201 = happySpecReduce_3  112 happyReduction_201
happyReduction_201 (HappyAbsSyn60  happy_var_3)
	_
	(HappyAbsSyn60  happy_var_1)
	 =  HappyAbsSyn60
		 (appEPAll myLocation ":"  [happy_var_1,happy_var_3]
	)
happyReduction_201 _ _ _  = notHappyAtAll 

happyReduce_202 = happySpecReduce_1  113 happyReduction_202
happyReduction_202 _
	 =  HappyAbsSyn113
		 (MNonempty
	)

happyReduce_203 = happySpecReduce_0  113 happyReduction_203
happyReduction_203  =  HappyAbsSyn113
		 (MEmpty
	)

happyReduce_204 = happySpecReduce_1  114 happyReduction_204
happyReduction_204 _
	 =  HappyAbsSyn60
		 (appEPAll myLocation  "MNonempty" []
	)

happyReduce_205 = happySpecReduce_0  114 happyReduction_205
happyReduction_205  =  HappyAbsSyn60
		 (appEPAll myLocation  "MEmpty" []
	)

happyReduce_206 = happySpecReduce_2  115 happyReduction_206
happyReduction_206 (HappyAbsSyn115  happy_var_2)
	(HappyAbsSyn115  happy_var_1)
	 =  HappyAbsSyn115
		 (RSeq (happy_var_1) (happy_var_2)
	)
happyReduction_206 _ _  = notHappyAtAll 

happyReduce_207 = happySpecReduce_1  115 happyReduction_207
happyReduction_207 (HappyAbsSyn115  happy_var_1)
	 =  HappyAbsSyn115
		 (happy_var_1
	)
happyReduction_207 _  = notHappyAtAll 

happyReduce_208 = happySpecReduce_2  116 happyReduction_208
happyReduction_208 (HappyAbsSyn60  happy_var_2)
	(HappyAbsSyn60  happy_var_1)
	 =  HappyAbsSyn60
		 (appEPAll myLocation "RSeq"  [happy_var_1,happy_var_2]
	)
happyReduction_208 _ _  = notHappyAtAll 

happyReduce_209 = happySpecReduce_1  116 happyReduction_209
happyReduction_209 (HappyAbsSyn60  happy_var_1)
	 =  HappyAbsSyn60
		 (happy_var_1
	)
happyReduction_209 _  = notHappyAtAll 

happyReduce_210 = happySpecReduce_3  117 happyReduction_210
happyReduction_210 (HappyAbsSyn115  happy_var_3)
	_
	(HappyAbsSyn115  happy_var_1)
	 =  HappyAbsSyn115
		 (RAlt (happy_var_1) (happy_var_3)
	)
happyReduction_210 _ _ _  = notHappyAtAll 

happyReduce_211 = happySpecReduce_3  117 happyReduction_211
happyReduction_211 (HappyAbsSyn115  happy_var_3)
	_
	(HappyAbsSyn115  happy_var_1)
	 =  HappyAbsSyn115
		 (RMinus (happy_var_1) (happy_var_3)
	)
happyReduction_211 _ _ _  = notHappyAtAll 

happyReduce_212 = happySpecReduce_1  117 happyReduction_212
happyReduction_212 (HappyAbsSyn115  happy_var_1)
	 =  HappyAbsSyn115
		 (happy_var_1
	)
happyReduction_212 _  = notHappyAtAll 

happyReduce_213 = happySpecReduce_3  118 happyReduction_213
happyReduction_213 (HappyAbsSyn60  happy_var_3)
	_
	(HappyAbsSyn60  happy_var_1)
	 =  HappyAbsSyn60
		 (appEPAll myLocation "RAlt"  [happy_var_1,happy_var_3]
	)
happyReduction_213 _ _ _  = notHappyAtAll 

happyReduce_214 = happySpecReduce_3  118 happyReduction_214
happyReduction_214 (HappyAbsSyn60  happy_var_3)
	_
	(HappyAbsSyn60  happy_var_1)
	 =  HappyAbsSyn60
		 (appEPAll myLocation "RMinus"  [happy_var_1,happy_var_3]
	)
happyReduction_214 _ _ _  = notHappyAtAll 

happyReduce_215 = happySpecReduce_1  118 happyReduction_215
happyReduction_215 (HappyAbsSyn60  happy_var_1)
	 =  HappyAbsSyn60
		 (happy_var_1
	)
happyReduction_215 _  = notHappyAtAll 

happyReduce_216 = happySpecReduce_2  119 happyReduction_216
happyReduction_216 _
	(HappyAbsSyn115  happy_var_1)
	 =  HappyAbsSyn115
		 (RStar (happy_var_1)
	)
happyReduction_216 _ _  = notHappyAtAll 

happyReduce_217 = happySpecReduce_2  119 happyReduction_217
happyReduction_217 _
	(HappyAbsSyn115  happy_var_1)
	 =  HappyAbsSyn115
		 (RPlus (happy_var_1)
	)
happyReduction_217 _ _  = notHappyAtAll 

happyReduce_218 = happySpecReduce_2  119 happyReduction_218
happyReduction_218 _
	(HappyAbsSyn115  happy_var_1)
	 =  HappyAbsSyn115
		 (ROpt (happy_var_1)
	)
happyReduction_218 _ _  = notHappyAtAll 

happyReduce_219 = happySpecReduce_1  119 happyReduction_219
happyReduction_219 _
	 =  HappyAbsSyn115
		 (REps
	)

happyReduce_220 = happySpecReduce_1  119 happyReduction_220
happyReduction_220 (HappyAbsSyn65  happy_var_1)
	 =  HappyAbsSyn115
		 (RChar (happy_var_1)
	)
happyReduction_220 _  = notHappyAtAll 

happyReduce_221 = happySpecReduce_3  119 happyReduction_221
happyReduction_221 _
	(HappyAbsSyn59  happy_var_2)
	_
	 =  HappyAbsSyn115
		 (RAlts (happy_var_2)
	)
happyReduction_221 _ _ _  = notHappyAtAll 

happyReduce_222 = happySpecReduce_3  119 happyReduction_222
happyReduction_222 _
	(HappyAbsSyn59  happy_var_2)
	_
	 =  HappyAbsSyn115
		 (RSeqs (happy_var_2)
	)
happyReduction_222 _ _ _  = notHappyAtAll 

happyReduce_223 = happySpecReduce_1  119 happyReduction_223
happyReduction_223 _
	 =  HappyAbsSyn115
		 (RDigit
	)

happyReduce_224 = happySpecReduce_1  119 happyReduction_224
happyReduction_224 _
	 =  HappyAbsSyn115
		 (RLetter
	)

happyReduce_225 = happySpecReduce_1  119 happyReduction_225
happyReduction_225 _
	 =  HappyAbsSyn115
		 (RUpper
	)

happyReduce_226 = happySpecReduce_1  119 happyReduction_226
happyReduction_226 _
	 =  HappyAbsSyn115
		 (RLower
	)

happyReduce_227 = happySpecReduce_1  119 happyReduction_227
happyReduction_227 _
	 =  HappyAbsSyn115
		 (RAny
	)

happyReduce_228 = happySpecReduce_3  119 happyReduction_228
happyReduction_228 _
	(HappyAbsSyn115  happy_var_2)
	_
	 =  HappyAbsSyn115
		 (happy_var_2
	)
happyReduction_228 _ _ _  = notHappyAtAll 

happyReduce_229 = happySpecReduce_2  120 happyReduction_229
happyReduction_229 _
	(HappyAbsSyn60  happy_var_1)
	 =  HappyAbsSyn60
		 (appEPAll myLocation "RStar"  [happy_var_1]
	)
happyReduction_229 _ _  = notHappyAtAll 

happyReduce_230 = happySpecReduce_2  120 happyReduction_230
happyReduction_230 _
	(HappyAbsSyn60  happy_var_1)
	 =  HappyAbsSyn60
		 (appEPAll myLocation "RPlus"  [happy_var_1]
	)
happyReduction_230 _ _  = notHappyAtAll 

happyReduce_231 = happySpecReduce_2  120 happyReduction_231
happyReduction_231 _
	(HappyAbsSyn60  happy_var_1)
	 =  HappyAbsSyn60
		 (appEPAll myLocation "ROpt"  [happy_var_1]
	)
happyReduction_231 _ _  = notHappyAtAll 

happyReduce_232 = happySpecReduce_1  120 happyReduction_232
happyReduction_232 _
	 =  HappyAbsSyn60
		 (appEPAll myLocation  "REps" []
	)

happyReduce_233 = happySpecReduce_1  120 happyReduction_233
happyReduction_233 (HappyAbsSyn60  happy_var_1)
	 =  HappyAbsSyn60
		 (appEPAll myLocation "RChar"  [happy_var_1]
	)
happyReduction_233 _  = notHappyAtAll 

happyReduce_234 = happySpecReduce_3  120 happyReduction_234
happyReduction_234 _
	(HappyAbsSyn60  happy_var_2)
	_
	 =  HappyAbsSyn60
		 (appEPAll myLocation "RAlts"  [happy_var_2]
	)
happyReduction_234 _ _ _  = notHappyAtAll 

happyReduce_235 = happySpecReduce_3  120 happyReduction_235
happyReduction_235 _
	(HappyAbsSyn60  happy_var_2)
	_
	 =  HappyAbsSyn60
		 (appEPAll myLocation "RSeqs"  [happy_var_2]
	)
happyReduction_235 _ _ _  = notHappyAtAll 

happyReduce_236 = happySpecReduce_1  120 happyReduction_236
happyReduction_236 _
	 =  HappyAbsSyn60
		 (appEPAll myLocation  "RDigit" []
	)

happyReduce_237 = happySpecReduce_1  120 happyReduction_237
happyReduction_237 _
	 =  HappyAbsSyn60
		 (appEPAll myLocation  "RLetter" []
	)

happyReduce_238 = happySpecReduce_1  120 happyReduction_238
happyReduction_238 _
	 =  HappyAbsSyn60
		 (appEPAll myLocation  "RUpper" []
	)

happyReduce_239 = happySpecReduce_1  120 happyReduction_239
happyReduction_239 _
	 =  HappyAbsSyn60
		 (appEPAll myLocation  "RLower" []
	)

happyReduce_240 = happySpecReduce_1  120 happyReduction_240
happyReduction_240 _
	 =  HappyAbsSyn60
		 (appEPAll myLocation  "RAny" []
	)

happyReduce_241 = happySpecReduce_3  120 happyReduction_241
happyReduction_241 _
	(HappyAbsSyn60  happy_var_2)
	_
	 =  HappyAbsSyn60
		 (happy_var_2
	)
happyReduction_241 _ _ _  = notHappyAtAll 

happyReduce_242 = happySpecReduce_1  121 happyReduction_242
happyReduction_242 (HappyAbsSyn115  happy_var_1)
	 =  HappyAbsSyn115
		 (happy_var_1
	)
happyReduction_242 _  = notHappyAtAll 

happyReduce_243 = happySpecReduce_1  122 happyReduction_243
happyReduction_243 (HappyAbsSyn60  happy_var_1)
	 =  HappyAbsSyn60
		 (happy_var_1
	)
happyReduction_243 _  = notHappyAtAll 

happyReduce_244 = happySpecReduce_1  123 happyReduction_244
happyReduction_244 (HappyAbsSyn61  happy_var_1)
	 =  HappyAbsSyn123
		 ((:[]) (happy_var_1)
	)
happyReduction_244 _  = notHappyAtAll 

happyReduce_245 = happySpecReduce_3  123 happyReduction_245
happyReduction_245 (HappyAbsSyn123  happy_var_3)
	_
	(HappyAbsSyn61  happy_var_1)
	 =  HappyAbsSyn123
		 ((:) (happy_var_1) (happy_var_3)
	)
happyReduction_245 _ _ _  = notHappyAtAll 

happyReduce_246 = happySpecReduce_1  124 happyReduction_246
happyReduction_246 (HappyAbsSyn60  happy_var_1)
	 =  HappyAbsSyn60
		 (appEPAllL myLocation  [happy_var_1]
	)
happyReduction_246 _  = notHappyAtAll 

happyReduce_247 = happySpecReduce_3  124 happyReduction_247
happyReduction_247 (HappyAbsSyn60  happy_var_3)
	_
	(HappyAbsSyn60  happy_var_1)
	 =  HappyAbsSyn60
		 (appEPAll myLocation ":"  [happy_var_1,happy_var_3]
	)
happyReduction_247 _ _ _  = notHappyAtAll 

happyNewToken action sts stk [] =
	action 173 173 notHappyAtAll (HappyState action) sts stk []

happyNewToken action sts stk (tk:tks) =
	let cont i = action i i tk (HappyState action) sts stk tks in
	case tk of {
	PT _ (TS ";") -> cont 125;
	PT _ (TS ".") -> cont 126;
	PT _ (TS "::=") -> cont 127;
	PT _ (TS "@") -> cont 128;
	PT _ (TS "|") -> cont 129;
	PT _ (TS "?") -> cont 130;
	PT _ (TS "[") -> cont 131;
	PT _ (TS "]") -> cont 132;
	PT _ (TS "_") -> cont 133;
	PT _ (TS "(") -> cont 134;
	PT _ (TS ":") -> cont 135;
	PT _ (TS ")") -> cont 136;
	PT _ (TS "$") -> cont 137;
	PT _ (TS "=") -> cont 138;
	PT _ (TS ",") -> cont 139;
	PT _ (TS "-") -> cont 140;
	PT _ (TS "*") -> cont 141;
	PT _ (TS "+") -> cont 142;
	PT _ (TS "{") -> cont 143;
	PT _ (TS "}") -> cont 144;
	PT _ (TS "antiquote") -> cont 145;
	PT _ (TS "char") -> cont 146;
	PT _ (TS "coercions") -> cont 147;
	PT _ (TS "comment") -> cont 148;
	PT _ (TS "define") -> cont 149;
	PT _ (TS "digit") -> cont 150;
	PT _ (TS "entrypoints") -> cont 151;
	PT _ (TS "eps") -> cont 152;
	PT _ (TS "external") -> cont 153;
	PT _ (TS "internal") -> cont 154;
	PT _ (TS "layout") -> cont 155;
	PT _ (TS "letter") -> cont 156;
	PT _ (TS "lower") -> cont 157;
	PT _ (TS "nonempty") -> cont 158;
	PT _ (TS "position") -> cont 159;
	PT _ (TS "rules") -> cont 160;
	PT _ (TS "separator") -> cont 161;
	PT _ (TS "stop") -> cont 162;
	PT _ (TS "terminator") -> cont 163;
	PT _ (TS "token") -> cont 164;
	PT _ (TS "toplevel") -> cont 165;
	PT _ (TS "upper") -> cont 166;
	PT _ (TL happy_dollar_dollar) -> cont 167;
	PT _ (TV happy_dollar_dollar) -> cont 168;
	PT _ (TI happy_dollar_dollar) -> cont 169;
	PT _ (TC happy_dollar_dollar) -> cont 170;
	PT _ (TD happy_dollar_dollar) -> cont 171;
	_ -> cont 172;
	_ -> happyError' (tk:tks)
	}

happyError_ tk tks = happyError' (tk:tks)

happyThen :: () => ParseMonad a -> (a -> ParseMonad b) -> ParseMonad b
happyThen = (>>=)
happyReturn :: () => a -> ParseMonad a
happyReturn = (return)
happyThen1 m k tks = (>>=) m (\a -> k a tks)
happyReturn1 :: () => a -> b -> ParseMonad a
happyReturn1 = \a tks -> (return) a
happyError' :: () => [(Token)] -> ParseMonad a
happyError' = happyError

pGrammar tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_0 tks) (\x -> case x of {HappyAbsSyn69 z -> happyReturn z; _other -> notHappyAtAll })

qGrammar tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_1 tks) (\x -> case x of {HappyAbsSyn60 z -> happyReturn z; _other -> notHappyAtAll })

pListDef tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_2 tks) (\x -> case x of {HappyAbsSyn71 z -> happyReturn z; _other -> notHappyAtAll })

qListDef tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_3 tks) (\x -> case x of {HappyAbsSyn60 z -> happyReturn z; _other -> notHappyAtAll })

pListItem tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_4 tks) (\x -> case x of {HappyAbsSyn73 z -> happyReturn z; _other -> notHappyAtAll })

qListItem tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_5 tks) (\x -> case x of {HappyAbsSyn60 z -> happyReturn z; _other -> notHappyAtAll })

pDef tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_6 tks) (\x -> case x of {HappyAbsSyn75 z -> happyReturn z; _other -> notHappyAtAll })

qDef tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_7 tks) (\x -> case x of {HappyAbsSyn60 z -> happyReturn z; _other -> notHappyAtAll })

pRHS tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_8 tks) (\x -> case x of {HappyAbsSyn77 z -> happyReturn z; _other -> notHappyAtAll })

qRHS tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_9 tks) (\x -> case x of {HappyAbsSyn60 z -> happyReturn z; _other -> notHappyAtAll })

pListRHS tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_10 tks) (\x -> case x of {HappyAbsSyn79 z -> happyReturn z; _other -> notHappyAtAll })

qListRHS tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_11 tks) (\x -> case x of {HappyAbsSyn60 z -> happyReturn z; _other -> notHappyAtAll })

pItem tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_12 tks) (\x -> case x of {HappyAbsSyn81 z -> happyReturn z; _other -> notHappyAtAll })

qItem tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_13 tks) (\x -> case x of {HappyAbsSyn60 z -> happyReturn z; _other -> notHappyAtAll })

pCat tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_14 tks) (\x -> case x of {HappyAbsSyn83 z -> happyReturn z; _other -> notHappyAtAll })

qCat tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_15 tks) (\x -> case x of {HappyAbsSyn60 z -> happyReturn z; _other -> notHappyAtAll })

pCat1 tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_16 tks) (\x -> case x of {HappyAbsSyn83 z -> happyReturn z; _other -> notHappyAtAll })

qCat1 tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_17 tks) (\x -> case x of {HappyAbsSyn60 z -> happyReturn z; _other -> notHappyAtAll })

pLabel tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_18 tks) (\x -> case x of {HappyAbsSyn87 z -> happyReturn z; _other -> notHappyAtAll })

qLabel tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_19 tks) (\x -> case x of {HappyAbsSyn60 z -> happyReturn z; _other -> notHappyAtAll })

pMIdent tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_20 tks) (\x -> case x of {HappyAbsSyn89 z -> happyReturn z; _other -> notHappyAtAll })

qMIdent tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_21 tks) (\x -> case x of {HappyAbsSyn60 z -> happyReturn z; _other -> notHappyAtAll })

pHsTyp tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_22 tks) (\x -> case x of {HappyAbsSyn91 z -> happyReturn z; _other -> notHappyAtAll })

qHsTyp tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_23 tks) (\x -> case x of {HappyAbsSyn60 z -> happyReturn z; _other -> notHappyAtAll })

pHsTyp1 tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_24 tks) (\x -> case x of {HappyAbsSyn91 z -> happyReturn z; _other -> notHappyAtAll })

qHsTyp1 tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_25 tks) (\x -> case x of {HappyAbsSyn60 z -> happyReturn z; _other -> notHappyAtAll })

pListHsTyp tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_26 tks) (\x -> case x of {HappyAbsSyn95 z -> happyReturn z; _other -> notHappyAtAll })

qListHsTyp tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_27 tks) (\x -> case x of {HappyAbsSyn60 z -> happyReturn z; _other -> notHappyAtAll })

pArg tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_28 tks) (\x -> case x of {HappyAbsSyn97 z -> happyReturn z; _other -> notHappyAtAll })

qArg tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_29 tks) (\x -> case x of {HappyAbsSyn60 z -> happyReturn z; _other -> notHappyAtAll })

pListArg tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_30 tks) (\x -> case x of {HappyAbsSyn99 z -> happyReturn z; _other -> notHappyAtAll })

qListArg tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_31 tks) (\x -> case x of {HappyAbsSyn60 z -> happyReturn z; _other -> notHappyAtAll })

pExp tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_32 tks) (\x -> case x of {HappyAbsSyn101 z -> happyReturn z; _other -> notHappyAtAll })

qExp tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_33 tks) (\x -> case x of {HappyAbsSyn60 z -> happyReturn z; _other -> notHappyAtAll })

pExp1 tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_34 tks) (\x -> case x of {HappyAbsSyn101 z -> happyReturn z; _other -> notHappyAtAll })

qExp1 tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_35 tks) (\x -> case x of {HappyAbsSyn60 z -> happyReturn z; _other -> notHappyAtAll })

pExp2 tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_36 tks) (\x -> case x of {HappyAbsSyn101 z -> happyReturn z; _other -> notHappyAtAll })

qExp2 tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_37 tks) (\x -> case x of {HappyAbsSyn60 z -> happyReturn z; _other -> notHappyAtAll })

pListExp2 tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_38 tks) (\x -> case x of {HappyAbsSyn107 z -> happyReturn z; _other -> notHappyAtAll })

qListExp2 tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_39 tks) (\x -> case x of {HappyAbsSyn60 z -> happyReturn z; _other -> notHappyAtAll })

pListExp tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_40 tks) (\x -> case x of {HappyAbsSyn107 z -> happyReturn z; _other -> notHappyAtAll })

qListExp tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_41 tks) (\x -> case x of {HappyAbsSyn60 z -> happyReturn z; _other -> notHappyAtAll })

pListString tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_42 tks) (\x -> case x of {HappyAbsSyn111 z -> happyReturn z; _other -> notHappyAtAll })

qListString tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_43 tks) (\x -> case x of {HappyAbsSyn60 z -> happyReturn z; _other -> notHappyAtAll })

pMinimumSize tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_44 tks) (\x -> case x of {HappyAbsSyn113 z -> happyReturn z; _other -> notHappyAtAll })

qMinimumSize tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_45 tks) (\x -> case x of {HappyAbsSyn60 z -> happyReturn z; _other -> notHappyAtAll })

pReg2 tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_46 tks) (\x -> case x of {HappyAbsSyn115 z -> happyReturn z; _other -> notHappyAtAll })

qReg2 tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_47 tks) (\x -> case x of {HappyAbsSyn60 z -> happyReturn z; _other -> notHappyAtAll })

pReg1 tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_48 tks) (\x -> case x of {HappyAbsSyn115 z -> happyReturn z; _other -> notHappyAtAll })

qReg1 tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_49 tks) (\x -> case x of {HappyAbsSyn60 z -> happyReturn z; _other -> notHappyAtAll })

pReg3 tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_50 tks) (\x -> case x of {HappyAbsSyn115 z -> happyReturn z; _other -> notHappyAtAll })

qReg3 tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_51 tks) (\x -> case x of {HappyAbsSyn60 z -> happyReturn z; _other -> notHappyAtAll })

pReg tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_52 tks) (\x -> case x of {HappyAbsSyn115 z -> happyReturn z; _other -> notHappyAtAll })

qReg tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_53 tks) (\x -> case x of {HappyAbsSyn60 z -> happyReturn z; _other -> notHappyAtAll })

pListIdent tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_54 tks) (\x -> case x of {HappyAbsSyn123 z -> happyReturn z; _other -> notHappyAtAll })

qListIdent tks = happySomeParser where
  happySomeParser = happyThen (happyParse action_55 tks) (\x -> case x of {HappyAbsSyn60 z -> happyReturn z; _other -> notHappyAtAll })

happySeq = happyDontSeq


happyError :: [Token] -> ParseMonad a
happyError ts =
  fail $ "syntax error at " ++ tokenPos ts ++ 
  case ts of
    [] -> []
    [Err _] -> " due to lexer error"
    _ -> " before " ++ unwords (map prToken (take 4 ts))

myLexer = tokens

myLocation = ("BNFC-meta-0.2.0.2","Language.LBNF.Grammar")

{-# LINE 1 "templates\GenericTemplate.hs" #-}
{-# LINE 1 "templates\\GenericTemplate.hs" #-}
{-# LINE 1 "<built-in>" #-}
{-# LINE 1 "<command line>" #-}
{-# LINE 1 "templates\\GenericTemplate.hs" #-}
-- Id: GenericTemplate.hs,v 1.26 2005/01/14 14:47:22 simonmar Exp 

{-# LINE 28 "templates\\GenericTemplate.hs" #-}








{-# LINE 49 "templates\\GenericTemplate.hs" #-}

{-# LINE 59 "templates\\GenericTemplate.hs" #-}

{-# LINE 68 "templates\\GenericTemplate.hs" #-}


-----------------------------------------------------------------------------
-- starting the parse

happyParse start_state = happyNewToken start_state notHappyAtAll notHappyAtAll

-----------------------------------------------------------------------------
-- Accepting the parse

-- If the current token is (1), it means we've just accepted a partial
-- parse (a %partial parser).  We must ignore the saved token on the top of
-- the stack in this case.
happyAccept (1) tk st sts (_ `HappyStk` ans `HappyStk` _) =
	happyReturn1 ans
happyAccept j tk st sts (HappyStk ans _) = 
	 (happyReturn1 ans)

-----------------------------------------------------------------------------
-- Arrays only: do the next action

{-# LINE 155 "templates\\GenericTemplate.hs" #-}

-----------------------------------------------------------------------------
-- HappyState data type (not arrays)



newtype HappyState b c = HappyState
        (Int ->                    -- token number
         Int ->                    -- token number (yes, again)
         b ->                           -- token semantic value
         HappyState b c ->              -- current state
         [HappyState b c] ->            -- state stack
         c)



-----------------------------------------------------------------------------
-- Shifting a token

happyShift new_state (1) tk st sts stk@(x `HappyStk` _) =
     let i = (case x of { HappyErrorToken (i) -> i }) in
--     trace "shifting the error token" $
     new_state i i tk (HappyState (new_state)) ((st):(sts)) (stk)

happyShift new_state i tk st sts stk =
     happyNewToken new_state ((st):(sts)) ((HappyTerminal (tk))`HappyStk`stk)

-- happyReduce is specialised for the common cases.

happySpecReduce_0 i fn (1) tk st sts stk
     = happyFail (1) tk st sts stk
happySpecReduce_0 nt fn j tk st@((HappyState (action))) sts stk
     = action nt j tk st ((st):(sts)) (fn `HappyStk` stk)

happySpecReduce_1 i fn (1) tk st sts stk
     = happyFail (1) tk st sts stk
happySpecReduce_1 nt fn j tk _ sts@(((st@(HappyState (action))):(_))) (v1`HappyStk`stk')
     = let r = fn v1 in
       happySeq r (action nt j tk st sts (r `HappyStk` stk'))

happySpecReduce_2 i fn (1) tk st sts stk
     = happyFail (1) tk st sts stk
happySpecReduce_2 nt fn j tk _ ((_):(sts@(((st@(HappyState (action))):(_))))) (v1`HappyStk`v2`HappyStk`stk')
     = let r = fn v1 v2 in
       happySeq r (action nt j tk st sts (r `HappyStk` stk'))

happySpecReduce_3 i fn (1) tk st sts stk
     = happyFail (1) tk st sts stk
happySpecReduce_3 nt fn j tk _ ((_):(((_):(sts@(((st@(HappyState (action))):(_))))))) (v1`HappyStk`v2`HappyStk`v3`HappyStk`stk')
     = let r = fn v1 v2 v3 in
       happySeq r (action nt j tk st sts (r `HappyStk` stk'))

happyReduce k i fn (1) tk st sts stk
     = happyFail (1) tk st sts stk
happyReduce k nt fn j tk st sts stk
     = case happyDrop (k - ((1) :: Int)) sts of
	 sts1@(((st1@(HappyState (action))):(_))) ->
        	let r = fn stk in  -- it doesn't hurt to always seq here...
       		happyDoSeq r (action nt j tk st1 sts1 r)

happyMonadReduce k nt fn (1) tk st sts stk
     = happyFail (1) tk st sts stk
happyMonadReduce k nt fn j tk st sts stk =
        happyThen1 (fn stk tk) (\r -> action nt j tk st1 sts1 (r `HappyStk` drop_stk))
       where sts1@(((st1@(HappyState (action))):(_))) = happyDrop k ((st):(sts))
             drop_stk = happyDropStk k stk

happyMonad2Reduce k nt fn (1) tk st sts stk
     = happyFail (1) tk st sts stk
happyMonad2Reduce k nt fn j tk st sts stk =
       happyThen1 (fn stk tk) (\r -> happyNewToken new_state sts1 (r `HappyStk` drop_stk))
       where sts1@(((st1@(HappyState (action))):(_))) = happyDrop k ((st):(sts))
             drop_stk = happyDropStk k stk





             new_state = action


happyDrop (0) l = l
happyDrop n ((_):(t)) = happyDrop (n - ((1) :: Int)) t

happyDropStk (0) l = l
happyDropStk n (x `HappyStk` xs) = happyDropStk (n - ((1)::Int)) xs

-----------------------------------------------------------------------------
-- Moving to a new state after a reduction

{-# LINE 253 "templates\\GenericTemplate.hs" #-}
happyGoto action j tk st = action j j tk (HappyState action)


-----------------------------------------------------------------------------
-- Error recovery ((1) is the error token)

-- parse error if we are in recovery and we fail again
happyFail  (1) tk old_st _ stk =
--	trace "failing" $ 
    	happyError_ tk

{-  We don't need state discarding for our restricted implementation of
    "error".  In fact, it can cause some bogus parses, so I've disabled it
    for now --SDM

-- discard a state
happyFail  (1) tk old_st (((HappyState (action))):(sts)) 
						(saved_tok `HappyStk` _ `HappyStk` stk) =
--	trace ("discarding state, depth " ++ show (length stk))  $
	action (1) (1) tk (HappyState (action)) sts ((saved_tok`HappyStk`stk))
-}

-- Enter error recovery: generate an error token,
--                       save the old token and carry on.
happyFail  i tk (HappyState (action)) sts stk =
--      trace "entering error recovery" $
	action (1) (1) tk (HappyState (action)) sts ( (HappyErrorToken (i)) `HappyStk` stk)

-- Internal happy errors:\n
notHappyAtAll = error "Internal Happy error\n"
-----------------------------------------------------------------------------
-- Hack to get the typechecker to accept our action functions







-----------------------------------------------------------------------------
-- Seq-ing.  If the --strict flag is given, then Happy emits 
--	happySeq = happyDoSeq
-- otherwise it emits
-- 	happySeq = happyDontSeq

happyDoSeq, happyDontSeq :: a -> b -> b
happyDoSeq   a b = a `seq` b
happyDontSeq a b = b

-----------------------------------------------------------------------------
-- Don't inline any functions from the template.  GHC has a nasty habit
-- of deciding to inline happyGoto everywhere, which increases the size of
-- the generated parser quite a bit.

{-# LINE 317 "templates\\GenericTemplate.hs" #-}
{-# NOINLINE happyShift #-}
{-# NOINLINE happySpecReduce_0 #-}
{-# NOINLINE happySpecReduce_1 #-}
{-# NOINLINE happySpecReduce_2 #-}
{-# NOINLINE happySpecReduce_3 #-}
{-# NOINLINE happyReduce #-}
{-# NOINLINE happyMonadReduce #-}
{-# NOINLINE happyGoto #-}
{-# NOINLINE happyFail #-}

-- end of Happy Template.