[project @ 2001-01-11 13:58:05 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 Outputable
13 import Ratio    ( Rational )
14 \end{code}
15
16
17 %************************************************************************
18 %*                                                                      *
19 \subsection[HsLit]{Literals}
20 %*                                                                      *
21 %************************************************************************
22
23
24 \begin{code}
25 data HsLit
26   = HsChar          Int                 -- Character
27   | HsCharPrim      Int                 -- Unboxed character
28   | HsString        FAST_STRING         -- String
29   | HsStringPrim    FAST_STRING         -- Packed string
30   | HsInt           Integer             -- Genuinely an Int; arises from TcGenDeriv, 
31                                         --      and from TRANSLATION
32   | HsIntPrim       Integer             -- Unboxed Int
33   | HsInteger       Integer             -- Genuinely an integer; arises only from TRANSLATION
34   | HsRat           Rational Type       -- Genuinely a rational; arises only from TRANSLATION
35   | HsFloatPrim     Rational            -- Unboxed Float
36   | HsDoublePrim    Rational            -- Unboxed Double
37   | HsLitLit        FAST_STRING Type    -- to pass ``literal literals'' through to C
38                                         -- also: "overloaded" type; but
39                                         -- must resolve to boxed-primitive!
40         -- The Type in HsLitLit is needed when desuaring;
41         -- before the typechecker it's just an error value
42   deriving( Eq )
43
44 data HsOverLit name     -- An overloaded literal
45   = HsIntegral      Integer name        -- Integer-looking literals;
46                                         -- The names is "fromInteger"
47   | HsFractional    Rational name       -- Frac-looking literals
48                                         -- The name is "fromRational"
49
50 instance Eq (HsOverLit name) where
51   (HsIntegral i1 _)   == (HsIntegral i2 _)   = i1 == i2
52   (HsFractional f1 _) == (HsFractional f2 _) = f1 == f2
53
54 instance Ord (HsOverLit name) where
55   compare (HsIntegral i1 _)   (HsIntegral i2 _)   = i1 `compare` i2
56   compare (HsIntegral _ _)    (HsFractional _ _)  = LT
57   compare (HsFractional f1 _) (HsFractional f2 _) = f1 `compare` f2
58   compare (HsFractional f1 _) (HsIntegral _ _)    = GT
59 \end{code}
60
61 \begin{code}
62 instance Outputable HsLit where
63         -- Use "show" because it puts in appropriate escapes
64     ppr (HsChar c)       = pprHsChar c
65     ppr (HsCharPrim c)   = pprHsChar c <> char '#'
66     ppr (HsString s)     = pprHsString s
67     ppr (HsStringPrim s) = pprHsString s <> char '#'
68     ppr (HsInt i)        = integer i
69     ppr (HsInteger i)    = integer i
70     ppr (HsRat f _)      = rational f
71     ppr (HsFloatPrim f)  = rational f <> char '#'
72     ppr (HsDoublePrim d) = rational d <> text "##"
73     ppr (HsIntPrim i)    = integer i  <> char '#'
74     ppr (HsLitLit s _)   = hcat [text "``", ptext s, text "''"]
75
76 instance Outputable (HsOverLit name) where
77   ppr (HsIntegral i _)   = integer i
78   ppr (HsFractional f _) = rational f
79 \end{code}
80
81