~ubuntu-branches/ubuntu/precise/ghc/precise

« back to all changes in this revision

Viewing changes to utils/genprimopcode/Parser.hs

  • Committer: Bazaar Package Importer
  • Author(s): Joachim Breitner
  • Date: 2011-01-17 12:49:24 UTC
  • Revision ID: james.westby@ubuntu.com-20110117124924-do1pym1jlf5o636m
Tags: upstream-7.0.1
ImportĀ upstreamĀ versionĀ 7.0.1

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
{-# OPTIONS_GHC -fno-warn-overlapping-patterns #-}
 
2
{-# OPTIONS -fglasgow-exts -cpp #-}
 
3
{-# OPTIONS -w -Wwarn #-}
 
4
-- The above warning supression flag is a temporary kludge.
 
5
-- While working on this module you are encouraged to remove it and fix
 
6
-- any warnings in the module. See
 
7
--     http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#Warnings
 
8
-- for details
 
9
 
 
10
module Parser (parse) where
 
11
 
 
12
import Lexer (lex_tok)
 
13
import ParserM (Token(..), ParserM, run_parser, get_pos, show_pos,
 
14
                happyError)
 
15
import Syntax
 
16
#if __GLASGOW_HASKELL__ >= 503
 
17
import qualified Data.Array as Happy_Data_Array
 
18
#else
 
19
import qualified Array as Happy_Data_Array
 
20
#endif
 
21
#if __GLASGOW_HASKELL__ >= 503
 
22
import qualified GHC.Exts as Happy_GHC_Exts
 
23
#else
 
24
import qualified GlaExts as Happy_GHC_Exts
 
25
#endif
 
26
 
 
27
-- parser produced by Happy Version 1.18.4
 
28
 
 
29
newtype HappyAbsSyn  = HappyAbsSyn HappyAny
 
30
#if __GLASGOW_HASKELL__ >= 607
 
31
type HappyAny = Happy_GHC_Exts.Any
 
32
#else
 
33
type HappyAny = forall a . a
 
34
#endif
 
35
happyIn4 :: (Info) -> (HappyAbsSyn )
 
36
happyIn4 x = Happy_GHC_Exts.unsafeCoerce# x
 
37
{-# INLINE happyIn4 #-}
 
38
happyOut4 :: (HappyAbsSyn ) -> (Info)
 
39
happyOut4 x = Happy_GHC_Exts.unsafeCoerce# x
 
40
{-# INLINE happyOut4 #-}
 
41
happyIn5 :: ([Option]) -> (HappyAbsSyn )
 
42
happyIn5 x = Happy_GHC_Exts.unsafeCoerce# x
 
43
{-# INLINE happyIn5 #-}
 
44
happyOut5 :: (HappyAbsSyn ) -> ([Option])
 
45
happyOut5 x = Happy_GHC_Exts.unsafeCoerce# x
 
46
{-# INLINE happyOut5 #-}
 
47
happyIn6 :: ([Option]) -> (HappyAbsSyn )
 
48
happyIn6 x = Happy_GHC_Exts.unsafeCoerce# x
 
49
{-# INLINE happyIn6 #-}
 
50
happyOut6 :: (HappyAbsSyn ) -> ([Option])
 
51
happyOut6 x = Happy_GHC_Exts.unsafeCoerce# x
 
52
{-# INLINE happyOut6 #-}
 
53
happyIn7 :: (Option) -> (HappyAbsSyn )
 
54
happyIn7 x = Happy_GHC_Exts.unsafeCoerce# x
 
55
{-# INLINE happyIn7 #-}
 
56
happyOut7 :: (HappyAbsSyn ) -> (Option)
 
57
happyOut7 x = Happy_GHC_Exts.unsafeCoerce# x
 
58
{-# INLINE happyOut7 #-}
 
59
happyIn8 :: ([Entry]) -> (HappyAbsSyn )
 
60
happyIn8 x = Happy_GHC_Exts.unsafeCoerce# x
 
61
{-# INLINE happyIn8 #-}
 
62
happyOut8 :: (HappyAbsSyn ) -> ([Entry])
 
63
happyOut8 x = Happy_GHC_Exts.unsafeCoerce# x
 
64
{-# INLINE happyOut8 #-}
 
65
happyIn9 :: (Entry) -> (HappyAbsSyn )
 
66
happyIn9 x = Happy_GHC_Exts.unsafeCoerce# x
 
67
{-# INLINE happyIn9 #-}
 
68
happyOut9 :: (HappyAbsSyn ) -> (Entry)
 
69
happyOut9 x = Happy_GHC_Exts.unsafeCoerce# x
 
70
{-# INLINE happyOut9 #-}
 
71
happyIn10 :: (Entry) -> (HappyAbsSyn )
 
72
happyIn10 x = Happy_GHC_Exts.unsafeCoerce# x
 
73
{-# INLINE happyIn10 #-}
 
74
happyOut10 :: (HappyAbsSyn ) -> (Entry)
 
75
happyOut10 x = Happy_GHC_Exts.unsafeCoerce# x
 
76
{-# INLINE happyOut10 #-}
 
77
happyIn11 :: (Entry) -> (HappyAbsSyn )
 
78
happyIn11 x = Happy_GHC_Exts.unsafeCoerce# x
 
79
{-# INLINE happyIn11 #-}
 
80
happyOut11 :: (HappyAbsSyn ) -> (Entry)
 
81
happyOut11 x = Happy_GHC_Exts.unsafeCoerce# x
 
82
{-# INLINE happyOut11 #-}
 
83
happyIn12 :: (Entry) -> (HappyAbsSyn )
 
84
happyIn12 x = Happy_GHC_Exts.unsafeCoerce# x
 
85
{-# INLINE happyIn12 #-}
 
86
happyOut12 :: (HappyAbsSyn ) -> (Entry)
 
87
happyOut12 x = Happy_GHC_Exts.unsafeCoerce# x
 
88
{-# INLINE happyOut12 #-}
 
89
happyIn13 :: (Entry) -> (HappyAbsSyn )
 
90
happyIn13 x = Happy_GHC_Exts.unsafeCoerce# x
 
91
{-# INLINE happyIn13 #-}
 
92
happyOut13 :: (HappyAbsSyn ) -> (Entry)
 
93
happyOut13 x = Happy_GHC_Exts.unsafeCoerce# x
 
94
{-# INLINE happyOut13 #-}
 
95
happyIn14 :: ([Option]) -> (HappyAbsSyn )
 
96
happyIn14 x = Happy_GHC_Exts.unsafeCoerce# x
 
97
{-# INLINE happyIn14 #-}
 
98
happyOut14 :: (HappyAbsSyn ) -> ([Option])
 
99
happyOut14 x = Happy_GHC_Exts.unsafeCoerce# x
 
100
{-# INLINE happyOut14 #-}
 
101
happyIn15 :: (Category) -> (HappyAbsSyn )
 
102
happyIn15 x = Happy_GHC_Exts.unsafeCoerce# x
 
103
{-# INLINE happyIn15 #-}
 
104
happyOut15 :: (HappyAbsSyn ) -> (Category)
 
105
happyOut15 x = Happy_GHC_Exts.unsafeCoerce# x
 
106
{-# INLINE happyOut15 #-}
 
107
happyIn16 :: (String) -> (HappyAbsSyn )
 
108
happyIn16 x = Happy_GHC_Exts.unsafeCoerce# x
 
109
{-# INLINE happyIn16 #-}
 
110
happyOut16 :: (HappyAbsSyn ) -> (String)
 
111
happyOut16 x = Happy_GHC_Exts.unsafeCoerce# x
 
112
{-# INLINE happyOut16 #-}
 
113
happyIn17 :: (String) -> (HappyAbsSyn )
 
114
happyIn17 x = Happy_GHC_Exts.unsafeCoerce# x
 
115
{-# INLINE happyIn17 #-}
 
116
happyOut17 :: (HappyAbsSyn ) -> (String)
 
117
happyOut17 x = Happy_GHC_Exts.unsafeCoerce# x
 
118
{-# INLINE happyOut17 #-}
 
119
happyIn18 :: (String) -> (HappyAbsSyn )
 
120
happyIn18 x = Happy_GHC_Exts.unsafeCoerce# x
 
121
{-# INLINE happyIn18 #-}
 
122
happyOut18 :: (HappyAbsSyn ) -> (String)
 
123
happyOut18 x = Happy_GHC_Exts.unsafeCoerce# x
 
124
{-# INLINE happyOut18 #-}
 
125
happyIn19 :: (String) -> (HappyAbsSyn )
 
126
happyIn19 x = Happy_GHC_Exts.unsafeCoerce# x
 
127
{-# INLINE happyIn19 #-}
 
128
happyOut19 :: (HappyAbsSyn ) -> (String)
 
129
happyOut19 x = Happy_GHC_Exts.unsafeCoerce# x
 
130
{-# INLINE happyOut19 #-}
 
131
happyIn20 :: (Ty) -> (HappyAbsSyn )
 
132
happyIn20 x = Happy_GHC_Exts.unsafeCoerce# x
 
133
{-# INLINE happyIn20 #-}
 
134
happyOut20 :: (HappyAbsSyn ) -> (Ty)
 
135
happyOut20 x = Happy_GHC_Exts.unsafeCoerce# x
 
136
{-# INLINE happyOut20 #-}
 
137
happyIn21 :: (Ty) -> (HappyAbsSyn )
 
138
happyIn21 x = Happy_GHC_Exts.unsafeCoerce# x
 
139
{-# INLINE happyIn21 #-}
 
140
happyOut21 :: (HappyAbsSyn ) -> (Ty)
 
141
happyOut21 x = Happy_GHC_Exts.unsafeCoerce# x
 
142
{-# INLINE happyOut21 #-}
 
143
happyIn22 :: (Ty) -> (HappyAbsSyn )
 
144
happyIn22 x = Happy_GHC_Exts.unsafeCoerce# x
 
145
{-# INLINE happyIn22 #-}
 
146
happyOut22 :: (HappyAbsSyn ) -> (Ty)
 
147
happyOut22 x = Happy_GHC_Exts.unsafeCoerce# x
 
148
{-# INLINE happyOut22 #-}
 
149
happyIn23 :: ([Ty]) -> (HappyAbsSyn )
 
150
happyIn23 x = Happy_GHC_Exts.unsafeCoerce# x
 
151
{-# INLINE happyIn23 #-}
 
152
happyOut23 :: (HappyAbsSyn ) -> ([Ty])
 
153
happyOut23 x = Happy_GHC_Exts.unsafeCoerce# x
 
154
{-# INLINE happyOut23 #-}
 
155
happyIn24 :: ([Ty]) -> (HappyAbsSyn )
 
156
happyIn24 x = Happy_GHC_Exts.unsafeCoerce# x
 
157
{-# INLINE happyIn24 #-}
 
158
happyOut24 :: (HappyAbsSyn ) -> ([Ty])
 
159
happyOut24 x = Happy_GHC_Exts.unsafeCoerce# x
 
160
{-# INLINE happyOut24 #-}
 
161
happyIn25 :: (Ty) -> (HappyAbsSyn )
 
162
happyIn25 x = Happy_GHC_Exts.unsafeCoerce# x
 
163
{-# INLINE happyIn25 #-}
 
164
happyOut25 :: (HappyAbsSyn ) -> (Ty)
 
165
happyOut25 x = Happy_GHC_Exts.unsafeCoerce# x
 
166
{-# INLINE happyOut25 #-}
 
167
happyIn26 :: (String) -> (HappyAbsSyn )
 
168
happyIn26 x = Happy_GHC_Exts.unsafeCoerce# x
 
169
{-# INLINE happyIn26 #-}
 
170
happyOut26 :: (HappyAbsSyn ) -> (String)
 
171
happyOut26 x = Happy_GHC_Exts.unsafeCoerce# x
 
172
{-# INLINE happyOut26 #-}
 
173
happyInTok :: (Token) -> (HappyAbsSyn )
 
174
happyInTok x = Happy_GHC_Exts.unsafeCoerce# x
 
175
{-# INLINE happyInTok #-}
 
176
happyOutTok :: (HappyAbsSyn ) -> (Token)
 
177
happyOutTok x = Happy_GHC_Exts.unsafeCoerce# x
 
178
{-# INLINE happyOutTok #-}
 
179
 
 
180
 
 
181
happyActOffsets :: HappyAddr
 
182
happyActOffsets = HappyA# "\x70\x00\x70\x00\x45\x00\x6e\x00\x5c\x00\x00\x00\x69\x00\x74\x00\x66\x00\x45\x00\x00\x00\x00\x00\x00\x00\x00\x00\x65\x00\x5b\x00\x64\x00\x01\x00\x6d\x00\x71\x00\x00\x00\x04\x00\xfd\xff\x01\x00\x00\x00\x00\x00\x01\x00\x56\x00\x6c\x00\x00\x00\x00\x00\xfe\xff\x00\x00\x00\x00\xfc\xff\x00\x00\x00\x00\x00\x00\x00\x00\x39\x00\x6c\x00\x6b\x00\x6a\x00\x68\x00\x00\x00\x00\x00\x04\x00\x00\x00\x67\x00\x00\x00\x01\x00\x62\x00\x00\x00\x54\x00\x00\x00\x00\x00\x00\x00\x00\x00\x01\x00\x5a\x00\x01\x00\x00\x00\x00\x00\x00\x00\x00\x00\x61\x00\xfc\xff\xfc\xff\x00\x00\x60\x00\x00\x00\x00\x00\x5e\x00\x00\x00\x00\x00\x00\x00\x59\x00\x00\x00\x00\x00\x00\x00"#
 
183
 
 
184
happyGotoOffsets :: HappyAddr
 
185
happyGotoOffsets = HappyA# "\x63\x00\x57\x00\x41\x00\x5f\x00\x00\x00\x00\x00\x5d\x00\x00\x00\x00\x00\x3b\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x28\x00\x51\x00\x00\x00\x00\x00\x3f\x00\x21\x00\x0d\x00\x00\x00\x00\x00\x1e\x00\x00\x00\x4f\x00\x00\x00\x00\x00\x58\x00\x00\x00\x00\x00\x4b\x00\x00\x00\x00\x00\x00\x00\x00\x00\x0c\x00\x4a\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x27\x00\x00\x00\x00\x00\x00\x00\x17\x00\x10\x00\x00\x00\x33\x00\x00\x00\x00\x00\x00\x00\x00\x00\xfa\xff\x09\x00\x14\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x1d\x00\x13\x00\x00\x00\x00\x00\x00\x00\x00\x00\x05\x00\x00\x00\x00\x00\x00\x00\xff\xff\x00\x00\x00\x00\x00\x00"#
 
186
 
 
187
happyDefActions :: HappyAddr
 
188
happyDefActions = HappyA# "\x00\x00\x00\x00\xf6\xff\xfb\xff\x00\x00\xfd\xff\xfb\xff\x00\x00\x00\x00\xf6\xff\xf5\xff\xf4\xff\xf3\xff\xf2\xff\x00\x00\x00\x00\x00\x00\x00\x00\xe6\xff\xdf\xff\xdd\xff\xd6\xff\x00\x00\x00\x00\xdb\xff\xd3\xff\x00\x00\x00\x00\xe6\xff\xf7\xff\xfe\xff\x00\x00\xfc\xff\xf8\xff\xe3\xff\xf9\xff\xfa\xff\xee\xff\xe7\xff\x00\x00\xe6\xff\xd8\xff\x00\x00\x00\x00\xd2\xff\xde\xff\xd6\xff\xd4\xff\x00\x00\xd5\xff\x00\x00\xec\xff\xf0\xff\xfb\xff\xe0\xff\xd7\xff\xdc\xff\xda\xff\x00\x00\xec\xff\x00\x00\xeb\xff\xea\xff\xe9\xff\xe8\xff\x00\x00\xe3\xff\xe3\xff\xe1\xff\x00\x00\xe4\xff\xe5\xff\xe6\xff\xef\xff\xd9\xff\xed\xff\xec\xff\xe2\xff\xf1\xff"#
 
189
 
 
190
happyCheck :: HappyAddr
 
191
happyCheck = HappyA# "\xff\xff\x04\x00\x05\x00\x06\x00\x08\x00\x04\x00\x08\x00\x06\x00\x04\x00\x0a\x00\x10\x00\x11\x00\x12\x00\x13\x00\x10\x00\x11\x00\x16\x00\x0c\x00\x0d\x00\x0a\x00\x17\x00\x18\x00\x1a\x00\x0b\x00\x17\x00\x18\x00\x0a\x00\x17\x00\x18\x00\x10\x00\x11\x00\x12\x00\x13\x00\x0e\x00\x0f\x00\x16\x00\x10\x00\x11\x00\x12\x00\x10\x00\x11\x00\x12\x00\x16\x00\x0e\x00\x0f\x00\x16\x00\x10\x00\x11\x00\x12\x00\x10\x00\x11\x00\x12\x00\x16\x00\x02\x00\x03\x00\x16\x00\x10\x00\x11\x00\x12\x00\x14\x00\x15\x00\x16\x00\x16\x00\x04\x00\x05\x00\x06\x00\x07\x00\x08\x00\x09\x00\x04\x00\x05\x00\x06\x00\x07\x00\x08\x00\x09\x00\x12\x00\x13\x00\x14\x00\x15\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x14\x00\x15\x00\x16\x00\x0c\x00\x0d\x00\x01\x00\x0e\x00\x0f\x00\x0c\x00\x0d\x00\x0c\x00\x0d\x00\x02\x00\x03\x00\x02\x00\x03\x00\x00\x00\x01\x00\x0d\x00\x08\x00\x0e\x00\x0e\x00\x09\x00\x09\x00\x17\x00\x05\x00\x05\x00\x03\x00\x19\x00\x0e\x00\x07\x00\x01\x00\x18\x00\x08\x00\x08\x00\x02\x00\x1b\x00\xff\xff\xff\xff\xff\xff\xff\xff\x16\x00\x19\x00\x19\x00\x0f\x00\x17\x00\xff\xff\xff\xff\xff\xff\xff\xff\x17\x00\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff"#
 
192
 
 
193
happyTable :: HappyAddr
 
194
happyTable = HappyA# "\x00\x00\x17\x00\x2d\x00\x18\x00\x44\x00\x17\x00\x23\x00\x18\x00\x31\x00\x4e\x00\x29\x00\x13\x00\x14\x00\x4a\x00\x24\x00\x25\x00\x15\x00\x4c\x00\x26\x00\x49\x00\x19\x00\x1a\x00\x45\x00\x3c\x00\x19\x00\x1a\x00\x34\x00\x32\x00\x1a\x00\x29\x00\x13\x00\x14\x00\x2a\x00\x45\x00\x42\x00\x15\x00\x48\x00\x13\x00\x14\x00\x36\x00\x13\x00\x14\x00\x15\x00\x46\x00\x42\x00\x15\x00\x28\x00\x13\x00\x14\x00\x2b\x00\x13\x00\x14\x00\x15\x00\x4b\x00\x06\x00\x15\x00\x12\x00\x13\x00\x14\x00\x37\x00\x2e\x00\x2f\x00\x15\x00\x1d\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x08\x00\x09\x00\x0a\x00\x0b\x00\x0c\x00\x0d\x00\x3e\x00\x3f\x00\x40\x00\x41\x00\x0f\x00\x10\x00\x11\x00\x12\x00\x2d\x00\x2e\x00\x2f\x00\x3b\x00\x26\x00\x02\x00\x41\x00\x42\x00\x25\x00\x26\x00\x33\x00\x26\x00\x20\x00\x06\x00\x05\x00\x06\x00\x04\x00\x02\x00\x21\x00\x23\x00\x36\x00\x36\x00\x4e\x00\x48\x00\x08\x00\x2d\x00\x39\x00\x3b\x00\x28\x00\x36\x00\x3a\x00\x33\x00\x1c\x00\x23\x00\x23\x00\x20\x00\xff\xff\x00\x00\x00\x00\x00\x00\x00\x00\x1f\x00\x1b\x00\x1d\x00\x04\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x08\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00"#
 
195
 
 
196
happyReduceArr = Happy_Data_Array.array (1, 45) [
 
197
        (1 , happyReduce_1),
 
198
        (2 , happyReduce_2),
 
199
        (3 , happyReduce_3),
 
200
        (4 , happyReduce_4),
 
201
        (5 , happyReduce_5),
 
202
        (6 , happyReduce_6),
 
203
        (7 , happyReduce_7),
 
204
        (8 , happyReduce_8),
 
205
        (9 , happyReduce_9),
 
206
        (10 , happyReduce_10),
 
207
        (11 , happyReduce_11),
 
208
        (12 , happyReduce_12),
 
209
        (13 , happyReduce_13),
 
210
        (14 , happyReduce_14),
 
211
        (15 , happyReduce_15),
 
212
        (16 , happyReduce_16),
 
213
        (17 , happyReduce_17),
 
214
        (18 , happyReduce_18),
 
215
        (19 , happyReduce_19),
 
216
        (20 , happyReduce_20),
 
217
        (21 , happyReduce_21),
 
218
        (22 , happyReduce_22),
 
219
        (23 , happyReduce_23),
 
220
        (24 , happyReduce_24),
 
221
        (25 , happyReduce_25),
 
222
        (26 , happyReduce_26),
 
223
        (27 , happyReduce_27),
 
224
        (28 , happyReduce_28),
 
225
        (29 , happyReduce_29),
 
226
        (30 , happyReduce_30),
 
227
        (31 , happyReduce_31),
 
228
        (32 , happyReduce_32),
 
229
        (33 , happyReduce_33),
 
230
        (34 , happyReduce_34),
 
231
        (35 , happyReduce_35),
 
232
        (36 , happyReduce_36),
 
233
        (37 , happyReduce_37),
 
234
        (38 , happyReduce_38),
 
235
        (39 , happyReduce_39),
 
236
        (40 , happyReduce_40),
 
237
        (41 , happyReduce_41),
 
238
        (42 , happyReduce_42),
 
239
        (43 , happyReduce_43),
 
240
        (44 , happyReduce_44),
 
241
        (45 , happyReduce_45)
 
242
        ]
 
243
 
 
244
happy_n_terms = 28 :: Int
 
245
happy_n_nonterms = 23 :: Int
 
246
 
 
247
happyReduce_1 = happySpecReduce_3  0# happyReduction_1
 
248
happyReduction_1 happy_x_3
 
249
        happy_x_2
 
250
        happy_x_1
 
251
         =  case happyOut5 happy_x_1 of { happy_var_1 -> 
 
252
        case happyOut8 happy_x_2 of { happy_var_2 -> 
 
253
        happyIn4
 
254
                 (Info happy_var_1 happy_var_2
 
255
        )}}
 
256
 
 
257
happyReduce_2 = happySpecReduce_2  1# happyReduction_2
 
258
happyReduction_2 happy_x_2
 
259
        happy_x_1
 
260
         =  case happyOut6 happy_x_2 of { happy_var_2 -> 
 
261
        happyIn5
 
262
                 (happy_var_2
 
263
        )}
 
264
 
 
265
happyReduce_3 = happySpecReduce_2  2# happyReduction_3
 
266
happyReduction_3 happy_x_2
 
267
        happy_x_1
 
268
         =  case happyOut7 happy_x_1 of { happy_var_1 -> 
 
269
        case happyOut6 happy_x_2 of { happy_var_2 -> 
 
270
        happyIn6
 
271
                 (happy_var_1 : happy_var_2
 
272
        )}}
 
273
 
 
274
happyReduce_4 = happySpecReduce_0  2# happyReduction_4
 
275
happyReduction_4  =  happyIn6
 
276
                 ([]
 
277
        )
 
278
 
 
279
happyReduce_5 = happySpecReduce_3  3# happyReduction_5
 
280
happyReduction_5 happy_x_3
 
281
        happy_x_2
 
282
        happy_x_1
 
283
         =  case happyOutTok happy_x_1 of { (TLowerName happy_var_1) -> 
 
284
        happyIn7
 
285
                 (OptionFalse  happy_var_1
 
286
        )}
 
287
 
 
288
happyReduce_6 = happySpecReduce_3  3# happyReduction_6
 
289
happyReduction_6 happy_x_3
 
290
        happy_x_2
 
291
        happy_x_1
 
292
         =  case happyOutTok happy_x_1 of { (TLowerName happy_var_1) -> 
 
293
        happyIn7
 
294
                 (OptionTrue   happy_var_1
 
295
        )}
 
296
 
 
297
happyReduce_7 = happySpecReduce_3  3# happyReduction_7
 
298
happyReduction_7 happy_x_3
 
299
        happy_x_2
 
300
        happy_x_1
 
301
         =  case happyOutTok happy_x_1 of { (TLowerName happy_var_1) -> 
 
302
        case happyOut17 happy_x_3 of { happy_var_3 -> 
 
303
        happyIn7
 
304
                 (OptionString happy_var_1 happy_var_3
 
305
        )}}
 
306
 
 
307
happyReduce_8 = happySpecReduce_2  4# happyReduction_8
 
308
happyReduction_8 happy_x_2
 
309
        happy_x_1
 
310
         =  case happyOut9 happy_x_1 of { happy_var_1 -> 
 
311
        case happyOut8 happy_x_2 of { happy_var_2 -> 
 
312
        happyIn8
 
313
                 (happy_var_1 : happy_var_2
 
314
        )}}
 
315
 
 
316
happyReduce_9 = happySpecReduce_0  4# happyReduction_9
 
317
happyReduction_9  =  happyIn8
 
318
                 ([]
 
319
        )
 
320
 
 
321
happyReduce_10 = happySpecReduce_1  5# happyReduction_10
 
322
happyReduction_10 happy_x_1
 
323
         =  case happyOut10 happy_x_1 of { happy_var_1 -> 
 
324
        happyIn9
 
325
                 (happy_var_1
 
326
        )}
 
327
 
 
328
happyReduce_11 = happySpecReduce_1  5# happyReduction_11
 
329
happyReduction_11 happy_x_1
 
330
         =  case happyOut11 happy_x_1 of { happy_var_1 -> 
 
331
        happyIn9
 
332
                 (happy_var_1
 
333
        )}
 
334
 
 
335
happyReduce_12 = happySpecReduce_1  5# happyReduction_12
 
336
happyReduction_12 happy_x_1
 
337
         =  case happyOut12 happy_x_1 of { happy_var_1 -> 
 
338
        happyIn9
 
339
                 (happy_var_1
 
340
        )}
 
341
 
 
342
happyReduce_13 = happySpecReduce_1  5# happyReduction_13
 
343
happyReduction_13 happy_x_1
 
344
         =  case happyOut13 happy_x_1 of { happy_var_1 -> 
 
345
        happyIn9
 
346
                 (happy_var_1
 
347
        )}
 
348
 
 
349
happyReduce_14 = happyReduce 7# 6# happyReduction_14
 
350
happyReduction_14 (happy_x_7 `HappyStk`
 
351
        happy_x_6 `HappyStk`
 
352
        happy_x_5 `HappyStk`
 
353
        happy_x_4 `HappyStk`
 
354
        happy_x_3 `HappyStk`
 
355
        happy_x_2 `HappyStk`
 
356
        happy_x_1 `HappyStk`
 
357
        happyRest)
 
358
         = case happyOutTok happy_x_2 of { (TUpperName happy_var_2) -> 
 
359
        case happyOutTok happy_x_3 of { (TString happy_var_3) -> 
 
360
        case happyOut15 happy_x_4 of { happy_var_4 -> 
 
361
        case happyOut20 happy_x_5 of { happy_var_5 -> 
 
362
        case happyOut16 happy_x_6 of { happy_var_6 -> 
 
363
        case happyOut14 happy_x_7 of { happy_var_7 -> 
 
364
        happyIn10
 
365
                 (PrimOpSpec {
 
366
                    cons = happy_var_2,
 
367
                    name = happy_var_3,
 
368
                    cat = happy_var_4,
 
369
                    ty = happy_var_5,
 
370
                    desc = happy_var_6,
 
371
                    opts = happy_var_7
 
372
                }
 
373
        ) `HappyStk` happyRest}}}}}}
 
374
 
 
375
happyReduce_15 = happyReduce 4# 7# happyReduction_15
 
376
happyReduction_15 (happy_x_4 `HappyStk`
 
377
        happy_x_3 `HappyStk`
 
378
        happy_x_2 `HappyStk`
 
379
        happy_x_1 `HappyStk`
 
380
        happyRest)
 
381
         = case happyOut20 happy_x_2 of { happy_var_2 -> 
 
382
        case happyOut16 happy_x_3 of { happy_var_3 -> 
 
383
        case happyOut14 happy_x_4 of { happy_var_4 -> 
 
384
        happyIn11
 
385
                 (PrimTypeSpec { ty = happy_var_2, desc = happy_var_3, opts = happy_var_4 }
 
386
        ) `HappyStk` happyRest}}}
 
387
 
 
388
happyReduce_16 = happyReduce 5# 8# happyReduction_16
 
389
happyReduction_16 (happy_x_5 `HappyStk`
 
390
        happy_x_4 `HappyStk`
 
391
        happy_x_3 `HappyStk`
 
392
        happy_x_2 `HappyStk`
 
393
        happy_x_1 `HappyStk`
 
394
        happyRest)
 
395
         = case happyOutTok happy_x_2 of { (TString happy_var_2) -> 
 
396
        case happyOut20 happy_x_3 of { happy_var_3 -> 
 
397
        case happyOut16 happy_x_4 of { happy_var_4 -> 
 
398
        case happyOut14 happy_x_5 of { happy_var_5 -> 
 
399
        happyIn12
 
400
                 (PseudoOpSpec { name = happy_var_2, ty = happy_var_3, desc = happy_var_4, opts = happy_var_5 }
 
401
        ) `HappyStk` happyRest}}}}
 
402
 
 
403
happyReduce_17 = happySpecReduce_3  9# happyReduction_17
 
404
happyReduction_17 happy_x_3
 
405
        happy_x_2
 
406
        happy_x_1
 
407
         =  case happyOutTok happy_x_2 of { (TString happy_var_2) -> 
 
408
        case happyOut16 happy_x_3 of { happy_var_3 -> 
 
409
        happyIn13
 
410
                 (Section { title = happy_var_2, desc = happy_var_3 }
 
411
        )}}
 
412
 
 
413
happyReduce_18 = happySpecReduce_2  10# happyReduction_18
 
414
happyReduction_18 happy_x_2
 
415
        happy_x_1
 
416
         =  case happyOut6 happy_x_2 of { happy_var_2 -> 
 
417
        happyIn14
 
418
                 (happy_var_2
 
419
        )}
 
420
 
 
421
happyReduce_19 = happySpecReduce_0  10# happyReduction_19
 
422
happyReduction_19  =  happyIn14
 
423
                 ([]
 
424
        )
 
425
 
 
426
happyReduce_20 = happySpecReduce_1  11# happyReduction_20
 
427
happyReduction_20 happy_x_1
 
428
         =  happyIn15
 
429
                 (Dyadic
 
430
        )
 
431
 
 
432
happyReduce_21 = happySpecReduce_1  11# happyReduction_21
 
433
happyReduction_21 happy_x_1
 
434
         =  happyIn15
 
435
                 (Monadic
 
436
        )
 
437
 
 
438
happyReduce_22 = happySpecReduce_1  11# happyReduction_22
 
439
happyReduction_22 happy_x_1
 
440
         =  happyIn15
 
441
                 (Compare
 
442
        )
 
443
 
 
444
happyReduce_23 = happySpecReduce_1  11# happyReduction_23
 
445
happyReduction_23 happy_x_1
 
446
         =  happyIn15
 
447
                 (GenPrimOp
 
448
        )
 
449
 
 
450
happyReduce_24 = happySpecReduce_1  12# happyReduction_24
 
451
happyReduction_24 happy_x_1
 
452
         =  case happyOut17 happy_x_1 of { happy_var_1 -> 
 
453
        happyIn16
 
454
                 (happy_var_1
 
455
        )}
 
456
 
 
457
happyReduce_25 = happySpecReduce_0  12# happyReduction_25
 
458
happyReduction_25  =  happyIn16
 
459
                 (""
 
460
        )
 
461
 
 
462
happyReduce_26 = happySpecReduce_3  13# happyReduction_26
 
463
happyReduction_26 happy_x_3
 
464
        happy_x_2
 
465
        happy_x_1
 
466
         =  case happyOut18 happy_x_2 of { happy_var_2 -> 
 
467
        happyIn17
 
468
                 (happy_var_2
 
469
        )}
 
470
 
 
471
happyReduce_27 = happySpecReduce_2  14# happyReduction_27
 
472
happyReduction_27 happy_x_2
 
473
        happy_x_1
 
474
         =  case happyOut19 happy_x_1 of { happy_var_1 -> 
 
475
        case happyOut18 happy_x_2 of { happy_var_2 -> 
 
476
        happyIn18
 
477
                 (happy_var_1 ++ happy_var_2
 
478
        )}}
 
479
 
 
480
happyReduce_28 = happySpecReduce_0  14# happyReduction_28
 
481
happyReduction_28  =  happyIn18
 
482
                 (""
 
483
        )
 
484
 
 
485
happyReduce_29 = happySpecReduce_3  15# happyReduction_29
 
486
happyReduction_29 happy_x_3
 
487
        happy_x_2
 
488
        happy_x_1
 
489
         =  case happyOut18 happy_x_2 of { happy_var_2 -> 
 
490
        happyIn19
 
491
                 ("{" ++ happy_var_2 ++ "}"
 
492
        )}
 
493
 
 
494
happyReduce_30 = happySpecReduce_1  15# happyReduction_30
 
495
happyReduction_30 happy_x_1
 
496
         =  case happyOutTok happy_x_1 of { (TNoBraces happy_var_1) -> 
 
497
        happyIn19
 
498
                 (happy_var_1
 
499
        )}
 
500
 
 
501
happyReduce_31 = happySpecReduce_3  16# happyReduction_31
 
502
happyReduction_31 happy_x_3
 
503
        happy_x_2
 
504
        happy_x_1
 
505
         =  case happyOut21 happy_x_1 of { happy_var_1 -> 
 
506
        case happyOut20 happy_x_3 of { happy_var_3 -> 
 
507
        happyIn20
 
508
                 (TyF happy_var_1 happy_var_3
 
509
        )}}
 
510
 
 
511
happyReduce_32 = happySpecReduce_1  16# happyReduction_32
 
512
happyReduction_32 happy_x_1
 
513
         =  case happyOut21 happy_x_1 of { happy_var_1 -> 
 
514
        happyIn20
 
515
                 (happy_var_1
 
516
        )}
 
517
 
 
518
happyReduce_33 = happySpecReduce_2  17# happyReduction_33
 
519
happyReduction_33 happy_x_2
 
520
        happy_x_1
 
521
         =  case happyOut26 happy_x_1 of { happy_var_1 -> 
 
522
        case happyOut24 happy_x_2 of { happy_var_2 -> 
 
523
        happyIn21
 
524
                 (TyApp happy_var_1 happy_var_2
 
525
        )}}
 
526
 
 
527
happyReduce_34 = happySpecReduce_1  17# happyReduction_34
 
528
happyReduction_34 happy_x_1
 
529
         =  case happyOut22 happy_x_1 of { happy_var_1 -> 
 
530
        happyIn21
 
531
                 (happy_var_1
 
532
        )}
 
533
 
 
534
happyReduce_35 = happySpecReduce_3  17# happyReduction_35
 
535
happyReduction_35 happy_x_3
 
536
        happy_x_2
 
537
        happy_x_1
 
538
         =  case happyOut20 happy_x_2 of { happy_var_2 -> 
 
539
        happyIn21
 
540
                 (happy_var_2
 
541
        )}
 
542
 
 
543
happyReduce_36 = happySpecReduce_1  17# happyReduction_36
 
544
happyReduction_36 happy_x_1
 
545
         =  case happyOutTok happy_x_1 of { (TLowerName happy_var_1) -> 
 
546
        happyIn21
 
547
                 (TyVar happy_var_1
 
548
        )}
 
549
 
 
550
happyReduce_37 = happySpecReduce_3  18# happyReduction_37
 
551
happyReduction_37 happy_x_3
 
552
        happy_x_2
 
553
        happy_x_1
 
554
         =  case happyOut23 happy_x_2 of { happy_var_2 -> 
 
555
        happyIn22
 
556
                 (TyUTup happy_var_2
 
557
        )}
 
558
 
 
559
happyReduce_38 = happySpecReduce_3  19# happyReduction_38
 
560
happyReduction_38 happy_x_3
 
561
        happy_x_2
 
562
        happy_x_1
 
563
         =  case happyOut20 happy_x_1 of { happy_var_1 -> 
 
564
        case happyOut23 happy_x_3 of { happy_var_3 -> 
 
565
        happyIn23
 
566
                 (happy_var_1 : happy_var_3
 
567
        )}}
 
568
 
 
569
happyReduce_39 = happySpecReduce_1  19# happyReduction_39
 
570
happyReduction_39 happy_x_1
 
571
         =  case happyOut20 happy_x_1 of { happy_var_1 -> 
 
572
        happyIn23
 
573
                 ([happy_var_1]
 
574
        )}
 
575
 
 
576
happyReduce_40 = happySpecReduce_2  20# happyReduction_40
 
577
happyReduction_40 happy_x_2
 
578
        happy_x_1
 
579
         =  case happyOut25 happy_x_1 of { happy_var_1 -> 
 
580
        case happyOut24 happy_x_2 of { happy_var_2 -> 
 
581
        happyIn24
 
582
                 (happy_var_1 : happy_var_2
 
583
        )}}
 
584
 
 
585
happyReduce_41 = happySpecReduce_0  20# happyReduction_41
 
586
happyReduction_41  =  happyIn24
 
587
                 ([]
 
588
        )
 
589
 
 
590
happyReduce_42 = happySpecReduce_1  21# happyReduction_42
 
591
happyReduction_42 happy_x_1
 
592
         =  case happyOutTok happy_x_1 of { (TLowerName happy_var_1) -> 
 
593
        happyIn25
 
594
                 (TyVar happy_var_1
 
595
        )}
 
596
 
 
597
happyReduce_43 = happySpecReduce_1  21# happyReduction_43
 
598
happyReduction_43 happy_x_1
 
599
         =  case happyOut26 happy_x_1 of { happy_var_1 -> 
 
600
        happyIn25
 
601
                 (TyApp happy_var_1 []
 
602
        )}
 
603
 
 
604
happyReduce_44 = happySpecReduce_1  22# happyReduction_44
 
605
happyReduction_44 happy_x_1
 
606
         =  case happyOutTok happy_x_1 of { (TUpperName happy_var_1) -> 
 
607
        happyIn26
 
608
                 (happy_var_1
 
609
        )}
 
610
 
 
611
happyReduce_45 = happySpecReduce_2  22# happyReduction_45
 
612
happyReduction_45 happy_x_2
 
613
        happy_x_1
 
614
         =  happyIn26
 
615
                 ("()"
 
616
        )
 
617
 
 
618
happyNewToken action sts stk
 
619
        = lex_tok(\tk -> 
 
620
        let cont i = happyDoAction i tk action sts stk in
 
621
        case tk of {
 
622
        TEOF -> happyDoAction 27# tk action sts stk;
 
623
        TArrow -> cont 1#;
 
624
        TEquals -> cont 2#;
 
625
        TComma -> cont 3#;
 
626
        TOpenParen -> cont 4#;
 
627
        TCloseParen -> cont 5#;
 
628
        TOpenParenHash -> cont 6#;
 
629
        THashCloseParen -> cont 7#;
 
630
        TOpenBrace -> cont 8#;
 
631
        TCloseBrace -> cont 9#;
 
632
        TSection -> cont 10#;
 
633
        TPrimop -> cont 11#;
 
634
        TPseudoop -> cont 12#;
 
635
        TPrimtype -> cont 13#;
 
636
        TWith -> cont 14#;
 
637
        TDefaults -> cont 15#;
 
638
        TTrue -> cont 16#;
 
639
        TFalse -> cont 17#;
 
640
        TDyadic -> cont 18#;
 
641
        TMonadic -> cont 19#;
 
642
        TCompare -> cont 20#;
 
643
        TGenPrimOp -> cont 21#;
 
644
        TThatsAllFolks -> cont 22#;
 
645
        TLowerName happy_dollar_dollar -> cont 23#;
 
646
        TUpperName happy_dollar_dollar -> cont 24#;
 
647
        TString happy_dollar_dollar -> cont 25#;
 
648
        TNoBraces happy_dollar_dollar -> cont 26#;
 
649
        _ -> happyError' tk
 
650
        })
 
651
 
 
652
happyError_ tk = happyError' tk
 
653
 
 
654
happyThen :: () => ParserM a -> (a -> ParserM b) -> ParserM b
 
655
happyThen = (>>=)
 
656
happyReturn :: () => a -> ParserM a
 
657
happyReturn = (return)
 
658
happyThen1 = happyThen
 
659
happyReturn1 :: () => a -> ParserM a
 
660
happyReturn1 = happyReturn
 
661
happyError' :: () => (Token) -> ParserM a
 
662
happyError' tk = (\token -> happyError) tk
 
663
 
 
664
parsex = happySomeParser where
 
665
  happySomeParser = happyThen (happyParse 0#) (\x -> happyReturn (happyOut4 x))
 
666
 
 
667
happySeq = happyDoSeq
 
668
 
 
669
 
 
670
parse :: String -> Either String Info
 
671
parse = run_parser parsex
 
672
{-# LINE 1 "templates/GenericTemplate.hs" #-}
 
673
{-# LINE 1 "templates/GenericTemplate.hs" #-}
 
674
{-# LINE 1 "<built-in>" #-}
 
675
{-# LINE 1 "<command-line>" #-}
 
676
{-# LINE 1 "templates/GenericTemplate.hs" #-}
 
677
-- Id: GenericTemplate.hs,v 1.26 2005/01/14 14:47:22 simonmar Exp 
 
678
 
 
679
{-# LINE 28 "templates/GenericTemplate.hs" #-}
 
680
 
 
681
 
 
682
data Happy_IntList = HappyCons Happy_GHC_Exts.Int# Happy_IntList
 
683
 
 
684
 
 
685
 
 
686
 
 
687
 
 
688
{-# LINE 49 "templates/GenericTemplate.hs" #-}
 
689
 
 
690
{-# LINE 59 "templates/GenericTemplate.hs" #-}
 
691
 
 
692
{-# LINE 68 "templates/GenericTemplate.hs" #-}
 
693
 
 
694
infixr 9 `HappyStk`
 
695
data HappyStk a = HappyStk a (HappyStk a)
 
696
 
 
697
-----------------------------------------------------------------------------
 
698
-- starting the parse
 
699
 
 
700
happyParse start_state = happyNewToken start_state notHappyAtAll notHappyAtAll
 
701
 
 
702
-----------------------------------------------------------------------------
 
703
-- Accepting the parse
 
704
 
 
705
-- If the current token is 0#, it means we've just accepted a partial
 
706
-- parse (a %partial parser).  We must ignore the saved token on the top of
 
707
-- the stack in this case.
 
708
happyAccept 0# tk st sts (_ `HappyStk` ans `HappyStk` _) =
 
709
        happyReturn1 ans
 
710
happyAccept j tk st sts (HappyStk ans _) = 
 
711
        (happyTcHack j (happyTcHack st)) (happyReturn1 ans)
 
712
 
 
713
-----------------------------------------------------------------------------
 
714
-- Arrays only: do the next action
 
715
 
 
716
 
 
717
 
 
718
happyDoAction i tk st
 
719
        = {- nothing -}
 
720
 
 
721
 
 
722
          case action of
 
723
                0#                -> {- nothing -}
 
724
                                     happyFail i tk st
 
725
                -1#       -> {- nothing -}
 
726
                                     happyAccept i tk st
 
727
                n | (n Happy_GHC_Exts.<# (0# :: Happy_GHC_Exts.Int#)) -> {- nothing -}
 
728
 
 
729
                                     (happyReduceArr Happy_Data_Array.! rule) i tk st
 
730
                                     where rule = (Happy_GHC_Exts.I# ((Happy_GHC_Exts.negateInt# ((n Happy_GHC_Exts.+# (1# :: Happy_GHC_Exts.Int#))))))
 
731
                n                 -> {- nothing -}
 
732
 
 
733
 
 
734
                                     happyShift new_state i tk st
 
735
                                     where new_state = (n Happy_GHC_Exts.-# (1# :: Happy_GHC_Exts.Int#))
 
736
   where off    = indexShortOffAddr happyActOffsets st
 
737
         off_i  = (off Happy_GHC_Exts.+# i)
 
738
         check  = if (off_i Happy_GHC_Exts.>=# (0# :: Happy_GHC_Exts.Int#))
 
739
                        then (indexShortOffAddr happyCheck off_i Happy_GHC_Exts.==#  i)
 
740
                        else False
 
741
         action | check     = indexShortOffAddr happyTable off_i
 
742
                | otherwise = indexShortOffAddr happyDefActions st
 
743
 
 
744
{-# LINE 127 "templates/GenericTemplate.hs" #-}
 
745
 
 
746
 
 
747
indexShortOffAddr (HappyA# arr) off =
 
748
#if __GLASGOW_HASKELL__ > 500
 
749
        Happy_GHC_Exts.narrow16Int# i
 
750
#elif __GLASGOW_HASKELL__ == 500
 
751
        Happy_GHC_Exts.intToInt16# i
 
752
#else
 
753
        Happy_GHC_Exts.iShiftRA# (Happy_GHC_Exts.iShiftL# i 16#) 16#
 
754
#endif
 
755
  where
 
756
#if __GLASGOW_HASKELL__ >= 503
 
757
        i = Happy_GHC_Exts.word2Int# (Happy_GHC_Exts.or# (Happy_GHC_Exts.uncheckedShiftL# high 8#) low)
 
758
#else
 
759
        i = Happy_GHC_Exts.word2Int# (Happy_GHC_Exts.or# (Happy_GHC_Exts.shiftL# high 8#) low)
 
760
#endif
 
761
        high = Happy_GHC_Exts.int2Word# (Happy_GHC_Exts.ord# (Happy_GHC_Exts.indexCharOffAddr# arr (off' Happy_GHC_Exts.+# 1#)))
 
762
        low  = Happy_GHC_Exts.int2Word# (Happy_GHC_Exts.ord# (Happy_GHC_Exts.indexCharOffAddr# arr off'))
 
763
        off' = off Happy_GHC_Exts.*# 2#
 
764
 
 
765
 
 
766
 
 
767
 
 
768
 
 
769
data HappyAddr = HappyA# Happy_GHC_Exts.Addr#
 
770
 
 
771
 
 
772
 
 
773
 
 
774
-----------------------------------------------------------------------------
 
775
-- HappyState data type (not arrays)
 
776
 
 
777
{-# LINE 170 "templates/GenericTemplate.hs" #-}
 
778
 
 
779
-----------------------------------------------------------------------------
 
780
-- Shifting a token
 
781
 
 
782
happyShift new_state 0# tk st sts stk@(x `HappyStk` _) =
 
783
     let i = (case Happy_GHC_Exts.unsafeCoerce# x of { (Happy_GHC_Exts.I# (i)) -> i }) in
 
784
--     trace "shifting the error token" $
 
785
     happyDoAction i tk new_state (HappyCons (st) (sts)) (stk)
 
786
 
 
787
happyShift new_state i tk st sts stk =
 
788
     happyNewToken new_state (HappyCons (st) (sts)) ((happyInTok (tk))`HappyStk`stk)
 
789
 
 
790
-- happyReduce is specialised for the common cases.
 
791
 
 
792
happySpecReduce_0 i fn 0# tk st sts stk
 
793
     = happyFail 0# tk st sts stk
 
794
happySpecReduce_0 nt fn j tk st@((action)) sts stk
 
795
     = happyGoto nt j tk st (HappyCons (st) (sts)) (fn `HappyStk` stk)
 
796
 
 
797
happySpecReduce_1 i fn 0# tk st sts stk
 
798
     = happyFail 0# tk st sts stk
 
799
happySpecReduce_1 nt fn j tk _ sts@((HappyCons (st@(action)) (_))) (v1`HappyStk`stk')
 
800
     = let r = fn v1 in
 
801
       happySeq r (happyGoto nt j tk st sts (r `HappyStk` stk'))
 
802
 
 
803
happySpecReduce_2 i fn 0# tk st sts stk
 
804
     = happyFail 0# tk st sts stk
 
805
happySpecReduce_2 nt fn j tk _ (HappyCons (_) (sts@((HappyCons (st@(action)) (_))))) (v1`HappyStk`v2`HappyStk`stk')
 
806
     = let r = fn v1 v2 in
 
807
       happySeq r (happyGoto nt j tk st sts (r `HappyStk` stk'))
 
808
 
 
809
happySpecReduce_3 i fn 0# tk st sts stk
 
810
     = happyFail 0# tk st sts stk
 
811
happySpecReduce_3 nt fn j tk _ (HappyCons (_) ((HappyCons (_) (sts@((HappyCons (st@(action)) (_))))))) (v1`HappyStk`v2`HappyStk`v3`HappyStk`stk')
 
812
     = let r = fn v1 v2 v3 in
 
813
       happySeq r (happyGoto nt j tk st sts (r `HappyStk` stk'))
 
814
 
 
815
happyReduce k i fn 0# tk st sts stk
 
816
     = happyFail 0# tk st sts stk
 
817
happyReduce k nt fn j tk st sts stk
 
818
     = case happyDrop (k Happy_GHC_Exts.-# (1# :: Happy_GHC_Exts.Int#)) sts of
 
819
         sts1@((HappyCons (st1@(action)) (_))) ->
 
820
                let r = fn stk in  -- it doesn't hurt to always seq here...
 
821
                happyDoSeq r (happyGoto nt j tk st1 sts1 r)
 
822
 
 
823
happyMonadReduce k nt fn 0# tk st sts stk
 
824
     = happyFail 0# tk st sts stk
 
825
happyMonadReduce k nt fn j tk st sts stk =
 
826
        happyThen1 (fn stk tk) (\r -> happyGoto nt j tk st1 sts1 (r `HappyStk` drop_stk))
 
827
       where sts1@((HappyCons (st1@(action)) (_))) = happyDrop k (HappyCons (st) (sts))
 
828
             drop_stk = happyDropStk k stk
 
829
 
 
830
happyMonad2Reduce k nt fn 0# tk st sts stk
 
831
     = happyFail 0# tk st sts stk
 
832
happyMonad2Reduce k nt fn j tk st sts stk =
 
833
       happyThen1 (fn stk tk) (\r -> happyNewToken new_state sts1 (r `HappyStk` drop_stk))
 
834
       where sts1@((HappyCons (st1@(action)) (_))) = happyDrop k (HappyCons (st) (sts))
 
835
             drop_stk = happyDropStk k stk
 
836
 
 
837
             off    = indexShortOffAddr happyGotoOffsets st1
 
838
             off_i  = (off Happy_GHC_Exts.+# nt)
 
839
             new_state = indexShortOffAddr happyTable off_i
 
840
 
 
841
 
 
842
 
 
843
 
 
844
happyDrop 0# l = l
 
845
happyDrop n (HappyCons (_) (t)) = happyDrop (n Happy_GHC_Exts.-# (1# :: Happy_GHC_Exts.Int#)) t
 
846
 
 
847
happyDropStk 0# l = l
 
848
happyDropStk n (x `HappyStk` xs) = happyDropStk (n Happy_GHC_Exts.-# (1#::Happy_GHC_Exts.Int#)) xs
 
849
 
 
850
-----------------------------------------------------------------------------
 
851
-- Moving to a new state after a reduction
 
852
 
 
853
 
 
854
happyGoto nt j tk st = 
 
855
   {- nothing -}
 
856
   happyDoAction j tk new_state
 
857
   where off    = indexShortOffAddr happyGotoOffsets st
 
858
         off_i  = (off Happy_GHC_Exts.+# nt)
 
859
         new_state = indexShortOffAddr happyTable off_i
 
860
 
 
861
 
 
862
 
 
863
 
 
864
-----------------------------------------------------------------------------
 
865
-- Error recovery (0# is the error token)
 
866
 
 
867
-- parse error if we are in recovery and we fail again
 
868
happyFail  0# tk old_st _ stk =
 
869
--      trace "failing" $ 
 
870
        happyError_ tk
 
871
 
 
872
{-  We don't need state discarding for our restricted implementation of
 
873
    "error".  In fact, it can cause some bogus parses, so I've disabled it
 
874
    for now --SDM
 
875
 
 
876
-- discard a state
 
877
happyFail  0# tk old_st (HappyCons ((action)) (sts)) 
 
878
                                                (saved_tok `HappyStk` _ `HappyStk` stk) =
 
879
--      trace ("discarding state, depth " ++ show (length stk))  $
 
880
        happyDoAction 0# tk action sts ((saved_tok`HappyStk`stk))
 
881
-}
 
882
 
 
883
-- Enter error recovery: generate an error token,
 
884
--                       save the old token and carry on.
 
885
happyFail  i tk (action) sts stk =
 
886
--      trace "entering error recovery" $
 
887
        happyDoAction 0# tk action sts ( (Happy_GHC_Exts.unsafeCoerce# (Happy_GHC_Exts.I# (i))) `HappyStk` stk)
 
888
 
 
889
-- Internal happy errors:
 
890
 
 
891
notHappyAtAll = error "Internal Happy error\n"
 
892
 
 
893
-----------------------------------------------------------------------------
 
894
-- Hack to get the typechecker to accept our action functions
 
895
 
 
896
 
 
897
happyTcHack :: Happy_GHC_Exts.Int# -> a -> a
 
898
happyTcHack x y = y
 
899
{-# INLINE happyTcHack #-}
 
900
 
 
901
 
 
902
-----------------------------------------------------------------------------
 
903
-- Seq-ing.  If the --strict flag is given, then Happy emits 
 
904
--      happySeq = happyDoSeq
 
905
-- otherwise it emits
 
906
--      happySeq = happyDontSeq
 
907
 
 
908
happyDoSeq, happyDontSeq :: a -> b -> b
 
909
happyDoSeq   a b = a `seq` b
 
910
happyDontSeq a b = b
 
911
 
 
912
-----------------------------------------------------------------------------
 
913
-- Don't inline any functions from the template.  GHC has a nasty habit
 
914
-- of deciding to inline happyGoto everywhere, which increases the size of
 
915
-- the generated parser quite a bit.
 
916
 
 
917
 
 
918
{-# NOINLINE happyDoAction #-}
 
919
{-# NOINLINE happyTable #-}
 
920
{-# NOINLINE happyCheck #-}
 
921
{-# NOINLINE happyActOffsets #-}
 
922
{-# NOINLINE happyGotoOffsets #-}
 
923
{-# NOINLINE happyDefActions #-}
 
924
 
 
925
{-# NOINLINE happyShift #-}
 
926
{-# NOINLINE happySpecReduce_0 #-}
 
927
{-# NOINLINE happySpecReduce_1 #-}
 
928
{-# NOINLINE happySpecReduce_2 #-}
 
929
{-# NOINLINE happySpecReduce_3 #-}
 
930
{-# NOINLINE happyReduce #-}
 
931
{-# NOINLINE happyMonadReduce #-}
 
932
{-# NOINLINE happyGoto #-}
 
933
{-# NOINLINE happyFail #-}
 
934
 
 
935
-- end of Happy Template.