Skip to content

Commit

Permalink
full compilation working again
Browse files Browse the repository at this point in the history
  • Loading branch information
meiersi committed Dec 6, 2010
1 parent 2630622 commit f2b4525
Show file tree
Hide file tree
Showing 6 changed files with 276 additions and 119 deletions.
6 changes: 4 additions & 2 deletions Blaze/ByteString/Builder.hs
Expand Up @@ -69,8 +69,10 @@ module Blaze.ByteString.Builder

-- * Executing builders
, toLazyByteString
-- , toLazyByteStringWith
-- , toByteString
, toLazyByteStringWith
, toByteString
, toByteStringIO
, toByteStringIOWith

) where

Expand Down
47 changes: 14 additions & 33 deletions Blaze/ByteString/Builder/Char/Utf8.hs
Expand Up @@ -35,45 +35,26 @@ import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Encoding as TS -- imported for documentation links

import Blaze.ByteString.Builder.Internal
import Blaze.ByteString.Builder.Write

-- | Write a UTF-8 encoded Unicode character to a buffer.
--
-- Note that the control flow of 'writeChar' is more complicated than the one
-- of 'writeWord8', as the size of the write depends on the 'Char' written.
-- Therefore,
--
-- > fromWrite $ writeChar a `mappend` writeChar b
--
-- must not always be faster than
--
-- > fromChar a `mappend` fromChar b
--
-- Use benchmarking to make informed decisions.
--

-- FIXME: Use a Write that always checks if 4 bytes are available and only take
-- care of the precise pointer advance once the data has been written. Either
-- formulate it using continuation passing or returning the increment using the
-- IO action. The latter is probably simpler and better understandable.
--
{-# INLINE writeChar #-}
writeChar :: Char -> Write
writeChar = encodeCharUtf8 f1 f2 f3 f4
writeChar c = boundedWrite 4 (encodeCharUtf8 f1 f2 f3 f4 c)
where
f1 x = Write 1 $ \ptr -> poke ptr x
f1 x1 = writeN 1 $ \op -> do pokeByteOff op 0 x1

f2 x1 x2 = Write 2 $ \ptr -> do poke ptr x1
poke (ptr `plusPtr` 1) x2
f2 x1 x2 = writeN 2 $ \op -> do pokeByteOff op 0 x1
pokeByteOff op 1 x2

f3 x1 x2 x3 = writeN 3 $ \op -> do pokeByteOff op 0 x1
pokeByteOff op 1 x2
pokeByteOff op 2 x3

f3 x1 x2 x3 = Write 3 $ \ptr -> do poke ptr x1
poke (ptr `plusPtr` 1) x2
poke (ptr `plusPtr` 2) x3

f4 x1 x2 x3 x4 = Write 4 $ \ptr -> do poke ptr x1
poke (ptr `plusPtr` 1) x2
poke (ptr `plusPtr` 2) x3
poke (ptr `plusPtr` 3) x4
{-# INLINE writeChar #-}
f4 x1 x2 x3 x4 = writeN 4 $ \op -> do pokeByteOff op 0 x1
pokeByteOff op 1 x2
pokeByteOff op 2 x3
pokeByteOff op 3 x4

-- | Encode a Unicode character to another datatype, using UTF-8. This function
-- acts as an abstract way of encoding characters, as it is unaware of what
Expand Down Expand Up @@ -113,7 +94,7 @@ fromChar = fromWriteSingleton writeChar
-- | /O(n)/. Serialize a Unicode 'String' using the UTF-8 encoding.
--
fromString :: String -> Builder
fromString = fromWrite1List writeChar
fromString = fromWriteList writeChar
-- Performance note: ^^^
--
-- fromWrite2List made things slightly worse for the blaze-html benchmarks
Expand Down
19 changes: 12 additions & 7 deletions Blaze/ByteString/Builder/Html/Utf8.hs
Expand Up @@ -36,17 +36,22 @@ import qualified Data.Text as TS
import qualified Data.Text.Lazy as TL

import Blaze.ByteString.Builder
import Blaze.ByteString.Builder.Internal
import Blaze.ByteString.Builder.Char.Utf8

-- | Write a HTML escaped and UTF-8 encoded Unicode character to a bufffer.
--
writeHtmlEscapedChar :: Char -> Write
writeHtmlEscapedChar '<' = writeByteString "&lt;"
writeHtmlEscapedChar '>' = writeByteString "&gt;"
writeHtmlEscapedChar '&' = writeByteString "&amp;"
writeHtmlEscapedChar '"' = writeByteString "&quot;"
writeHtmlEscapedChar '\'' = writeByteString "&#39;"
writeHtmlEscapedChar c = writeChar c
writeHtmlEscapedChar c0 =
boundedWrite 6 (io c0)
-- WARNING: Don't forget to change the bound if you change the bytestrings.
where
io '<' = runWrite $ writeByteString "&lt;"
io '>' = runWrite $ writeByteString "&gt;"
io '&' = runWrite $ writeByteString "&amp;"
io '"' = runWrite $ writeByteString "&quot;"
io '\'' = runWrite $ writeByteString "&#39;"
io c = runWrite $ writeChar c
{-# INLINE writeHtmlEscapedChar #-}

-- | /O(1)./ Serialize a HTML escaped Unicode character using the UTF-8
Expand All @@ -59,7 +64,7 @@ fromHtmlEscapedChar = fromWriteSingleton writeHtmlEscapedChar
-- encoding.
--
fromHtmlEscapedString :: String -> Builder
fromHtmlEscapedString = fromWrite1List writeHtmlEscapedChar
fromHtmlEscapedString = fromWriteList writeHtmlEscapedChar

-- | /O(n)/. Serialize a value by 'Show'ing it and then, HTML escaping and
-- UTF-8 encoding the resulting 'String'.
Expand Down

0 comments on commit f2b4525

Please sign in to comment.