blob: f18cde5a67d609eeb36b6cf07563fd59fbe9c37d (
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
|
%
% (c) The GRASP/AQUA Project, Glasgow University, 1992-1996
%
\section[HsLit]{Abstract syntax: source-language literals}
\begin{code}
#include "HsVersions.h"
module HsLit where
import Ubiq{-uitous-}
import Pretty
\end{code}
\begin{code}
data HsLit
= HsChar Char -- characters
| HsCharPrim Char -- unboxed char literals
| HsString FAST_STRING -- strings
| HsStringPrim FAST_STRING -- packed string
| HsInt Integer -- integer-looking literals
| HsFrac Rational -- frac-looking literals
-- Up through dict-simplification, HsInt and HsFrac simply
-- mean the literal was integral- or fractional-looking; i.e.,
-- whether it had an explicit decimal-point in it. *After*
-- dict-simplification, they mean (boxed) "Integer" and
-- "Rational" [Ratio Integer], respectively.
-- Dict-simplification tries to replace such lits w/ more
-- specific ones, using the unboxed variants that follow...
| HsIntPrim Integer -- unboxed Int literals
| HsFloatPrim Rational -- unboxed Float literals
| HsDoublePrim Rational -- unboxed Double literals
| HsLitLit FAST_STRING -- to pass ``literal literals'' through to C
-- also: "overloaded" type; but
-- must resolve to boxed-primitive!
-- (WDP 94/10)
\end{code}
\begin{code}
negLiteral (HsInt i) = HsInt (-i)
negLiteral (HsFrac f) = HsFrac (-f)
\end{code}
\begin{code}
instance Outputable HsLit where
ppr sty (HsChar c) = ppStr (show c)
ppr sty (HsCharPrim c) = ppBeside (ppStr (show c)) (ppChar '#')
ppr sty (HsString s) = ppStr (show s)
ppr sty (HsStringPrim s) = ppBeside (ppStr (show s)) (ppChar '#')
ppr sty (HsInt i) = ppInteger i
ppr sty (HsFrac f) = ppRational f
ppr sty (HsFloatPrim f) = ppBeside (ppRational f) (ppChar '#')
ppr sty (HsDoublePrim d) = ppBeside (ppRational d) (ppStr "##")
ppr sty (HsIntPrim i) = ppBeside (ppInteger i) (ppChar '#')
ppr sty (HsLitLit s) = ppBesides [ppStr "``", ppPStr s, ppStr "''"]
\end{code}
|