Whitespace only in nativeGen/RegAlloc/Linear/Main.hs
[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 {-# LANGUAGE DeriveDataTypeable #-}
9
10 module HsLit where
11
12 #include "HsVersions.h"
13
14 import {-# SOURCE #-} HsExpr( SyntaxExpr, pprExpr )
15 import BasicTypes ( FractionalLit(..) )
16 import HsTypes  ( PostTcType )
17 import Type     ( Type )
18 import Outputable
19 import FastString
20
21 import Data.Data
22 \end{code}
23
24
25 %************************************************************************
26 %*                                                                      *
27 \subsection[HsLit]{Literals}
28 %*                                                                      *
29 %************************************************************************
30
31
32 \begin{code}
33 data HsLit
34   = HsChar          Char                -- Character
35   | HsCharPrim      Char                -- Unboxed character
36   | HsString        FastString          -- String
37   | HsStringPrim    FastString          -- Packed string
38   | HsInt           Integer             -- Genuinely an Int; arises from TcGenDeriv, 
39                                         --      and from TRANSLATION
40   | HsIntPrim       Integer             -- Unboxed Int
41   | HsWordPrim      Integer             -- Unboxed Word
42   | HsInteger       Integer  Type       -- Genuinely an integer; arises only from TRANSLATION
43                                         --      (overloaded literals are done with HsOverLit)
44   | HsRat           FractionalLit Type  -- Genuinely a rational; arises only from TRANSLATION
45                                         --      (overloaded literals are done with HsOverLit)
46   | HsFloatPrim     FractionalLit       -- Unboxed Float
47   | HsDoublePrim    FractionalLit       -- Unboxed Double
48   deriving (Data, Typeable)
49
50 instance Eq HsLit where
51   (HsChar x1)       == (HsChar x2)       = x1==x2
52   (HsCharPrim x1)   == (HsCharPrim x2)   = x1==x2
53   (HsString x1)     == (HsString x2)     = x1==x2
54   (HsStringPrim x1) == (HsStringPrim x2) = x1==x2
55   (HsInt x1)        == (HsInt x2)        = x1==x2
56   (HsIntPrim x1)    == (HsIntPrim x2)    = x1==x2
57   (HsWordPrim x1)   == (HsWordPrim x2)   = x1==x2
58   (HsInteger x1 _)  == (HsInteger x2 _)  = x1==x2
59   (HsRat x1 _)      == (HsRat x2 _)      = x1==x2
60   (HsFloatPrim x1)  == (HsFloatPrim x2)  = x1==x2
61   (HsDoublePrim x1) == (HsDoublePrim x2) = x1==x2
62   _                 == _                 = False
63
64 data HsOverLit id       -- An overloaded literal
65   = OverLit {
66         ol_val :: OverLitVal, 
67         ol_rebindable :: Bool,          -- Note [ol_rebindable]
68         ol_witness :: SyntaxExpr id,    -- Note [Overloaded literal witnesses]
69         ol_type :: PostTcType }
70   deriving (Data, Typeable)
71
72 data OverLitVal
73   = HsIntegral   !Integer       -- Integer-looking literals;
74   | HsFractional !FractionalLit -- Frac-looking literals
75   | HsIsString   !FastString    -- String-looking literals
76   deriving (Data, Typeable)
77
78 overLitType :: HsOverLit a -> Type
79 overLitType = ol_type
80 \end{code}
81
82 Note [ol_rebindable]
83 ~~~~~~~~~~~~~~~~~~~~
84 The ol_rebindable field is True if this literal is actually 
85 using rebindable syntax.  Specifically:
86
87   False iff ol_witness is the standard one
88   True  iff ol_witness is non-standard
89
90 Equivalently it's True if
91   a) RebindableSyntax is on
92   b) the witness for fromInteger/fromRational/fromString
93      that happens to be in scope isn't the standard one
94
95 Note [Overloaded literal witnesses]
96 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
97 *Before* type checking, the SyntaxExpr in an HsOverLit is the
98 name of the coercion function, 'fromInteger' or 'fromRational'.
99 *After* type checking, it is a witness for the literal, such as
100         (fromInteger 3) or lit_78
101 This witness should replace the literal.
102
103 This dual role is unusual, because we're replacing 'fromInteger' with 
104 a call to fromInteger.  Reason: it allows commoning up of the fromInteger
105 calls, which wouldn't be possible if the desguarar made the application.
106
107 The PostTcType in each branch records the type the overload literal is
108 found to have.
109
110 \begin{code}
111 -- Comparison operations are needed when grouping literals
112 -- for compiling pattern-matching (module MatchLit)
113 instance Eq (HsOverLit id) where
114   (OverLit {ol_val = val1}) == (OverLit {ol_val=val2}) = val1 == val2
115
116 instance Eq OverLitVal where
117   (HsIntegral i1)   == (HsIntegral i2)   = i1 == i2
118   (HsFractional f1) == (HsFractional f2) = f1 == f2
119   (HsIsString s1)   == (HsIsString s2)   = s1 == s2
120   _                 == _                 = False
121
122 instance Ord (HsOverLit id) where
123   compare (OverLit {ol_val=val1}) (OverLit {ol_val=val2}) = val1 `compare` val2
124
125 instance Ord OverLitVal where
126   compare (HsIntegral i1)   (HsIntegral i2)   = i1 `compare` i2
127   compare (HsIntegral _)    (HsFractional _)  = LT
128   compare (HsIntegral _)    (HsIsString _)    = LT
129   compare (HsFractional f1) (HsFractional f2) = f1 `compare` f2
130   compare (HsFractional _)  (HsIntegral _)    = GT
131   compare (HsFractional _)  (HsIsString _)    = LT
132   compare (HsIsString s1)   (HsIsString s2)   = s1 `compare` s2
133   compare (HsIsString _)    (HsIntegral _)    = GT
134   compare (HsIsString _)    (HsFractional _)  = GT
135 \end{code}
136
137 \begin{code}
138 instance Outputable HsLit where
139         -- Use "show" because it puts in appropriate escapes
140     ppr (HsChar c)       = pprHsChar c
141     ppr (HsCharPrim c)   = pprHsChar c <> char '#'
142     ppr (HsString s)     = pprHsString s
143     ppr (HsStringPrim s) = pprHsString s <> char '#'
144     ppr (HsInt i)        = integer i
145     ppr (HsInteger i _)  = integer i
146     ppr (HsRat f _)      = ppr f
147     ppr (HsFloatPrim f)  = ppr f <> char '#'
148     ppr (HsDoublePrim d) = ppr d <> text "##"
149     ppr (HsIntPrim i)    = integer i  <> char '#'
150     ppr (HsWordPrim w)   = integer w  <> text "##"
151
152 -- in debug mode, print the expression that it's resolved to, too
153 instance OutputableBndr id => Outputable (HsOverLit id) where
154   ppr (OverLit {ol_val=val, ol_witness=witness}) 
155         = ppr val <+> (ifPprDebug (parens (pprExpr witness)))
156
157 instance Outputable OverLitVal where
158   ppr (HsIntegral i)   = integer i 
159   ppr (HsFractional f) = ppr f
160   ppr (HsIsString s)   = pprHsString s
161 \end{code}