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