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