HsLiteral.hs

Plain Haskell source file: HsLiteral.hs

-- $Id: HsLiteral.hs,v 1.4 2001/03/24 02:14:55 moran Exp $

module HsLiteral where

-- import Ratio
import PrettyPrint


data HsLiteral
    = HsInt         Integer
    | HsChar        Char
    | HsString      String
    | HsFrac        Rational
    -- GHC unboxed literals:
    | HsCharPrim    Char
    | HsStringPrim  String
    | HsIntPrim     Integer
    | HsFloatPrim   Rational       -- Why is this not Float?
    | HsDoublePrim  Rational       -- And this not Double?
    -- GHC extension:
    | HsLitLit      String
      deriving (Eq, Show)


instance Printable HsLiteral where
    ppi	(HsInt i)        = ppi i
    ppi	(HsChar c)       = litChar c
    ppi	(HsString s)     = litString s
    ppi	(HsFrac r)       = ppi r
    -- GHC unboxed literals:
    ppi (HsCharPrim c)   = litChar c               <> char '#'
    ppi (HsStringPrim s) = litString s             <> char '#'
    ppi (HsIntPrim i)    = ppi i                   <> char '#'
    ppi (HsFloatPrim r)  = float  (fromRational r) <> char '#'
    ppi (HsDoublePrim r) = double (fromRational r) <> text "##"
    -- GHC extension:
    ppi (HsLitLit s)     = doubleQuotes $ text s

    wrap = ppi

Index