summaryrefslogtreecommitdiff
path: root/compiler/hsSyn/HsLit.hs
diff options
context:
space:
mode:
Diffstat (limited to 'compiler/hsSyn/HsLit.hs')
-rw-r--r--compiler/hsSyn/HsLit.hs43
1 files changed, 24 insertions, 19 deletions
diff --git a/compiler/hsSyn/HsLit.hs b/compiler/hsSyn/HsLit.hs
index 4cf571917c..e513fe9e00 100644
--- a/compiler/hsSyn/HsLit.hs
+++ b/compiler/hsSyn/HsLit.hs
@@ -19,11 +19,11 @@ module HsLit where
#include "HsVersions.h"
import {-# SOURCE #-} HsExpr( HsExpr, pprExpr )
-import BasicTypes ( FractionalLit(..),SourceText )
+import BasicTypes ( FractionalLit(..),SourceText(..),pprWithSourceText )
import Type ( Type )
import Outputable
import FastString
-import PlaceHolder ( PostTc,PostRn,DataId,OutputableBndrId )
+import PlaceHolder ( PostTc,PostRn,DataId,OutputableBndrId, HasOccNameId )
import Data.ByteString (ByteString)
import Data.Data hiding ( Fixity )
@@ -166,29 +166,34 @@ instance Ord OverLitVal where
compare (HsIsString _ _) (HsFractional _) = GT
instance Outputable HsLit where
- ppr (HsChar _ c) = pprHsChar c
- ppr (HsCharPrim _ c) = pprPrimChar c
- ppr (HsString _ s) = pprHsString s
- ppr (HsStringPrim _ s) = pprHsBytes s
- ppr (HsInt _ i) = integer i
- ppr (HsInteger _ i _) = integer i
- ppr (HsRat f _) = ppr f
- ppr (HsFloatPrim f) = ppr f <> primFloatSuffix
- ppr (HsDoublePrim d) = ppr d <> primDoubleSuffix
- ppr (HsIntPrim _ i) = pprPrimInt i
- ppr (HsWordPrim _ w) = pprPrimWord w
- ppr (HsInt64Prim _ i) = pprPrimInt64 i
- ppr (HsWord64Prim _ w) = pprPrimWord64 w
+ ppr (HsChar st c) = pprWithSourceText st (pprHsChar c)
+ ppr (HsCharPrim st c) = pp_st_suffix st primCharSuffix (pprPrimChar c)
+ ppr (HsString st s) = pprWithSourceText st (pprHsString s)
+ ppr (HsStringPrim st s) = pprWithSourceText st (pprHsBytes s)
+ ppr (HsInt st i) = pprWithSourceText st (integer i)
+ ppr (HsInteger st i _) = pprWithSourceText st (integer i)
+ ppr (HsRat f _) = ppr f
+ ppr (HsFloatPrim f) = ppr f <> primFloatSuffix
+ ppr (HsDoublePrim d) = ppr d <> primDoubleSuffix
+ ppr (HsIntPrim st i) = pprWithSourceText st (pprPrimInt i)
+ ppr (HsWordPrim st w) = pprWithSourceText st (pprPrimWord w)
+ ppr (HsInt64Prim st i) = pp_st_suffix st primInt64Suffix (pprPrimInt64 i)
+ ppr (HsWord64Prim st w) = pp_st_suffix st primWord64Suffix (pprPrimWord64 w)
+
+pp_st_suffix :: SourceText -> SDoc -> SDoc -> SDoc
+pp_st_suffix NoSourceText _ doc = doc
+pp_st_suffix (SourceText st) suffix _ = text st <> suffix
-- in debug mode, print the expression that it's resolved to, too
-instance (OutputableBndrId id) => Outputable (HsOverLit id) where
+instance (OutputableBndrId id, HasOccNameId id)
+ => Outputable (HsOverLit id) where
ppr (OverLit {ol_val=val, ol_witness=witness})
= ppr val <+> (ifPprDebug (parens (pprExpr witness)))
instance Outputable OverLitVal where
- ppr (HsIntegral _ i) = integer i
+ ppr (HsIntegral st i) = pprWithSourceText st (integer i)
ppr (HsFractional f) = ppr f
- ppr (HsIsString _ s) = pprHsString s
+ ppr (HsIsString st s) = pprWithSourceText st (pprHsString s)
-- | pmPprHsLit pretty prints literals and is used when pretty printing pattern
-- match warnings. All are printed the same (i.e., without hashes if they are
@@ -199,7 +204,7 @@ instance Outputable OverLitVal where
pmPprHsLit :: HsLit -> SDoc
pmPprHsLit (HsChar _ c) = pprHsChar c
pmPprHsLit (HsCharPrim _ c) = pprHsChar c
-pmPprHsLit (HsString _ s) = pprHsString s
+pmPprHsLit (HsString st s) = pprWithSourceText st (pprHsString s)
pmPprHsLit (HsStringPrim _ s) = pprHsBytes s
pmPprHsLit (HsInt _ i) = integer i
pmPprHsLit (HsIntPrim _ i) = integer i