Add 123## literals for Word#
[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   = HsIntegral   !Integer    (SyntaxExpr id)  PostTcType        -- Integer-looking literals;
61   | HsFractional !Rational   (SyntaxExpr id)  PostTcType        -- Frac-looking literals
62   | HsIsString   !FastString (SyntaxExpr id)  PostTcType        -- String-looking literals
63   -- Before type checking, the SyntaxExpr is 'fromInteger' or 'fromRational'
64   -- After type checking, it is (fromInteger 3) or lit_78; that is,
65   -- the expression that should replace the literal.
66   -- This is unusual, because we're replacing 'fromInteger' with a call 
67   -- to fromInteger.  Reason: it allows commoning up of the fromInteger
68   -- calls, which wouldn't be possible if the desguarar made the application
69   --
70   -- The PostTcType in each branch records the type the overload literal is
71   -- found to have.
72
73 overLitExpr :: HsOverLit id -> SyntaxExpr id
74 overLitExpr (HsIntegral _ e _) = e
75 overLitExpr (HsFractional _ e _) = e
76 overLitExpr (HsIsString _ e _) = e
77
78 overLitType :: HsOverLit id -> PostTcType
79 overLitType (HsIntegral _ _ t) = t
80 overLitType (HsFractional _ _ t) = t
81 overLitType (HsIsString _ _ t) = t
82
83
84 -- Comparison operations are needed when grouping literals
85 -- for compiling pattern-matching (module MatchLit)
86 instance Eq (HsOverLit id) where
87   (HsIntegral i1 _ _)   == (HsIntegral i2 _ _)   = i1 == i2
88   (HsFractional f1 _ _) == (HsFractional f2 _ _) = f1 == f2
89   (HsIsString s1 _ _)   == (HsIsString s2 _ _)   = s1 == s2
90   _                     == _                     = False
91
92 instance Ord (HsOverLit id) where
93   compare (HsIntegral i1 _ _)   (HsIntegral i2 _ _)   = i1 `compare` i2
94   compare (HsIntegral _ _ _)    (HsFractional _ _ _)  = LT
95   compare (HsIntegral _ _ _)    (HsIsString _ _ _)    = LT
96   compare (HsFractional f1 _ _) (HsFractional f2 _ _) = f1 `compare` f2
97   compare (HsFractional _ _ _)  (HsIntegral _ _ _)    = GT
98   compare (HsFractional _ _ _)  (HsIsString _ _ _)    = LT
99   compare (HsIsString s1 _ _)   (HsIsString s2 _ _)   = s1 `compare` s2
100   compare (HsIsString _ _ _)    (HsIntegral _ _ _)    = GT
101   compare (HsIsString _ _ _)    (HsFractional _ _ _)  = GT
102 \end{code}
103
104 \begin{code}
105 instance Outputable HsLit where
106         -- Use "show" because it puts in appropriate escapes
107     ppr (HsChar c)       = pprHsChar c
108     ppr (HsCharPrim c)   = pprHsChar c <> char '#'
109     ppr (HsString s)     = pprHsString s
110     ppr (HsStringPrim s) = pprHsString s <> char '#'
111     ppr (HsInt i)        = integer i
112     ppr (HsInteger i _)  = integer i
113     ppr (HsRat f _)      = rational f
114     ppr (HsFloatPrim f)  = rational f <> char '#'
115     ppr (HsDoublePrim d) = rational d <> text "##"
116     ppr (HsIntPrim i)    = integer i  <> char '#'
117     ppr (HsWordPrim w)   = integer w  <> text "##"
118
119 -- in debug mode, print the expression that it's resolved to, too
120 instance OutputableBndr id => Outputable (HsOverLit id) where
121   ppr (HsIntegral i e _)   = integer i <+> (ifPprDebug (parens (pprExpr e)))
122   ppr (HsFractional f e _) = rational f <+> (ifPprDebug (parens (pprExpr e)))
123   ppr (HsIsString s e _)   = pprHsString s <+> (ifPprDebug (parens (pprExpr e)))
124 \end{code}