[project @ 1996-01-08 20:28:12 by partain]
[ghc-hetmet.git] / ghc / compiler / coreSyn / AnnCoreSyn.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1994
3 %
4 \section[AnnCoreSyntax]{Annotated core syntax}
5
6 For when you want @CoreSyntax@ trees annotated at every node.  Other
7 than that, just like @CoreSyntax@.  (Important to be sure that it {\em
8 really is} just like @CoreSyntax@.)
9
10 \begin{code}
11 #include "HsVersions.h"
12
13 module AnnCoreSyn (
14         AnnCoreBinding(..), AnnCoreExpr(..),
15         AnnCoreExpr'(..),       -- v sad that this must be exported
16         AnnCoreCaseAlternatives(..), AnnCoreCaseDefault(..),
17 #ifdef DPH
18         AnnCoreParQuals(..),
19         AnnCoreParCommunicate(..),
20 #endif {- Data Parallel Haskell -}
21
22         deAnnotate, -- we may eventually export some of the other deAnners
23
24         -- and to make the interface self-sufficient
25         BasicLit, Id, PrimOp, TyCon, TyVar, UniType, CostCentre
26         IF_ATTACK_PRAGMAS(COMMA cmpTyCon COMMA cmpTyVar)
27         IF_ATTACK_PRAGMAS(COMMA cmpUniType)
28     ) where
29
30 import AbsPrel          ( PrimOp(..), PrimKind
31                           IF_ATTACK_PRAGMAS(COMMA tagOf_PrimOp)
32                           IF_ATTACK_PRAGMAS(COMMA pprPrimOp)
33                         )
34 import AbsUniType       ( Id, TyVar, TyCon, UniType
35                           IF_ATTACK_PRAGMAS(COMMA cmpTyCon COMMA cmpTyVar)
36                           IF_ATTACK_PRAGMAS(COMMA cmpUniType)
37                         )
38 import BasicLit         ( BasicLit )
39 import CoreSyn
40 import Outputable
41 import CostCentre       ( CostCentre )
42 #if USE_ATTACK_PRAGMAS
43 import Util
44 #endif
45 \end{code}
46
47 \begin{code}
48 data AnnCoreBinding binder bindee annot
49   = AnnCoNonRec binder (AnnCoreExpr binder bindee annot)
50   | AnnCoRec    [(binder, AnnCoreExpr binder bindee annot)]
51 \end{code}
52
53 \begin{code}
54 type AnnCoreExpr binder bindee annot = (annot, AnnCoreExpr' binder bindee annot)
55
56 data AnnCoreExpr' binder bindee annot
57   = AnnCoVar     bindee
58   | AnnCoLit BasicLit
59
60   | AnnCoCon     Id [UniType] [CoreAtom bindee]
61
62   | AnnCoPrim    PrimOp [UniType] [CoreAtom bindee]
63
64   | AnnCoLam     [binder]
65                  (AnnCoreExpr binder bindee annot)
66   | AnnCoTyLam   TyVar
67                  (AnnCoreExpr binder bindee annot)
68
69   | AnnCoApp     (AnnCoreExpr binder bindee annot)
70                  (CoreAtom    bindee)
71   | AnnCoTyApp   (AnnCoreExpr binder bindee annot)
72                  UniType
73
74   | AnnCoCase    (AnnCoreExpr binder bindee annot)
75                  (AnnCoreCaseAlternatives binder bindee annot)
76
77   | AnnCoLet     (AnnCoreBinding binder bindee annot)
78                  (AnnCoreExpr binder bindee annot)
79
80   | AnnCoSCC     CostCentre
81                  (AnnCoreExpr binder bindee annot)
82 #ifdef DPH
83   | AnnCoZfExpr  (AnnCoreExpr binder bindee annot) 
84                  (AnnCoreParQuals binder bindee annot)
85
86   | AnnCoParCon  Id Int [UniType] [AnnCoreExpr binder bindee annot]
87
88   | AnnCoParComm
89                      Int
90                     (AnnCoreExpr binder bindee annot)
91                     (AnnCoreParCommunicate binder bindee annot)
92   | AnnCoParZipWith
93                      Int 
94                      (AnnCoreExpr binder bindee annot)
95                      [AnnCoreExpr binder bindee annot]
96 #endif {- Data Parallel Haskell -}
97 \end{code}
98
99 \begin{code}
100 #ifdef DPH
101 data AnnCoreParQuals binder bindee annot
102    = AnnCoAndQuals  (AnnCoreParQuals binder bindee annot)
103                     (AnnCoreParQuals binder bindee annot)
104    | AnnCoParFilter (AnnCoreExpr binder bindee annot)
105    | AnnCoDrawnGen  [binder]
106                     (binder)
107                     (AnnCoreExpr binder bindee annot)   
108    | AnnCoIndexGen  [AnnCoreExpr binder bindee annot]
109                     (binder)
110                     (AnnCoreExpr binder bindee annot)   
111 #endif {- Data Parallel Haskell -}
112 \end{code}
113
114 \begin{code}
115 data AnnCoreCaseAlternatives binder bindee annot
116   = AnnCoAlgAlts        [(Id,
117                          [binder],
118                          AnnCoreExpr binder bindee annot)]
119                         (AnnCoreCaseDefault binder bindee annot)
120   | AnnCoPrimAlts       [(BasicLit,
121                           AnnCoreExpr binder bindee annot)]
122                         (AnnCoreCaseDefault binder bindee annot)
123 #ifdef DPH
124   | AnnCoParAlgAlts     TyCon   
125                         Int
126                         [binder]
127                         [(Id,
128                          AnnCoreExpr binder bindee annot)]
129                         (AnnCoreCaseDefault binder bindee annot)
130   | AnnCoParPrimAlts    TyCon   
131                         Int
132                         [(BasicLit,
133                           AnnCoreExpr binder bindee annot)]
134                         (AnnCoreCaseDefault binder bindee annot)
135 #endif {- Data Parallel Haskell -}
136
137 data AnnCoreCaseDefault binder bindee annot
138   = AnnCoNoDefault
139   | AnnCoBindDefault    binder
140                         (AnnCoreExpr binder bindee annot)
141 \end{code}
142
143 \begin{code}
144 #ifdef DPH
145 data AnnCoreParCommunicate binder bindee annot
146   = AnnCoParSend        [AnnCoreExpr binder bindee annot]     
147   | AnnCoParFetch       [AnnCoreExpr binder bindee annot]     
148   | AnnCoToPodized
149   | AnnCoFromPodized
150 #endif {- Data Parallel Haskell -}
151 \end{code}
152
153 \begin{code}
154 deAnnotate :: AnnCoreExpr bndr bdee ann -> CoreExpr bndr bdee
155
156 deAnnotate (_, AnnCoVar v)            = CoVar v
157 deAnnotate (_, AnnCoLit lit)      = CoLit lit
158 deAnnotate (_, AnnCoCon con tys args) = CoCon con tys args
159 deAnnotate (_, AnnCoPrim op tys args) = CoPrim op tys args
160 deAnnotate (_, AnnCoLam binders body) = CoLam binders (deAnnotate body)
161 deAnnotate (_, AnnCoTyLam tyvar body) = CoTyLam tyvar (deAnnotate body)
162 deAnnotate (_, AnnCoApp fun arg)      = CoApp (deAnnotate fun) arg
163 deAnnotate (_, AnnCoTyApp fun ty)     = CoTyApp (deAnnotate fun) ty
164 deAnnotate (_, AnnCoSCC lbl body)     = CoSCC lbl (deAnnotate body) 
165
166 deAnnotate (_, AnnCoLet bind body)
167   = CoLet (deAnnBind bind) (deAnnotate body)
168   where
169     deAnnBind (AnnCoNonRec var rhs) = CoNonRec var (deAnnotate rhs)
170     deAnnBind (AnnCoRec pairs) = CoRec [(v,deAnnotate rhs) | (v,rhs) <- pairs]
171
172 deAnnotate (_, AnnCoCase scrut alts)
173   = CoCase (deAnnotate scrut) (deAnnAlts alts)
174   where
175     deAnnAlts (AnnCoAlgAlts alts deflt)  
176       = CoAlgAlts [(con,args,deAnnotate rhs) | (con,args,rhs) <- alts]
177                  (deAnnDeflt deflt)
178
179     deAnnAlts (AnnCoPrimAlts alts deflt) 
180       = CoPrimAlts [(lit,deAnnotate rhs) | (lit,rhs) <- alts]
181                    (deAnnDeflt deflt)
182
183     deAnnDeflt AnnCoNoDefault         = CoNoDefault
184     deAnnDeflt (AnnCoBindDefault var rhs) = CoBindDefault var (deAnnotate rhs)
185 \end{code}