[project @ 2005-03-07 15:59:27 by simonmar]
[ghc-hetmet.git] / ghc / compiler / iface / BinIface.hs
1 {-% DrIFT (Automatic class derivations for Haskell) v1.1 %-}
2 {-% DrIFT (Automatic class derivations for Haskell) v1.1 %-}
3 -- 
4 --  (c) The University of Glasgow 2002
5 -- 
6 -- Binary interface file support.
7
8 module BinIface ( writeBinIface, readBinIface, v_IgnoreHiWay ) where
9
10 #include "HsVersions.h"
11 #include "MachDeps.h"
12
13 import HscTypes
14 import BasicTypes
15 import NewDemand
16 import IfaceSyn
17 import VarEnv
18 import Packages         ( PackageIdH(..) )
19 import Class            ( DefMeth(..) )
20 import CostCentre
21 import DriverState      ( v_Build_tag )
22 import CmdLineOpts      ( opt_HiVersion )
23 import Kind             ( Kind(..) )
24 import Panic
25 import Binary
26 import Util
27
28 import DATA_IOREF
29 import DATA_WORD        ( Word8 )
30 import EXCEPTION        ( throwDyn )
31 import Monad            ( when )
32 import Outputable
33
34 -- ---------------------------------------------------------------------------
35 writeBinIface :: FilePath -> ModIface -> IO ()
36 writeBinIface hi_path mod_iface
37   = putBinFileWithDict hi_path mod_iface
38
39 readBinIface :: FilePath -> IO ModIface
40 readBinIface hi_path = getBinFileWithDict hi_path
41
42
43 -- %*********************************************************
44 -- %*                                                       *
45 --              All the Binary instances
46 -- %*                                                       *
47 -- %*********************************************************
48
49 -- BasicTypes
50 {-! for IPName derive: Binary !-}
51 {-! for Fixity derive: Binary !-}
52 {-! for FixityDirection derive: Binary !-}
53 {-! for Boxity derive: Binary !-}
54 {-! for StrictnessMark derive: Binary !-}
55 {-! for Activation derive: Binary !-}
56
57 -- NewDemand
58 {-! for Demand derive: Binary !-}
59 {-! for Demands derive: Binary !-}
60 {-! for DmdResult derive: Binary !-}
61 {-! for StrictSig derive: Binary !-}
62
63 -- Class
64 {-! for DefMeth derive: Binary !-}
65
66 -- HsTypes
67 {-! for HsPred derive: Binary !-}
68 {-! for HsType derive: Binary !-}
69 {-! for TupCon derive: Binary !-}
70 {-! for HsTyVarBndr derive: Binary !-}
71
72 -- HsCore
73 {-! for UfExpr derive: Binary !-}
74 {-! for UfConAlt derive: Binary !-}
75 {-! for UfBinding derive: Binary !-}
76 {-! for UfBinder derive: Binary !-}
77 {-! for HsIdInfo derive: Binary !-}
78 {-! for UfNote derive: Binary !-}
79
80 -- HsDecls
81 {-! for ConDetails derive: Binary !-}
82 {-! for BangType derive: Binary !-}
83
84 -- CostCentre
85 {-! for IsCafCC derive: Binary !-}
86 {-! for IsDupdCC derive: Binary !-}
87 {-! for CostCentre derive: Binary !-}
88
89
90
91 -- ---------------------------------------------------------------------------
92 -- Reading a binary interface into ParsedIface
93
94 instance Binary ModIface where
95    put_ bh (ModIface {
96                  mi_module    = mod,
97                  mi_boot      = is_boot,
98                  mi_mod_vers  = mod_vers,
99                  mi_package   = _, -- we ignore the package on output
100                  mi_orphan    = orphan,
101                  mi_deps      = deps,
102                  mi_usages    = usages,
103                  mi_exports   = exports,
104                  mi_exp_vers  = exp_vers,
105                  mi_fixities  = fixities,
106                  mi_deprecs   = deprecs,
107                  mi_decls     = decls,
108                  mi_insts     = insts,
109                  mi_rules     = rules,
110                  mi_rule_vers = rule_vers }) = do
111         put_ bh (show opt_HiVersion)
112         build_tag <- readIORef v_Build_tag
113         put  bh build_tag
114         put_ bh (WORD_SIZE_IN_BITS :: Word8)
115         put_ bh mod
116         put_ bh is_boot
117         put_ bh mod_vers
118         put_ bh orphan
119         lazyPut bh deps
120         lazyPut bh usages
121         put_ bh exports
122         put_ bh exp_vers
123         put_ bh fixities
124         lazyPut bh deprecs
125         put_ bh decls
126         put_ bh insts
127         lazyPut bh rules
128         put_ bh rule_vers
129
130    get bh = do
131         check_ver  <- get bh
132         let our_ver = show opt_HiVersion
133         when (check_ver /= our_ver) $
134            -- use userError because this will be caught by readIface
135            -- which will emit an error msg containing the iface module name.
136            throwDyn (ProgramError (
137                 "mismatched interface file versions: expected "
138                 ++ our_ver ++ ", found " ++ check_ver))
139
140         check_way <- get bh
141         ignore_way <- readIORef v_IgnoreHiWay
142         build_tag <- readIORef v_Build_tag
143         when (not ignore_way && check_way /= build_tag) $
144            -- use userError because this will be caught by readIface
145            -- which will emit an error msg containing the iface module name.
146            throwDyn (ProgramError (
147                 "mismatched interface file ways: expected "
148                 ++ build_tag ++ ", found " ++ check_way))
149
150         check_ws <- get bh
151         let our_ws = WORD_SIZE_IN_BITS :: Word8
152         when (check_ws /= our_ws) $
153            -- use userError because this will be caught by readIface
154            -- which will emit an error msg containing the iface module name.
155            throwDyn (ProgramError (
156                 "mismatched word size: expected "
157                 ++ show our_ws ++ ", found " ++ show check_ws))
158
159         mod_name  <- get bh
160         is_boot   <- get bh
161         mod_vers  <- get bh
162         orphan    <- get bh
163         deps      <- lazyGet bh
164         usages    <- {-# SCC "bin_usages" #-} lazyGet bh
165         exports   <- {-# SCC "bin_exports" #-} get bh
166         exp_vers  <- get bh
167         fixities  <- {-# SCC "bin_fixities" #-} get bh
168         deprecs   <- {-# SCC "bin_deprecs" #-} lazyGet bh
169         decls     <- {-# SCC "bin_tycldecls" #-} get bh
170         insts     <- {-# SCC "bin_insts" #-} get bh
171         rules     <- {-# SCC "bin_rules" #-} lazyGet bh
172         rule_vers <- get bh
173         return (ModIface {
174                  mi_package   = HomePackage, -- to be filled in properly later
175                  mi_module    = mod_name,
176                  mi_boot      = is_boot,
177                  mi_mod_vers  = mod_vers,
178                  mi_orphan    = orphan,
179                  mi_deps      = deps,
180                  mi_usages    = usages,
181                  mi_exports   = exports,
182                  mi_exp_vers  = exp_vers,
183                  mi_fixities  = fixities,
184                  mi_deprecs   = deprecs,
185                  mi_decls     = decls,
186                  mi_globals   = Nothing,
187                  mi_insts     = insts,
188                  mi_rules     = rules,
189                  mi_rule_vers = rule_vers,
190                         -- And build the cached values
191                  mi_dep_fn = mkIfaceDepCache deprecs,
192                  mi_fix_fn = mkIfaceFixCache fixities,
193                  mi_ver_fn = mkIfaceVerCache decls })
194
195 GLOBAL_VAR(v_IgnoreHiWay, False, Bool)
196
197 -------------------------------------------------------------------------
198 --              Types from: HscTypes
199 -------------------------------------------------------------------------
200
201 instance Binary Dependencies where
202     put_ bh deps = do put_ bh (dep_mods deps)
203                       put_ bh (dep_pkgs deps)
204                       put_ bh (dep_orphs deps)
205
206     get bh = do ms <- get bh 
207                 ps <- get bh
208                 os <- get bh
209                 return (Deps { dep_mods = ms, dep_pkgs = ps, dep_orphs = os })
210
211 instance (Binary name) => Binary (GenAvailInfo name) where
212     put_ bh (Avail aa) = do
213             putByte bh 0
214             put_ bh aa
215     put_ bh (AvailTC ab ac) = do
216             putByte bh 1
217             put_ bh ab
218             put_ bh ac
219     get bh = do
220             h <- getByte bh
221             case h of
222               0 -> do aa <- get bh
223                       return (Avail aa)
224               _ -> do ab <- get bh
225                       ac <- get bh
226                       return (AvailTC ab ac)
227
228 instance Binary Usage where
229     put_ bh usg = do 
230         put_ bh (usg_name     usg)
231         put_ bh (usg_mod      usg)
232         put_ bh (usg_exports  usg)
233         put_ bh (usg_entities usg)
234         put_ bh (usg_rules    usg)
235
236     get bh = do
237         nm    <- get bh
238         mod   <- get bh
239         exps  <- get bh
240         ents  <- get bh
241         rules <- get bh
242         return (Usage { usg_name = nm, usg_mod = mod,
243                         usg_exports = exps, usg_entities = ents,
244                         usg_rules = rules })
245
246 instance Binary a => Binary (Deprecs a) where
247     put_ bh NoDeprecs     = putByte bh 0
248     put_ bh (DeprecAll t) = do
249             putByte bh 1
250             put_ bh t
251     put_ bh (DeprecSome ts) = do
252             putByte bh 2
253             put_ bh ts
254
255     get bh = do
256             h <- getByte bh
257             case h of
258               0 -> return NoDeprecs
259               1 -> do aa <- get bh
260                       return (DeprecAll aa)
261               _ -> do aa <- get bh
262                       return (DeprecSome aa)
263
264 -------------------------------------------------------------------------
265 --              Types from: BasicTypes
266 -------------------------------------------------------------------------
267
268 instance Binary Activation where
269     put_ bh NeverActive = do
270             putByte bh 0
271     put_ bh AlwaysActive = do
272             putByte bh 1
273     put_ bh (ActiveBefore aa) = do
274             putByte bh 2
275             put_ bh aa
276     put_ bh (ActiveAfter ab) = do
277             putByte bh 3
278             put_ bh ab
279     get bh = do
280             h <- getByte bh
281             case h of
282               0 -> do return NeverActive
283               1 -> do return AlwaysActive
284               2 -> do aa <- get bh
285                       return (ActiveBefore aa)
286               _ -> do ab <- get bh
287                       return (ActiveAfter ab)
288
289 instance Binary StrictnessMark where
290     put_ bh MarkedStrict = do
291             putByte bh 0
292     put_ bh MarkedUnboxed = do
293             putByte bh 1
294     put_ bh NotMarkedStrict = do
295             putByte bh 2
296     get bh = do
297             h <- getByte bh
298             case h of
299               0 -> do return MarkedStrict
300               1 -> do return MarkedUnboxed
301               _ -> do return NotMarkedStrict
302
303 instance Binary Boxity where
304     put_ bh Boxed = do
305             putByte bh 0
306     put_ bh Unboxed = do
307             putByte bh 1
308     get bh = do
309             h <- getByte bh
310             case h of
311               0 -> do return Boxed
312               _ -> do return Unboxed
313
314 instance Binary TupCon where
315     put_ bh (TupCon ab ac) = do
316             put_ bh ab
317             put_ bh ac
318     get bh = do
319           ab <- get bh
320           ac <- get bh
321           return (TupCon ab ac)
322
323 instance Binary RecFlag where
324     put_ bh Recursive = do
325             putByte bh 0
326     put_ bh NonRecursive = do
327             putByte bh 1
328     get bh = do
329             h <- getByte bh
330             case h of
331               0 -> do return Recursive
332               _ -> do return NonRecursive
333
334 instance Binary DefMeth where
335     put_ bh NoDefMeth  = putByte bh 0
336     put_ bh DefMeth    = putByte bh 1
337     put_ bh GenDefMeth = putByte bh 2
338     get bh = do
339             h <- getByte bh
340             case h of
341               0 -> return NoDefMeth
342               1 -> return DefMeth
343               _ -> return GenDefMeth
344
345 instance Binary FixityDirection where
346     put_ bh InfixL = do
347             putByte bh 0
348     put_ bh InfixR = do
349             putByte bh 1
350     put_ bh InfixN = do
351             putByte bh 2
352     get bh = do
353             h <- getByte bh
354             case h of
355               0 -> do return InfixL
356               1 -> do return InfixR
357               _ -> do return InfixN
358
359 instance Binary Fixity where
360     put_ bh (Fixity aa ab) = do
361             put_ bh aa
362             put_ bh ab
363     get bh = do
364           aa <- get bh
365           ab <- get bh
366           return (Fixity aa ab)
367
368 instance (Binary name) => Binary (IPName name) where
369     put_ bh (Dupable aa) = do
370             putByte bh 0
371             put_ bh aa
372     put_ bh (Linear ab) = do
373             putByte bh 1
374             put_ bh ab
375     get bh = do
376             h <- getByte bh
377             case h of
378               0 -> do aa <- get bh
379                       return (Dupable aa)
380               _ -> do ab <- get bh
381                       return (Linear ab)
382
383 -------------------------------------------------------------------------
384 --              Types from: Demand
385 -------------------------------------------------------------------------
386
387 instance Binary DmdType where
388         -- Ignore DmdEnv when spitting out the DmdType
389   put bh (DmdType _ ds dr) = do p <- put bh ds; put bh dr; return (castBin p)
390   get bh = do ds <- get bh; dr <- get bh; return (DmdType emptyVarEnv ds dr)
391
392 instance Binary Demand where
393     put_ bh Top = do
394             putByte bh 0
395     put_ bh Abs = do
396             putByte bh 1
397     put_ bh (Call aa) = do
398             putByte bh 2
399             put_ bh aa
400     put_ bh (Eval ab) = do
401             putByte bh 3
402             put_ bh ab
403     put_ bh (Defer ac) = do
404             putByte bh 4
405             put_ bh ac
406     put_ bh (Box ad) = do
407             putByte bh 5
408             put_ bh ad
409     put_ bh Bot = do
410             putByte bh 6
411     get bh = do
412             h <- getByte bh
413             case h of
414               0 -> do return Top
415               1 -> do return Abs
416               2 -> do aa <- get bh
417                       return (Call aa)
418               3 -> do ab <- get bh
419                       return (Eval ab)
420               4 -> do ac <- get bh
421                       return (Defer ac)
422               5 -> do ad <- get bh
423                       return (Box ad)
424               _ -> do return Bot
425
426 instance Binary Demands where
427     put_ bh (Poly aa) = do
428             putByte bh 0
429             put_ bh aa
430     put_ bh (Prod ab) = do
431             putByte bh 1
432             put_ bh ab
433     get bh = do
434             h <- getByte bh
435             case h of
436               0 -> do aa <- get bh
437                       return (Poly aa)
438               _ -> do ab <- get bh
439                       return (Prod ab)
440
441 instance Binary DmdResult where
442     put_ bh TopRes = do
443             putByte bh 0
444     put_ bh RetCPR = do
445             putByte bh 1
446     put_ bh BotRes = do
447             putByte bh 2
448     get bh = do
449             h <- getByte bh
450             case h of
451               0 -> do return TopRes
452               1 -> do return RetCPR     -- Really use RetCPR even if -fcpr-off
453                                         -- The wrapper was generated for CPR in 
454                                         -- the imported module!
455               _ -> do return BotRes
456
457 instance Binary StrictSig where
458     put_ bh (StrictSig aa) = do
459             put_ bh aa
460     get bh = do
461           aa <- get bh
462           return (StrictSig aa)
463
464
465 -------------------------------------------------------------------------
466 --              Types from: CostCentre
467 -------------------------------------------------------------------------
468
469 instance Binary IsCafCC where
470     put_ bh CafCC = do
471             putByte bh 0
472     put_ bh NotCafCC = do
473             putByte bh 1
474     get bh = do
475             h <- getByte bh
476             case h of
477               0 -> do return CafCC
478               _ -> do return NotCafCC
479
480 instance Binary IsDupdCC where
481     put_ bh OriginalCC = do
482             putByte bh 0
483     put_ bh DupdCC = do
484             putByte bh 1
485     get bh = do
486             h <- getByte bh
487             case h of
488               0 -> do return OriginalCC
489               _ -> do return DupdCC
490
491 instance Binary CostCentre where
492     put_ bh NoCostCentre = do
493             putByte bh 0
494     put_ bh (NormalCC aa ab ac ad) = do
495             putByte bh 1
496             put_ bh aa
497             put_ bh ab
498             put_ bh ac
499             put_ bh ad
500     put_ bh (AllCafsCC ae) = do
501             putByte bh 2
502             put_ bh ae
503     get bh = do
504             h <- getByte bh
505             case h of
506               0 -> do return NoCostCentre
507               1 -> do aa <- get bh
508                       ab <- get bh
509                       ac <- get bh
510                       ad <- get bh
511                       return (NormalCC aa ab ac ad)
512               _ -> do ae <- get bh
513                       return (AllCafsCC ae)
514
515 -------------------------------------------------------------------------
516 --              IfaceTypes and friends
517 -------------------------------------------------------------------------
518
519 instance Binary IfaceExtName where
520     put_ bh (ExtPkg mod occ) = do
521             putByte bh 0
522             put_ bh mod
523             put_ bh occ
524     put_ bh (HomePkg mod occ vers) = do
525             putByte bh 1
526             put_ bh mod
527             put_ bh occ
528             put_ bh vers
529     put_ bh (LocalTop occ) = do
530             putByte bh 2
531             put_ bh occ
532     put_ bh (LocalTopSub occ _) = do    -- Write LocalTopSub just like LocalTop
533             putByte bh 2
534             put_ bh occ
535
536     get bh = do
537             h <- getByte bh
538             case h of
539               0 -> do mod <- get bh
540                       occ <- get bh
541                       return (ExtPkg mod occ)
542               1 -> do mod <- get bh
543                       occ <- get bh
544                       vers <- get bh
545                       return (HomePkg mod occ vers)
546               _ -> do occ <- get bh
547                       return (LocalTop occ)
548
549 instance Binary IfaceBndr where
550     put_ bh (IfaceIdBndr aa) = do
551             putByte bh 0
552             put_ bh aa
553     put_ bh (IfaceTvBndr ab) = do
554             putByte bh 1
555             put_ bh ab
556     get bh = do
557             h <- getByte bh
558             case h of
559               0 -> do aa <- get bh
560                       return (IfaceIdBndr aa)
561               _ -> do ab <- get bh
562                       return (IfaceTvBndr ab)
563
564 instance Binary Kind where
565     put_ bh LiftedTypeKind   = putByte bh 0
566     put_ bh UnliftedTypeKind = putByte bh 1
567     put_ bh OpenTypeKind     = putByte bh 2
568     put_ bh ArgTypeKind      = putByte bh 3
569     put_ bh UbxTupleKind     = putByte bh 4
570     put_ bh (FunKind k1 k2)  = do 
571             putByte bh 5
572             put_ bh k1
573             put_ bh k2
574     put_ bh (KindVar kv) = pprPanic "BinIface.put_: kind var" (ppr kv)
575
576     get bh = do
577             h <- getByte bh
578             case h of
579               0 -> return LiftedTypeKind 
580               1 -> return UnliftedTypeKind
581               2 -> return OpenTypeKind
582               3 -> return ArgTypeKind
583               4 -> return UbxTupleKind
584               _ -> do k1 <- get bh
585                       k2 <- get bh
586                       return (FunKind k1 k2)
587
588 instance Binary IfaceType where
589     put_ bh (IfaceForAllTy aa ab) = do
590             putByte bh 0
591             put_ bh aa
592             put_ bh ab
593     put_ bh (IfaceTyVar ad) = do
594             putByte bh 1
595             put_ bh ad
596     put_ bh (IfaceAppTy ae af) = do
597             putByte bh 2
598             put_ bh ae
599             put_ bh af
600     put_ bh (IfaceFunTy ag ah) = do
601             putByte bh 3
602             put_ bh ag
603             put_ bh ah
604     put_ bh (IfacePredTy aq) = do
605             putByte bh 5
606             put_ bh aq
607
608         -- Simple compression for common cases of TyConApp
609     put_ bh (IfaceTyConApp IfaceIntTc  [])   = putByte bh 6
610     put_ bh (IfaceTyConApp IfaceCharTc [])   = putByte bh 7
611     put_ bh (IfaceTyConApp IfaceBoolTc [])   = putByte bh 8
612     put_ bh (IfaceTyConApp IfaceListTc [ty]) = do { putByte bh 9; put_ bh ty }
613         -- Unit tuple and pairs
614     put_ bh (IfaceTyConApp (IfaceTupTc Boxed 0) [])      = putByte bh 10
615     put_ bh (IfaceTyConApp (IfaceTupTc Boxed 2) [t1,t2]) = do { putByte bh 11; put_ bh t1; put_ bh t2 }
616         -- Generic cases
617     put_ bh (IfaceTyConApp (IfaceTc tc) tys) = do { putByte bh 12; put_ bh tc; put_ bh tys }
618     put_ bh (IfaceTyConApp tc tys)           = do { putByte bh 13; put_ bh tc; put_ bh tys }
619
620     get bh = do
621             h <- getByte bh
622             case h of
623               0 -> do aa <- get bh
624                       ab <- get bh
625                       return (IfaceForAllTy aa ab)
626               1 -> do ad <- get bh
627                       return (IfaceTyVar ad)
628               2 -> do ae <- get bh
629                       af <- get bh
630                       return (IfaceAppTy ae af)
631               3 -> do ag <- get bh
632                       ah <- get bh
633                       return (IfaceFunTy ag ah)
634               5 -> do ap <- get bh
635                       return (IfacePredTy ap)
636
637                 -- Now the special cases for TyConApp
638               6 -> return (IfaceTyConApp IfaceIntTc [])
639               7 -> return (IfaceTyConApp IfaceCharTc [])
640               8 -> return (IfaceTyConApp IfaceBoolTc [])
641               9 -> do { ty <- get bh; return (IfaceTyConApp IfaceListTc [ty]) }
642               10 -> return (IfaceTyConApp (IfaceTupTc Boxed 0) [])
643               11 -> do { t1 <- get bh; t2 <- get bh; return (IfaceTyConApp (IfaceTupTc Boxed 2) [t1,t2]) }
644               12 -> do { tc <- get bh; tys <- get bh; return (IfaceTyConApp (IfaceTc tc) tys) }
645               _  -> do { tc <- get bh; tys <- get bh; return (IfaceTyConApp tc tys) }
646
647 instance Binary IfaceTyCon where
648         -- Int,Char,Bool can't show up here because they can't not be saturated
649    put_ bh IfaceListTc = putByte bh 1
650    put_ bh IfacePArrTc = putByte bh 2
651    put_ bh (IfaceTupTc bx ar) = do { putByte bh 3; put_ bh bx; put_ bh ar }
652    put_ bh tc = pprPanic "BinIface.put:" (ppr tc)       -- Dealt with by the IfaceType instance
653
654    get bh = do
655         h <- getByte bh
656         case h of
657           1 -> return IfaceListTc
658           2 -> return IfacePArrTc
659           _ -> do { bx <- get bh; ar <- get bh; return (IfaceTupTc bx ar) }
660
661 instance Binary IfacePredType where
662     put_ bh (IfaceClassP aa ab) = do
663             putByte bh 0
664             put_ bh aa
665             put_ bh ab
666     put_ bh (IfaceIParam ac ad) = do
667             putByte bh 1
668             put_ bh ac
669             put_ bh ad
670     get bh = do
671             h <- getByte bh
672             case h of
673               0 -> do aa <- get bh
674                       ab <- get bh
675                       return (IfaceClassP aa ab)
676               _ -> do ac <- get bh
677                       ad <- get bh
678                       return (IfaceIParam ac ad)
679
680 -------------------------------------------------------------------------
681 --              IfaceExpr and friends
682 -------------------------------------------------------------------------
683
684 instance Binary IfaceExpr where
685     put_ bh (IfaceLcl aa) = do
686             putByte bh 0
687             put_ bh aa
688     put_ bh (IfaceType ab) = do
689             putByte bh 1
690             put_ bh ab
691     put_ bh (IfaceTuple ac ad) = do
692             putByte bh 2
693             put_ bh ac
694             put_ bh ad
695     put_ bh (IfaceLam ae af) = do
696             putByte bh 3
697             put_ bh ae
698             put_ bh af
699     put_ bh (IfaceApp ag ah) = do
700             putByte bh 4
701             put_ bh ag
702             put_ bh ah
703 -- gaw 2004
704     put_ bh (IfaceCase ai aj al ak) = do
705             putByte bh 5
706             put_ bh ai
707             put_ bh aj
708 -- gaw 2004
709             put_ bh al
710             put_ bh ak
711     put_ bh (IfaceLet al am) = do
712             putByte bh 6
713             put_ bh al
714             put_ bh am
715     put_ bh (IfaceNote an ao) = do
716             putByte bh 7
717             put_ bh an
718             put_ bh ao
719     put_ bh (IfaceLit ap) = do
720             putByte bh 8
721             put_ bh ap
722     put_ bh (IfaceFCall as at) = do
723             putByte bh 9
724             put_ bh as
725             put_ bh at
726     put_ bh (IfaceExt aa) = do
727             putByte bh 10
728             put_ bh aa
729     get bh = do
730             h <- getByte bh
731             case h of
732               0 -> do aa <- get bh
733                       return (IfaceLcl aa)
734               1 -> do ab <- get bh
735                       return (IfaceType ab)
736               2 -> do ac <- get bh
737                       ad <- get bh
738                       return (IfaceTuple ac ad)
739               3 -> do ae <- get bh
740                       af <- get bh
741                       return (IfaceLam ae af)
742               4 -> do ag <- get bh
743                       ah <- get bh
744                       return (IfaceApp ag ah)
745               5 -> do ai <- get bh
746                       aj <- get bh
747 -- gaw 2004
748                       al <- get bh                   
749                       ak <- get bh
750 -- gaw 2004
751                       return (IfaceCase ai aj al ak)
752               6 -> do al <- get bh
753                       am <- get bh
754                       return (IfaceLet al am)
755               7 -> do an <- get bh
756                       ao <- get bh
757                       return (IfaceNote an ao)
758               8 -> do ap <- get bh
759                       return (IfaceLit ap)
760               9 -> do as <- get bh
761                       at <- get bh
762                       return (IfaceFCall as at)
763               _ -> do aa <- get bh
764                       return (IfaceExt aa)
765
766 instance Binary IfaceConAlt where
767     put_ bh IfaceDefault = do
768             putByte bh 0
769     put_ bh (IfaceDataAlt aa) = do
770             putByte bh 1
771             put_ bh aa
772     put_ bh (IfaceTupleAlt ab) = do
773             putByte bh 2
774             put_ bh ab
775     put_ bh (IfaceLitAlt ac) = do
776             putByte bh 3
777             put_ bh ac
778     get bh = do
779             h <- getByte bh
780             case h of
781               0 -> do return IfaceDefault
782               1 -> do aa <- get bh
783                       return (IfaceDataAlt aa)
784               2 -> do ab <- get bh
785                       return (IfaceTupleAlt ab)
786               _ -> do ac <- get bh
787                       return (IfaceLitAlt ac)
788
789 instance Binary IfaceBinding where
790     put_ bh (IfaceNonRec aa ab) = do
791             putByte bh 0
792             put_ bh aa
793             put_ bh ab
794     put_ bh (IfaceRec ac) = do
795             putByte bh 1
796             put_ bh ac
797     get bh = do
798             h <- getByte bh
799             case h of
800               0 -> do aa <- get bh
801                       ab <- get bh
802                       return (IfaceNonRec aa ab)
803               _ -> do ac <- get bh
804                       return (IfaceRec ac)
805
806 instance Binary IfaceIdInfo where
807     put_ bh NoInfo = putByte bh 0
808     put_ bh (HasInfo i) = do
809             putByte bh 1
810             lazyPut bh i
811
812     get bh = do
813             h <- getByte bh
814             case h of
815               0 -> return NoInfo
816               _ -> do info <- lazyGet bh
817                       return (HasInfo info)
818
819 instance Binary IfaceInfoItem where
820     put_ bh (HsArity aa) = do
821             putByte bh 0
822             put_ bh aa
823     put_ bh (HsStrictness ab) = do
824             putByte bh 1
825             put_ bh ab
826     put_ bh (HsUnfold ac ad) = do
827             putByte bh 2
828             put_ bh ac
829             put_ bh ad
830     put_ bh HsNoCafRefs = do
831             putByte bh 3
832     put_ bh (HsWorker ae af) = do
833             putByte bh 4
834             put_ bh ae
835             put_ bh af
836     get bh = do
837             h <- getByte bh
838             case h of
839               0 -> do aa <- get bh
840                       return (HsArity aa)
841               1 -> do ab <- get bh
842                       return (HsStrictness ab)
843               2 -> do ac <- get bh
844                       ad <- get bh
845                       return (HsUnfold ac ad)
846               3 -> do return HsNoCafRefs
847               _ -> do ae <- get bh
848                       af <- get bh
849                       return (HsWorker ae af)
850
851 instance Binary IfaceNote where
852     put_ bh (IfaceSCC aa) = do
853             putByte bh 0
854             put_ bh aa
855     put_ bh (IfaceCoerce ab) = do
856             putByte bh 1
857             put_ bh ab
858     put_ bh IfaceInlineCall = do
859             putByte bh 2
860     put_ bh IfaceInlineMe = do
861             putByte bh 3
862     put_ bh (IfaceCoreNote s) = do
863             putByte bh 4
864             put_ bh s
865     get bh = do
866             h <- getByte bh
867             case h of
868               0 -> do aa <- get bh
869                       return (IfaceSCC aa)
870               1 -> do ab <- get bh
871                       return (IfaceCoerce ab)
872               2 -> do return IfaceInlineCall
873               3 -> do return IfaceInlineMe
874               _ -> do ac <- get bh
875                       return (IfaceCoreNote ac)
876
877
878 -------------------------------------------------------------------------
879 --              IfaceDecl and friends
880 -------------------------------------------------------------------------
881
882 instance Binary IfaceDecl where
883     put_ bh (IfaceId name ty idinfo) = do
884             putByte bh 0
885             put_ bh name
886             put_ bh ty
887             put_ bh idinfo
888     put_ bh (IfaceForeign ae af) = 
889         error "Binary.put_(IfaceDecl): IfaceForeign"
890     put_ bh (IfaceData a1 a2 a3 a4 a5 a6) = do
891             putByte bh 2
892             put_ bh a1
893             put_ bh a2
894             put_ bh a3
895             put_ bh a4
896             put_ bh a5
897             put_ bh a6
898
899     put_ bh (IfaceSyn aq ar as at) = do
900             putByte bh 3
901             put_ bh aq
902             put_ bh ar
903             put_ bh as
904             put_ bh at
905     put_ bh (IfaceClass a1 a2 a3 a4 a5 a6 a7) = do
906             putByte bh 4
907             put_ bh a1
908             put_ bh a2
909             put_ bh a3
910             put_ bh a4
911             put_ bh a5
912             put_ bh a6
913             put_ bh a7
914     get bh = do
915             h <- getByte bh
916             case h of
917               0 -> do name   <- get bh
918                       ty     <- get bh
919                       idinfo <- get bh
920                       return (IfaceId name ty idinfo)
921               1 -> error "Binary.get(TyClDecl): ForeignType"
922               2 -> do
923                     a1 <- get bh
924                     a2 <- get bh
925                     a3 <- get bh
926                     a4 <- get bh
927                     a5 <- get bh
928                     a6 <- get bh
929                     return (IfaceData a1 a2 a3 a4 a5 a6)
930               3 -> do
931                     aq <- get bh
932                     ar <- get bh
933                     as <- get bh
934                     at <- get bh
935                     return (IfaceSyn aq ar as at)
936               _ -> do
937                     a1 <- get bh
938                     a2 <- get bh
939                     a3 <- get bh
940                     a4 <- get bh
941                     a5 <- get bh
942                     a6 <- get bh
943                     a7 <- get bh
944                     return (IfaceClass a1 a2 a3 a4 a5 a6 a7)
945
946 instance Binary IfaceInst where
947     put_ bh (IfaceInst ty dfun) = do
948             put_ bh ty
949             put_ bh dfun
950     get bh = do ty   <- get bh
951                 dfun <- get bh
952                 return (IfaceInst ty dfun)
953
954 instance Binary IfaceConDecls where
955     put_ bh IfAbstractTyCon = putByte bh 0
956     put_ bh (IfDataTyCon st cs) = do { putByte bh 1
957                                      ; put_ bh st
958                                      ; put_ bh cs }
959     put_ bh (IfNewTyCon c)  = do { putByte bh 2
960                                   ; put_ bh c }
961     get bh = do
962             h <- getByte bh
963             case h of
964               0 -> return IfAbstractTyCon
965               1 -> do st <- get bh
966                       cs <- get bh
967                       return (IfDataTyCon st cs)
968               _ -> do aa <- get bh
969                       return (IfNewTyCon aa)
970
971 instance Binary IfaceConDecl where
972     put_ bh (IfVanillaCon a1 a2 a3 a4 a5) = do
973             putByte bh 0
974             put_ bh a1
975             put_ bh a2
976             put_ bh a3
977             put_ bh a4
978             put_ bh a5
979     put_ bh (IfGadtCon a1 a2 a3 a4 a5 a6) = do
980             putByte bh 1
981             put_ bh a1
982             put_ bh a2
983             put_ bh a3
984             put_ bh a4
985             put_ bh a5
986             put_ bh a6
987     get bh = do
988             h <- getByte bh
989             case h of
990               0 -> do a1 <- get bh
991                       a2 <- get bh
992                       a3 <- get bh            
993                       a4 <- get bh
994                       a5 <- get bh
995                       return (IfVanillaCon a1 a2 a3 a4 a5)
996               _ -> do a1 <- get bh
997                       a2 <- get bh
998                       a3 <- get bh            
999                       a4 <- get bh
1000                       a5 <- get bh
1001                       a6 <- get bh
1002                       return (IfGadtCon a1 a2 a3 a4 a5 a6)
1003
1004 instance Binary IfaceClassOp where
1005    put_ bh (IfaceClassOp n def ty) = do 
1006         put_ bh n 
1007         put_ bh def     
1008         put_ bh ty
1009    get bh = do
1010         n <- get bh
1011         def <- get bh
1012         ty <- get bh
1013         return (IfaceClassOp n def ty)
1014
1015 instance Binary IfaceRule where
1016         -- IfaceBuiltinRule should not happen here
1017     put_ bh (IfaceRule a1 a2 a3 a4 a5 a6) = do
1018             put_ bh a1
1019             put_ bh a2
1020             put_ bh a3
1021             put_ bh a4
1022             put_ bh a5
1023             put_ bh a6
1024     get bh = do
1025             a1 <- get bh
1026             a2 <- get bh
1027             a3 <- get bh
1028             a4 <- get bh
1029             a5 <- get bh
1030             a6 <- get bh
1031             return (IfaceRule a1 a2 a3 a4 a5 a6)
1032
1033