{-# OPTIONS_GHC -w #-}
{-# OPTIONS -fglasgow-exts -cpp #-}
module Camfort.Specification.Stencils.Parser
  ( specParser
  , SpecParseError
  ) where

import Control.Monad.Except (throwError)
import Data.Char (isLetter, isNumber, isAlphaNum, toLower, isAlpha, isSpace)
import Data.List (intercalate, isInfixOf)

import           Camfort.Specification.Parser
  (SpecParser, mkParser)
import           Camfort.Specification.Stencils.Model
  (Approximation(..), Multiplicity(..))
import           Camfort.Specification.Stencils.Parser.Types
import qualified Camfort.Specification.Stencils.Syntax as Syn
import qualified Data.Array as Happy_Data_Array
import qualified GHC.Exts as Happy_GHC_Exts
import Control.Applicative(Applicative(..))
import Control.Monad (ap)

-- parser produced by Happy Version 1.19.5

newtype HappyAbsSyn  = HappyAbsSyn HappyAny
#if __GLASGOW_HASKELL__ >= 607
type HappyAny = Happy_GHC_Exts.Any
#else
type HappyAny = forall a . a
#endif
happyIn4 :: (Specification) -> (HappyAbsSyn )
happyIn4 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn4 #-}
happyOut4 :: (HappyAbsSyn ) -> (Specification)
happyOut4 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut4 #-}
happyIn5 :: ((String, Region)) -> (HappyAbsSyn )
happyIn5 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn5 #-}
happyOut5 :: (HappyAbsSyn ) -> ((String, Region))
happyOut5 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut5 #-}
happyIn6 :: (Region) -> (HappyAbsSyn )
happyIn6 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn6 #-}
happyOut6 :: (HappyAbsSyn ) -> (Region)
happyOut6 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut6 #-}
happyIn7 :: (Syn.Region) -> (HappyAbsSyn )
happyIn7 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn7 #-}
happyOut7 :: (HappyAbsSyn ) -> (Syn.Region)
happyOut7 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut7 #-}
happyIn8 :: ((Depth Int, Dim Int, Bool)) -> (HappyAbsSyn )
happyIn8 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn8 #-}
happyOut8 :: (HappyAbsSyn ) -> ((Depth Int, Dim Int, Bool))
happyOut8 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut8 #-}
happyIn9 :: ((Dim Int, Bool)) -> (HappyAbsSyn )
happyIn9 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn9 #-}
happyOut9 :: (HappyAbsSyn ) -> ((Dim Int, Bool))
happyOut9 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut9 #-}
happyIn10 :: ((Depth Int, Bool)) -> (HappyAbsSyn )
happyIn10 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn10 #-}
happyOut10 :: (HappyAbsSyn ) -> ((Depth Int, Bool))
happyOut10 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut10 #-}
happyIn11 :: (Depth Int) -> (HappyAbsSyn )
happyIn11 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn11 #-}
happyOut11 :: (HappyAbsSyn ) -> (Depth Int)
happyOut11 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut11 #-}
happyIn12 :: (Dim Int) -> (HappyAbsSyn )
happyIn12 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn12 #-}
happyOut12 :: (HappyAbsSyn ) -> (Dim Int)
happyOut12 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut12 #-}
happyIn13 :: (Bool) -> (HappyAbsSyn )
happyIn13 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn13 #-}
happyOut13 :: (HappyAbsSyn ) -> (Bool)
happyOut13 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut13 #-}
happyIn14 :: (Syn.IsStencil -> SpecInner) -> (HappyAbsSyn )
happyIn14 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn14 #-}
happyOut14 :: (HappyAbsSyn ) -> (Syn.IsStencil -> SpecInner)
happyOut14 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut14 #-}
happyIn15 :: (Multiplicity (Approximation Region)) -> (HappyAbsSyn )
happyIn15 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn15 #-}
happyOut15 :: (HappyAbsSyn ) -> (Multiplicity (Approximation Region))
happyOut15 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut15 #-}
happyIn16 :: (Approximation Region) -> (HappyAbsSyn )
happyIn16 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn16 #-}
happyOut16 :: (HappyAbsSyn ) -> (Approximation Region)
happyOut16 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut16 #-}
happyIn17 :: ([String]) -> (HappyAbsSyn )
happyIn17 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyIn17 #-}
happyOut17 :: (HappyAbsSyn ) -> ([String])
happyOut17 x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOut17 #-}
happyInTok :: (Token) -> (HappyAbsSyn )
happyInTok x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyInTok #-}
happyOutTok :: (HappyAbsSyn ) -> (Token)
happyOutTok x = Happy_GHC_Exts.unsafeCoerce# x
{-# INLINE happyOutTok #-}


happyActOffsets :: HappyAddr
happyActOffsets = HappyA# "\x48\x00\x84\x00\x00\x00\x79\x00\x6e\x00\xfd\xff\xfd\xff\x4d\x00\x00\x00\x77\x00\x00\x00\x00\x00\x07\x00\x76\x00\x0b\x00\x0b\x00\x74\x00\x72\x00\x71\x00\x00\x00\x0b\x00\x4f\x00\x75\x00\x6f\x00\x73\x00\x28\x00\x38\x00\x38\x00\x38\x00\x4d\x00\x4d\x00\x6d\x00\x00\x00\x70\x00\x0b\x00\x0b\x00\x00\x00\x68\x00\x00\x00\x67\x00\x6c\x00\x6b\x00\x3f\x00\x14\x00\x51\x00\x00\x00\x6a\x00\x69\x00\x66\x00\x65\x00\x00\x00\x00\x00\x0b\x00\x2f\x00\x00\x00\x00\x00\x64\x00\x61\x00\x63\x00\x5f\x00\x00\x00\x62\x00\x5d\x00\x00\x00\x60\x00\x5c\x00\x00\x00\x5b\x00\x00\x00\x5a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00"#

happyGotoOffsets :: HappyAddr
happyGotoOffsets = HappyA# "\x58\x00\x5e\x00\x00\x00\x00\x00\x00\x00\x1e\x00\x1a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x20\x00\x00\x00\x54\x00\x52\x00\x00\x00\x00\x00\x00\x00\x00\x00\x50\x00\x00\x00\x00\x00\x00\x00\x57\x00\x00\x00\x33\x00\x2d\x00\x27\x00\x00\x00\x00\x00\x00\x00\x00\x00\x56\x00\x4e\x00\x4c\x00\x00\x00\x00\x00\x00\x00\x55\x00\x00\x00\x00\x00\xfe\xff\x3d\x00\x45\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x30\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x1f\x00\x59\x00\x00\x00\x53\x00\x40\x00\x00\x00\x24\x00\x05\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00"#

happyDefActions :: HappyAddr
happyDefActions = HappyA# "\x00\x00\x00\x00\xfe\xff\x00\x00\x00\x00\x00\x00\x00\x00\xdf\xff\xfa\xff\x00\x00\xe4\xff\xe2\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xf6\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe1\xff\xe0\xff\x00\x00\xe3\xff\x00\x00\x00\x00\x00\x00\xf8\xff\xf9\xff\xfc\xff\xdd\xff\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\xe5\xff\x00\x00\x00\x00\x00\x00\x00\x00\xf7\xff\xfd\xff\x00\x00\xfb\xff\xf3\xff\xf4\xff\x00\x00\x00\x00\x00\x00\x00\x00\xf0\xff\xe8\xff\x00\x00\xf1\xff\xeb\xff\x00\x00\xf5\xff\x00\x00\xde\xff\x00\x00\xed\xff\xec\xff\xe9\xff\xea\xff\xee\xff\xef\xff\xe6\xff\xe7\xff\xf2\xff"#

happyCheck :: HappyAddr
happyCheck = HappyA# "\xff\xff\x04\x00\x05\x00\x05\x00\x07\x00\x08\x00\x08\x00\x09\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x05\x00\x08\x00\x07\x00\x08\x00\x05\x00\x14\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x0b\x00\x0c\x00\x0d\x00\x0e\x00\x06\x00\x14\x00\x02\x00\x03\x00\x0a\x00\x14\x00\x02\x00\x03\x00\x02\x00\x03\x00\x0a\x00\x0b\x00\x0c\x00\x08\x00\x0a\x00\x0b\x00\x0c\x00\x04\x00\x0c\x00\x09\x00\x07\x00\x08\x00\x09\x00\x04\x00\x02\x00\x03\x00\x07\x00\x08\x00\x09\x00\x04\x00\x10\x00\x11\x00\x07\x00\x08\x00\x09\x00\x15\x00\x06\x00\x10\x00\x11\x00\x09\x00\x0a\x00\x06\x00\x07\x00\x06\x00\x09\x00\x07\x00\x09\x00\x01\x00\x02\x00\x03\x00\x07\x00\x08\x00\x02\x00\x03\x00\x02\x00\x03\x00\x02\x00\x03\x00\x02\x00\x03\x00\x02\x00\x03\x00\x00\x00\x01\x00\x09\x00\x0a\x00\x09\x00\x10\x00\x11\x00\x01\x00\x07\x00\x12\x00\x0d\x00\x0d\x00\x0d\x00\x09\x00\x06\x00\x0a\x00\x06\x00\x0a\x00\x0f\x00\xff\xff\x09\x00\xff\xff\xff\xff\x15\x00\x0f\x00\xff\xff\xff\xff\x0f\x00\xff\xff\x0e\x00\x09\x00\xff\xff\xff\xff\x11\x00\x15\x00\x15\x00\x13\x00\x13\x00\x0e\x00\x13\x00\x15\x00\x0e\x00\x13\x00\x0e\x00\x16\x00\x14\x00\x14\x00\x03\x00\x14\x00\x12\x00\x14\x00\x12\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff"#

happyTable :: HappyAddr
happyTable = HappyA# "\x00\x00\x0d\x00\x0e\x00\x3f\x00\x0f\x00\x10\x00\x40\x00\x41\x00\x11\x00\x12\x00\x13\x00\x14\x00\x0e\x00\x46\x00\x0f\x00\x10\x00\x0e\x00\x15\x00\x11\x00\x12\x00\x13\x00\x14\x00\x11\x00\x12\x00\x13\x00\x14\x00\x2e\x00\x15\x00\x07\x00\x08\x00\x30\x00\x15\x00\x07\x00\x08\x00\x07\x00\x08\x00\x09\x00\x0a\x00\x0b\x00\x4b\x00\x15\x00\x0a\x00\x0b\x00\x29\x00\x20\x00\x47\x00\x2a\x00\x2b\x00\x2c\x00\x30\x00\x35\x00\x08\x00\x2a\x00\x2b\x00\x2c\x00\x31\x00\x23\x00\x24\x00\x2a\x00\x2b\x00\x2c\x00\x33\x00\x2e\x00\x23\x00\x24\x00\x2f\x00\x30\x00\x3c\x00\x3d\x00\x2e\x00\x3e\x00\x48\x00\x2f\x00\x06\x00\x07\x00\x04\x00\x3a\x00\x3b\x00\x24\x00\x08\x00\x25\x00\x08\x00\x19\x00\x08\x00\x1d\x00\x08\x00\x1e\x00\x08\x00\x04\x00\x02\x00\x2f\x00\x30\x00\x49\x00\x23\x00\x24\x00\x02\x00\x4a\x00\x19\x00\x44\x00\x26\x00\x33\x00\x2f\x00\x2e\x00\x30\x00\x2e\x00\x30\x00\x46\x00\x00\x00\x2f\x00\x00\x00\x00\x00\x4f\x00\x4d\x00\x00\x00\x00\x00\x4e\x00\x00\x00\x28\x00\x29\x00\x00\x00\x00\x00\x24\x00\x37\x00\x38\x00\x39\x00\x3a\x00\x28\x00\x44\x00\x43\x00\x28\x00\x35\x00\x18\x00\xff\xff\x1b\x00\x1c\x00\x04\x00\x1d\x00\x22\x00\x20\x00\x17\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00"#

happyReduceArr = Happy_Data_Array.array (1, 34) [
	(1 , happyReduce_1),
	(2 , happyReduce_2),
	(3 , happyReduce_3),
	(4 , happyReduce_4),
	(5 , happyReduce_5),
	(6 , happyReduce_6),
	(7 , happyReduce_7),
	(8 , happyReduce_8),
	(9 , happyReduce_9),
	(10 , happyReduce_10),
	(11 , happyReduce_11),
	(12 , happyReduce_12),
	(13 , happyReduce_13),
	(14 , happyReduce_14),
	(15 , happyReduce_15),
	(16 , happyReduce_16),
	(17 , happyReduce_17),
	(18 , happyReduce_18),
	(19 , happyReduce_19),
	(20 , happyReduce_20),
	(21 , happyReduce_21),
	(22 , happyReduce_22),
	(23 , happyReduce_23),
	(24 , happyReduce_24),
	(25 , happyReduce_25),
	(26 , happyReduce_26),
	(27 , happyReduce_27),
	(28 , happyReduce_28),
	(29 , happyReduce_29),
	(30 , happyReduce_30),
	(31 , happyReduce_31),
	(32 , happyReduce_32),
	(33 , happyReduce_33),
	(34 , happyReduce_34)
	]

happy_n_terms = 23 :: Int
happy_n_nonterms = 14 :: Int

happyReduce_1 = happySpecReduce_1  0# happyReduction_1
happyReduction_1 happy_x_1
	 =  case happyOut5 happy_x_1 of { happy_var_1 -> 
	happyIn4
		 (RegionDec (fst happy_var_1) (snd happy_var_1)
	)}

happyReduce_2 = happyReduce 4# 0# happyReduction_2
happyReduction_2 (happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOut14 happy_x_2 of { happy_var_2 -> 
	case happyOut17 happy_x_4 of { happy_var_4 -> 
	happyIn4
		 (SpecDec (happy_var_2 True) happy_var_4
	) `HappyStk` happyRest}}

happyReduce_3 = happyReduce 4# 0# happyReduction_3
happyReduction_3 (happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOut14 happy_x_2 of { happy_var_2 -> 
	case happyOut17 happy_x_4 of { happy_var_4 -> 
	happyIn4
		 (SpecDec (happy_var_2 False) happy_var_4
	) `HappyStk` happyRest}}

happyReduce_4 = happyReduce 5# 1# happyReduction_4
happyReduction_4 (happy_x_5 `HappyStk`
	happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOutTok happy_x_3 of { (TId _ happy_var_3) -> 
	case happyOut6 happy_x_5 of { happy_var_5 -> 
	happyIn5
		 ((happy_var_3, happy_var_5)
	) `HappyStk` happyRest}}

happyReduce_5 = happySpecReduce_1  2# happyReduction_5
happyReduction_5 happy_x_1
	 =  case happyOut7 happy_x_1 of { happy_var_1 -> 
	happyIn6
		 (RegionConst happy_var_1
	)}

happyReduce_6 = happySpecReduce_3  2# happyReduction_6
happyReduction_6 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOut6 happy_x_1 of { happy_var_1 -> 
	case happyOut6 happy_x_3 of { happy_var_3 -> 
	happyIn6
		 (Or happy_var_1 happy_var_3
	)}}

happyReduce_7 = happySpecReduce_3  2# happyReduction_7
happyReduction_7 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOut6 happy_x_1 of { happy_var_1 -> 
	case happyOut6 happy_x_3 of { happy_var_3 -> 
	happyIn6
		 (And happy_var_1 happy_var_3
	)}}

happyReduce_8 = happySpecReduce_3  2# happyReduction_8
happyReduction_8 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOut6 happy_x_2 of { happy_var_2 -> 
	happyIn6
		 (happy_var_2
	)}

happyReduce_9 = happySpecReduce_1  2# happyReduction_9
happyReduction_9 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TId _ happy_var_1) -> 
	happyIn6
		 (Var happy_var_1
	)}

happyReduce_10 = happyReduce 4# 3# happyReduction_10
happyReduction_10 (happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOut8 happy_x_3 of { happy_var_3 -> 
	happyIn7
		 (applyAttr Syn.Forward  happy_var_3
	) `HappyStk` happyRest}

happyReduce_11 = happyReduce 4# 3# happyReduction_11
happyReduction_11 (happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOut8 happy_x_3 of { happy_var_3 -> 
	happyIn7
		 (applyAttr Syn.Backward happy_var_3
	) `HappyStk` happyRest}

happyReduce_12 = happyReduce 4# 3# happyReduction_12
happyReduction_12 (happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOut8 happy_x_3 of { happy_var_3 -> 
	happyIn7
		 (applyAttr Syn.Centered happy_var_3
	) `HappyStk` happyRest}

happyReduce_13 = happyReduce 6# 3# happyReduction_13
happyReduction_13 (happy_x_6 `HappyStk`
	happy_x_5 `HappyStk`
	happy_x_4 `HappyStk`
	happy_x_3 `HappyStk`
	happy_x_2 `HappyStk`
	happy_x_1 `HappyStk`
	happyRest)
	 = case happyOutTok happy_x_5 of { (TNum happy_var_5) -> 
	happyIn7
		 (Syn.Centered 0 (read happy_var_5) True
	) `HappyStk` happyRest}

happyReduce_14 = happySpecReduce_2  4# happyReduction_14
happyReduction_14 happy_x_2
	happy_x_1
	 =  case happyOut11 happy_x_1 of { happy_var_1 -> 
	case happyOut9 happy_x_2 of { happy_var_2 -> 
	happyIn8
		 ((happy_var_1, fst happy_var_2, snd happy_var_2)
	)}}

happyReduce_15 = happySpecReduce_2  4# happyReduction_15
happyReduction_15 happy_x_2
	happy_x_1
	 =  case happyOut12 happy_x_1 of { happy_var_1 -> 
	case happyOut10 happy_x_2 of { happy_var_2 -> 
	happyIn8
		 ((fst happy_var_2, happy_var_1, snd happy_var_2)
	)}}

happyReduce_16 = happySpecReduce_3  4# happyReduction_16
happyReduction_16 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOut13 happy_x_1 of { happy_var_1 -> 
	case happyOut11 happy_x_2 of { happy_var_2 -> 
	case happyOut12 happy_x_3 of { happy_var_3 -> 
	happyIn8
		 ((happy_var_2, happy_var_3, happy_var_1)
	)}}}

happyReduce_17 = happySpecReduce_3  4# happyReduction_17
happyReduction_17 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOut13 happy_x_1 of { happy_var_1 -> 
	case happyOut12 happy_x_2 of { happy_var_2 -> 
	case happyOut11 happy_x_3 of { happy_var_3 -> 
	happyIn8
		 ((happy_var_3, happy_var_2, happy_var_1)
	)}}}

happyReduce_18 = happySpecReduce_2  5# happyReduction_18
happyReduction_18 happy_x_2
	happy_x_1
	 =  case happyOut13 happy_x_1 of { happy_var_1 -> 
	case happyOut12 happy_x_2 of { happy_var_2 -> 
	happyIn9
		 ((happy_var_2, happy_var_1)
	)}}

happyReduce_19 = happySpecReduce_2  5# happyReduction_19
happyReduction_19 happy_x_2
	happy_x_1
	 =  case happyOut12 happy_x_1 of { happy_var_1 -> 
	case happyOut13 happy_x_2 of { happy_var_2 -> 
	happyIn9
		 ((happy_var_1, happy_var_2)
	)}}

happyReduce_20 = happySpecReduce_1  5# happyReduction_20
happyReduction_20 happy_x_1
	 =  case happyOut12 happy_x_1 of { happy_var_1 -> 
	happyIn9
		 ((happy_var_1, True)
	)}

happyReduce_21 = happySpecReduce_2  6# happyReduction_21
happyReduction_21 happy_x_2
	happy_x_1
	 =  case happyOut11 happy_x_1 of { happy_var_1 -> 
	case happyOut13 happy_x_2 of { happy_var_2 -> 
	happyIn10
		 ((happy_var_1, happy_var_2)
	)}}

happyReduce_22 = happySpecReduce_2  6# happyReduction_22
happyReduction_22 happy_x_2
	happy_x_1
	 =  case happyOut13 happy_x_1 of { happy_var_1 -> 
	case happyOut11 happy_x_2 of { happy_var_2 -> 
	happyIn10
		 ((happy_var_2, happy_var_1)
	)}}

happyReduce_23 = happySpecReduce_1  6# happyReduction_23
happyReduction_23 happy_x_1
	 =  case happyOut11 happy_x_1 of { happy_var_1 -> 
	happyIn10
		 ((happy_var_1, True)
	)}

happyReduce_24 = happySpecReduce_3  7# happyReduction_24
happyReduction_24 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOutTok happy_x_3 of { (TNum happy_var_3) -> 
	happyIn11
		 (Depth $ read happy_var_3
	)}

happyReduce_25 = happySpecReduce_3  8# happyReduction_25
happyReduction_25 happy_x_3
	happy_x_2
	happy_x_1
	 =  case happyOutTok happy_x_3 of { (TNum happy_var_3) -> 
	happyIn12
		 (Dim $ read happy_var_3
	)}

happyReduce_26 = happySpecReduce_1  9# happyReduction_26
happyReduction_26 happy_x_1
	 =  happyIn13
		 (False
	)

happyReduce_27 = happySpecReduce_1  10# happyReduction_27
happyReduction_27 happy_x_1
	 =  case happyOut15 happy_x_1 of { happy_var_1 -> 
	happyIn14
		 (SpecInner happy_var_1
	)}

happyReduce_28 = happySpecReduce_2  11# happyReduction_28
happyReduction_28 happy_x_2
	happy_x_1
	 =  case happyOut16 happy_x_2 of { happy_var_2 -> 
	happyIn15
		 (Once happy_var_2
	)}

happyReduce_29 = happySpecReduce_1  11# happyReduction_29
happyReduction_29 happy_x_1
	 =  case happyOut16 happy_x_1 of { happy_var_1 -> 
	happyIn15
		 (Mult happy_var_1
	)}

happyReduce_30 = happySpecReduce_2  12# happyReduction_30
happyReduction_30 happy_x_2
	happy_x_1
	 =  case happyOut6 happy_x_2 of { happy_var_2 -> 
	happyIn16
		 (Bound (Just happy_var_2) Nothing
	)}

happyReduce_31 = happySpecReduce_2  12# happyReduction_31
happyReduction_31 happy_x_2
	happy_x_1
	 =  case happyOut6 happy_x_2 of { happy_var_2 -> 
	happyIn16
		 (Bound Nothing (Just happy_var_2)
	)}

happyReduce_32 = happySpecReduce_1  12# happyReduction_32
happyReduction_32 happy_x_1
	 =  case happyOut6 happy_x_1 of { happy_var_1 -> 
	happyIn16
		 (Exact happy_var_1
	)}

happyReduce_33 = happySpecReduce_2  13# happyReduction_33
happyReduction_33 happy_x_2
	happy_x_1
	 =  case happyOutTok happy_x_1 of { (TId _ happy_var_1) -> 
	case happyOut17 happy_x_2 of { happy_var_2 -> 
	happyIn17
		 (happy_var_1 : happy_var_2
	)}}

happyReduce_34 = happySpecReduce_1  13# happyReduction_34
happyReduction_34 happy_x_1
	 =  case happyOutTok happy_x_1 of { (TId _ happy_var_1) -> 
	happyIn17
		 ([happy_var_1]
	)}

happyNewToken action sts stk [] =
	happyDoAction 22# notHappyAtAll action sts stk []

happyNewToken action sts stk (tk:tks) =
	let cont i = happyDoAction i tk action sts stk tks in
	case tk of {
	TId _ "stencil" -> cont 1#;
	TId _ "access" -> cont 2#;
	TId _ "region" -> cont 3#;
	TId _ "readonce" -> cont 4#;
	TId _ "pointed" -> cont 5#;
	TId _ "nonpointed" -> cont 6#;
	TId _ "atmost" -> cont 7#;
	TId _ "atleast" -> cont 8#;
	TId _ "dim" -> cont 9#;
	TId _ "depth" -> cont 10#;
	TId _ "forward" -> cont 11#;
	TId _ "backward" -> cont 12#;
	TId _ "centered" -> cont 13#;
	TId _ happy_dollar_dollar -> cont 14#;
	TNum happy_dollar_dollar -> cont 15#;
	TPlus -> cont 16#;
	TStar -> cont 17#;
	TDoubleColon -> cont 18#;
	TEqual -> cont 19#;
	TLParen -> cont 20#;
	TRParen -> cont 21#;
	_ -> happyError' (tk:tks)
	}

happyError_ 22# tk tks = happyError' tks
happyError_ _ tk tks = happyError' (tk:tks)

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

parseSpecification tks = happySomeParser where
  happySomeParser = happyThen (happyParse 0# tks) (\x -> happyReturn (happyOut4 x))

happySeq = happyDontSeq


-- ** Errors

data SpecParseError
  -- | Not a valid identifier character.
  = NotAnIdentifier Char
  -- | Tokens do not represent a syntactically valid specification.
  | CouldNotParseSpecification [Token]
  deriving (Eq)

instance Show SpecParseError where
  show (CouldNotParseSpecification ts) =
    "Could not parse specification at: \"" ++ prettyTokens ts ++ "\"\n"
  show (NotAnIdentifier c) = "Invalid character in identifier: " ++ show c

notAnIdentifier :: Char -> SpecParseError
notAnIdentifier = NotAnIdentifier

couldNotParseSpecification :: [Token] -> SpecParseError
couldNotParseSpecification = CouldNotParseSpecification

type StencilSpecParser a = Either SpecParseError a

newtype Depth a = Depth a
newtype Dim a = Dim a

applyAttr :: (Int -> Int -> Bool -> Syn.Region)
          -> (Depth Int, Dim Int, Bool)
          -> Syn.Region
applyAttr constr (Depth d, Dim dim, irrefl) = constr d dim irrefl

data Token
  = TDoubleColon
  | TStar
  | TPlus
  | TEqual
  | TComma
  | TLParen
  | TRParen
  | TId String String -- first string contains the original text
                      -- second is normalised (e.g., for keywords)
  | TNum String
 deriving (Show, Eq)

addToTokens :: Token -> String -> StencilSpecParser [ Token ]
addToTokens tok rest = do
 tokens <- lexer rest
 return $ tok : tokens

lexer :: String -> StencilSpecParser [ Token ]
lexer []                                              = return []
lexer (' ':xs)                                        = lexer xs
lexer ('\t':xs)                                       = lexer xs
lexer (':':':':xs)                                    = addToTokens TDoubleColon xs
lexer ('*':xs)                                        = addToTokens TStar xs
lexer ('+':xs)                                        = addToTokens TPlus xs
lexer ('=':xs)                                        = addToTokens TEqual xs
-- Comma hack: drop commas that are not separating numbers,
-- in order to avoid need for 2-token lookahead.
lexer (',':xs)
  | x':xs' <- dropWhile isSpace xs, not (isNumber x') = lexer (x':xs')
  | otherwise                                         = addToTokens TComma xs
lexer ('(':xs)                                       = addToTokens TLParen xs
lexer (')':xs)                                       = addToTokens TRParen xs
lexer (x:xs)
  | isLetter x                                        =
        aux (\x -> TId x $ fmap toLower x) $ \ c -> isAlphaNum c || c == '_'
  | isPositiveNumber x                                = aux TNum isNumber
  | otherwise
     = throwError $ notAnIdentifier x
 where
   isPositiveNumber x = isNumber x && x /= '0'
   aux f p = (f target :) <$> lexer rest
     where (target, rest) = span p (x:xs)

specParser :: SpecParser SpecParseError Specification
specParser = mkParser (\src -> do
                          tokens <- lexer src
                          parseSpecification tokens)
             ["stencil", "region", "access"]

happyError :: [ Token ] -> StencilSpecParser a
happyError = throwError . couldNotParseSpecification

-- | Pretty-print the tokens, showing the smallest unique prefix of tokens
prettyTokens :: [ Token ] -> String
prettyTokens =
    (++ "... ") . intercalate " " . map prettyToken . takeUniquePrefix 1
  where
    takeUniquePrefix _ [] = []
    takeUniquePrefix n ts =
      if ((take n ts) `isInfixOf` (drop n ts))
      then takeUniquePrefix (n+1) ts
      else take n ts

prettyToken TDoubleColon = "::"
prettyToken TStar        = "*"
prettyToken TPlus        = "+"
prettyToken TEqual       = "="
prettyToken TComma       = ","
prettyToken TLParen      = "("
prettyToken TRParen      = ")"
prettyToken (TId s _)    = s
prettyToken (TNum n)     = n
{-# LINE 1 "templates/GenericTemplate.hs" #-}
{-# LINE 1 "templates/GenericTemplate.hs" #-}
{-# LINE 1 "<built-in>" #-}
{-# LINE 1 "<command-line>" #-}
{-# LINE 11 "<command-line>" #-}
# 1 "/usr/include/stdc-predef.h" 1 3 4

# 17 "/usr/include/stdc-predef.h" 3 4










































{-# LINE 11 "<command-line>" #-}
{-# LINE 1 "/opt/ghc/8.0.2/lib/ghc-8.0.1.20160521/include/ghcversion.h" #-}


















{-# LINE 11 "<command-line>" #-}
{-# LINE 1 "/tmp/ghc16675_0/ghc_2.h" #-}






































































































































































































































































































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

{-# LINE 13 "templates/GenericTemplate.hs" #-}





-- Do not remove this comment. Required to fix CPP parsing when using GCC and a clang-compiled alex.
#if __GLASGOW_HASKELL__ > 706
#define LT(n,m) ((Happy_GHC_Exts.tagToEnum# (n Happy_GHC_Exts.<# m)) :: Bool)
#define GTE(n,m) ((Happy_GHC_Exts.tagToEnum# (n Happy_GHC_Exts.>=# m)) :: Bool)
#define EQ(n,m) ((Happy_GHC_Exts.tagToEnum# (n Happy_GHC_Exts.==# m)) :: Bool)
#else
#define LT(n,m) (n Happy_GHC_Exts.<# m)
#define GTE(n,m) (n Happy_GHC_Exts.>=# m)
#define EQ(n,m) (n Happy_GHC_Exts.==# m)
#endif
{-# LINE 46 "templates/GenericTemplate.hs" #-}


data Happy_IntList = HappyCons Happy_GHC_Exts.Int# Happy_IntList





{-# LINE 67 "templates/GenericTemplate.hs" #-}

{-# LINE 77 "templates/GenericTemplate.hs" #-}

{-# LINE 86 "templates/GenericTemplate.hs" #-}

infixr 9 `HappyStk`
data HappyStk a = HappyStk a (HappyStk a)

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

happyParse start_state = happyNewToken start_state notHappyAtAll notHappyAtAll

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

-- If the current token is 0#, 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 0# tk st sts (_ `HappyStk` ans `HappyStk` _) =
        happyReturn1 ans
happyAccept j tk st sts (HappyStk ans _) = 
        (happyTcHack j (happyTcHack st)) (happyReturn1 ans)

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



happyDoAction i tk st
        = {- nothing -}


          case action of
                0#           -> {- nothing -}
                                     happyFail i tk st
                -1#          -> {- nothing -}
                                     happyAccept i tk st
                n | LT(n,(0# :: Happy_GHC_Exts.Int#)) -> {- nothing -}

                                                   (happyReduceArr Happy_Data_Array.! rule) i tk st
                                                   where rule = (Happy_GHC_Exts.I# ((Happy_GHC_Exts.negateInt# ((n Happy_GHC_Exts.+# (1# :: Happy_GHC_Exts.Int#))))))
                n                 -> {- nothing -}


                                     happyShift new_state i tk st
                                     where new_state = (n Happy_GHC_Exts.-# (1# :: Happy_GHC_Exts.Int#))
   where off    = indexShortOffAddr happyActOffsets st
         off_i  = (off Happy_GHC_Exts.+# i)
         check  = if GTE(off_i,(0# :: Happy_GHC_Exts.Int#))
                  then EQ(indexShortOffAddr happyCheck off_i, i)
                  else False
         action
          | check     = indexShortOffAddr happyTable off_i
          | otherwise = indexShortOffAddr happyDefActions st


indexShortOffAddr (HappyA# arr) off =
        Happy_GHC_Exts.narrow16Int# i
  where
        i = Happy_GHC_Exts.word2Int# (Happy_GHC_Exts.or# (Happy_GHC_Exts.uncheckedShiftL# high 8#) low)
        high = Happy_GHC_Exts.int2Word# (Happy_GHC_Exts.ord# (Happy_GHC_Exts.indexCharOffAddr# arr (off' Happy_GHC_Exts.+# 1#)))
        low  = Happy_GHC_Exts.int2Word# (Happy_GHC_Exts.ord# (Happy_GHC_Exts.indexCharOffAddr# arr off'))
        off' = off Happy_GHC_Exts.*# 2#





data HappyAddr = HappyA# Happy_GHC_Exts.Addr#




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

{-# LINE 170 "templates/GenericTemplate.hs" #-}

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

happyShift new_state 0# tk st sts stk@(x `HappyStk` _) =
     let i = (case Happy_GHC_Exts.unsafeCoerce# x of { (Happy_GHC_Exts.I# (i)) -> i }) in
--     trace "shifting the error token" $
     happyDoAction i tk new_state (HappyCons (st) (sts)) (stk)

happyShift new_state i tk st sts stk =
     happyNewToken new_state (HappyCons (st) (sts)) ((happyInTok (tk))`HappyStk`stk)

-- happyReduce is specialised for the common cases.

happySpecReduce_0 i fn 0# tk st sts stk
     = happyFail 0# tk st sts stk
happySpecReduce_0 nt fn j tk st@((action)) sts stk
     = happyGoto nt j tk st (HappyCons (st) (sts)) (fn `HappyStk` stk)

happySpecReduce_1 i fn 0# tk st sts stk
     = happyFail 0# tk st sts stk
happySpecReduce_1 nt fn j tk _ sts@((HappyCons (st@(action)) (_))) (v1`HappyStk`stk')
     = let r = fn v1 in
       happySeq r (happyGoto nt j tk st sts (r `HappyStk` stk'))

happySpecReduce_2 i fn 0# tk st sts stk
     = happyFail 0# tk st sts stk
happySpecReduce_2 nt fn j tk _ (HappyCons (_) (sts@((HappyCons (st@(action)) (_))))) (v1`HappyStk`v2`HappyStk`stk')
     = let r = fn v1 v2 in
       happySeq r (happyGoto nt j tk st sts (r `HappyStk` stk'))

happySpecReduce_3 i fn 0# tk st sts stk
     = happyFail 0# tk st sts stk
happySpecReduce_3 nt fn j tk _ (HappyCons (_) ((HappyCons (_) (sts@((HappyCons (st@(action)) (_))))))) (v1`HappyStk`v2`HappyStk`v3`HappyStk`stk')
     = let r = fn v1 v2 v3 in
       happySeq r (happyGoto nt j tk st sts (r `HappyStk` stk'))

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

happyMonadReduce k nt fn 0# tk st sts stk
     = happyFail 0# tk st sts stk
happyMonadReduce k nt fn j tk st sts stk =
      case happyDrop k (HappyCons (st) (sts)) of
        sts1@((HappyCons (st1@(action)) (_))) ->
          let drop_stk = happyDropStk k stk in
          happyThen1 (fn stk tk) (\r -> happyGoto nt j tk st1 sts1 (r `HappyStk` drop_stk))

happyMonad2Reduce k nt fn 0# tk st sts stk
     = happyFail 0# tk st sts stk
happyMonad2Reduce k nt fn j tk st sts stk =
      case happyDrop k (HappyCons (st) (sts)) of
        sts1@((HappyCons (st1@(action)) (_))) ->
         let drop_stk = happyDropStk k stk

             off = indexShortOffAddr happyGotoOffsets st1
             off_i = (off Happy_GHC_Exts.+# nt)
             new_state = indexShortOffAddr happyTable off_i



          in
          happyThen1 (fn stk tk) (\r -> happyNewToken new_state sts1 (r `HappyStk` drop_stk))

happyDrop 0# l = l
happyDrop n (HappyCons (_) (t)) = happyDrop (n Happy_GHC_Exts.-# (1# :: Happy_GHC_Exts.Int#)) t

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

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


happyGoto nt j tk st = 
   {- nothing -}
   happyDoAction j tk new_state
   where off = indexShortOffAddr happyGotoOffsets st
         off_i = (off Happy_GHC_Exts.+# nt)
         new_state = indexShortOffAddr happyTable off_i




-----------------------------------------------------------------------------
-- Error recovery (0# is the error token)

-- parse error if we are in recovery and we fail again
happyFail 0# tk old_st _ stk@(x `HappyStk` _) =
     let i = (case Happy_GHC_Exts.unsafeCoerce# x of { (Happy_GHC_Exts.I# (i)) -> i }) in
--      trace "failing" $ 
        happyError_ i 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  0# tk old_st (HappyCons ((action)) (sts)) 
                                                (saved_tok `HappyStk` _ `HappyStk` stk) =
--      trace ("discarding state, depth " ++ show (length stk))  $
        happyDoAction 0# tk action sts ((saved_tok`HappyStk`stk))
-}

-- Enter error recovery: generate an error token,
--                       save the old token and carry on.
happyFail  i tk (action) sts stk =
--      trace "entering error recovery" $
        happyDoAction 0# tk action sts ( (Happy_GHC_Exts.unsafeCoerce# (Happy_GHC_Exts.I# (i))) `HappyStk` stk)

-- Internal happy errors:

notHappyAtAll :: a
notHappyAtAll = error "Internal Happy error\n"

-----------------------------------------------------------------------------
-- Hack to get the typechecker to accept our action functions


happyTcHack :: Happy_GHC_Exts.Int# -> a -> a
happyTcHack x y = y
{-# INLINE happyTcHack #-}


-----------------------------------------------------------------------------
-- 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.


{-# NOINLINE happyDoAction #-}
{-# NOINLINE happyTable #-}
{-# NOINLINE happyCheck #-}
{-# NOINLINE happyActOffsets #-}
{-# NOINLINE happyGotoOffsets #-}
{-# NOINLINE happyDefActions #-}

{-# 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.