b6d5d7b337ca413b00141be1c2b915330f99ceaa
[ghc-hetmet.git] / ghc / compiler / rename / ParseIface.y
1 {
2 module ParseIface ( parseIface, IfaceStuff(..) ) where
3
4 #include "HsVersions.h"
5
6 import HsSyn            -- quite a bit of stuff
7 import RdrHsSyn         -- oodles of synonyms
8 import HsDecls          ( HsIdInfo(..), HsStrictnessInfo(..) )
9 import HsTypes          ( mkHsForAllTy )
10 import HsCore
11 import Literal
12 import BasicTypes       ( IfaceFlavour(..), Fixity(..), FixityDirection(..), NewOrData(..), Version )
13 import HsPragmas        ( noDataPragmas, noClassPragmas )
14 import Kind             ( Kind, mkArrowKind, mkBoxedTypeKind, mkTypeKind )
15 import IdInfo           ( ArgUsageInfo, FBTypeInfo, ArityInfo, exactArity )
16 import PrimRep          ( decodePrimRep )
17 import Lex              
18
19 import RnMonad          ( ImportVersion, LocalVersion, ParsedIface(..), WhatsImported(..),
20                           RdrNamePragma, ExportItem, RdrAvailInfo, GenAvailInfo(..)
21                         ) 
22 import Bag              ( emptyBag, unitBag, snocBag )
23 import FiniteMap        ( emptyFM, unitFM, addToFM, plusFM, bagToFM, FiniteMap )
24 import Name             ( OccName(..), isTCOcc, Provenance, SYN_IE(Module) )
25 import SrcLoc           ( SrcLoc )
26 import Maybes
27 import Outputable
28
29 }
30
31 %name       parseIface
32 %tokentype  { IfaceToken }
33 %monad      { IfM }{ thenIf }{ returnIf }
34 %lexer      { lexIface } { ITeof }
35
36 %token
37         INTERFACE           { ITinterface }
38         USAGES_PART         { ITusages }
39         EXPORTS_PART        { ITexports }
40         INSTANCE_MODULES_PART { ITinstance_modules }
41         INSTANCES_PART      { ITinstances }
42         FIXITIES_PART       { ITfixities }
43         DECLARATIONS_PART   { ITdeclarations }
44         DATA                { ITdata }
45         TYPE                { ITtype }
46         NEWTYPE             { ITnewtype }
47         DERIVING            { ITderiving }
48         CLASS               { ITclass }
49         WHERE               { ITwhere }
50         INSTANCE            { ITinstance }
51         INFIXL              { ITinfixl }
52         INFIXR              { ITinfixr }
53         INFIX               { ITinfix }
54         FORALL              { ITforall }
55         BANG                { ITbang }
56         VBAR                { ITvbar }
57         DCOLON              { ITdcolon }
58         COMMA               { ITcomma }
59         DARROW              { ITdarrow }
60         EQUAL               { ITequal }
61         OCURLY              { ITocurly }
62         OBRACK              { ITobrack }
63         OPAREN              { IToparen }
64         RARROW              { ITrarrow }
65         CCURLY              { ITccurly }
66         CBRACK              { ITcbrack }
67         CPAREN              { ITcparen }
68         SEMI                { ITsemi }
69
70         VARID               { ITvarid    $$ }
71         CONID               { ITconid    $$ }
72         VARSYM              { ITvarsym   $$ }
73         CONSYM              { ITconsym   $$ }
74         QVARID              { ITqvarid   $$ }
75         QCONID              { ITqconid   $$ }
76         QVARSYM             { ITqvarsym  $$ }
77         QCONSYM             { ITqconsym  $$ }
78
79         STRICT_PART     { ITstrict $$ }
80         TYPE_PART       { ITtysig _ _ }
81         ARITY_PART      { ITarity }
82         UNFOLD_PART     { ITunfold $$ }
83         SPECIALISE      { ITspecialise }
84         BOTTOM          { ITbottom }
85         LAM             { ITlam }
86         BIGLAM          { ITbiglam }
87         CASE            { ITcase }
88         PRIM_CASE       { ITprim_case }
89         LET             { ITlet }
90         LETREC          { ITletrec }
91         IN              { ITin }
92         OF              { ITof }
93         COERCE          { ITcoerce }
94         ATSIGN          { ITatsign }
95         CCALL           { ITccall $$ }
96         SCC             { ITscc $$ }
97         INLINE_CALL     { ITinline }
98
99         CHAR            { ITchar $$ }
100         STRING          { ITstring $$ } 
101         INTEGER         { ITinteger  $$ }
102         RATIONAL        { ITrational $$ }
103
104         INTEGER_LIT     { ITinteger_lit }
105         FLOAT_LIT       { ITfloat_lit }
106         RATIONAL_LIT    { ITrational_lit }
107         ADDR_LIT        { ITaddr_lit }
108         LIT_LIT         { ITlit_lit }
109         STRING_LIT      { ITstring_lit }
110
111         UNKNOWN         { ITunknown $$ }
112 %%
113
114 -- iface_stuff is the main production.
115 -- It recognises (a) a whole interface file
116 --               (b) a type (so that type sigs can be parsed lazily)
117 --               (c) the IdInfo part of a signature (same reason)
118
119 iface_stuff :: { IfaceStuff }
120 iface_stuff : iface             { PIface  $1 }
121             | type              { PType   $1 }
122             | id_info           { PIdInfo $1 }
123
124
125 iface           :: { ParsedIface }
126 iface           : INTERFACE CONID INTEGER checkVersion
127                   inst_modules_part 
128                   usages_part
129                   exports_part fixities_part
130                   instances_part
131                   decls_part
132                   { ParsedIface 
133                         $2                      -- Module name
134                         (fromInteger $3)        -- Module version
135                         $6                      -- Usages
136                         $7                      -- Exports
137                         $5                      -- Instance modules
138                         $8                      -- Fixities
139                         $10                     -- Decls
140                         $9                      -- Local instances
141                     }
142
143
144 usages_part         :: { [ImportVersion OccName] }
145 usages_part         :  USAGES_PART module_stuff_pairs           { $2 }
146                     |                                           { [] }
147
148 module_stuff_pairs  :: { [ImportVersion OccName] }
149 module_stuff_pairs  :                                           { [] }
150                     |  module_stuff_pair module_stuff_pairs     { $1 : $2 }
151
152 module_stuff_pair   ::  { ImportVersion OccName }
153 module_stuff_pair   :  mod_name opt_bang INTEGER DCOLON whats_imported SEMI
154                         { ($1, $2, fromInteger $3, $5) }
155
156 whats_imported      :: { WhatsImported OccName }
157 whats_imported      :                                           { Everything }
158                     | name_version_pair name_version_pairs      { Specifically ($1:$2) }
159
160 name_version_pairs  ::  { [LocalVersion OccName] }
161 name_version_pairs  :                                           { [] }
162                     |  name_version_pair name_version_pairs     { $1 : $2 }
163
164 name_version_pair   ::  { LocalVersion OccName }
165 name_version_pair   :  entity_occ INTEGER                       { ($1, fromInteger $2)
166 --------------------------------------------------------------------------
167                                                                 }
168
169 exports_part    :: { [ExportItem] }
170 exports_part    :  EXPORTS_PART export_items                    { $2 }
171                 |                                               { [] }
172
173 export_items    :: { [ExportItem] }
174 export_items    :                                               { [] }
175                 |  opt_bang mod_name entities SEMI export_items { ($2,$1,$3) : $5 }
176
177 opt_bang        :: { IfaceFlavour }
178 opt_bang        :                                               { HiFile }
179                 | BANG                                          { HiBootFile }
180
181 entities        :: { [RdrAvailInfo] }
182 entities        :                                               { [] }
183                 |  entity entities                              { $1 : $2 }
184
185 entity          :: { RdrAvailInfo }
186 entity          :  entity_occ                           { if isTCOcc $1 
187                                                           then AvailTC $1 [$1]
188                                                           else Avail $1 }
189                 |  entity_occ stuff_inside              { AvailTC $1 ($1:$2) }
190                 |  entity_occ VBAR stuff_inside         { AvailTC $1 $3 }
191
192 stuff_inside    :: { [OccName] }
193 stuff_inside    :  OPAREN val_occs CPAREN               { $2
194 --------------------------------------------------------------------------
195                                                         }
196
197 inst_modules_part :: { [Module] }
198 inst_modules_part :                                             { [] }
199                   |  INSTANCE_MODULES_PART mod_list             { $2 }
200
201 mod_list        :: { [Module] }
202 mod_list        :                                               { [] }
203                 |  mod_name mod_list                            { $1 : $2
204 --------------------------------------------------------------------------
205                                                                   }
206
207 fixities_part   :: { [(OccName,Fixity)] }
208 fixities_part   :                                               { [] }
209                 |  FIXITIES_PART fixes                          { $2 }
210
211 fixes           :: { [(OccName,Fixity)] }
212 fixes           :                                               { []  }
213                 |  fix fixes                                    { $1 : $2 }
214
215 fix             :: { (OccName, Fixity) }
216 fix             :  INFIXL INTEGER val_occ SEMI { ($3, Fixity (fromInteger $2) InfixL) }
217                 |  INFIXR INTEGER val_occ SEMI { ($3, Fixity (fromInteger $2) InfixR) }
218                 |  INFIX  INTEGER val_occ SEMI { ($3, Fixity (fromInteger $2) InfixN)
219 --------------------------------------------------------------------------
220                                                                                       }
221
222 decls_part      :: { [(Version, RdrNameHsDecl)] }
223 decls_part      :                                       { [] }
224                 |       DECLARATIONS_PART topdecls      { $2 }
225
226 topdecls        :: { [(Version, RdrNameHsDecl)] }
227 topdecls        :                                       { [] }
228                 |  version topdecl topdecls             { ($1,$2) : $3 }
229
230 version         :: { Version }
231 version         :  INTEGER                              { fromInteger $1 }
232
233 topdecl         :: { RdrNameHsDecl }
234 topdecl         :  src_loc TYPE  tc_name tv_bndrs EQUAL type SEMI
235                         { TyD (TySynonym $3 $4 $6 $1) }
236                 |  src_loc DATA decl_context tc_name tv_bndrs constrs deriving SEMI
237                         { TyD (TyData DataType $3 $4 $5 $6 $7 noDataPragmas $1) }
238                 |  src_loc NEWTYPE decl_context tc_name tv_bndrs newtype_constr deriving SEMI
239                         { TyD (TyData NewType $3 $4 $5 $6 $7 noDataPragmas $1) }
240                 |  src_loc CLASS decl_context tc_name tv_bndrs csigs SEMI
241                         { ClD (mkClassDecl $3 $4 $5 $6 EmptyMonoBinds noClassPragmas $1) }
242                 |  src_loc var_name TYPE_PART
243                         {
244                          case $3 of
245                             ITtysig sig idinfo_part ->  -- Parse type and idinfo lazily
246                                 let info = 
247                                       case idinfo_part of
248                                         Nothing -> []
249                                         Just s  -> case parseIface s $1 of 
250                                                      Succeeded (PIdInfo id_info) -> id_info
251                                                      other ->  pprPanic "IdInfo parse failed"
252                                                                         (ppr $2)
253
254                                     tp = case parseIface sig $1 of
255                                             Succeeded (PType tp) -> tp
256                                             other -> pprPanic "Id type parse failed"
257                                                               (ppr $2)
258                                  in
259                                  SigD (IfaceSig $2 tp info $1) }
260
261 decl_context    :: { RdrNameContext }
262 decl_context    :                                       { [] }
263                 | OCURLY context_list1 CCURLY DARROW    { $2 }
264
265
266 csigs           :: { [RdrNameSig] }
267 csigs           :                               { [] }
268                 | WHERE OCURLY csigs1 CCURLY    { $3 }
269
270 csigs1          :: { [RdrNameSig] }
271 csigs1          : csig                          { [$1] }
272                 | csig SEMI csigs1              { $1 : $3 }
273
274 csig            :: { RdrNameSig }
275 csig            :  src_loc var_name DCOLON type { ClassOpSig $2 Nothing $4 $1 }
276                 |  src_loc var_name EQUAL DCOLON type   { ClassOpSig $2 
277                                                                 (Just (error "Un-filled-in default method"))
278                                                                 $5 $1 }
279 ----------------------------------------------------------------
280
281
282 constrs         :: { [RdrNameConDecl] {- empty for handwritten abstract -} }
283                 :                               { [] }
284                 | EQUAL constrs1                { $2 }
285
286 constrs1        :: { [RdrNameConDecl] }
287 constrs1        :  constr               { [$1] }
288                 |  constr VBAR constrs1 { $1 : $3 }
289
290 constr          :: { RdrNameConDecl }
291 constr          :  src_loc data_name batypes                    { ConDecl $2 [] (VanillaCon $3) $1 }
292                 |  src_loc data_name OCURLY fields1 CCURLY      { ConDecl $2 [] (RecCon $4)     $1 }
293
294 newtype_constr  :: { [RdrNameConDecl] {- Empty if handwritten abstract -} }
295 newtype_constr  :                                       { [] }
296                 | src_loc EQUAL data_name atype         { [ConDecl $3 [] (NewCon $4) $1] }
297
298 deriving        :: { Maybe [RdrName] }
299                 :                                       { Nothing }
300                 | DERIVING OPAREN tc_names1 CPAREN      { Just $3 }
301
302 batypes         :: { [RdrNameBangType] }
303 batypes         :                                       { [] }
304                 |  batype batypes                       { $1 : $2 }
305
306 batype          :: { RdrNameBangType }
307 batype          :  atype                                { Unbanged $1 }
308                 |  BANG atype                           { Banged   $2 }
309
310 fields1         :: { [([RdrName], RdrNameBangType)] }
311 fields1         : field                                 { [$1] }
312                 | field COMMA fields1                   { $1 : $3 }
313
314 field           :: { ([RdrName], RdrNameBangType) }
315 field           :  var_names1 DCOLON type               { ($1, Unbanged $3) }
316                 |  var_names1 DCOLON BANG type          { ($1, Banged   $4) }
317 --------------------------------------------------------------------------
318
319 type            :: { RdrNameHsType }
320 type            : FORALL forall context DARROW type     { mkHsForAllTy $2 $3 $5 }
321                 |  btype RARROW type                    { MonoFunTy $1 $3 }
322                 |  btype                                { $1 }
323
324 forall          :: { [HsTyVar RdrName] }
325 forall          : OBRACK tv_bndrs CBRACK                { $2 }
326
327 context         :: { RdrNameContext }
328 context         :                                       { [] }
329                 | OCURLY context_list1 CCURLY           { $2 }
330
331 context_list1   :: { RdrNameContext }
332 context_list1   : class                                 { [$1] }
333                 | class COMMA context_list1             { $1 : $3 }
334
335 class           :: { (RdrName, [RdrNameHsType]) }
336 class           :  tc_name atypes                       { ($1, $2) }
337
338 types2          :: { [RdrNameHsType]                    {- Two or more -}  }    
339 types2          :  type COMMA type                      { [$1,$3] }
340                 |  type COMMA types2                    { $1 : $3 }
341
342 btype           :: { RdrNameHsType }
343 btype           :  atype                                { $1 }
344                 |  btype atype                          { MonoTyApp $1 $2 }
345
346 atype           :: { RdrNameHsType }
347 atype           :  tc_name                              { MonoTyVar $1 }
348                 |  tv_name                              { MonoTyVar $1 }
349                 |  OPAREN types2 CPAREN                 { MonoTupleTy dummyRdrTcName $2 }
350                 |  OBRACK type CBRACK                   { MonoListTy  dummyRdrTcName $2 }
351                 |  OCURLY tc_name atypes CCURLY         { MonoDictTy $2 $3 }
352                 |  OPAREN type CPAREN                   { $2 }
353
354 atypes          :: { [RdrNameHsType]    {-  Zero or more -} }
355 atypes          :                                       { [] }
356                 |  atype atypes                         { $1 : $2 }
357 ---------------------------------------------------------------------
358
359 mod_name        :: { Module }
360                 :  CONID                { $1 }
361
362 var_occ         :: { OccName }
363 var_occ         : VARID                 { VarOcc $1 }
364                 | VARSYM                { VarOcc $1 }
365                 | BANG                  { VarOcc SLIT("!") {-sigh, double-sigh-} }
366
367 tc_occ          :: { OccName }
368 tc_occ          :  CONID                { TCOcc $1 }
369                 |  CONSYM               { TCOcc $1 }
370                 |  OPAREN RARROW CPAREN { TCOcc SLIT("->") }
371
372 entity_occ      :: { OccName }
373 entity_occ      :  var_occ              { $1 }
374                 |  tc_occ               { $1 }
375                 |  RARROW               { TCOcc SLIT("->") {- Allow un-paren'd arrow -} }
376
377 val_occ         :: { OccName }
378 val_occ         :  var_occ              { $1 }
379                 |  CONID                { VarOcc $1 }
380                 |  CONSYM               { VarOcc $1 }
381
382 val_occs        :: { [OccName] }
383                 :  val_occ              { [$1] }
384                 |  val_occ val_occs     { $1 : $2 }
385
386
387 var_name        :: { RdrName }
388 var_name        :  var_occ              { Unqual $1 }
389
390 qvar_name       :: { RdrName }
391 qvar_name       :  var_name             { $1 }
392                 |  QVARID               { lexVarQual $1 }
393                 |  QVARSYM              { lexVarQual $1 }
394
395 var_names       :: { [RdrName] }
396 var_names       :                       { [] }
397                 | var_name var_names    { $1 : $2 }
398
399 var_names1      :: { [RdrName] }
400 var_names1      : var_name var_names    { $1 : $2 }
401
402 data_name       :: { RdrName }
403 data_name       :  CONID                { Unqual (VarOcc $1) }
404                 |  CONSYM               { Unqual (VarOcc $1) }
405
406 qdata_name      :: { RdrName }
407 qdata_name      : data_name             { $1 }
408                 |  QCONID               { lexVarQual $1 }
409                 |  QCONSYM              { lexVarQual $1 }
410                                 
411 qdata_names     :: { [RdrName] }
412 qdata_names     :                               { [] }
413                 | qdata_name qdata_names        { $1 : $2 }
414
415 tc_name         :: { RdrName }
416 tc_name         : tc_occ                        { Unqual $1 }
417                 | QCONID                        { lexTcQual $1 }
418                 | QCONSYM                       { lexTcQual $1 }
419
420 tc_names1       :: { [RdrName] }
421                 : tc_name                       { [$1] }
422                 | tc_name COMMA tc_names1       { $1 : $3 }
423
424 tv_name         :: { RdrName }
425 tv_name         :  VARID                { Unqual (TvOcc $1) }
426                 |  VARSYM               { Unqual (TvOcc $1) {- Allow t2 as a tyvar -} }
427
428 tv_bndr         :: { HsTyVar RdrName }
429 tv_bndr         :  tv_name DCOLON akind { IfaceTyVar $1 $3 }
430                 |  tv_name              { UserTyVar $1 }
431
432 tv_bndrs        :: { [HsTyVar RdrName] }
433                 :                       { [] }
434                 | tv_bndr tv_bndrs      { $1 : $2 }
435
436 kind            :: { Kind }
437                 : akind                 { $1 }
438                 | akind RARROW kind     { mkArrowKind $1 $3 }
439
440 akind           :: { Kind }
441                 : VARSYM                { if $1 == SLIT("*") then
442                                                 mkBoxedTypeKind
443                                           else if $1 == SLIT("**") then
444                                                 mkTypeKind
445                                           else panic "ParseInterface: akind"
446                                         }
447                 | OPAREN kind CPAREN    { $2 }
448 --------------------------------------------------------------------------
449
450
451 instances_part  :: { [RdrNameInstDecl] }
452 instances_part  :  INSTANCES_PART instdecls { $2 }
453                 |                           { [] }
454
455 instdecls       :: { [RdrNameInstDecl] }
456 instdecls       :                           { [] }
457                 |  instd instdecls          { $1 : $2 }
458
459 instd           :: { RdrNameInstDecl }
460 instd           :  src_loc INSTANCE type EQUAL var_name SEMI 
461                         { InstDecl $3
462                                    EmptyMonoBinds       {- No bindings -}
463                                    []                   {- No user pragmas -}
464                                    (Just $5)            {- Dfun id -}
465                                    $1
466                     }
467 --------------------------------------------------------------------------
468
469 id_info         :: { [HsIdInfo RdrName] }
470 id_info         :                                               { [] }
471                 | id_info_item id_info                          { $1 : $2 }
472
473 id_info_item    :: { HsIdInfo RdrName }
474 id_info_item    : ARITY_PART arity_info                 { HsArity $2 }
475                 | strict_info                           { HsStrictness $1 }
476                 | BOTTOM                                { HsStrictness HsBottom }
477                 | UNFOLD_PART core_expr                 { HsUnfold $1 $2 }
478                 | SPECIALISE spec_tvs
479                      atypes EQUAL core_expr             { HsSpecialise $2 $3 $5 }
480
481
482 spec_tvs        :: { [HsTyVar RdrName] }
483 spec_tvs        : OBRACK tv_bndrs CBRACK                { $2 }
484         
485
486 arity_info      :: { ArityInfo }
487 arity_info      : INTEGER                                       { exactArity (fromInteger $1) }
488
489 strict_info     :: { HsStrictnessInfo RdrName }
490 strict_info     : STRICT_PART qvar_name OCURLY qdata_names CCURLY       { HsStrictnessInfo $1 (Just ($2,$4)) }
491                 | STRICT_PART qvar_name                                 { HsStrictnessInfo $1 (Just ($2,[])) }
492                 | STRICT_PART                                           { HsStrictnessInfo $1 Nothing }
493
494 core_expr :: { UfExpr RdrName }
495           : LAM core_val_bndrs RARROW core_expr         { foldr UfLam $4 $2 }
496           | BIGLAM core_tv_bndrs RARROW core_expr       { foldr UfLam $4 $2 }
497           | CASE core_expr OF 
498              OCURLY alg_alts core_default CCURLY        { UfCase $2 (UfAlgAlts  $5 $6) }
499           | PRIM_CASE core_expr OF 
500              OCURLY prim_alts core_default CCURLY       { UfCase $2 (UfPrimAlts $5 $6) }
501
502           | LET OCURLY core_val_bndr EQUAL core_expr CCURLY
503             IN core_expr                                { UfLet (UfNonRec $3 $5) $8 }
504           | LETREC OCURLY rec_binds CCURLY              
505             IN core_expr                                { UfLet (UfRec $3) $6 }
506
507           | CCALL ccall_string 
508               OBRACK atype atypes CBRACK core_args      { let
509                                                                 (is_casm, may_gc) = $1
510                                                           in
511                                                           UfPrim (UfCCallOp $2 is_casm may_gc $5 $4)
512                                                                  $7
513                                                         }
514
515           | INLINE_CALL core_expr                       {  UfNote UfInlineCall $2 }
516           | COERCE atype core_expr                      {  UfNote (UfCoerce $2) $3 }
517           | SCC core_expr                               {  UfNote (UfSCC $1) $2 }
518           | fexpr                                       { $1 }
519
520 fexpr   :: { UfExpr RdrName }
521 fexpr   : fexpr core_arg                                { UfApp $1 $2 }
522         | fexpr ATSIGN atype                            { UfApp $1 (UfTyArg  $3) }
523         | aexpr                                         { $1 }
524
525 aexpr   :: { UfExpr RdrName }
526 aexpr   : qvar_name                                     { UfVar $1 }
527         | qdata_name                                    { UfVar $1 }
528         | core_lit                                      { UfLit $1 }
529         | OPAREN core_expr CPAREN                       { $2 }
530         | qdata_name OCURLY data_args CCURLY            { UfCon $1 $3 }
531
532
533 rec_binds       :: { [(UfBinder RdrName, UfExpr RdrName)] }
534                 :                                               { [] }
535                 | core_val_bndr EQUAL core_expr SEMI rec_binds  { ($1,$3) : $5 }
536
537 prim_alts       :: { [(Literal,UfExpr RdrName)] }
538                 :                                               { [] }
539                 | core_lit RARROW core_expr SEMI prim_alts      { ($1,$3) : $5 }
540
541 alg_alts        :: { [(RdrName, [RdrName], UfExpr RdrName)] }
542                 :                                               { [] }
543                 | qdata_name var_names RARROW 
544                         core_expr SEMI alg_alts                 { ($1,$2,$4) : $6 }
545
546 core_default    :: { UfDefault RdrName }
547                 :                                               { UfNoDefault }
548                 | var_name RARROW core_expr SEMI                { UfBindDefault $1 $3 }
549
550 core_arg        :: { UfArg RdrName }
551                 : qvar_name                                     { UfVarArg $1 }
552                 | qdata_name                                    { UfVarArg $1 }
553                 | core_lit                                      { UfLitArg $1 }
554
555 core_args       :: { [UfArg RdrName] }
556                 :                                               { [] }
557                 | core_arg core_args                            { $1 : $2 }
558
559 data_args       :: { [UfArg RdrName] }
560                 :                                               { [] }
561                 | core_arg data_args                            { $1 : $2 }
562                 | ATSIGN atype data_args                        { UfTyArg $2 : $3 }
563
564 core_lit        :: { Literal }
565 core_lit        : INTEGER                       { mkMachInt_safe $1 }
566                 | CHAR                          { MachChar $1 }
567                 | STRING                        { MachStr $1 }
568                 | STRING_LIT STRING             { NoRepStr $2 }
569                 | RATIONAL                      { MachDouble $1 }
570                 | FLOAT_LIT RATIONAL            { MachFloat $2 }
571
572                 | INTEGER_LIT INTEGER           { NoRepInteger  $2 (panic "NoRepInteger type") 
573                                                         -- The type checker will add the types
574                                                 }
575
576                 | RATIONAL_LIT INTEGER INTEGER  { NoRepRational ($2 % $3) 
577                                                                 (panic "NoRepRational type")
578                                                                         -- The type checker will add the type
579                                                 }
580
581                 | ADDR_LIT INTEGER              { MachAddr $2 }
582                 | LIT_LIT prim_rep STRING       { MachLitLit $3 (decodePrimRep $2) }
583
584 core_val_bndr   :: { UfBinder RdrName }
585 core_val_bndr   : var_name DCOLON atype                         { UfValBinder $1 $3 }
586
587 core_val_bndrs  :: { [UfBinder RdrName] }
588 core_val_bndrs  :                                               { [] }
589                 | core_val_bndr core_val_bndrs                  { $1 : $2 }
590
591 core_tv_bndr    :: { UfBinder RdrName }
592 core_tv_bndr    :  tv_name DCOLON akind                         { UfTyBinder $1 $3 }
593                 |  tv_name                                      { UfTyBinder $1 mkBoxedTypeKind }
594
595 core_tv_bndrs   :: { [UfBinder RdrName] }
596 core_tv_bndrs   :                                               { [] }
597                 | core_tv_bndr core_tv_bndrs                    { $1 : $2 }
598
599 ccall_string    :: { FAST_STRING }
600                 : STRING                                        { $1 }
601                 | VARID                                         { $1 }
602                 | CONID                                         { $1 }
603
604 prim_rep  :: { Char }
605           : VARID                                               { head (_UNPK_ $1) }
606           | CONID                                               { head (_UNPK_ $1) }
607
608 -------------------------------------------------------------------
609
610 src_loc :: { SrcLoc }
611 src_loc :                               {% getSrcLocIf }
612
613 checkVersion :: { () }
614            : {-empty-}                  {% checkVersion Nothing }
615            | INTEGER                    {% checkVersion (Just (fromInteger $1)) }
616
617 ------------------------------------------------------------------- 
618
619 --                      Haskell code 
620 {
621
622 data IfaceStuff = PIface        ParsedIface
623                 | PIdInfo       [HsIdInfo RdrName]
624                 | PType         RdrNameHsType
625
626 }