View patterns, record wildcards, and record puns
[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 {-# OPTIONS -w #-}
9 -- The above warning supression flag is a temporary kludge.
10 -- While working on this module you are encouraged to remove it and fix
11 -- any warnings in the module. See
12 --     http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#Warnings
13 -- for details
14
15 module HsLit where
16
17 #include "HsVersions.h"
18
19 import {-# SOURCE #-} HsExpr( SyntaxExpr, pprExpr )
20 import HsTypes (PostTcType)
21 import Type     ( Type )
22 import Outputable
23 import FastString
24 import Ratio    ( Rational )
25 \end{code}
26
27
28 %************************************************************************
29 %*                                                                      *
30 \subsection[HsLit]{Literals}
31 %*                                                                      *
32 %************************************************************************
33
34
35 \begin{code}
36 data HsLit
37   = HsChar          Char                -- Character
38   | HsCharPrim      Char                -- Unboxed character
39   | HsString        FastString          -- String
40   | HsStringPrim    FastString          -- Packed string
41   | HsInt           Integer             -- Genuinely an Int; arises from TcGenDeriv, 
42                                         --      and from TRANSLATION
43   | HsIntPrim       Integer             -- Unboxed Int
44   | HsInteger       Integer  Type       -- Genuinely an integer; arises only from TRANSLATION
45                                         --      (overloaded literals are done with HsOverLit)
46   | HsRat           Rational Type       -- Genuinely a rational; arises only from TRANSLATION
47                                         --      (overloaded literals are done with HsOverLit)
48   | HsFloatPrim     Rational            -- Unboxed Float
49   | HsDoublePrim    Rational            -- Unboxed Double
50
51 instance Eq HsLit where
52   (HsChar x1)       == (HsChar x2)       = x1==x2
53   (HsCharPrim x1)   == (HsCharPrim x2)   = x1==x2
54   (HsString x1)     == (HsString x2)     = x1==x2
55   (HsStringPrim x1) == (HsStringPrim x2) = x1==x2
56   (HsInt x1)        == (HsInt x2)        = x1==x2
57   (HsIntPrim x1)    == (HsIntPrim 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   lit1              == lit2              = False
63
64 data HsOverLit id       -- An overloaded literal
65   = HsIntegral   Integer    (SyntaxExpr id)  PostTcType -- Integer-looking literals;
66   | HsFractional Rational   (SyntaxExpr id)  PostTcType -- Frac-looking literals
67   | HsIsString   FastString (SyntaxExpr id)  PostTcType -- String-looking literals
68   -- Before type checking, the SyntaxExpr is 'fromInteger' or 'fromRational'
69   -- After type checking, it is (fromInteger 3) or lit_78; that is,
70   -- the expression that should replace the literal.
71   -- This is unusual, because we're replacing 'fromInteger' with a call 
72   -- to fromInteger.  Reason: it allows commoning up of the fromInteger
73   -- calls, which wouldn't be possible if the desguarar made the application
74   --
75   -- The PostTcType in each branch records the type the overload literal is
76   -- found to have.
77
78 overLitExpr :: HsOverLit id -> SyntaxExpr id
79 overLitExpr (HsIntegral _ e _) = e
80 overLitExpr (HsFractional _ e _) = e
81 overLitExpr (HsIsString _ e _) = e
82
83 overLitType :: HsOverLit id -> PostTcType
84 overLitType (HsIntegral _ _ t) = t
85 overLitType (HsFractional _ _ t) = t
86 overLitType (HsIsString _ _ t) = t
87
88
89 -- Comparison operations are needed when grouping literals
90 -- for compiling pattern-matching (module MatchLit)
91 instance Eq (HsOverLit id) where
92   (HsIntegral i1 _ _)   == (HsIntegral i2 _ _)   = i1 == i2
93   (HsFractional f1 _ _) == (HsFractional f2 _ _) = f1 == f2
94   (HsIsString s1 _ _)   == (HsIsString s2 _ _)   = s1 == s2
95   l1                  == l2                  = False
96
97 instance Ord (HsOverLit id) where
98   compare (HsIntegral i1 _ _)   (HsIntegral i2 _ _)   = i1 `compare` i2
99   compare (HsIntegral _ _ _)    (HsFractional _ _ _)  = LT
100   compare (HsIntegral _ _ _)    (HsIsString _ _ _)    = LT
101   compare (HsFractional f1 _ _) (HsFractional f2 _ _) = f1 `compare` f2
102   compare (HsFractional f1 _ _) (HsIntegral _ _ _)    = GT
103   compare (HsFractional f1 _ _) (HsIsString _ _ _)    = LT
104   compare (HsIsString s1 _ _)   (HsIsString s2 _ _)   = s1 `compare` s2
105   compare (HsIsString s1 _ _)   (HsIntegral _ _ _)    = GT
106   compare (HsIsString s1 _ _)   (HsFractional _ _ _)  = GT
107 \end{code}
108
109 \begin{code}
110 instance Outputable HsLit where
111         -- Use "show" because it puts in appropriate escapes
112     ppr (HsChar c)       = pprHsChar c
113     ppr (HsCharPrim c)   = pprHsChar c <> char '#'
114     ppr (HsString s)     = pprHsString s
115     ppr (HsStringPrim s) = pprHsString s <> char '#'
116     ppr (HsInt i)        = integer i
117     ppr (HsInteger i _)  = integer i
118     ppr (HsRat f _)      = rational f
119     ppr (HsFloatPrim f)  = rational f <> char '#'
120     ppr (HsDoublePrim d) = rational d <> text "##"
121     ppr (HsIntPrim i)    = integer i  <> char '#'
122
123 -- in debug mode, print the expression that it's resolved to, too
124 instance OutputableBndr id => Outputable (HsOverLit id) where
125   ppr (HsIntegral i e _)   = integer i <+> (ifPprDebug (parens (pprExpr e)))
126   ppr (HsFractional f e _) = rational f <+> (ifPprDebug (parens (pprExpr e)))
127   ppr (HsIsString s e _)   = pprHsString s <+> (ifPprDebug (parens (pprExpr e)))
128 \end{code}