Use OPTIONS rather than OPTIONS_GHC for pragmas
[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/CodingStyle#Warnings
13 -- for details
14
15 module HsLit where
16
17 #include "HsVersions.h"
18
19 import {-# SOURCE #-} HsExpr( SyntaxExpr )
20 import Type     ( Type )
21 import Outputable
22 import FastString
23 import Ratio    ( Rational )
24 \end{code}
25
26
27 %************************************************************************
28 %*                                                                      *
29 \subsection[HsLit]{Literals}
30 %*                                                                      *
31 %************************************************************************
32
33
34 \begin{code}
35 data HsLit
36   = HsChar          Char                -- Character
37   | HsCharPrim      Char                -- Unboxed character
38   | HsString        FastString          -- String
39   | HsStringPrim    FastString          -- Packed string
40   | HsInt           Integer             -- Genuinely an Int; arises from TcGenDeriv, 
41                                         --      and from TRANSLATION
42   | HsIntPrim       Integer             -- Unboxed Int
43   | HsInteger       Integer  Type       -- Genuinely an integer; arises only from TRANSLATION
44                                         --      (overloaded literals are done with HsOverLit)
45   | HsRat           Rational Type       -- Genuinely a rational; arises only from TRANSLATION
46                                         --      (overloaded literals are done with HsOverLit)
47   | HsFloatPrim     Rational            -- Unboxed Float
48   | HsDoublePrim    Rational            -- Unboxed Double
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   (HsInteger x1 _)  == (HsInteger x2 _)  = x1==x2
58   (HsRat x1 _)      == (HsRat x2 _)      = x1==x2
59   (HsFloatPrim x1)  == (HsFloatPrim x2)  = x1==x2
60   (HsDoublePrim x1) == (HsDoublePrim x2) = x1==x2
61   lit1              == lit2              = False
62
63 data HsOverLit id       -- An overloaded literal
64   = HsIntegral   Integer  (SyntaxExpr id)       -- Integer-looking literals;
65   | HsFractional Rational (SyntaxExpr id)       -- Frac-looking literals
66   | HsIsString   FastString (SyntaxExpr id)     -- String-looking literals
67   -- Before type checking, the SyntaxExpr is 'fromInteger' or 'fromRational'
68   -- After type checking, it is (fromInteger 3) or lit_78; that is,
69   -- the expression that should replace the literal.
70   -- This is unusual, because we're replacing 'fromInteger' with a call 
71   -- to fromInteger.  Reason: it allows commoning up of the fromInteger
72   -- calls, which wouldn't be possible if the desguarar made the application
73
74 -- Comparison operations are needed when grouping literals
75 -- for compiling pattern-matching (module MatchLit)
76 instance Eq (HsOverLit id) where
77   (HsIntegral i1 _)   == (HsIntegral i2 _)   = i1 == i2
78   (HsFractional f1 _) == (HsFractional f2 _) = f1 == f2
79   (HsIsString s1 _)   == (HsIsString s2 _)   = s1 == s2
80   l1                  == l2                  = False
81
82 instance Ord (HsOverLit id) where
83   compare (HsIntegral i1 _)   (HsIntegral i2 _)   = i1 `compare` i2
84   compare (HsIntegral _ _)    (HsFractional _ _)  = LT
85   compare (HsIntegral _ _)    (HsIsString _ _)    = LT
86   compare (HsFractional f1 _) (HsFractional f2 _) = f1 `compare` f2
87   compare (HsFractional f1 _) (HsIntegral _ _)    = GT
88   compare (HsFractional f1 _) (HsIsString _ _)    = LT
89   compare (HsIsString s1 _)   (HsIsString s2 _)   = s1 `compare` s2
90   compare (HsIsString s1 _)   (HsIntegral _ _)    = GT
91   compare (HsIsString s1 _)   (HsFractional _ _)  = GT
92 \end{code}
93
94 \begin{code}
95 instance Outputable HsLit where
96         -- Use "show" because it puts in appropriate escapes
97     ppr (HsChar c)       = pprHsChar c
98     ppr (HsCharPrim c)   = pprHsChar c <> char '#'
99     ppr (HsString s)     = pprHsString s
100     ppr (HsStringPrim s) = pprHsString s <> char '#'
101     ppr (HsInt i)        = integer i
102     ppr (HsInteger i _)  = integer i
103     ppr (HsRat f _)      = rational f
104     ppr (HsFloatPrim f)  = rational f <> char '#'
105     ppr (HsDoublePrim d) = rational d <> text "##"
106     ppr (HsIntPrim i)    = integer i  <> char '#'
107
108 instance Outputable (HsOverLit id) where
109   ppr (HsIntegral i _)   = integer i
110   ppr (HsFractional f _) = rational f
111   ppr (HsIsString s _)   = pprHsString s
112 \end{code}