Ah, could we, please, merge this to stable?
On 6/19/2012 18:54, Paolo Capriotti wrote:
Repository : ssh://darcs.haskell.org//srv/darcs/packages/template-haskell
On branch : master
http://hackage.haskell.org/trac/ghc/changeset/82291b03b45b4a72ed98419e1893cd74c2e420ca
---------------------------------------------------------------
commit 82291b03b45b4a72ed98419e1893cd74c2e420ca
Author: Reiner Pope <[email protected]>
Date: Thu Feb 16 10:58:28 2012 +1100
StringPrimL now takes [Word8]
---------------------------------------------------------------
Language/Haskell/TH/Lib.hs | 3 ++-
Language/Haskell/TH/Ppr.hs | 8 ++++++--
Language/Haskell/TH/Syntax.hs | 3 ++-
3 files changed, 10 insertions(+), 4 deletions(-)
diff --git a/Language/Haskell/TH/Lib.hs b/Language/Haskell/TH/Lib.hs
index abb070f..dabad62 100644
--- a/Language/Haskell/TH/Lib.hs
+++ b/Language/Haskell/TH/Lib.hs
@@ -9,6 +9,7 @@ module Language.Haskell.TH.Lib where
import Language.Haskell.TH.Syntax
import Control.Monad( liftM, liftM2 )
+import Data.Word( Word8 )
----------------------------------------------------------
-- * Type synonyms
@@ -54,7 +55,7 @@ charL :: Char -> Lit
charL = CharL
stringL :: String -> Lit
stringL = StringL
-stringPrimL :: String -> Lit
+stringPrimL :: [Word8] -> Lit
stringPrimL = StringPrimL
rationalL :: Rational -> Lit
rationalL = RationalL
diff --git a/Language/Haskell/TH/Ppr.hs b/Language/Haskell/TH/Ppr.hs
index 8255f77..0e443ef 100644
--- a/Language/Haskell/TH/Ppr.hs
+++ b/Language/Haskell/TH/Ppr.hs
@@ -9,7 +9,8 @@ module Language.Haskell.TH.Ppr where
import Text.PrettyPrint (render)
import Language.Haskell.TH.PprLib
import Language.Haskell.TH.Syntax
-import Data.Char ( toLower )
+import Data.Word ( Word8 )
+import Data.Char ( toLower, chr )
import GHC.Show ( showMultiLineString )
nestDepth :: Int
@@ -173,9 +174,12 @@ pprLit i (DoublePrimL x) = parensIf (i > noPrec && x < 0)
pprLit i (IntegerL x) = parensIf (i > noPrec && x < 0) (integer x)
pprLit _ (CharL c) = text (show c)
pprLit _ (StringL s) = pprString s
-pprLit _ (StringPrimL s) = pprString s <> char '#'
+pprLit _ (StringPrimL s) = pprString (bytesToString s) <> char '#'
pprLit i (RationalL rat) = parensIf (i > noPrec) $ rational rat
+bytesToString :: [Word8] -> String
+bytesToString = map (chr . fromIntegral)
+
pprString :: String -> Doc
-- Print newlines as newlines with Haskell string escape notation,
-- not as '\n'. For other non-printables use regular escape notation.
diff --git a/Language/Haskell/TH/Syntax.hs b/Language/Haskell/TH/Syntax.hs
index c18d801..5cf9c07 100644
--- a/Language/Haskell/TH/Syntax.hs
+++ b/Language/Haskell/TH/Syntax.hs
@@ -66,6 +66,7 @@ import System.IO.Unsafe ( unsafePerformIO )
import Control.Monad (liftM)
import System.IO ( hPutStrLn, stderr )
import Data.Char ( isAlpha )
+import Data.Word ( Word8 )
-----------------------------------------------------
--
@@ -792,7 +793,7 @@ data Lit = CharL Char
| WordPrimL Integer
| FloatPrimL Rational
| DoublePrimL Rational
- | StringPrimL String -- ^ A primitive C-style string, type Addr#
+ | StringPrimL [Word8] -- ^ A primitive C-style string, type Addr#
deriving( Show, Eq, Data, Typeable )
-- We could add Int, Float, Double etc, as we do in HsLit,
_______________________________________________
Cvs-libraries mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-libraries
_______________________________________________
Cvs-libraries mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-libraries