summaryrefslogtreecommitdiff
path: root/compiler/hsSyn/HsLit.lhs
blob: 9d909242794f658a7071b31534228b4f5d4157fc (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
%
% (c) The University of Glasgow 2006
% (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
%
\section[HsLit]{Abstract syntax: source-language literals}

\begin{code}
{-# OPTIONS_GHC -w #-}
-- The above warning supression flag is a temporary kludge.
-- While working on this module you are encouraged to remove it and fix
-- any warnings in the module. See
--     http://hackage.haskell.org/trac/ghc/wiki/WorkingConventions#Warnings
-- for details

module HsLit where

#include "HsVersions.h"

import {-# SOURCE #-} HsExpr( SyntaxExpr )
import Type	( Type )
import Outputable
import FastString
import Ratio	( Rational )
\end{code}


%************************************************************************
%*									*
\subsection[HsLit]{Literals}
%*									*
%************************************************************************


\begin{code}
data HsLit
  = HsChar	    Char		-- Character
  | HsCharPrim	    Char		-- Unboxed character
  | HsString	    FastString		-- String
  | HsStringPrim    FastString		-- Packed string
  | HsInt	    Integer		-- Genuinely an Int; arises from TcGenDeriv, 
					--	and from TRANSLATION
  | HsIntPrim	    Integer		-- Unboxed Int
  | HsInteger	    Integer  Type	-- Genuinely an integer; arises only from TRANSLATION
					-- 	(overloaded literals are done with HsOverLit)
  | HsRat	    Rational Type	-- Genuinely a rational; arises only from TRANSLATION
					-- 	(overloaded literals are done with HsOverLit)
  | HsFloatPrim	    Rational		-- Unboxed Float
  | HsDoublePrim    Rational		-- Unboxed Double

instance Eq HsLit where
  (HsChar x1)	    == (HsChar x2)	 = x1==x2
  (HsCharPrim x1)   == (HsCharPrim x2)	 = x1==x2
  (HsString x1)     == (HsString x2)	 = x1==x2
  (HsStringPrim x1) == (HsStringPrim x2) = x1==x2
  (HsInt x1)	    == (HsInt x2)	 = x1==x2
  (HsIntPrim x1)    == (HsIntPrim x2)    = x1==x2
  (HsInteger x1 _)  == (HsInteger x2 _)  = x1==x2
  (HsRat x1 _)	    == (HsRat x2 _)      = x1==x2
  (HsFloatPrim x1)  == (HsFloatPrim x2)  = x1==x2
  (HsDoublePrim x1) == (HsDoublePrim x2) = x1==x2
  lit1		    == lit2		 = False

data HsOverLit id 	-- An overloaded literal
  = HsIntegral	 Integer  (SyntaxExpr id)	-- Integer-looking literals;
  | HsFractional Rational (SyntaxExpr id)	-- Frac-looking literals
  | HsIsString   FastString (SyntaxExpr id)	-- String-looking literals
  -- Before type checking, the SyntaxExpr is 'fromInteger' or 'fromRational'
  -- After type checking, it is (fromInteger 3) or lit_78; that is,
  -- the expression that should replace the literal.
  -- This is unusual, because we're replacing 'fromInteger' with a call 
  -- to fromInteger.  Reason: it allows commoning up of the fromInteger
  -- calls, which wouldn't be possible if the desguarar made the application

-- Comparison operations are needed when grouping literals
-- for compiling pattern-matching (module MatchLit)
instance Eq (HsOverLit id) where
  (HsIntegral i1 _)   == (HsIntegral i2 _)   = i1 == i2
  (HsFractional f1 _) == (HsFractional f2 _) = f1 == f2
  (HsIsString s1 _)   == (HsIsString s2 _)   = s1 == s2
  l1		      == l2		     = False

instance Ord (HsOverLit id) where
  compare (HsIntegral i1 _)   (HsIntegral i2 _)   = i1 `compare` i2
  compare (HsIntegral _ _)    (HsFractional _ _)  = LT
  compare (HsIntegral _ _)    (HsIsString _ _)    = LT
  compare (HsFractional f1 _) (HsFractional f2 _) = f1 `compare` f2
  compare (HsFractional f1 _) (HsIntegral _ _)    = GT
  compare (HsFractional f1 _) (HsIsString _ _)    = LT
  compare (HsIsString s1 _)   (HsIsString s2 _)   = s1 `compare` s2
  compare (HsIsString s1 _)   (HsIntegral _ _)    = GT
  compare (HsIsString s1 _)   (HsFractional _ _)  = GT
\end{code}

\begin{code}
instance Outputable HsLit where
	-- Use "show" because it puts in appropriate escapes
    ppr (HsChar c)	 = pprHsChar c
    ppr (HsCharPrim c)	 = pprHsChar c <> char '#'
    ppr (HsString s)	 = pprHsString s
    ppr (HsStringPrim s) = pprHsString s <> char '#'
    ppr (HsInt i)	 = integer i
    ppr (HsInteger i _)	 = integer i
    ppr (HsRat f _)	 = rational f
    ppr (HsFloatPrim f)	 = rational f <> char '#'
    ppr (HsDoublePrim d) = rational d <> text "##"
    ppr (HsIntPrim i)	 = integer i  <> char '#'

instance Outputable (HsOverLit id) where
  ppr (HsIntegral i _)   = integer i
  ppr (HsFractional f _) = rational f
  ppr (HsIsString s _)   = pprHsString s
\end{code}