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