PrintAs.hs revision dc808c58c91f82311454b4b66d206cd813d0aa70
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
$Id$
Authors: Christian Maeder
Year: 2002
printing As data types
-}
module PrintAs where
import As
import Keywords
import HToken
import Pretty
import PrettyPrint
import GlobalAnnotations(GlobalAnnos)
import Print_AS_Annotation()
commas, semis :: PrettyPrint a => GlobalAnnos -> [a] -> Doc
commas ga l = fcat $ punctuate comma (map (printText0 ga) l)
semis ga l = sep $ punctuate semi (map (printText0 ga) l)
instance PrettyPrint TypePattern where
printText0 ga (TypePattern name args _) = printText0 ga name
<> fcat (map (parens . printText0 ga) args)
printText0 ga (TypePatternToken t) = printText0 ga t
printText0 ga (MixfixTypePattern ts) = fsep (map (printText0 ga) ts)
printText0 ga (BracketTypePattern k l _) = bracket k $ commas ga l
printText0 ga (TypePatternArgs l) = semis ga l
bracket :: BracketKind -> Doc -> Doc
bracket Parens t = parens t
bracket Squares t = Pretty.brackets t
bracket Braces t = braces t
printKind :: GlobalAnnos -> Kind -> Doc
printKind ga kind = case kind of
Kind [] (Intersection [] _) _ -> empty
_ -> space <> colon <> printText0 ga kind
instance PrettyPrint Type where
printText0 ga (TypeConstrAppl name i kind args _) = printText0 ga name
<> if i == 0 then empty
else parens (int i)
<> printKind ga kind
<> if null args then empty
else parens (commas ga args)
printText0 ga (TypeToken t) = printText0 ga t
printText0 ga (BracketType k l _) = bracket k $ commas ga l
printText0 ga (KindedType t kind _) = printText0 ga t
<> printKind ga kind
printText0 ga (MixfixType ts) = fsep (map (printText0 ga) ts)
printText0 ga (LazyType t _) = text quMark <+> printText0 ga (t)
printText0 ga (ProductType ts _) = fsep (punctuate (space <> text timesS)
(map (printText0 ga) ts))
printText0 ga (FunType t1 arr t2 _) = printText0 ga t1
<+> printText0 ga arr
<+> printText0 ga t2
instance PrettyPrint Pred where
printText0 ga (IsIn c ts) = if null ts then printText0 ga c
else if null $ tail ts then
printText0 ga (head ts) <+>
colon <+> printText0 ga c
else printText0 ga c <+>
fsep (punctuate space
(map (printText0 ga) ts))
instance PrettyPrint t => PrettyPrint (Qual t) where
printText0 ga (ps :=> t) = (if null ps then empty
else parens $ commas ga ps <+>
ptext implS <+> space) <>
printText0 ga t
-- no curried notation for bound variables
instance PrettyPrint TypeScheme where
printText0 ga (SimpleTypeScheme t) = printText0 ga t
printText0 ga (TypeScheme vs t _) = text forallS
<+> semis ga vs
<+> text dotS
<+> printText0 ga t
instance PrettyPrint Partiality where
printText0 _ Partial = text quMark
printText0 _ Total = text exMark
instance PrettyPrint Arrow where
printText0 _ FunArr = text funS
printText0 _ PFunArr = text pFun
printText0 _ ContFunArr = text contFun
printText0 _ PContFunArr = text pContFun
instance PrettyPrint Quantifier where
printText0 _ Universal = text forallS
printText0 _ Existential = text existsS
printText0 _ Unique = text $ existsS ++ exMark
instance PrettyPrint TypeQual where
printText0 _ OfType = colon
printText0 _ AsType = text asS
printText0 _ InType = text inS
instance PrettyPrint LogOp where
printText0 _ NotOp = text notS
printText0 _ AndOp = text lAnd
printText0 _ OrOp = text lOr
printText0 _ ImplOp = text implS
printText0 _ EquivOp = text equivS
instance PrettyPrint EqOp where
printText0 _ EqualOp = text equalS
printText0 _ ExEqualOp = text exEqual
instance PrettyPrint Formula where
printText0 ga (TermFormula t) = printText0 ga t
printText0 ga (ConnectFormula o fs _) = parens $
fsep (punctuate (space <> printText0 ga o) (map (printText0 ga) fs))
printText0 ga (EqFormula o t1 t2 _) = printText0 ga t1
<+> printText0 ga o
<+> printText0 ga t2
printText0 ga (DefFormula t _) = text defS <+> printText0 ga t
printText0 ga (QuantifiedFormula q vs f _) =
printText0 ga q <+> semis ga vs <+> text dotS <+> printText0 ga f
printText0 ga (PolyFormula ts f _) =
text forallS <+> semis ga ts <+> text dotS <+> printText0 ga f
instance PrettyPrint Term where
printText0 ga (CondTerm t1 f t2 _) = printText0 ga t1
<+> text whenS
<+> printText0 ga f
<+> text elseS
<+> printText0 ga t2
printText0 ga (QualVar v t _) = parens $ text varS
<+> printText0 ga v
<+> colon
<+> printText0 ga t
printText0 ga (QualOp n t _) = parens $
text opS
<+> printText0 ga n
<+> colon
<+> printText0 ga t
printText0 ga (ApplTerm t1 t2 _) = printText0 ga t1
<+> parens (printText0 ga t2)
printText0 ga (TupleTerm ts _) = parens $ commas ga ts
printText0 ga (TypedTerm term q typ _) = printText0 ga term
<+> printText0 ga q
<+> printText0 ga typ
printText0 ga (QuantifiedTerm q vs t _) = printText0 ga q
<+> semis ga vs
<+> text dotS
<+> printText0 ga t
printText0 ga (LambdaTerm ps q t _) = text lamS
<+> (if length ps == 1 then
printText0 ga $ head ps
else fcat $ map
(parens.printText0 ga) ps)
<+> (case q of
Partial -> text dotS
Total -> text $ dotS ++ exMark)
<+> printText0 ga t
printText0 ga (CaseTerm t es _ ) = text caseS
<+> printText0 ga t
<+> text ofS
<+> vcat (punctuate (text " | ")
(map (printEq0 ga funS) es))
printText0 ga (LetTerm es t _) = text letS
<+> vcat (punctuate semi
(map (printEq0 ga equalS) es))
<+> text inS
<+> printText0 ga t
printText0 ga (TermToken t) = printText0 ga t
printText0 ga (MixfixTerm ts) = fsep $ map (printText0 ga) ts
printText0 ga (BracketTerm k l _) = bracket k $ commas ga l
instance PrettyPrint Pattern where
printText0 ga (PatternVars vs _) = semis ga vs
printText0 ga (PatternConstr n t args _) = printText0 ga n
<+> colon
<+> printText0 ga t
<+> fcat (map (parens.printText0 ga) args)
printText0 ga (PatternToken t) = printText0 ga t
printText0 ga (BracketPattern k l _) =
case l of
[TuplePattern _ _] -> printText0 ga $ head l
_ -> bracket k $ commas ga l
printText0 ga (TuplePattern ps _) = parens $ commas ga ps
printText0 ga (MixfixPattern ps) = fsep (map (printText0 ga) ps)
printText0 ga (TypedPattern p t _) = printText0 ga p
<+> colon
<+> printText0 ga t
printText0 ga (AsPattern v p _) = printText0 ga v
<+> text asP
<+> printText0 ga p
printEq0 :: GlobalAnnos -> String -> ProgEq -> Doc
printEq0 ga s (ProgEq p t _) = fsep [printText0 ga p
, text s
, printText0 ga t]
instance PrettyPrint VarDecl where
printText0 ga (VarDecl v t _ _) = printText0 ga v <+> colon
<+> printText0 ga t
instance PrettyPrint TypeVarDecl where
printText0 ga (TypeVarDecl v c _ _) =
printText0 ga v <+>
case c of
Kind [] (Downset t) _ ->
text lessS <+> printText0 ga t
_ -> colon <+> printText0 ga c
instance PrettyPrint GenVarDecl where
printText0 ga (GenVarDecl v) = printText0 ga v
printText0 ga (GenTypeVarDecl tv) = printText0 ga tv
instance PrettyPrint TypeArg where
printText0 ga (TypeArg v c _ _) = printText0 ga v <> colon
<> printText0 ga c
instance PrettyPrint Variance where
printText0 _ CoVar = text plusS
printText0 _ ContraVar = text minusS
printText0 _ InVar = empty
instance PrettyPrint ExtClass where
printText0 ga (ExtClass c v _) = printText0 ga c <> printText0 ga v
<> space
printText0 ga (KindArg k) = parens (printText0 ga k)
instance PrettyPrint ProdClass where
printText0 ga (ProdClass l _) = fcat $ punctuate (text timesS)
(map (printText0 ga) l)
instance PrettyPrint Kind where
printText0 ga (Kind l c _) = (if null l then empty else
(fcat $ punctuate (text funS)
(map (printText0 ga) l))
<> text funS)
<> printText0 ga c
instance PrettyPrint Class where
printText0 ga (Downset t) = braces $
text "_" <+> text lessS <+> printText0 ga t
printText0 ga (Intersection c _) = if null c then ptext "Type"
else if null $ tail c then printText0 ga $ head c
else parens $ commas ga c
instance PrettyPrint Types where
printText0 ga (Types l _) = Pretty.brackets $ commas ga l
instance PrettyPrint InstOpId where
printText0 ga (InstOpId n l) = printText0 ga n
<> fcat(map (printText0 ga) l)
------------------------------------------------------------------------
-- item stuff
------------------------------------------------------------------------
instance PrettyPrint PseudoType where
printText0 ga (SimplePseudoType t) = printText0 ga t
printText0 ga (PseudoType l t _) = text lamS
<+> fcat(map (printText0 ga) l)
<+> text dotS <+> printText0 ga t
instance PrettyPrint TypeArgs where
printText0 ga (TypeArgs l _) = semis ga l
instance PrettyPrint TypeVarDecls where
printText0 ga (TypeVarDecls l _) = Pretty.brackets $ semis ga l
instance PrettyPrint BasicSpec where
printText0 ga (BasicSpec l) = vcat (map (printText0 ga) l)
instance PrettyPrint ProgEq where
printText0 ga = printEq0 ga equalS
instance PrettyPrint BasicItem where
printText0 ga (SigItems s) = printText0 ga s
printText0 ga (ProgItems l _) = text programS <+> semis ga l
printText0 ga (ClassItems i l _) = text classS <+> printText0 ga i
<+> semis ga l
printText0 ga (GenVarItems l _) = text varS <+> semis ga l
printText0 ga (FreeDatatype l _) = text freeS <+> text typeS
<+> semis ga l
printText0 ga (GenItems l _) = text generatedS <+> braces (semis ga l)
printText0 ga (AxiomItems vs fs _) = (if null vs then empty
else text forallS <+> semis ga vs)
$$ vcat (map
(\x -> text dotS <+> printText0 ga x)
fs)
instance PrettyPrint SigItems where
printText0 ga (TypeItems i l _) = text typeS <+> printText0 ga i
<+> semis ga l
printText0 ga (OpItems l _) = text opS <+> semis ga l
printText0 ga (PredItems l _) = text predS <+> semis ga l
instance PrettyPrint Instance where
printText0 _ Instance = text instanceS
printText0 _ _ = empty
instance PrettyPrint ClassItem where
printText0 ga (ClassItem d l _) = printText0 ga d $$
if null l then empty
else braces (semis ga l)
instance PrettyPrint ClassDecl where
printText0 ga (ClassDecl l _) = commas ga l
printText0 ga (SubclassDecl l s _) = commas ga l <> text lessS
<> printText0 ga s
printText0 ga (ClassDefn n c _) = printText0 ga n
<> text equalS
<> printText0 ga c
printText0 ga (DownsetDefn c v t _) =
let pv = printText0 ga v in
printText0 ga c
<> text equalS
<> braces (pv <> text dotS <> pv
<> text lessS
<+> printText0 ga t)
instance PrettyPrint TypeItem where
printText0 ga (TypeDecl l k _) = commas ga l <>
printKind ga k
printText0 ga (SubtypeDecl l t _) = commas ga l <+> text lessS
<+> printText0 ga t
printText0 ga (IsoDecl l _) = cat(punctuate (text " = ")
(map (printText0 ga) l))
printText0 ga (SubtypeDefn p v t f _) = printText0 ga p
<+> text equalS
<+> braces (printText0 ga v
<+> colon
<+> printText0 ga t
<+> text dotS
<+> printText0 ga f)
printText0 ga (AliasType p k t _) = (printText0 ga p <>
printKind ga k)
<+> text assignS
<+> printText0 ga t
printText0 ga (Datatype t) = printText0 ga t
instance PrettyPrint OpItem where
printText0 ga (OpDecl l t as _) = commas ga l <+> colon
<+> (printText0 ga t
<> (if null as then empty else comma)
<> commas ga as)
printText0 ga (OpDefn n ps s p t _) = (printText0 ga n
<> fcat (map (printText0 ga) ps))
<+> (colon <> if p == Partial
then text quMark else empty)
<+> printText0 ga s
<+> text equalS
<+> printText0 ga t
instance PrettyPrint PredItem where
printText0 ga (PredDecl l t _) = commas ga l <+> colon <+> printText0 ga t
printText0 ga (PredDefn n ps f _) = (printText0 ga n
<> fcat (map (printText0 ga) ps))
<+> text equivS
<+> printText0 ga f
instance PrettyPrint BinOpAttr where
printText0 _ Assoc = text assocS
printText0 _ Comm = text commS
printText0 _ Idem = text idemS
instance PrettyPrint OpAttr where
printText0 ga (BinOpAttr a _) = printText0 ga a
printText0 ga (UnitOpAttr t _) = text unitS <+> printText0 ga t
instance PrettyPrint DatatypeDecl where
printText0 ga (DatatypeDecl p k as d _) = (printText0 ga p <>
printKind ga k)
<+> text defnS
<+> vcat(punctuate (text " | ")
(map (printText0 ga) as))
<+> case d of { Nothing -> empty
; Just c -> text derivingS
<+> printText0 ga c
}
instance PrettyPrint Alternative where
printText0 ga (Constructor n cs p _) = printText0 ga n
<> fcat (map (printText0 ga) cs)
<> (case p of {Partial -> text quMark;
_ -> empty})
printText0 ga (Subtype l _) = text typeS <+> commas ga l
instance PrettyPrint Components where
printText0 ga (Selector n p t _ _) = printText0 ga n
<> colon <> (case p of { Partial ->text quMark;
_ -> empty }
<+> printText0 ga t)
printText0 ga (NoSelector t) = printText0 ga t
printText0 ga (NestedComponents l _) = parens $ semis ga l
instance PrettyPrint OpId where
printText0 ga (OpId n ts) = printText0 ga n
<+> fcat(map (printText0 ga) ts)