[project @ 1997-03-14 07:52:06 by simonpj]
[ghc-hetmet.git] / ghc / compiler / hsSyn / HsBasic.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1996
3 %
4 \section[HsLit]{Abstract syntax: source-language literals}
5
6 \begin{code}
7 #include "HsVersions.h"
8
9 module HsBasic where
10
11 IMP_Ubiq(){-uitous-}
12 IMPORT_1_3(Ratio(Rational))
13
14 import Pretty
15 \end{code}
16
17 %************************************************************************
18 %*                                                                      *
19 \subsection[Version]{Module and identifier version numbers}
20 %*                                                                      *
21 %************************************************************************
22
23 \begin{code}
24 type Version = Int
25 \end{code}
26
27 %************************************************************************
28 %*                                                                      *
29 \subsection[HsLit]{Literals}
30 %*                                                                      *
31 %************************************************************************
32
33
34 \begin{code}
35 data HsLit
36   = HsChar          Char        -- characters
37   | HsCharPrim      Char        -- unboxed char literals
38   | HsString        FAST_STRING -- strings
39   | HsStringPrim    FAST_STRING -- packed string
40
41   | HsInt           Integer     -- integer-looking literals
42   | HsFrac          Rational    -- frac-looking literals
43         -- Up through dict-simplification, HsInt and HsFrac simply
44         -- mean the literal was integral- or fractional-looking; i.e.,
45         -- whether it had an explicit decimal-point in it.  *After*
46         -- dict-simplification, they mean (boxed) "Integer" and
47         -- "Rational" [Ratio Integer], respectively.
48
49         -- Dict-simplification tries to replace such lits w/ more
50         -- specific ones, using the unboxed variants that follow...
51   | HsIntPrim       Integer     -- unboxed Int literals
52   | HsFloatPrim     Rational    -- unboxed Float literals
53   | HsDoublePrim    Rational    -- unboxed Double literals
54
55   | HsLitLit        FAST_STRING -- to pass ``literal literals'' through to C
56                                 -- also: "overloaded" type; but
57                                 -- must resolve to boxed-primitive!
58                                 -- (WDP 94/10)
59 \end{code}
60
61 \begin{code}
62 negLiteral (HsInt  i) = HsInt  (-i)
63 negLiteral (HsFrac f) = HsFrac (-f)
64 \end{code}
65
66 \begin{code}
67 instance Outputable HsLit where
68     ppr sty (HsChar c)          = ppStr (show c)
69     ppr sty (HsCharPrim c)      = ppBeside (ppStr (show c)) (ppChar '#')
70     ppr sty (HsString s)        = ppStr (show s)
71     ppr sty (HsStringPrim s)    = ppBeside (ppStr (show s)) (ppChar '#')
72     ppr sty (HsInt i)           = ppInteger i
73     ppr sty (HsFrac f)          = ppRational f
74     ppr sty (HsFloatPrim f)     = ppBeside (ppRational f) (ppChar '#')
75     ppr sty (HsDoublePrim d)    = ppBeside (ppRational d) (ppStr "##")
76     ppr sty (HsIntPrim i)       = ppBeside (ppInteger i) (ppChar '#')
77     ppr sty (HsLitLit s)        = ppBesides [ppStr "``", ppPStr s, ppStr "''"]
78 \end{code}
79
80 %************************************************************************
81 %*                                                                      *
82 \subsection[Fixity]{Fixity info}
83 %*                                                                      *
84 %************************************************************************
85
86 \begin{code}
87 data Fixity = Fixity Int FixityDirection
88 data FixityDirection = InfixL | InfixR | InfixN 
89                      deriving(Eq)
90
91 instance Outputable Fixity where
92     ppr sty (Fixity prec dir) = ppBesides [ppr sty dir, ppSP, ppInt prec]
93
94 instance Outputable FixityDirection where
95     ppr sty InfixL = ppPStr SLIT("infixl")
96     ppr sty InfixR = ppPStr SLIT("infixr")
97     ppr sty InfixN = ppPStr SLIT("infix")
98
99 instance Eq Fixity where                -- Used to determine if two fixities conflict
100   (Fixity p1 dir1) == (Fixity p2 dir2) = p1==p2 && dir1 == dir2
101 \end{code}
102