[project @ 2001-07-12 16:21:22 by simonpj]
[ghc-hetmet.git] / ghc / compiler / hsSyn / HsLit.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
3 %
4 \section[HsLit]{Abstract syntax: source-language literals}
5
6 \begin{code}
7 module HsLit where
8
9 #include "HsVersions.h"
10
11 import Type     ( Type )
12 import HsTypes  ( PostTcType )
13 import Outputable
14 import Ratio    ( Rational )
15 \end{code}
16
17
18 %************************************************************************
19 %*                                                                      *
20 \subsection[HsLit]{Literals}
21 %*                                                                      *
22 %************************************************************************
23
24
25 \begin{code}
26 data HsLit
27   = HsChar          Int                 -- Character
28   | HsCharPrim      Int                 -- Unboxed character
29   | HsString        FAST_STRING         -- String
30   | HsStringPrim    FAST_STRING         -- Packed string
31   | HsInt           Integer             -- Genuinely an Int; arises from TcGenDeriv, 
32                                         --      and from TRANSLATION
33   | HsIntPrim       Integer             -- Unboxed Int
34   | HsInteger       Integer             -- Genuinely an integer; arises only from TRANSLATION
35   | HsRat           Rational Type       -- Genuinely a rational; arises only from TRANSLATION
36   | HsFloatPrim     Rational            -- Unboxed Float
37   | HsDoublePrim    Rational            -- Unboxed Double
38   | HsLitLit        FAST_STRING PostTcType      -- to pass ``literal literals'' through to C
39                                                 -- also: "overloaded" type; but
40                                                 -- must resolve to boxed-primitive!
41         -- The Type in HsLitLit is needed when desuaring;
42         -- before the typechecker it's just an error value
43
44 instance Eq HsLit where
45   (HsChar x1)       == (HsChar x2)       = x1==x2
46   (HsCharPrim x1)   == (HsCharPrim x2)   = x1==x2
47   (HsString x1)     == (HsString x2)     = x1==x2
48   (HsStringPrim x1) == (HsStringPrim x2) = x1==x2
49   (HsInt x1)        == (HsInt x2)        = x1==x2
50   (HsIntPrim x1)    == (HsIntPrim x2)    = x1==x2
51   (HsInteger x1)    == (HsInteger x2)    = x1==x2
52   (HsRat x1 _)      == (HsRat x2 _)      = x1==x2
53   (HsFloatPrim x1)  == (HsFloatPrim x2)  = x1==x2
54   (HsDoublePrim x1) == (HsDoublePrim x2) = x1==x2
55   (HsLitLit x1 _)   == (HsLitLit x2 _)   = x1==x2
56   lit1              == lit2              = False
57
58 data HsOverLit          -- An overloaded literal
59   = HsIntegral      Integer             -- Integer-looking literals;
60   | HsFractional    Rational            -- Frac-looking literals
61
62 instance Eq HsOverLit where
63   (HsIntegral i1)   == (HsIntegral i2)   = i1 == i2
64   (HsFractional f1) == (HsFractional f2) = f1 == f2
65
66 instance Ord HsOverLit where
67   compare (HsIntegral i1)   (HsIntegral i2)   = i1 `compare` i2
68   compare (HsIntegral _)    (HsFractional _)  = LT
69   compare (HsFractional f1) (HsFractional f2) = f1 `compare` f2
70   compare (HsFractional f1) (HsIntegral _)    = GT
71 \end{code}
72
73 \begin{code}
74 instance Outputable HsLit where
75         -- Use "show" because it puts in appropriate escapes
76     ppr (HsChar c)       = pprHsChar c
77     ppr (HsCharPrim c)   = pprHsChar c <> char '#'
78     ppr (HsString s)     = pprHsString s
79     ppr (HsStringPrim s) = pprHsString s <> char '#'
80     ppr (HsInt i)        = integer i
81     ppr (HsInteger i)    = integer i
82     ppr (HsRat f _)      = rational f
83     ppr (HsFloatPrim f)  = rational f <> char '#'
84     ppr (HsDoublePrim d) = rational d <> text "##"
85     ppr (HsIntPrim i)    = integer i  <> char '#'
86     ppr (HsLitLit s _)   = hcat [text "``", ptext s, text "''"]
87
88 instance Outputable HsOverLit where
89   ppr (HsIntegral i)   = integer i
90   ppr (HsFractional f) = rational f
91 \end{code}
92
93