[project @ 2003-12-16 16:24:42 by simonpj]
[ghc-hetmet.git] / ghc / compiler / hsSyn / HsLit.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
3 %
4 \section[HsLit]{Abstract syntax: source-language literals}
5
6 \begin{code}
7 module HsLit where
8
9 #include "HsVersions.h"
10
11 import Type     ( Type )
12 import HsTypes  ( SyntaxName )
13 import Outputable
14 import FastString
15 import Ratio    ( Rational )
16 \end{code}
17
18
19 %************************************************************************
20 %*                                                                      *
21 \subsection[HsLit]{Literals}
22 %*                                                                      *
23 %************************************************************************
24
25
26 \begin{code}
27 data HsLit
28   = HsChar          Char                -- Character
29   | HsCharPrim      Char                -- Unboxed character
30   | HsString        FastString          -- String
31   | HsStringPrim    FastString          -- Packed string
32   | HsInt           Integer             -- Genuinely an Int; arises from TcGenDeriv, 
33                                         --      and from TRANSLATION
34   | HsIntPrim       Integer             -- Unboxed Int
35   | HsInteger       Integer  Type       -- Genuinely an integer; arises only from TRANSLATION
36                                         --      (overloaded literals are done with HsOverLit)
37   | HsRat           Rational Type       -- Genuinely a rational; arises only from TRANSLATION
38                                         --      (overloaded literals are done with HsOverLit)
39   | HsFloatPrim     Rational            -- Unboxed Float
40   | HsDoublePrim    Rational            -- Unboxed Double
41
42 instance Eq HsLit where
43   (HsChar x1)       == (HsChar x2)       = x1==x2
44   (HsCharPrim x1)   == (HsCharPrim x2)   = x1==x2
45   (HsString x1)     == (HsString x2)     = x1==x2
46   (HsStringPrim x1) == (HsStringPrim x2) = x1==x2
47   (HsInt x1)        == (HsInt x2)        = x1==x2
48   (HsIntPrim x1)    == (HsIntPrim x2)    = x1==x2
49   (HsInteger x1 _)  == (HsInteger x2 _)  = x1==x2
50   (HsRat x1 _)      == (HsRat x2 _)      = x1==x2
51   (HsFloatPrim x1)  == (HsFloatPrim x2)  = x1==x2
52   (HsDoublePrim x1) == (HsDoublePrim x2) = x1==x2
53   lit1              == lit2              = False
54
55 data HsOverLit                  -- An overloaded literal
56   = HsIntegral      Integer  SyntaxName -- Integer-looking literals;
57                                         -- The name is fromInteger
58   | HsFractional    Rational SyntaxName -- Frac-looking literals
59                                         -- The name is fromRational
60
61 -- Comparison operations are needed when grouping literals
62 -- for compiling pattern-matching (module MatchLit)
63 instance Eq HsOverLit where
64   (HsIntegral i1 _)   == (HsIntegral i2 _)   = i1 == i2
65   (HsFractional f1 _) == (HsFractional f2 _) = f1 == f2
66   l1                  == l2                  = False
67
68 instance Ord HsOverLit where
69   compare (HsIntegral i1 _)   (HsIntegral i2 _)   = i1 `compare` i2
70   compare (HsIntegral _ _)    (HsFractional _ _)  = LT
71   compare (HsFractional f1 _) (HsFractional f2 _) = f1 `compare` f2
72   compare (HsFractional f1 _) (HsIntegral _ _)    = GT
73 \end{code}
74
75 \begin{code}
76 instance Outputable HsLit where
77         -- Use "show" because it puts in appropriate escapes
78     ppr (HsChar c)       = pprHsChar c
79     ppr (HsCharPrim c)   = pprHsChar c <> char '#'
80     ppr (HsString s)     = pprHsString s
81     ppr (HsStringPrim s) = pprHsString s <> char '#'
82     ppr (HsInt i)        = integer i
83     ppr (HsInteger i _)  = integer i
84     ppr (HsRat f _)      = rational f
85     ppr (HsFloatPrim f)  = rational f <> char '#'
86     ppr (HsDoublePrim d) = rational d <> text "##"
87     ppr (HsIntPrim i)    = integer i  <> char '#'
88
89 instance Outputable HsOverLit where
90   ppr (HsIntegral i _)   = integer i
91   ppr (HsFractional f _) = rational f
92 \end{code}