summaryrefslogtreecommitdiff
path: root/compiler/hsSyn/HsDecls.lhs
blob: 0038ebed0a59d5d8b0e34ae03de1a9998b50d3e0 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
407
408
409
410
411
412
413
414
415
416
417
418
419
420
421
422
423
424
425
426
427
428
429
430
431
432
433
434
435
436
437
438
439
440
441
442
443
444
445
446
447
448
449
450
451
452
453
454
455
456
457
458
459
460
461
462
463
464
465
466
467
468
469
470
471
472
473
474
475
476
477
478
479
480
481
482
483
484
485
486
487
488
489
490
491
492
493
494
495
496
497
498
499
500
501
502
503
504
505
506
507
508
509
510
511
512
513
514
515
516
517
518
519
520
521
522
523
524
525
526
527
528
529
530
531
532
533
534
535
536
537
538
539
540
541
542
543
544
545
546
547
548
549
550
551
552
553
554
555
556
557
558
559
560
561
562
563
564
565
566
567
568
569
570
571
572
573
574
575
576
577
578
579
580
581
582
583
584
585
586
587
588
589
590
591
592
593
594
595
596
597
598
599
600
601
602
603
604
605
606
607
608
609
610
611
612
613
614
615
616
617
618
619
620
621
622
623
624
625
626
627
628
629
630
631
632
633
634
635
636
637
638
639
640
641
642
643
644
645
646
647
648
649
650
651
652
653
654
655
656
657
658
659
660
661
662
663
664
665
666
667
668
669
670
671
672
673
674
675
676
677
678
679
680
681
682
683
684
685
686
687
688
689
690
691
692
693
694
695
696
697
698
699
700
701
702
703
704
705
706
707
708
709
710
711
712
713
714
715
716
717
718
719
720
721
722
723
724
725
726
727
728
729
730
731
732
733
734
735
736
737
738
739
740
741
742
743
744
745
746
747
748
749
750
751
752
753
754
755
756
757
758
759
760
761
762
763
764
765
766
767
768
769
770
771
772
773
774
775
776
777
778
779
780
781
782
783
784
785
786
787
788
789
790
791
792
793
794
795
796
797
798
799
800
801
802
803
804
805
806
807
808
809
810
811
812
813
814
815
816
817
818
819
820
821
822
823
824
825
826
827
828
829
830
831
832
833
834
835
836
837
838
839
840
841
842
843
844
845
846
847
848
849
850
851
852
853
854
855
856
857
858
859
860
861
862
863
864
865
866
867
868
869
870
871
872
873
874
875
876
877
878
879
880
881
882
883
884
885
886
887
888
889
890
891
892
893
894
895
896
897
898
899
900
901
902
903
904
905
906
907
908
909
910
911
912
913
914
915
916
917
918
919
920
921
922
923
924
925
926
927
928
929
930
931
932
933
934
935
936
937
938
939
940
941
942
943
944
945
946
947
948
949
950
951
952
953
954
955
956
957
958
959
960
961
962
963
964
965
966
967
968
969
970
971
972
973
974
975
976
977
978
979
980
981
982
983
984
985
986
987
988
989
990
991
992
993
994
995
996
997
998
999
1000
1001
1002
1003
1004
1005
1006
1007
1008
1009
1010
1011
1012
1013
1014
1015
1016
1017
1018
1019
1020
1021
1022
1023
1024
1025
1026
1027
1028
1029
1030
1031
1032
1033
1034
1035
1036
1037
1038
1039
1040
1041
1042
1043
1044
1045
1046
1047
1048
1049
1050
1051
1052
1053
1054
1055
1056
1057
1058
1059
1060
1061
1062
1063
1064
1065
1066
1067
1068
1069
1070
1071
1072
1073
1074
1075
1076
1077
1078
1079
1080
1081
1082
1083
1084
1085
1086
1087
1088
1089
1090
1091
1092
1093
1094
1095
1096
1097
1098
1099
1100
%
% (c) The University of Glasgow 2006
% (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
%



\begin{code}
{-# OPTIONS -fno-warn-incomplete-patterns #-}
-- The above warning supression flag is a temporary kludge.
-- While working on this module you are encouraged to remove it and fix
-- any warnings in the module. See
--     http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#Warnings
-- for details
{-# LANGUAGE DeriveDataTypeable #-}

-- | Abstract syntax of global declarations.
--
-- Definitions for: @TyDecl@ and @ConDecl@, @ClassDecl@,
-- @InstDecl@, @DefaultDecl@ and @ForeignDecl@.
module HsDecls (
  -- * Toplevel declarations
  HsDecl(..), LHsDecl,
  -- ** Class or type declarations
  TyClDecl(..), LTyClDecl,
  isClassDecl, isSynDecl, isDataDecl, isTypeDecl, isFamilyDecl,
  isFamInstDecl, tcdName, tyClDeclNames, tyClDeclTyVars,
  countTyClDecls,
  -- ** Instance declarations
  InstDecl(..), LInstDecl, NewOrData(..), FamilyFlavour(..),
  instDeclATs,
  -- ** Standalone deriving declarations
  DerivDecl(..), LDerivDecl,
  -- ** @RULE@ declarations
  RuleDecl(..), LRuleDecl, RuleBndr(..),
  collectRuleBndrSigTys,
  -- ** @default@ declarations
  DefaultDecl(..), LDefaultDecl,
  -- ** Top-level template haskell splice
  SpliceDecl(..),
  -- ** Foreign function interface declarations
  ForeignDecl(..), LForeignDecl, ForeignImport(..), ForeignExport(..),
  CImportSpec(..),
  -- ** Data-constructor declarations
  ConDecl(..), LConDecl, ResType(..), 
  HsConDeclDetails, hsConDeclArgTys, hsConDeclsNames,
  -- ** Document comments
  DocDecl(..), LDocDecl, docDeclDoc,
  -- ** Deprecations
  WarnDecl(..),  LWarnDecl,
  -- ** Annotations
  AnnDecl(..), LAnnDecl, 
  AnnProvenance(..), annProvenanceName_maybe, modifyAnnProvenanceNameM,

  -- * Grouping
  HsGroup(..),  emptyRdrGroup, emptyRnGroup, appendGroups
    ) where

-- friends:
import {-# SOURCE #-}	HsExpr( HsExpr, pprExpr )
	-- Because Expr imports Decls via HsBracket

import HsBinds
import HsPat
import HsTypes
import HsDoc
import NameSet
import {- Kind parts of -} Type
import BasicTypes
import ForeignCall

-- others:
import Class
import Outputable	
import Util
import SrcLoc
import FastString

import Control.Monad    ( liftM )
import Data.Data
import Data.Maybe       ( isJust )
\end{code}

%************************************************************************
%*									*
\subsection[HsDecl]{Declarations}
%*									*
%************************************************************************

\begin{code}
type LHsDecl id = Located (HsDecl id)

-- | A Haskell Declaration
data HsDecl id
  = TyClD	(TyClDecl id)     -- ^ A type or class declaration.
  | InstD	(InstDecl  id)    -- ^ An instance declaration.
  | DerivD      (DerivDecl id)
  | ValD	(HsBind id)
  | SigD	(Sig id)
  | DefD	(DefaultDecl id)
  | ForD        (ForeignDecl id)
  | WarningD	(WarnDecl id)
  | AnnD	(AnnDecl id)
  | RuleD	(RuleDecl id)
  | SpliceD	(SpliceDecl id)
  | DocD	(DocDecl)
  | QuasiQuoteD	(HsQuasiQuote id)
  deriving (Data, Typeable)


-- NB: all top-level fixity decls are contained EITHER
-- EITHER SigDs
-- OR     in the ClassDecls in TyClDs
--
-- The former covers
-- 	a) data constructors
-- 	b) class methods (but they can be also done in the
-- 		signatures of class decls)
--	c) imported functions (that have an IfacSig)
--	d) top level decls
--
-- The latter is for class methods only

-- | A 'HsDecl' is categorised into a 'HsGroup' before being
-- fed to the renamer.
data HsGroup id
  = HsGroup {
	hs_valds  :: HsValBinds id,
	hs_tyclds :: [LTyClDecl id],
	hs_instds :: [LInstDecl id],
        hs_derivds :: [LDerivDecl id],

	hs_fixds  :: [LFixitySig id],
		-- Snaffled out of both top-level fixity signatures,
		-- and those in class declarations

	hs_defds  :: [LDefaultDecl id],
	hs_fords  :: [LForeignDecl id],
	hs_warnds :: [LWarnDecl id],
	hs_annds   :: [LAnnDecl id],
	hs_ruleds :: [LRuleDecl id],

	hs_docs   :: [LDocDecl]
  } deriving (Data, Typeable)

emptyGroup, emptyRdrGroup, emptyRnGroup :: HsGroup a
emptyRdrGroup = emptyGroup { hs_valds = emptyValBindsIn }
emptyRnGroup  = emptyGroup { hs_valds = emptyValBindsOut }

emptyGroup = HsGroup { hs_tyclds = [], hs_instds = [], hs_derivds = [],
		       hs_fixds = [], hs_defds = [], hs_annds = [],
		       hs_fords = [], hs_warnds = [], hs_ruleds = [],
		       hs_valds = error "emptyGroup hs_valds: Can't happen",
                       hs_docs = [] }

appendGroups :: HsGroup a -> HsGroup a -> HsGroup a
appendGroups 
    HsGroup { 
	hs_valds  = val_groups1,
	hs_tyclds = tyclds1, 
	hs_instds = instds1,
        hs_derivds = derivds1,
	hs_fixds  = fixds1, 
	hs_defds  = defds1,
	hs_annds  = annds1,
	hs_fords  = fords1, 
	hs_warnds = warnds1,
	hs_ruleds = rulds1,
  hs_docs   = docs1 }
    HsGroup { 
	hs_valds  = val_groups2,
	hs_tyclds = tyclds2, 
	hs_instds = instds2,
        hs_derivds = derivds2,
	hs_fixds  = fixds2, 
	hs_defds  = defds2,
	hs_annds  = annds2,
	hs_fords  = fords2, 
	hs_warnds = warnds2,
	hs_ruleds = rulds2,
  hs_docs   = docs2 }
  = 
    HsGroup { 
	hs_valds  = val_groups1 `plusHsValBinds` val_groups2,
	hs_tyclds = tyclds1 ++ tyclds2, 
	hs_instds = instds1 ++ instds2,
        hs_derivds = derivds1 ++ derivds2,
	hs_fixds  = fixds1 ++ fixds2,
	hs_annds  = annds1 ++ annds2,
	hs_defds  = defds1 ++ defds2,
	hs_fords  = fords1 ++ fords2, 
	hs_warnds = warnds1 ++ warnds2,
	hs_ruleds = rulds1 ++ rulds2,
  hs_docs   = docs1  ++ docs2 }
\end{code}

\begin{code}
instance OutputableBndr name => Outputable (HsDecl name) where
    ppr (TyClD dcl)             = ppr dcl
    ppr (ValD binds)            = ppr binds
    ppr (DefD def)              = ppr def
    ppr (InstD inst)            = ppr inst
    ppr (DerivD deriv)          = ppr deriv
    ppr (ForD fd)               = ppr fd
    ppr (SigD sd)               = ppr sd
    ppr (RuleD rd)              = ppr rd
    ppr (WarningD wd)           = ppr wd
    ppr (AnnD ad)               = ppr ad
    ppr (SpliceD dd)            = ppr dd
    ppr (DocD doc)              = ppr doc
    ppr (QuasiQuoteD qq)        = ppr qq

instance OutputableBndr name => Outputable (HsGroup name) where
    ppr (HsGroup { hs_valds  = val_decls,
		   hs_tyclds = tycl_decls,
		   hs_instds = inst_decls,
                   hs_derivds = deriv_decls,
		   hs_fixds  = fix_decls,
		   hs_warnds = deprec_decls,
		   hs_annds  = ann_decls,
		   hs_fords  = foreign_decls,
		   hs_defds  = default_decls,
		   hs_ruleds = rule_decls })
	= vcat [ppr_ds fix_decls, ppr_ds default_decls, 
		ppr_ds deprec_decls, ppr_ds ann_decls,
		ppr_ds rule_decls,
		ppr val_decls,
		ppr_ds tycl_decls, ppr_ds inst_decls,
                ppr_ds deriv_decls,
		ppr_ds foreign_decls]
	where
	  ppr_ds [] = empty
	  ppr_ds ds = blankLine $$ vcat (map ppr ds)

data SpliceDecl id = SpliceDecl (Located (HsExpr id))	-- Top level splice
    deriving (Data, Typeable)

instance OutputableBndr name => Outputable (SpliceDecl name) where
   ppr (SpliceDecl e) = ptext (sLit "$") <> parens (pprExpr (unLoc e))
\end{code}


%************************************************************************
%*									*
\subsection[TyDecl]{@data@, @newtype@ or @type@ (synonym) type declaration}
%*									*
%************************************************************************

		--------------------------------
			THE NAMING STORY
		--------------------------------

Here is the story about the implicit names that go with type, class,
and instance decls.  It's a bit tricky, so pay attention!

"Implicit" (or "system") binders
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
  Each data type decl defines 
	a worker name for each constructor
	to-T and from-T convertors
  Each class decl defines
	a tycon for the class
	a data constructor for that tycon
	the worker for that constructor
	a selector for each superclass

All have occurrence names that are derived uniquely from their parent
declaration.

None of these get separate definitions in an interface file; they are
fully defined by the data or class decl.  But they may *occur* in
interface files, of course.  Any such occurrence must haul in the
relevant type or class decl.

Plan of attack:
 - Ensure they "point to" the parent data/class decl 
   when loading that decl from an interface file
   (See RnHiFiles.getSysBinders)

 - When typechecking the decl, we build the implicit TyCons and Ids.
   When doing so we look them up in the name cache (RnEnv.lookupSysName),
   to ensure correct module and provenance is set

These are the two places that we have to conjure up the magic derived
names.  (The actual magic is in OccName.mkWorkerOcc, etc.)

Default methods
~~~~~~~~~~~~~~~
 - Occurrence name is derived uniquely from the method name
   E.g. $dmmax

 - If there is a default method name at all, it's recorded in
   the ClassOpSig (in HsBinds), in the DefMeth field.
   (DefMeth is defined in Class.lhs)

Source-code class decls and interface-code class decls are treated subtly
differently, which has given me a great deal of confusion over the years.
Here's the deal.  (We distinguish the two cases because source-code decls
have (Just binds) in the tcdMeths field, whereas interface decls have Nothing.

In *source-code* class declarations:

 - When parsing, every ClassOpSig gets a DefMeth with a suitable RdrName
   This is done by RdrHsSyn.mkClassOpSigDM

 - The renamer renames it to a Name

 - During typechecking, we generate a binding for each $dm for 
   which there's a programmer-supplied default method:
	class Foo a where
	  op1 :: <type>
	  op2 :: <type>
	  op1 = ...
   We generate a binding for $dmop1 but not for $dmop2.
   The Class for Foo has a NoDefMeth for op2 and a DefMeth for op1.
   The Name for $dmop2 is simply discarded.

In *interface-file* class declarations:
  - When parsing, we see if there's an explicit programmer-supplied default method
    because there's an '=' sign to indicate it:
	class Foo a where
	  op1 = :: <type>	-- NB the '='
  	  op2   :: <type>
    We use this info to generate a DefMeth with a suitable RdrName for op1,
    and a NoDefMeth for op2
  - The interface file has a separate definition for $dmop1, with unfolding etc.
  - The renamer renames it to a Name.
  - The renamer treats $dmop1 as a free variable of the declaration, so that
    the binding for $dmop1 will be sucked in.  (See RnHsSyn.tyClDeclFVs)  
    This doesn't happen for source code class decls, because they *bind* the default method.

Dictionary functions
~~~~~~~~~~~~~~~~~~~~
Each instance declaration gives rise to one dictionary function binding.

The type checker makes up new source-code instance declarations
(e.g. from 'deriving' or generic default methods --- see
TcInstDcls.tcInstDecls1).  So we can't generate the names for
dictionary functions in advance (we don't know how many we need).

On the other hand for interface-file instance declarations, the decl
specifies the name of the dictionary function, and it has a binding elsewhere
in the interface file:
	instance {Eq Int} = dEqInt
	dEqInt :: {Eq Int} <pragma info>

So again we treat source code and interface file code slightly differently.

Source code:
  - Source code instance decls have a Nothing in the (Maybe name) field
    (see data InstDecl below)

  - The typechecker makes up a Local name for the dict fun for any source-code
    instance decl, whether it comes from a source-code instance decl, or whether
    the instance decl is derived from some other construct (e.g. 'deriving').

  - The occurrence name it chooses is derived from the instance decl (just for 
    documentation really) --- e.g. dNumInt.  Two dict funs may share a common
    occurrence name, but will have different uniques.  E.g.
	instance Foo [Int]  where ...
	instance Foo [Bool] where ...
    These might both be dFooList

  - The CoreTidy phase externalises the name, and ensures the occurrence name is
    unique (this isn't special to dict funs).  So we'd get dFooList and dFooList1.

  - We can take this relaxed approach (changing the occurrence name later) 
    because dict fun Ids are not captured in a TyCon or Class (unlike default
    methods, say).  Instead, they are kept separately in the InstEnv.  This
    makes it easy to adjust them after compiling a module.  (Once we've finished
    compiling that module, they don't change any more.)


Interface file code:
  - The instance decl gives the dict fun name, so the InstDecl has a (Just name)
    in the (Maybe name) field.

  - RnHsSyn.instDeclFVs treats the dict fun name as free in the decl, so that we
    suck in the dfun binding


\begin{code}
-- Representation of indexed types
-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-- Family kind signatures are represented by the variant `TyFamily'.  It
-- covers "type family", "newtype family", and "data family" declarations,
-- distinguished by the value of the field `tcdFlavour'.
--
-- Indexed types are represented by 'TyData' and 'TySynonym' using the field
-- 'tcdTyPats::Maybe [LHsType name]', with the following meaning:
--
--   * If it is 'Nothing', we have a *vanilla* data type declaration or type
--     synonym declaration and 'tcdVars' contains the type parameters of the
--     type constructor.
--
--   * If it is 'Just pats', we have the definition of an indexed type.  Then,
--     'pats' are type patterns for the type-indexes of the type constructor
--     and 'tcdTyVars' are the variables in those patterns.  Hence, the arity of
--     the indexed type (ie, the number of indexes) is 'length tcdTyPats' and
--     *not* 'length tcdVars'.
--
-- In both cases, 'tcdVars' collects all variables we need to quantify over.

type LTyClDecl name = Located (TyClDecl name)

-- | A type or class declaration.
data TyClDecl name
  = ForeignType { 
		tcdLName    :: Located name,
		tcdExtName  :: Maybe FastString
    }


  | -- | @type/data family T :: *->*@
    TyFamily {  tcdFlavour:: FamilyFlavour,	        -- type or data
		tcdLName  :: Located name,	        -- type constructor
		tcdTyVars :: [LHsTyVarBndr name],	-- type variables
		tcdKind   :: Maybe Kind			-- result kind
    }


  | -- | Declares a data type or newtype, giving its construcors
    -- @
    -- 	data/newtype T a = <constrs>
    --	data/newtype instance T [a] = <constrs>
    -- @
    TyData {	tcdND     :: NewOrData,
		tcdCtxt   :: LHsContext name,	 	-- ^ Context
		tcdLName  :: Located name,	 	-- ^ Type constructor

		tcdTyVars :: [LHsTyVarBndr name], 	-- ^ Type variables
			
		tcdTyPats :: Maybe [LHsType name],
                        -- ^ Type patterns.
                        --
			-- @Just [t1..tn]@ for @data instance T t1..tn = ...@
			--	in this case @tcdTyVars = fv( tcdTyPats )@.
			-- @Nothing@ for everything else.

		tcdKindSig:: Maybe Kind,
                        -- ^ Optional kind signature.
                        --
			-- @(Just k)@ for a GADT-style @data@, or @data
			-- instance@ decl with explicit kind sig

		tcdCons	  :: [LConDecl name],
                        -- ^ Data constructors
                        --
			-- For @data T a = T1 | T2 a@
                        --   the 'LConDecl's all have 'ResTyH98'.
			-- For @data T a where { T1 :: T a }@
                        --   the 'LConDecls' all have 'ResTyGADT'.

		tcdDerivs :: Maybe [LHsType name]
			-- ^ Derivings; @Nothing@ => not specified,
			-- 	        @Just []@ => derive exactly what is asked
                        --
			-- These "types" must be of form
                        -- @
			--	forall ab. C ty1 ty2
                        -- @
			-- Typically the foralls and ty args are empty, but they
			-- are non-empty for the newtype-deriving case
    }

  | TySynonym {	tcdLName  :: Located name,	        -- ^ type constructor
		tcdTyVars :: [LHsTyVarBndr name],	-- ^ type variables
		tcdTyPats :: Maybe [LHsType name],	-- ^ Type patterns
			-- See comments for tcdTyPats in TyData
			-- 'Nothing' => vanilla type synonym

		tcdSynRhs :: LHsType name	        -- ^ synonym expansion
    }

  | ClassDecl {	tcdCtxt    :: LHsContext name, 	 	-- ^ Context...
		tcdLName   :: Located name,	    	-- ^ Name of the class
		tcdTyVars  :: [LHsTyVarBndr name],	-- ^ Class type variables
		tcdFDs     :: [Located (FunDep name)],	-- ^ Functional deps
		tcdSigs    :: [LSig name],		-- ^ Methods' signatures
		tcdMeths   :: LHsBinds name,		-- ^ Default methods
		tcdATs	   :: [LTyClDecl name],		-- ^ Associated types; ie
							--   only 'TyFamily' and
							--   'TySynonym'; the
                                                        --   latter for defaults
		tcdDocs    :: [LDocDecl]		-- ^ Haddock docs
    }
  deriving (Data, Typeable)

data NewOrData
  = NewType			-- ^ @newtype Blah ...@
  | DataType			-- ^ @data Blah ...@
  deriving( Eq, Data, Typeable )		-- Needed because Demand derives Eq

data FamilyFlavour
  = TypeFamily			-- ^ @type family ...@
  | DataFamily	                -- ^ @data family ...@
  deriving (Data, Typeable)
\end{code}

Simple classifiers

\begin{code}
-- | @True@ <=> argument is a @data@\/@newtype@ or @data@\/@newtype instance@
-- declaration.
isDataDecl :: TyClDecl name -> Bool
isDataDecl (TyData {}) = True
isDataDecl _other      = False

-- | type or type instance declaration
isTypeDecl :: TyClDecl name -> Bool
isTypeDecl (TySynonym {}) = True
isTypeDecl _other	  = False

-- | vanilla Haskell type synonym (ie, not a type instance)
isSynDecl :: TyClDecl name -> Bool
isSynDecl (TySynonym {tcdTyPats = Nothing}) = True
isSynDecl _other	                    = False

-- | type class
isClassDecl :: TyClDecl name -> Bool
isClassDecl (ClassDecl {}) = True
isClassDecl _              = False

-- | type family declaration
isFamilyDecl :: TyClDecl name -> Bool
isFamilyDecl (TyFamily {}) = True
isFamilyDecl _other        = False

-- | family instance (types, newtypes, and data types)
isFamInstDecl :: TyClDecl name -> Bool
isFamInstDecl tydecl
   | isTypeDecl tydecl
     || isDataDecl tydecl = isJust (tcdTyPats tydecl)
   | otherwise	          = False
\end{code}

Dealing with names

\begin{code}
tcdName :: TyClDecl name -> name
tcdName decl = unLoc (tcdLName decl)

tyClDeclNames :: Eq name => TyClDecl name -> [Located name]
-- ^ Returns all the /binding/ names of the decl, along with their SrcLocs.
-- The first one is guaranteed to be the name of the decl. For record fields
-- mentioned in multiple constructors, the SrcLoc will be from the first
-- occurence.  We use the equality to filter out duplicate field names

tyClDeclNames (TyFamily    {tcdLName = name})    = [name]
tyClDeclNames (TySynonym   {tcdLName = name})    = [name]
tyClDeclNames (ForeignType {tcdLName = name})    = [name]

tyClDeclNames (ClassDecl {tcdLName = cls_name, tcdSigs = sigs, tcdATs = ats})
  = cls_name : 
    concatMap (tyClDeclNames . unLoc) ats ++ [n | L _ (TypeSig n _) <- sigs]

tyClDeclNames (TyData {tcdLName = tc_name, tcdCons = cons})
  = tc_name : hsConDeclsNames cons

tyClDeclTyVars :: TyClDecl name -> [LHsTyVarBndr name]
tyClDeclTyVars (TyFamily    {tcdTyVars = tvs}) = tvs
tyClDeclTyVars (TySynonym   {tcdTyVars = tvs}) = tvs
tyClDeclTyVars (TyData      {tcdTyVars = tvs}) = tvs
tyClDeclTyVars (ClassDecl   {tcdTyVars = tvs}) = tvs
tyClDeclTyVars (ForeignType {})		       = []
\end{code}

\begin{code}
countTyClDecls :: [TyClDecl name] -> (Int, Int, Int, Int, Int, Int)
	-- class, synonym decls, data, newtype, family decls, family instances
countTyClDecls decls 
 = (count isClassDecl    decls,
    count isSynDecl      decls,  -- excluding...
    count isDataTy       decls,  -- ...family...
    count isNewTy        decls,  -- ...instances
    count isFamilyDecl   decls,
    count isFamInstDecl  decls)
 where
   isDataTy TyData{tcdND = DataType, tcdTyPats = Nothing} = True
   isDataTy _                                             = False
   
   isNewTy TyData{tcdND = NewType, tcdTyPats = Nothing} = True
   isNewTy _                                            = False
\end{code}

\begin{code}
instance OutputableBndr name
	      => Outputable (TyClDecl name) where

    ppr (ForeignType {tcdLName = ltycon})
	= hsep [ptext (sLit "foreign import type dotnet"), ppr ltycon]

    ppr (TyFamily {tcdFlavour = flavour, tcdLName = ltycon, 
		   tcdTyVars = tyvars, tcdKind = mb_kind})
      = pp_flavour <+> pp_decl_head [] ltycon tyvars Nothing <+> pp_kind
        where
	  pp_flavour = case flavour of
		         TypeFamily -> ptext (sLit "type family")
			 DataFamily -> ptext (sLit "data family")

          pp_kind = case mb_kind of
		      Nothing   -> empty
		      Just kind -> dcolon <+> pprKind kind

    ppr (TySynonym {tcdLName = ltycon, tcdTyVars = tyvars, tcdTyPats = typats,
		    tcdSynRhs = mono_ty})
      = hang (ptext (sLit "type") <+> 
	      (if isJust typats then ptext (sLit "instance") else empty) <+>
	      pp_decl_head [] ltycon tyvars typats <+> 
	      equals)
	     4 (ppr mono_ty)

    ppr (TyData {tcdND = new_or_data, tcdCtxt = context, tcdLName = ltycon,
		 tcdTyVars = tyvars, tcdTyPats = typats, tcdKindSig = mb_sig, 
		 tcdCons = condecls, tcdDerivs = derivings})
      = pp_tydecl (null condecls && isJust mb_sig) 
                  (ppr new_or_data <+> 
		   (if isJust typats then ptext (sLit "instance") else empty) <+>
		   pp_decl_head (unLoc context) ltycon tyvars typats <+> 
		   ppr_sig mb_sig)
		  (pp_condecls condecls)
		  derivings
      where
	ppr_sig Nothing = empty
	ppr_sig (Just kind) = dcolon <+> pprKind kind

    ppr (ClassDecl {tcdCtxt = context, tcdLName = lclas, tcdTyVars = tyvars, 
		    tcdFDs = fds, 
		    tcdSigs = sigs, tcdMeths = methods, tcdATs = ats})
      | null sigs && null ats  -- No "where" part
      = top_matter

      | otherwise	-- Laid out
      = sep [hsep [top_matter, ptext (sLit "where {")],
	     nest 4 (sep [ sep (map ppr_semi ats)
			 , sep (map ppr_semi sigs)
			 , pprLHsBinds methods
			 , char '}'])]
      where
        top_matter    =     ptext (sLit "class") 
		        <+> pp_decl_head (unLoc context) lclas tyvars Nothing
		        <+> pprFundeps (map unLoc fds)
	ppr_semi decl = ppr decl <> semi

pp_decl_head :: OutputableBndr name
   => HsContext name
   -> Located name
   -> [LHsTyVarBndr name]
   -> Maybe [LHsType name]
   -> SDoc
pp_decl_head context thing tyvars Nothing	-- no explicit type patterns
  = hsep [pprHsContext context, ppr thing, interppSP tyvars]
pp_decl_head context thing _      (Just typats) -- explicit type patterns
  = hsep [ pprHsContext context, ppr thing
	 , hsep (map (pprParendHsType.unLoc) typats)]

pp_condecls :: OutputableBndr name => [LConDecl name] -> SDoc
pp_condecls cs@(L _ ConDecl{ con_res = ResTyGADT _ } : _) -- In GADT syntax
  = hang (ptext (sLit "where")) 2 (vcat (map ppr cs))
pp_condecls cs 			  -- In H98 syntax
  = equals <+> sep (punctuate (ptext (sLit " |")) (map ppr cs))

pp_tydecl :: OutputableBndr name => Bool -> SDoc -> SDoc -> Maybe [LHsType name] -> SDoc
pp_tydecl True  pp_head _ _
  = pp_head
pp_tydecl False pp_head pp_decl_rhs derivings
  = hang pp_head 4 (sep [
      pp_decl_rhs,
      case derivings of
        Nothing -> empty
	Just ds -> hsep [ptext (sLit "deriving"), parens (interpp'SP ds)]
    ])

instance Outputable NewOrData where
  ppr NewType  = ptext (sLit "newtype")
  ppr DataType = ptext (sLit "data")
\end{code}


%************************************************************************
%*									*
\subsection[ConDecl]{A data-constructor declaration}
%*									*
%************************************************************************

\begin{code}
type LConDecl name = Located (ConDecl name)

-- data T b = forall a. Eq a => MkT a b
--   MkT :: forall b a. Eq a => MkT a b

-- data T b where
--	MkT1 :: Int -> T Int

-- data T = Int `MkT` Int
--	  | MkT2

-- data T a where
--	Int `MkT` Int :: T Int

data ConDecl name
  = ConDecl
    { con_name      :: Located name
        -- ^ Constructor name.  This is used for the DataCon itself, and for
        -- the user-callable wrapper Id.

    , con_explicit  :: HsExplicitFlag
        -- ^ Is there an user-written forall? (cf. 'HsTypes.HsForAllTy')

    , con_qvars     :: [LHsTyVarBndr name]
        -- ^ Type variables.  Depending on 'con_res' this describes the
	-- follewing entities
        --
        --  - ResTyH98:  the constructor's *existential* type variables
        --  - ResTyGADT: *all* the constructor's quantified type variables

    , con_cxt       :: LHsContext name
        -- ^ The context.  This /does not/ include the \"stupid theta\" which
	-- lives only in the 'TyData' decl.

    , con_details   :: HsConDeclDetails name
        -- ^ The main payload

    , con_res       :: ResType name
        -- ^ Result type of the constructor

    , con_doc       :: Maybe LHsDocString
        -- ^ A possible Haddock comment.

    , con_old_rec :: Bool   
        -- ^ TEMPORARY field; True <=> user has employed now-deprecated syntax for
	--   	       	               GADT-style record decl   C { blah } :: T a b
	-- Remove this when we no longer parse this stuff, and hence do not
	-- need to report decprecated use
    } deriving (Data, Typeable)

type HsConDeclDetails name = HsConDetails (LBangType name) [ConDeclField name]

hsConDeclArgTys :: HsConDeclDetails name -> [LBangType name]
hsConDeclArgTys (PrefixCon tys)    = tys
hsConDeclArgTys (InfixCon ty1 ty2) = [ty1,ty2]
hsConDeclArgTys (RecCon flds)      = map cd_fld_type flds

data ResType name
   = ResTyH98		-- Constructor was declared using Haskell 98 syntax
   | ResTyGADT (LHsType name)	-- Constructor was declared using GADT-style syntax,
				--	and here is its result type
   deriving (Data, Typeable)

instance OutputableBndr name => Outputable (ResType name) where
	 -- Debugging only
   ppr ResTyH98 = ptext (sLit "ResTyH98")
   ppr (ResTyGADT ty) = ptext (sLit "ResTyGADT") <+> pprParendHsType (unLoc ty)
\end{code}

\begin{code}
hsConDeclsNames :: (Eq name) => [LConDecl name] -> [Located name]
  -- See tyClDeclNames for what this does
  -- The function is boringly complicated because of the records
  -- And since we only have equality, we have to be a little careful
hsConDeclsNames cons
  = snd (foldl do_one ([], []) cons)
  where
    do_one (flds_seen, acc) (L _ (ConDecl { con_name = lname, con_details = RecCon flds }))
	= (map unLoc new_flds ++ flds_seen, lname : new_flds ++ acc)
	where
	  new_flds = filterOut (\f -> unLoc f `elem` flds_seen) 
			       (map cd_fld_name flds)

    do_one (flds_seen, acc) (L _ (ConDecl { con_name = lname }))
	= (flds_seen, lname:acc)
\end{code}
  

\begin{code}
instance (OutputableBndr name) => Outputable (ConDecl name) where
    ppr = pprConDecl

pprConDecl :: OutputableBndr name => ConDecl name -> SDoc
pprConDecl (ConDecl { con_name =con, con_explicit = expl, con_qvars = tvs
                    , con_cxt = cxt, con_details = details
                    , con_res = ResTyH98, con_doc = doc })
  = sep [ppr_mbDoc doc, pprHsForAll expl tvs cxt, ppr_details con details]
  where
    ppr_details con (InfixCon t1 t2) = hsep [ppr t1, pprHsInfix con, ppr t2]
    ppr_details con (PrefixCon tys)  = hsep (pprHsVar con : map ppr tys)
    ppr_details con (RecCon fields)  = ppr con <+> pprConDeclFields fields

pprConDecl (ConDecl { con_name = con, con_explicit = expl, con_qvars = tvs
                    , con_cxt = cxt, con_details = PrefixCon arg_tys
                    , con_res = ResTyGADT res_ty })
  = ppr con <+> dcolon <+> 
    sep [pprHsForAll expl tvs cxt, ppr (foldr mk_fun_ty res_ty arg_tys)]
  where
    mk_fun_ty a b = noLoc (HsFunTy a b)

pprConDecl (ConDecl { con_name = con, con_explicit = expl, con_qvars = tvs
                    , con_cxt = cxt, con_details = RecCon fields, con_res = ResTyGADT res_ty })
  = sep [ppr con <+> dcolon <+> pprHsForAll expl tvs cxt, 
         pprConDeclFields fields <+> arrow <+> ppr res_ty]

pprConDecl (ConDecl {con_name = con, con_details = InfixCon {}, con_res = ResTyGADT {} })
  = pprPanic "pprConDecl" (ppr con)
	-- In GADT syntax we don't allow infix constructors
\end{code}

%************************************************************************
%*									*
\subsection[InstDecl]{An instance declaration
%*									*
%************************************************************************

\begin{code}
type LInstDecl name = Located (InstDecl name)

data InstDecl name
  = InstDecl	(LHsType name)	-- Context => Class Instance-type
				-- Using a polytype means that the renamer conveniently
				-- figures out the quantified type variables for us.
		(LHsBinds name)
		[LSig name]	-- User-supplied pragmatic info
		[LTyClDecl name]-- Associated types (ie, 'TyData' and
				-- 'TySynonym' only)
  deriving (Data, Typeable)

instance (OutputableBndr name) => Outputable (InstDecl name) where

    ppr (InstDecl inst_ty binds uprags ats)
      = vcat [hsep [ptext (sLit "instance"), ppr inst_ty, ptext (sLit "where")]
             , nest 4 $ vcat (map ppr ats)
 	     , nest 4 $ vcat (map ppr uprags)
	     , nest 4 $ pprLHsBinds binds ]

-- Extract the declarations of associated types from an instance
--
instDeclATs :: InstDecl name -> [LTyClDecl name]
instDeclATs (InstDecl _ _ _ ats) = ats
\end{code}

%************************************************************************
%*									*
\subsection[DerivDecl]{A stand-alone instance deriving declaration
%*									*
%************************************************************************

\begin{code}
type LDerivDecl name = Located (DerivDecl name)

data DerivDecl name = DerivDecl (LHsType name)
  deriving (Data, Typeable)

instance (OutputableBndr name) => Outputable (DerivDecl name) where
    ppr (DerivDecl ty) 
        = hsep [ptext (sLit "deriving instance"), ppr ty]
\end{code}

%************************************************************************
%*									*
\subsection[DefaultDecl]{A @default@ declaration}
%*									*
%************************************************************************

There can only be one default declaration per module, but it is hard
for the parser to check that; we pass them all through in the abstract
syntax, and that restriction must be checked in the front end.

\begin{code}
type LDefaultDecl name = Located (DefaultDecl name)

data DefaultDecl name
  = DefaultDecl	[LHsType name]
  deriving (Data, Typeable)

instance (OutputableBndr name)
	      => Outputable (DefaultDecl name) where

    ppr (DefaultDecl tys)
      = ptext (sLit "default") <+> parens (interpp'SP tys)
\end{code}

%************************************************************************
%*									*
\subsection{Foreign function interface declaration}
%*									*
%************************************************************************

\begin{code}

-- foreign declarations are distinguished as to whether they define or use a
-- Haskell name
--
--  * the Boolean value indicates whether the pre-standard deprecated syntax
--   has been used
--
type LForeignDecl name = Located (ForeignDecl name)

data ForeignDecl name
  = ForeignImport (Located name) (LHsType name) ForeignImport  -- defines name
  | ForeignExport (Located name) (LHsType name) ForeignExport  -- uses name
  deriving (Data, Typeable)

-- Specification Of an imported external entity in dependence on the calling
-- convention 
--
data ForeignImport = -- import of a C entity
		     --
                     --  * the two strings specifying a header file or library
                     --   may be empty, which indicates the absence of a
                     --   header or object specification (both are not used
                     --   in the case of `CWrapper' and when `CFunction'
                     --   has a dynamic target)
		     --
		     --  * the calling convention is irrelevant for code
		     --   generation in the case of `CLabel', but is needed
		     --   for pretty printing 
		     --
		     --  * `Safety' is irrelevant for `CLabel' and `CWrapper'
		     --
		     CImport  CCallConv	      -- ccall or stdcall
			      Safety	      -- safe or unsafe
			      FastString      -- name of C header
			      CImportSpec     -- details of the C entity
  deriving (Data, Typeable)

-- details of an external C entity
--
data CImportSpec = CLabel    CLabelString     -- import address of a C label
		 | CFunction CCallTarget      -- static or dynamic function
		 | CWrapper		      -- wrapper to expose closures
					      -- (former f.e.d.)
  deriving (Data, Typeable)

-- specification of an externally exported entity in dependence on the calling
-- convention
--
data ForeignExport = CExport  CExportSpec    -- contains the calling convention
  deriving (Data, Typeable)

-- pretty printing of foreign declarations
--

instance OutputableBndr name => Outputable (ForeignDecl name) where
  ppr (ForeignImport n ty fimport) =
    hang (ptext (sLit "foreign import") <+> ppr fimport <+> ppr n)
       2 (dcolon <+> ppr ty)
  ppr (ForeignExport n ty fexport) =
    hang (ptext (sLit "foreign export") <+> ppr fexport <+> ppr n)
       2 (dcolon <+> ppr ty)

instance Outputable ForeignImport where
  ppr (CImport  cconv safety header spec) =
    ppr cconv <+> ppr safety <+> 
    char '"' <> pprCEntity spec <> char '"'
    where
      pp_hdr = if nullFS header then empty else ftext header

      pprCEntity (CLabel lbl) = 
        ptext (sLit "static") <+> pp_hdr <+> char '&' <> ppr lbl
      pprCEntity (CFunction (StaticTarget lbl _)) = 
        ptext (sLit "static") <+> pp_hdr <+> ppr lbl
      pprCEntity (CFunction (DynamicTarget)) =
        ptext (sLit "dynamic")
      pprCEntity (CWrapper) = ptext (sLit "wrapper")

instance Outputable ForeignExport where
  ppr (CExport  (CExportStatic lbl cconv)) = 
    ppr cconv <+> char '"' <> ppr lbl <> char '"'
\end{code}


%************************************************************************
%*									*
\subsection{Transformation rules}
%*									*
%************************************************************************

\begin{code}
type LRuleDecl name = Located (RuleDecl name)

data RuleDecl name
  = HsRule			-- Source rule
	RuleName		-- Rule name
	Activation
	[RuleBndr name]		-- Forall'd vars; after typechecking this includes tyvars
	(Located (HsExpr name))	-- LHS
        NameSet                 -- Free-vars from the LHS
	(Located (HsExpr name))	-- RHS
        NameSet                 -- Free-vars from the RHS
  deriving (Data, Typeable)

data RuleBndr name
  = RuleBndr (Located name)
  | RuleBndrSig (Located name) (LHsType name)
  deriving (Data, Typeable)

collectRuleBndrSigTys :: [RuleBndr name] -> [LHsType name]
collectRuleBndrSigTys bndrs = [ty | RuleBndrSig _ ty <- bndrs]

instance OutputableBndr name => Outputable (RuleDecl name) where
  ppr (HsRule name act ns lhs _fv_lhs rhs _fv_rhs)
	= sep [text "{-# RULES" <+> doubleQuotes (ftext name) <+> ppr act,
	       nest 4 (pp_forall <+> pprExpr (unLoc lhs)), 
	       nest 4 (equals <+> pprExpr (unLoc rhs) <+> text "#-}") ]
	where
	  pp_forall | null ns   = empty
		    | otherwise	= text "forall" <+> fsep (map ppr ns) <> dot

instance OutputableBndr name => Outputable (RuleBndr name) where
   ppr (RuleBndr name) = ppr name
   ppr (RuleBndrSig name ty) = ppr name <> dcolon <> ppr ty
\end{code}

%************************************************************************
%*									*
\subsection[DocDecl]{Document comments}
%*									*
%************************************************************************

\begin{code}

type LDocDecl = Located (DocDecl)

data DocDecl
  = DocCommentNext HsDocString
  | DocCommentPrev HsDocString
  | DocCommentNamed String HsDocString
  | DocGroup Int HsDocString
  deriving (Data, Typeable)
 
-- Okay, I need to reconstruct the document comments, but for now:
instance Outputable DocDecl where
  ppr _ = text "<document comment>"

docDeclDoc :: DocDecl -> HsDocString
docDeclDoc (DocCommentNext d) = d
docDeclDoc (DocCommentPrev d) = d
docDeclDoc (DocCommentNamed _ d) = d
docDeclDoc (DocGroup _ d) = d

\end{code}

%************************************************************************
%*									*
\subsection[DeprecDecl]{Deprecations}
%*									*
%************************************************************************

We use exported entities for things to deprecate.

\begin{code}
type LWarnDecl name = Located (WarnDecl name)

data WarnDecl name = Warning name WarningTxt
  deriving (Data, Typeable)

instance OutputableBndr name => Outputable (WarnDecl name) where
    ppr (Warning thing txt)
      = hsep [text "{-# DEPRECATED", ppr thing, doubleQuotes (ppr txt), text "#-}"]
\end{code}

%************************************************************************
%*									*
\subsection[AnnDecl]{Annotations}
%*									*
%************************************************************************

\begin{code}
type LAnnDecl name = Located (AnnDecl name)

data AnnDecl name = HsAnnotation (AnnProvenance name) (Located (HsExpr name))
  deriving (Data, Typeable)

instance (OutputableBndr name) => Outputable (AnnDecl name) where
    ppr (HsAnnotation provenance expr) 
      = hsep [text "{-#", pprAnnProvenance provenance, pprExpr (unLoc expr), text "#-}"]


data AnnProvenance name = ValueAnnProvenance name
                        | TypeAnnProvenance name
                        | ModuleAnnProvenance
  deriving (Data, Typeable)

annProvenanceName_maybe :: AnnProvenance name -> Maybe name
annProvenanceName_maybe (ValueAnnProvenance name) = Just name
annProvenanceName_maybe (TypeAnnProvenance name)  = Just name
annProvenanceName_maybe ModuleAnnProvenance       = Nothing

-- TODO: Replace with Traversable instance when GHC bootstrap version rises high enough
modifyAnnProvenanceNameM :: Monad m => (before -> m after) -> AnnProvenance before -> m (AnnProvenance after)
modifyAnnProvenanceNameM fm prov =
    case prov of
            ValueAnnProvenance name -> liftM ValueAnnProvenance (fm name)
            TypeAnnProvenance name -> liftM TypeAnnProvenance (fm name)
            ModuleAnnProvenance -> return ModuleAnnProvenance

pprAnnProvenance :: OutputableBndr name => AnnProvenance name -> SDoc
pprAnnProvenance ModuleAnnProvenance       = ptext (sLit "ANN module")
pprAnnProvenance (ValueAnnProvenance name) = ptext (sLit "ANN") <+> ppr name
pprAnnProvenance (TypeAnnProvenance name)  = ptext (sLit "ANN type") <+> ppr name
\end{code}