Remove unused imports
[ghc-hetmet.git] / compiler / hsSyn / HsLit.lhs
1 %
2 % (c) The University of Glasgow 2006
3 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
4 %
5 \section[HsLit]{Abstract syntax: source-language literals}
6
7 \begin{code}
8 module HsLit where
9
10 #include "HsVersions.h"
11
12 import {-# SOURCE #-} HsExpr( SyntaxExpr, pprExpr )
13 import HsTypes (PostTcType)
14 import Type     ( Type )
15 import Outputable
16 import FastString
17 \end{code}
18
19
20 %************************************************************************
21 %*                                                                      *
22 \subsection[HsLit]{Literals}
23 %*                                                                      *
24 %************************************************************************
25
26
27 \begin{code}
28 data HsLit
29   = HsChar          Char                -- Character
30   | HsCharPrim      Char                -- 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   | HsWordPrim      Integer             -- Unboxed Word
37   | HsInteger       Integer  Type       -- Genuinely an integer; arises only from TRANSLATION
38                                         --      (overloaded literals are done with HsOverLit)
39   | HsRat           Rational Type       -- Genuinely a rational; arises only from TRANSLATION
40                                         --      (overloaded literals are done with HsOverLit)
41   | HsFloatPrim     Rational            -- Unboxed Float
42   | HsDoublePrim    Rational            -- Unboxed Double
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   (HsWordPrim x1)   == (HsWordPrim x2)   = x1==x2
52   (HsInteger x1 _)  == (HsInteger x2 _)  = x1==x2
53   (HsRat x1 _)      == (HsRat x2 _)      = x1==x2
54   (HsFloatPrim x1)  == (HsFloatPrim x2)  = x1==x2
55   (HsDoublePrim x1) == (HsDoublePrim x2) = x1==x2
56   _                 == _                 = False
57
58 data HsOverLit id       -- An overloaded literal
59   = OverLit {
60         ol_val :: OverLitVal, 
61         ol_rebindable :: Bool,          -- True <=> rebindable syntax
62                                         -- False <=> standard syntax
63         ol_witness :: SyntaxExpr id,    -- Note [Overloaded literal witnesses]
64         ol_type :: PostTcType }
65
66 data OverLitVal
67   = HsIntegral   !Integer       -- Integer-looking literals;
68   | HsFractional !Rational      -- Frac-looking literals
69   | HsIsString   !FastString    -- String-looking literals
70
71 overLitType :: HsOverLit a -> Type
72 overLitType = ol_type
73 \end{code}
74
75 Note [Overloaded literal witnesses]
76 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
77 *Before* type checking, the SyntaxExpr in an HsOverLit is the
78 name of the coercion function, 'fromInteger' or 'fromRational'.
79 *After* type checking, it is a witness for the literal, such as
80         (fromInteger 3) or lit_78
81 This witness should replace the literal.
82
83 This dual role is unusual, because we're replacing 'fromInteger' with 
84 a call to fromInteger.  Reason: it allows commoning up of the fromInteger
85 calls, which wouldn't be possible if the desguarar made the application
86
87 The PostTcType in each branch records the type the overload literal is
88 found to have.
89
90 \begin{code}
91 -- Comparison operations are needed when grouping literals
92 -- for compiling pattern-matching (module MatchLit)
93 instance Eq (HsOverLit id) where
94   (OverLit {ol_val = val1}) == (OverLit {ol_val=val2}) = val1 == val2
95
96 instance Eq OverLitVal where
97   (HsIntegral i1)   == (HsIntegral i2)   = i1 == i2
98   (HsFractional f1) == (HsFractional f2) = f1 == f2
99   (HsIsString s1)   == (HsIsString s2)   = s1 == s2
100   _                 == _                 = False
101
102 instance Ord (HsOverLit id) where
103   compare (OverLit {ol_val=val1}) (OverLit {ol_val=val2}) = val1 `compare` val2
104
105 instance Ord OverLitVal where
106   compare (HsIntegral i1)   (HsIntegral i2)   = i1 `compare` i2
107   compare (HsIntegral _)    (HsFractional _)  = LT
108   compare (HsIntegral _)    (HsIsString _)    = LT
109   compare (HsFractional f1) (HsFractional f2) = f1 `compare` f2
110   compare (HsFractional _)  (HsIntegral _)    = GT
111   compare (HsFractional _)  (HsIsString _)    = LT
112   compare (HsIsString s1)   (HsIsString s2)   = s1 `compare` s2
113   compare (HsIsString _)    (HsIntegral _)    = GT
114   compare (HsIsString _)    (HsFractional _)  = GT
115 \end{code}
116
117 \begin{code}
118 instance Outputable HsLit where
119         -- Use "show" because it puts in appropriate escapes
120     ppr (HsChar c)       = pprHsChar c
121     ppr (HsCharPrim c)   = pprHsChar c <> char '#'
122     ppr (HsString s)     = pprHsString s
123     ppr (HsStringPrim s) = pprHsString s <> char '#'
124     ppr (HsInt i)        = integer i
125     ppr (HsInteger i _)  = integer i
126     ppr (HsRat f _)      = rational f
127     ppr (HsFloatPrim f)  = rational f <> char '#'
128     ppr (HsDoublePrim d) = rational d <> text "##"
129     ppr (HsIntPrim i)    = integer i  <> char '#'
130     ppr (HsWordPrim w)   = integer w  <> text "##"
131
132 -- in debug mode, print the expression that it's resolved to, too
133 instance OutputableBndr id => Outputable (HsOverLit id) where
134   ppr (OverLit {ol_val=val, ol_witness=witness}) 
135         = ppr val <+> (ifPprDebug (parens (pprExpr witness)))
136
137 instance Outputable OverLitVal where
138   ppr (HsIntegral i)   = integer i 
139   ppr (HsFractional f) = rational f
140   ppr (HsIsString s)   = pprHsString s
141 \end{code}