[project @ 2002-02-11 15:16:25 by simonpj]
[ghc-hetmet.git] / ghc / compiler / rename / ParseIface.y
1 {-      Notes about the syntax of interface files                 -*-haskell-*-
2         ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
3 The header
4 ~~~~~~~~~~
5   interface "edison" M 4 6 2 ! 406      Module M, version 4, from package 'edison',
6                                         Fixities version 6, rules version 2
7                                         Interface syntax version 406
8                                         ! means M contains orphans
9
10 Import declarations
11 ~~~~~~~~~~~~~~~~~~~
12   import Foo ;                          To compile M I used nothing from Foo, but it's 
13                                         below me in the hierarchy
14
15   import Foo ! @ ;                      Ditto, but the ! means that Foo contains orphans
16                                         and        the @ means that Foo is a boot interface
17
18   import Foo :: 3 ;                     To compile M I used everything from Foo, which has 
19                                         module version 3
20
21   import Foo :: 3 2 6 a 1 b 3 c 7 ;     To compile M I used Foo.  It had 
22                                                 module version 3
23                                                 fixity version 2
24                                                 rules  version 6
25                                         and some specific things besides.
26
27 -}
28
29
30 {
31 module ParseIface ( parseIface, parseType, parseRules, parseIdInfo ) where
32
33 #include "HsVersions.h"
34
35 import HsSyn            -- quite a bit of stuff
36 import RdrHsSyn         -- oodles of synonyms
37 import HsTypes          ( mkHsForAllTy, mkHsTupCon )
38 import HsCore
39 import Literal          ( Literal(..), mkMachInt, mkMachInt64, mkMachWord, mkMachWord64 )
40 import BasicTypes       ( Fixity(..), FixityDirection(..), StrictnessMark(..),
41                           NewOrData(..), Version, initialVersion, Boxity(..),
42                           Activation(..), IPName(..)
43                         )
44 import CostCentre       ( CostCentre(..), IsCafCC(..), IsDupdCC(..) )
45 import Type             ( Kind, mkArrowKind, liftedTypeKind, openTypeKind, usageTypeKind )
46 import ForeignCall      ( ForeignCall(..), CCallConv(..), CCallSpec(..), CCallTarget(..) )
47 import Lex              
48
49 import RnMonad          ( ParsedIface(..), ExportItem, IfaceDeprecs ) 
50 import HscTypes         ( WhetherHasOrphans, IsBootInterface, GenAvailInfo(..), 
51                           ImportVersion, WhatsImported(..),
52                           RdrAvailInfo )
53
54 import RdrName          ( RdrName, mkRdrUnqual, mkIfaceOrig )
55 import Name             ( OccName )
56 import OccName          ( mkSysOccFS,
57                           tcName, varName, dataName, clsName, tvName,
58                           EncodedFS 
59                         )
60 import Module           ( ModuleName, PackageName, mkSysModuleNameFS )
61 import SrcLoc           ( SrcLoc )
62 import CmdLineOpts      ( opt_InPackage, opt_IgnoreIfacePragmas )
63 import Outputable
64 import Class            ( DefMeth (..) )
65
66 import GlaExts
67 import FastString       ( tailFS )
68 }
69
70 %name       parseIface      iface
71 %name       parseType       type
72 %name       parseIdInfo     id_info
73 %name       parseRules      rules_and_deprecs
74
75 %tokentype  { Token }
76 %monad      { P }{ thenP }{ returnP }
77 %lexer      { lexer } { ITeof }
78
79 %token
80  'as'           { ITas }
81  'case'         { ITcase }                      -- Haskell keywords
82  'class'        { ITclass } 
83  'data'         { ITdata } 
84  'hiding'       { IThiding }
85  'import'       { ITimport }
86  'in'           { ITin }
87  'infix'        { ITinfix }
88  'infixl'       { ITinfixl }
89  'infixr'       { ITinfixr }
90  'instance'     { ITinstance }
91  'let'          { ITlet }
92  'newtype'      { ITnewtype }
93  'of'           { ITof }
94  'qualified'    { ITqualified }
95  'type'         { ITtype }
96  'where'        { ITwhere }
97
98  'forall'       { ITforall }                    -- GHC extension keywords
99  'foreign'      { ITforeign }
100  'export'       { ITexport }
101  'label'        { ITlabel } 
102  'dynamic'      { ITdynamic }
103  'unsafe'       { ITunsafe }
104  'with'         { ITwith }
105  'stdcall'      { ITstdcallconv }
106  'ccall'        { ITccallconv }
107
108  '__interface'  { ITinterface }                 -- interface keywords
109  '__export'     { IT__export }
110  '__forall'     { IT__forall }
111  '__letrec'     { ITletrec }
112  '__coerce'     { ITcoerce }
113  '__inline_me'  { ITinlineMe }
114  '__inline_call'{ ITinlineCall }
115  '__DEFAULT'    { ITdefaultbranch }
116  '__float'      { ITfloat_lit }
117  '__word'       { ITword_lit }
118  '__int64'      { ITint64_lit }
119  '__word64'     { ITword64_lit }
120  '__addr'       { ITaddr_lit }
121  '__label'      { ITlabel_lit }
122  '__litlit'     { ITlit_lit }
123  '__ccall'      { ITccall $$ }
124  '__scc'        { ITscc }
125  '__sccC'       { ITsccAllCafs }
126
127  '__u'          { ITusage }
128
129  '__A'          { ITarity }
130  '__P'          { ITspecialise }
131  '__C'          { ITnocaf }
132  '__U'          { ITunfold }
133  '__S'          { ITstrict $$ }
134  '__R'          { ITrules }
135  '__D'          { ITdeprecated }
136
137  '::'           { ITdcolon }
138  '='            { ITequal }
139  '\\'           { ITlam }
140  '|'            { ITvbar }
141  '->'           { ITrarrow }
142  '@'            { ITat }
143  '~'            { ITtilde }
144  '=>'           { ITdarrow }
145  '-'            { ITminus }
146  '!'            { ITbang }
147  '*'            { ITstar }
148
149  '{'            { ITocurly }                    -- special symbols
150  '}'            { ITccurly }
151  '['            { ITobrack }
152  ']'            { ITcbrack }
153  '[:'           { ITopabrack }
154  ':]'           { ITcpabrack }
155  '('            { IToparen }
156  ')'            { ITcparen }
157  '(#'           { IToubxparen }
158  '#)'           { ITcubxparen }
159  ';'            { ITsemi }
160  ','            { ITcomma }
161  '.'            { ITdot }
162
163  VARID          { ITvarid    $$ }               -- identifiers
164  CONID          { ITconid    $$ }
165  VARSYM         { ITvarsym   $$ }
166  QVARID         { ITqvarid   $$ }
167  QCONID         { ITqconid   $$ }
168
169  IPDUPVARID     { ITdupipvarid   $$ }           -- GHC extension
170  IPSPLITVARID   { ITsplitipvarid $$ }           -- GHC extension
171
172  PRAGMA         { ITpragma   $$ }
173
174  CHAR           { ITchar     $$ }
175  STRING         { ITstring   $$ }
176  INTEGER        { ITinteger  $$ }
177  RATIONAL       { ITrational $$ }
178  CLITLIT        { ITlitlit   $$ }
179 %%
180
181 iface           :: { ParsedIface }
182 iface           : '__interface' package mod_name 
183                         version sub_versions
184                         orphans checkVersion 'where'
185                   exports_part
186                   import_part
187                   fix_decl_part
188                   instance_decl_part
189                   decls_part
190                   rules_and_deprecs_part
191                   { let (rules,deprecs) = $14 () in
192                     ParsedIface {
193                         pi_mod  = $3,                   -- Module name
194                         pi_pkg = $2,                    -- Package name
195                         pi_vers = $4,                   -- Module version
196                         pi_orphan  = $6,
197                         pi_exports = (fst $5, $9),      -- Exports
198                         pi_usages  = $10,               -- Usages
199                         pi_fixity  = $11,               -- Fixies
200                         pi_insts   = $12,               -- Local instances
201                         pi_decls   = $13,               -- Decls
202                         pi_rules   = (snd $5,rules),    -- Rules 
203                         pi_deprecs = deprecs            -- Deprecations 
204                    } }
205
206 -- Versions for exports and rules (optional)
207 sub_versions :: { (Version,Version) }
208         : '[' version version ']'               { ($2,$3) }
209         | {- empty -}                           { (initialVersion, initialVersion) }
210
211 --------------------------------------------------------------------------
212
213 import_part :: { [ImportVersion OccName] }
214 import_part :                                             { [] }
215             |  import_decl import_part                    { $1 : $2 }
216             
217 import_decl :: { ImportVersion OccName }
218 import_decl : 'import' mod_name orphans is_boot whats_imported ';'
219                         { ({-mkSysModuleNameFS-} $2, $3, $4, $5) }
220
221 orphans             :: { WhetherHasOrphans }
222 orphans             :                                           { False }
223                     | '!'                                       { True }
224
225 is_boot             :: { IsBootInterface }
226 is_boot             :                                           { False }
227                     | '@'                                       { True }
228
229 whats_imported      :: { WhatsImported OccName }
230 whats_imported      :                                                   { NothingAtAll }
231                     | '::' version                                      { Everything $2 }
232                     | '::' version version version name_version_pairs   { Specifically $2 (Just $3) $5 $4 }
233                     | '::' version version name_version_pairs           { Specifically $2 Nothing $4 $3 }
234
235 name_version_pairs  ::  { [(OccName, Version)] }
236 name_version_pairs  :                                           { [] }
237                     |  name_version_pair name_version_pairs     { $1 : $2 }
238
239 name_version_pair   ::  { (OccName, Version) }
240 name_version_pair   :  var_occ version                          { ($1, $2) }
241                     |  tc_occ  version                          { ($1, $2) }
242
243
244 --------------------------------------------------------------------------
245
246 exports_part    :: { [ExportItem] }
247 exports_part    :                                       { [] }
248                 | '__export' mod_name entities ';'
249                         exports_part                    { ({-mkSysModuleNameFS-} $2, $3) : $5 }
250
251 entities        :: { [RdrAvailInfo] }
252 entities        :                                       { [] }
253                 |  entity entities                      { $1 : $2 }
254
255 entity          :: { RdrAvailInfo }
256 entity          :  var_occ                              { Avail $1 }
257                 |  tc_occ                               { AvailTC $1 [$1] }
258                 |  tc_occ '|' stuff_inside              { AvailTC $1 $3 }
259                 |  tc_occ stuff_inside                  { AvailTC $1 ($1:$2) }
260                 -- Note that the "main name" comes at the beginning
261
262 stuff_inside    :: { [OccName] }
263 stuff_inside    :  '{' val_occs '}'                     { $2 }
264
265 val_occ         :: { OccName }
266                 :  var_occ              { $1 }
267                 |  data_occ             { $1 }
268
269 val_occs        :: { [OccName] }
270                 :  val_occ              { [$1] }
271                 |  val_occ val_occs     { $1 : $2 }
272
273
274 --------------------------------------------------------------------------
275
276 fix_decl_part :: { [RdrNameFixitySig] }
277 fix_decl_part : {- empty -}                             { [] }
278               | fix_decls ';'                           { $1 }
279
280 fix_decls     :: { [RdrNameFixitySig] }
281 fix_decls     :                                         { [] }
282               | fix_decl fix_decls                      { $1 : $2 }
283
284 fix_decl :: { RdrNameFixitySig }
285 fix_decl : src_loc fixity prec var_or_data_name         { FixitySig $4 (Fixity $3 $2) $1 }
286
287 fixity      :: { FixityDirection }
288 fixity      : 'infixl'                                  { InfixL }
289             | 'infixr'                                  { InfixR }
290             | 'infix'                                   { InfixN }
291    
292 prec        :: { Int }
293 prec        : INTEGER                                   { fromInteger $1 }
294
295 -----------------------------------------------------------------------------
296
297 csigs           :: { [RdrNameSig] }
298 csigs           :                               { [] }
299                 | 'where' '{' csigs1 '}'        { $3 }
300
301 csigs1          :: { [RdrNameSig] }
302 csigs1          :                               { [] }
303                 | csig ';' csigs1               { $1 : $3 }
304
305 csig            :: { RdrNameSig }
306 csig            :  src_loc qvar_name '::' type          { ClassOpSig $2 NoDefMeth $4 $1 }
307                 |  src_loc qvar_name ';' '::' type      { ClassOpSig $2 GenDefMeth $5 $1 }              
308                 |  src_loc qvar_name '=' '::' type      { mkClassOpSigDM $2 $5 $1 }
309
310 --------------------------------------------------------------------------
311
312 instance_decl_part :: { [RdrNameInstDecl] }
313 instance_decl_part : {- empty -}                       { [] }
314                    | instance_decl_part inst_decl      { $2 : $1 }
315
316 inst_decl       :: { RdrNameInstDecl }
317 inst_decl       :  src_loc 'instance' type '=' qvar_name ';'
318                         { InstDecl $3
319                                    EmptyMonoBinds       {- No bindings -}
320                                    []                   {- No user pragmas -}
321                                    (Just $5)            {- Dfun id -}
322                                    $1
323                         }
324
325 --------------------------------------------------------------------------
326
327 decls_part :: { [(Version, RdrNameTyClDecl)] }
328 decls_part 
329         :  {- empty -}                          { [] }
330         |  opt_version decl ';' decls_part              { ($1,$2):$4 }
331
332 decl    :: { RdrNameTyClDecl }
333 decl    : src_loc qvar_name '::' type maybe_idinfo
334                         { IfaceSig $2 $4 ($5 $2) $1 }
335         | src_loc 'type' qtc_name tv_bndrs '=' type                    
336                         { TySynonym $3 $4 $6 $1 }
337         | src_loc 'foreign' 'type' qtc_name                    
338                         { ForeignType $4 Nothing DNType $1 }
339         | src_loc 'data' tycl_hdr constrs              
340                         { mkTyData DataType $3 $4 (length $4) Nothing $1 }
341         | src_loc 'newtype' tycl_hdr newtype_constr
342                         { mkTyData NewType $3 $4 1 Nothing $1 }
343         | src_loc 'class' tycl_hdr fds csigs
344                         { mkClassDecl $3 $4 $5 Nothing $1 }
345
346 tycl_hdr :: { (RdrNameContext, RdrName, [RdrNameHsTyVar]) }
347         : context '=>' qtc_name tv_bndrs        { ($1, $3, $4) }
348         | qtc_name tv_bndrs                     { ([], $1, $2) }
349
350 maybe_idinfo  :: { RdrName -> [HsIdInfo RdrName] }
351 maybe_idinfo  : {- empty -}     { \_ -> [] }
352               | pragma          { \x -> if opt_IgnoreIfacePragmas then [] 
353                                         else case $1 of
354                                                 Just (POk _ id_info) -> id_info
355                                                 Just (PFailed err) -> pprPanic "IdInfo parse failed" 
356                                                                         (vcat [ppr x, err])
357                                 }
358     {-
359       If a signature decl is being loaded, and opt_IgnoreIfacePragmas is on,
360       we toss away unfolding information.
361
362       Also, if the signature is loaded from a module we're importing from source,
363       we do the same. This is to avoid situations when compiling a pair of mutually
364       recursive modules, peering at unfolding info in the interface file of the other, 
365       e.g., you compile A, it looks at B's interface file and may as a result change
366       its interface file. Hence, B is recompiled, maybe changing its interface file,
367       which will the unfolding info used in A to become invalid. Simple way out is to
368       just ignore unfolding info.
369
370       [Jan 99: I junked the second test above.  If we're importing from an hi-boot
371        file there isn't going to *be* any pragma info.  The above comment
372        dates from a time where we picked up a .hi file first if it existed.]
373     -}
374
375 pragma  :: { Maybe (ParseResult [HsIdInfo RdrName]) }
376 pragma  : src_loc PRAGMA        { let exts = ExtFlags {glasgowExtsEF = True,
377                                                        parrEF        = True}
378                                   in
379                                   Just (parseIdInfo $2 (mkPState $1 exts))
380                                 }
381
382 -----------------------------------------------------------------------------
383
384 -- This production is lifted so that it doesn't get eagerly parsed when we
385 -- use happy --strict.
386 rules_and_deprecs_part :: { () -> ([RdrNameRuleDecl], IfaceDeprecs) }
387 rules_and_deprecs_part
388   : {- empty -}         { \_ -> ([], Nothing) }
389   | src_loc PRAGMA      { \_ -> let exts = ExtFlags {glasgowExtsEF = True,
390                                                      parrEF        = True}
391                                 in case parseRules $2 (mkPState $1 exts) of
392                                         POk _ rds   -> rds
393                                         PFailed err -> pprPanic "Rules/Deprecations parse failed" err
394                         }
395
396 rules_and_deprecs :: { ([RdrNameRuleDecl], IfaceDeprecs) }
397 rules_and_deprecs : rule_prag deprec_prag       { ($1, $2) }
398
399
400 -----------------------------------------------------------------------------
401
402 rule_prag :: { [RdrNameRuleDecl] }
403 rule_prag : {- empty -}                 { [] }
404           | '__R' rules                 { $2 }
405
406 rules      :: { [RdrNameRuleDecl] }
407            : {- empty -}        { [] }
408            | rule ';' rules     { $1:$3 }
409
410 rule       :: { RdrNameRuleDecl }
411 rule       : src_loc STRING activation rule_forall qvar_name 
412              core_args '=' core_expr    { IfaceRule $2 $3 $4 $5 $6 $8 $1 } 
413
414 activation :: { Activation }
415 activation : {- empty -}                { AlwaysActive }
416            | '[' INTEGER ']'            { ActiveAfter (fromInteger $2) }
417            | '[' '~' INTEGER ']'        { ActiveBefore (fromInteger $3) }
418
419 rule_forall     :: { [UfBinder RdrName] }
420 rule_forall     : '__forall' '{' core_bndrs '}' { $3 }
421                   
422 -----------------------------------------------------------------------------
423
424 deprec_prag     :: { IfaceDeprecs }
425 deprec_prag     : {- empty -}           { Nothing }
426                 | '__D' deprecs         { Just $2 } 
427
428 deprecs         :: { Either DeprecTxt [(RdrName,DeprecTxt)] }
429 deprecs         : STRING                { Left $1 }
430                 | deprec_list           { Right $1 }
431
432 deprec_list     :: { [(RdrName,DeprecTxt)] }
433 deprec_list     : deprec                        { [$1] }
434                 | deprec ';' deprec_list        { $1 : $3 }
435
436 deprec          :: { (RdrName,DeprecTxt) }
437 deprec          : deprec_name STRING    { ($1, $2) }
438
439 deprec_name     :: { RdrName }
440                 : qvar_name             { $1 }
441                 | qtc_name              { $1 }
442
443 -----------------------------------------------------------------------------
444
445 version         :: { Version }
446 version         :  INTEGER                      { fromInteger $1 }
447
448 opt_version     :: { Version }
449 opt_version     : version                       { $1 }
450                 | {- empty -}                   { initialVersion }
451         
452
453 ----------------------------------------------------------------------------
454
455 constrs         :: { [RdrNameConDecl] {- empty for handwritten abstract -} }
456                 :                       { [] }
457                 | '=' constrs1          { $2 }
458
459 constrs1        :: { [RdrNameConDecl] }
460 constrs1        :  constr               { [$1] }
461                 |  constr '|' constrs1  { $1 : $3 }
462
463 constr          :: { RdrNameConDecl }
464 constr          :  src_loc ex_stuff qdata_name batypes          { mk_con_decl $3 $2 (VanillaCon $4) $1 }
465                 |  src_loc ex_stuff qdata_name '{' fields1 '}'  { mk_con_decl $3 $2 (RecCon $5)     $1 }
466                 -- We use "data_fs" so as to include ()
467
468 newtype_constr  :: { [RdrNameConDecl] {- Not allowed to be empty -} }
469 newtype_constr  : src_loc '=' ex_stuff qdata_name atype { [mk_con_decl $4 $3 (VanillaCon [unbangedType $5]) $1] }
470                 | src_loc '=' ex_stuff qdata_name '{' qvar_name '::' atype '}'
471                                                         { [mk_con_decl $4 $3 (RecCon [([$6], unbangedType $8)]) $1] }
472
473 ex_stuff :: { ([HsTyVarBndr RdrName], RdrNameContext) }
474 ex_stuff        :                                       { ([],[]) }
475                 | '__forall' tv_bndrs opt_context '=>'  { ($2,$3) }
476
477 batypes         :: { [RdrNameBangType] }
478 batypes         :                                       { [] }
479                 |  batype batypes                       { $1 : $2 }
480
481 batype          :: { RdrNameBangType }
482 batype          :  tatype                               { unbangedType $1 }
483                 |  '!' tatype                           { BangType MarkedStrict    $2 }
484                 |  '!' '!' tatype                       { BangType MarkedUnboxed   $3 }
485
486 fields1         :: { [([RdrName], RdrNameBangType)] }
487 fields1         : field                                 { [$1] }
488                 | field ',' fields1                     { $1 : $3 }
489
490 field           :: { ([RdrName], RdrNameBangType) }
491 field           :  qvar_names1 '::' ttype               { ($1, unbangedType $3) }
492                 |  qvar_names1 '::' '!' ttype           { ($1, BangType MarkedStrict    $4) }
493                 |  qvar_names1 '::' '!' '!' ttype       { ($1, BangType MarkedUnboxed   $5) }
494
495 --------------------------------------------------------------------------
496
497 type            :: { RdrNameHsType }
498 type            : '__forall' tv_bndrs 
499                         opt_context '=>' type   { mkHsForAllTy (Just $2) $3 $5 }
500                 | btype '->' type               { HsFunTy $1 $3 }
501                 | btype                         { $1 }
502
503 opt_context     :: { RdrNameContext }
504 opt_context     :                                       { [] }
505                 | context                               { $1 }
506
507 context         :: { RdrNameContext }
508 context         : '(' context_list1 ')'                 { $2 }
509                 | '{' context_list1 '}'                 { $2 }  -- Backward compatibility
510
511 context_list1   :: { RdrNameContext }
512 context_list1   : class                                 { [$1] }
513                 | class ',' context_list1               { $1 : $3 }
514
515 class           :: { HsPred RdrName }
516 class           :  qcls_name atypes                     { (HsClassP $1 $2) }
517                 |  ipvar_name '::' type                 { (HsIParam $1 $3) }
518
519 types0          :: { [RdrNameHsType]                    {- Zero or more -}  }   
520 types0          :  {- empty -}                          { [ ] }
521                 |  type                                 { [ $1 ] }
522                 |  types2                               { $1 }
523
524 types2          :: { [RdrNameHsType]                    {- Two or more -}  }    
525 types2          :  type ',' type                        { [$1,$3] }
526                 |  type ',' types2                      { $1 : $3 }
527
528 btype           :: { RdrNameHsType }
529 btype           :  atype                                { $1 }
530                 |  btype atype                          { HsAppTy $1 $2 }
531
532 atype           :: { RdrNameHsType }
533 atype           :  qtc_name                             { HsTyVar $1 }
534                 |  tv_name                              { HsTyVar $1 }
535                 |  '.'                                  { hsUsOnce }
536                 |  '!'                                  { hsUsMany }
537                 |  '(' ')'                              { HsTupleTy (mkHsTupCon tcName Boxed   []) [] }
538                 |  '(' types2 ')'                       { HsTupleTy (mkHsTupCon tcName Boxed   $2) $2 }
539                 |  '(#' types0 '#)'                     { HsTupleTy (mkHsTupCon tcName Unboxed $2) $2 }
540                 |  '[' type ']'                         { HsListTy  $2 }
541                 |  '[:' type ':]'                       { HsPArrTy $2 }
542                 |  '{' qcls_name atypes '}'             { mkHsDictTy $2 $3 }
543                 |  '{' ipvar_name '::' type '}'         { mkHsIParamTy $2 $4 }
544                 |  '(' type ')'                         { $2 }
545
546 atypes          :: { [RdrNameHsType]    {-  Zero or more -} }
547 atypes          :                                       { [] }
548                 |  atype atypes                         { $1 : $2 }
549 --------------------------------------------------------------------------
550
551 -- versions of type/btype/atype that cant begin with '!' (or '.')
552 -- for use where the kind is definitely known NOT to be '$'
553
554 ttype           :: { RdrNameHsType }
555 ttype           : '__forall' tv_bndrs 
556                         opt_context '=>' type           { mkHsForAllTy (Just $2) $3 $5 }
557                 | tbtype '->' type                      { HsFunTy $1 $3 }
558                 | tbtype                                { $1 }
559
560 tbtype          :: { RdrNameHsType }
561 tbtype          :  tatype                               { $1 }
562                 |  tbtype atype                         { HsAppTy $1 $2 }
563
564 tatype          :: { RdrNameHsType }
565 tatype          :  qtc_name                             { HsTyVar $1 }
566                 |  tv_name                              { HsTyVar $1 }
567                 |  '(' ')'                              { HsTupleTy (mkHsTupCon tcName Boxed   []) [] }
568                 |  '(' types2 ')'                       { HsTupleTy (mkHsTupCon tcName Boxed   $2) $2 }
569                 |  '(#' types0 '#)'                     { HsTupleTy (mkHsTupCon tcName Unboxed $2) $2 }
570                 |  '[' type ']'                         { HsListTy  $2 }
571                 |  '[:' type ':]'                       { HsPArrTy $2 }
572                 |  '{' qcls_name atypes '}'             { mkHsDictTy $2 $3 }
573                 |  '{' ipvar_name '::' type '}'         { mkHsIParamTy $2 $4 }
574                 |  '(' type ')'                         { $2 }
575 ---------------------------------------------------------------------
576
577 package         :: { PackageName }
578                 :  STRING               { $1 }
579                 | {- empty -}           { opt_InPackage }
580                                 -- Useful for .hi-boot files,
581                                 -- which can omit the package Id
582                                 -- Module loops are always within a package
583
584 mod_name        :: { ModuleName }
585                 :  CONID                { mkSysModuleNameFS $1 }
586
587
588 ---------------------------------------------------
589 var_fs          :: { EncodedFS }
590                 : VARID                 { $1 }
591                 | 'as'                  { SLIT("as") }
592                 | 'qualified'           { SLIT("qualified") }
593                 | 'hiding'              { SLIT("hiding") }
594                 | 'forall'              { SLIT("forall") }
595                 | 'foreign'             { SLIT("foreign") }
596                 | 'export'              { SLIT("export") }
597                 | 'label'               { SLIT("label") }
598                 | 'dynamic'             { SLIT("dynamic") }
599                 | 'unsafe'              { SLIT("unsafe") }
600                 | 'with'                { SLIT("with") }
601                 | 'ccall'               { SLIT("ccall") }
602                 | 'stdcall'             { SLIT("stdcall") }
603
604 var_occ         :: { OccName }
605                 :  var_fs               { mkSysOccFS varName $1 }
606
607 var_name        :: { RdrName }
608 var_name        :  var_occ              { mkRdrUnqual $1 }
609
610 qvar_name       :: { RdrName }
611 qvar_name       :  var_name             { $1 }
612                 |  QVARID               { mkIfaceOrig varName $1 }
613
614 ipvar_name      :: { IPName RdrName }
615                 : IPDUPVARID            { Dupable (mkRdrUnqual (mkSysOccFS varName $1)) }
616                 | IPSPLITVARID          { Linear  (mkRdrUnqual (mkSysOccFS varName $1)) }
617
618 qvar_names1     :: { [RdrName] }
619 qvar_names1     : qvar_name             { [$1] }
620                 | qvar_name qvar_names1 { $1 : $2 }
621
622 ---------------------------------------------------
623
624 data_occ        :: { OccName }
625                 :  CONID                { mkSysOccFS dataName $1 }
626
627 qdata_name      :: { RdrName }
628                 :  data_occ             { mkRdrUnqual $1 }
629                 |  QCONID               { mkIfaceOrig dataName $1 }
630                                 
631 var_or_data_name :: { RdrName }
632                   : qvar_name           { $1 }
633                   | qdata_name          { $1 }
634
635 ---------------------------------------------------
636 tc_occ          :: { OccName }
637                 :  CONID                { mkSysOccFS tcName $1 }
638
639 qtc_name        :: { RdrName }
640                 : tc_occ                { mkRdrUnqual $1 }
641                 | QCONID                { mkIfaceOrig tcName $1 }
642
643 ---------------------------------------------------
644 qcls_name       :: { RdrName }
645                 : CONID                 { mkRdrUnqual (mkSysOccFS clsName $1) }
646                 | QCONID                { mkIfaceOrig clsName $1 }
647
648 ---------------------------------------------------
649 tv_name         :: { RdrName }
650                 :  var_fs               { mkRdrUnqual (mkSysOccFS tvName $1) }
651
652 tv_bndr         :: { HsTyVarBndr RdrName }
653                 :  tv_name '::' akind   { IfaceTyVar $1 $3 }
654                 |  tv_name              { IfaceTyVar $1 liftedTypeKind }
655
656 tv_bndrs        :: { [HsTyVarBndr RdrName] }
657                 : tv_bndrs1             { $1 }
658                 | '[' tv_bndrs1 ']'     { $2 }  -- Backward compatibility
659
660 tv_bndrs1       :: { [HsTyVarBndr RdrName] }
661                 :                       { [] }
662                 | tv_bndr tv_bndrs1     { $1 : $2 }
663
664 ---------------------------------------------------
665 fds :: { [([RdrName], [RdrName])] }
666         : {- empty -}                   { [] }
667         | '|' fds1                      { reverse $2 }
668
669 fds1 :: { [([RdrName], [RdrName])] }
670         : fds1 ',' fd                   { $3 : $1 }
671         | fd                            { [$1] }
672
673 fd :: { ([RdrName], [RdrName]) }
674         : varids0 '->' varids0          { (reverse $1, reverse $3) }
675
676 varids0 :: { [RdrName] }
677         : {- empty -}                   { [] }
678         | varids0 tv_name               { $2 : $1 }
679
680 ---------------------------------------------------
681 kind            :: { Kind }
682                 : akind                 { $1 }
683                 | akind '->' kind       { mkArrowKind $1 $3 }
684
685 akind           :: { Kind }
686                 : '*'                   { liftedTypeKind }
687                 | VARSYM                { if $1 == SLIT("?") then
688                                                 openTypeKind
689                                           else if $1 == SLIT("\36") then
690                                                 usageTypeKind  -- dollar
691                                           else panic "ParseInterface: akind"
692                                         }
693                 | '(' kind ')'  { $2 }
694
695 --------------------------------------------------------------------------
696
697 id_info         :: { [HsIdInfo RdrName] }
698                 : id_info_item                  { [$1] }
699                 | id_info_item id_info          { $1 : $2 }
700
701 id_info_item    :: { HsIdInfo RdrName }
702                 : '__A' INTEGER                 { HsArity (fromInteger $2) }
703                 | '__U' activation core_expr    { HsUnfold $2 $3 }
704                 | '__S'                         { HsStrictness $1 }
705                 | '__C'                         { HsNoCafRefs }
706                 | '__P' qvar_name INTEGER       { HsWorker $2 (fromInteger $3) }
707
708 -------------------------------------------------------
709 core_expr       :: { UfExpr RdrName }
710 core_expr       : '\\' core_bndrs '->' core_expr        { foldr UfLam $4 $2 }
711                 | 'case' core_expr 'of' var_name
712                   '{' core_alts '}'                     { UfCase $2 $4 $6 }
713
714                 | 'let' '{' core_val_bndr '=' core_expr
715                       '}' 'in' core_expr                { UfLet (UfNonRec $3 $5) $8 }
716                 | '__letrec' '{' rec_binds '}'          
717                   'in' core_expr                        { UfLet (UfRec $3) $6 }
718
719                 | '__litlit' STRING atype               { UfLitLit $2 $3 }
720
721                 | fexpr                                 { $1 }
722
723 fexpr   :: { UfExpr RdrName }
724 fexpr   : fexpr core_arg                                { UfApp $1 $2 }
725         | scc core_aexpr                                { UfNote (UfSCC $1) $2  }
726         | '__inline_me' core_aexpr                      { UfNote UfInlineMe $2 }
727         | '__inline_call' core_aexpr                    { UfNote UfInlineCall $2 }
728         | '__coerce' atype core_aexpr                   { UfNote (UfCoerce $2) $3 }
729         | core_aexpr                                    { $1 }
730
731 core_arg        :: { UfExpr RdrName }
732                 : '@' atype                                     { UfType $2 }
733                 | core_aexpr                                    { $1 }
734
735 core_args       :: { [UfExpr RdrName] }
736                 :                                               { [] }
737                 | core_arg core_args                            { $1 : $2 }
738
739 core_aexpr      :: { UfExpr RdrName }              -- Atomic expressions
740 core_aexpr      : qvar_name                                     { UfVar $1 }
741                 | qdata_name                                    { UfVar $1 }
742
743                 | core_lit               { UfLit $1 }
744                 | '(' core_expr ')'      { $2 }
745
746                 | '('  ')'               { UfTuple (mkHsTupCon dataName Boxed [])   [] }
747                 | '(' comma_exprs2 ')'   { UfTuple (mkHsTupCon dataName Boxed $2)   $2 }
748                 | '(#' comma_exprs0 '#)' { UfTuple (mkHsTupCon dataName Unboxed $2) $2 }
749
750                 | '{' '__ccall' ccall_string type '}'       
751                            { let
752                                  (is_dyn, is_casm, may_gc) = $2
753
754                                  target | is_dyn    = DynamicTarget
755                                         | is_casm   = CasmTarget $3
756                                         | otherwise = StaticTarget $3
757
758                                  ccall = CCallSpec target CCallConv may_gc
759                              in
760                              UfFCall (CCall ccall) $4
761                            }
762
763
764 comma_exprs0    :: { [UfExpr RdrName] } -- Zero or more
765 comma_exprs0    : {- empty -}                   { [ ] }
766                 | core_expr                     { [ $1 ] }
767                 | comma_exprs2                  { $1 }
768
769 comma_exprs2    :: { [UfExpr RdrName] } -- Two or more
770 comma_exprs2    : core_expr ',' core_expr                       { [$1,$3] }
771                 | core_expr ',' comma_exprs2                    { $1 : $3 }
772
773 rec_binds       :: { [(UfBinder RdrName, UfExpr RdrName)] }
774                 :                                               { [] }
775                 | core_val_bndr '=' core_expr ';' rec_binds     { ($1,$3) : $5 }
776
777 core_alts       :: { [UfAlt RdrName] }
778                 :                                               { [] }
779                 | core_alt ';' core_alts                        { $1 : $3 }
780
781 core_alt        :: { UfAlt RdrName }
782 core_alt        : core_pat '->' core_expr       { (fst $1, snd $1, $3) }
783
784 core_pat        :: { (UfConAlt RdrName, [RdrName]) }
785 core_pat        : core_lit                      { (UfLitAlt  $1, []) }
786                 | '__litlit' STRING atype       { (UfLitLitAlt $2 $3, []) }
787                 | qdata_name core_pat_names     { (UfDataAlt $1, $2) }
788                 | '('  ')'                      { (UfTupleAlt (mkHsTupCon dataName Boxed []),   []) }
789                 | '(' comma_var_names1 ')'      { (UfTupleAlt (mkHsTupCon dataName Boxed $2),   $2) }
790                 | '(#' comma_var_names1 '#)'    { (UfTupleAlt (mkHsTupCon dataName Unboxed $2), $2) }
791                 | '__DEFAULT'                   { (UfDefault, []) }
792                 | '(' core_pat ')'              { $2 }
793
794 core_pat_names :: { [RdrName] }
795 core_pat_names :                                { [] }
796                 | core_pat_name core_pat_names  { $1 : $2 }
797
798 -- Tyvar names and variable names live in different name spaces
799 -- so they need to be signalled separately.  But we don't record 
800 -- types or kinds in a pattern; we work that out from the type 
801 -- of the case scrutinee
802 core_pat_name   :: { RdrName }
803 core_pat_name   : var_name                      { $1 }
804                 | '@' tv_name                   { $2 }
805         
806 comma_var_names1 :: { [RdrName] }       -- One or more
807 comma_var_names1 : var_name                                     { [$1] }
808                  | var_name ',' comma_var_names1                { $1 : $3 }
809
810 core_lit        :: { Literal }
811 core_lit        : integer                       { mkMachInt $1 }
812                 | CHAR                          { MachChar $1 }
813                 | STRING                        { MachStr $1 }
814                 | rational                      { MachDouble $1 }
815                 | '__word' integer              { mkMachWord $2 }
816                 | '__word64' integer            { mkMachWord64 $2 }
817                 | '__int64' integer             { mkMachInt64 $2 }
818                 | '__float' rational            { MachFloat $2 }
819                 | '__addr' integer              { MachAddr $2 }
820                 | '__label' STRING              { MachLabel $2 }
821
822 integer         :: { Integer }
823                 : INTEGER                       { $1 }
824                 | '-' INTEGER                   { (-$2) }
825
826 rational        :: { Rational }
827                 : RATIONAL                      { $1 }
828                 | '-' RATIONAL                  { (-$2) }
829
830 core_bndr       :: { UfBinder RdrName }
831 core_bndr       : core_val_bndr                                 { $1 }
832                 | core_tv_bndr                                  { $1 }
833
834 core_bndrs      :: { [UfBinder RdrName] }
835 core_bndrs      :                                               { [] }
836                 | core_bndr core_bndrs                          { $1 : $2 }
837
838 core_val_bndr   :: { UfBinder RdrName }
839 core_val_bndr   : var_name '::' atype                           { UfValBinder $1 $3 }
840
841 core_tv_bndr    :: { UfBinder RdrName }
842 core_tv_bndr    :  '@' tv_name '::' akind               { UfTyBinder $2 $4 }
843                 |  '@' tv_name                          { UfTyBinder $2 liftedTypeKind }
844
845 ccall_string    :: { FAST_STRING }
846                 : STRING                                        { $1 }
847                 | CLITLIT                                       { $1 }
848                 | VARID                                         { $1 }
849                 | CONID                                         { $1 }
850
851 ------------------------------------------------------------------------
852 scc     :: { CostCentre }
853         :  '__sccC' '{' mod_name '}'                      { AllCafsCC $3 }
854         |  '__scc' '{' cc_name mod_name cc_dup cc_caf '}'
855                              { NormalCC { cc_name = $3, cc_mod = $4,
856                                           cc_is_dupd = $5, cc_is_caf = $6 } }
857
858 cc_name :: { EncodedFS }
859         : CONID                 { $1 }
860         | var_fs                { $1 }
861   
862 cc_dup  :: { IsDupdCC }
863 cc_dup  :                       { OriginalCC }
864         | '!'                   { DupdCC }
865
866 cc_caf  :: { IsCafCC }
867         :                       { NotCafCC }
868         | '__C'                 { CafCC }
869
870 -------------------------------------------------------------------
871
872 src_loc :: { SrcLoc }
873 src_loc :                               {% getSrcLocP }
874
875 -- Check the project version: this makes sure
876 -- that the project version (e.g. 407) in the interface
877 -- file is the same as that for the compiler that's reading it
878 checkVersion :: { () }
879            : {-empty-}                  {% checkVersion Nothing }
880            | INTEGER                    {% checkVersion (Just (fromInteger $1)) }
881
882 ------------------------------------------------------------------- 
883
884 --                      Haskell code 
885 {
886 happyError :: P a
887 happyError buf PState{ loc = loc } = PFailed (ifaceParseErr buf loc)
888
889 mk_con_decl name (ex_tvs, ex_ctxt) details loc = mkConDecl name ex_tvs ex_ctxt details loc
890 }