aboutsummaryrefslogtreecommitdiffhomepage
path: root/Pipes/Text/Internal/Decoding.hs
diff options
context:
space:
mode:
Diffstat (limited to 'Pipes/Text/Internal/Decoding.hs')
-rw-r--r--Pipes/Text/Internal/Decoding.hs23
1 files changed, 13 insertions, 10 deletions
diff --git a/Pipes/Text/Internal/Decoding.hs b/Pipes/Text/Internal/Decoding.hs
index 4b4bbe6..b5d928a 100644
--- a/Pipes/Text/Internal/Decoding.hs
+++ b/Pipes/Text/Internal/Decoding.hs
@@ -2,11 +2,10 @@
2{-# LANGUAGE GeneralizedNewtypeDeriving, MagicHash, UnliftedFFITypes #-} 2{-# LANGUAGE GeneralizedNewtypeDeriving, MagicHash, UnliftedFFITypes #-}
3{-# LANGUAGE DeriveDataTypeable, RankNTypes #-} 3{-# LANGUAGE DeriveDataTypeable, RankNTypes #-}
4 4
5{- | 5-- This module lifts assorted materials from Brian O'Sullivan's text package
6This module lifts assorted materials from Brian O'Sullivan's text package 6-- especially @Data.Text.Encoding@ in order to define a pipes-appropriate
7especially @Data.Text.Encoding@ in order to define a pipes-appropriate 7-- 'streamDecodeUtf8'
8'streamDecodeUtf8' 8
9-}
10module Pipes.Text.Internal.Decoding 9module Pipes.Text.Internal.Decoding
11 ( Decoding(..) 10 ( Decoding(..)
12 , streamDecodeUtf8 11 , streamDecodeUtf8
@@ -43,9 +42,13 @@ import Data.Maybe (catMaybes)
43 42
44 43
45 44
46-- | A stream oriented decoding result. Distinct from the similar type in @Data.Text.Encoding@ 45-- A stream oriented decoding result. Distinct from the similar type in Data.Text.Encoding
47data Decoding = Some Text ByteString (ByteString -> Decoding) -- | Text, continuation and any undecoded fragment. 46
48 | Other Text ByteString -- | Text followed by an undecodable ByteString 47data Decoding = Some Text ByteString (ByteString -> Decoding)
48 -- Text, continuation and any undecoded fragment.
49 | Other Text ByteString
50 -- Text followed by an undecodable ByteString
51
49instance Show Decoding where 52instance Show Decoding where
50 showsPrec d (Some t bs _) = showParen (d > prec) $ 53 showsPrec d (Some t bs _) = showParen (d > prec) $
51 showString "Some " . showsPrec prec' t . 54 showString "Some " . showsPrec prec' t .
@@ -61,7 +64,7 @@ instance Show Decoding where
61newtype CodePoint = CodePoint Word32 deriving (Eq, Show, Num, Storable) 64newtype CodePoint = CodePoint Word32 deriving (Eq, Show, Num, Storable)
62newtype DecoderState = DecoderState Word32 deriving (Eq, Show, Num, Storable) 65newtype DecoderState = DecoderState Word32 deriving (Eq, Show, Num, Storable)
63 66
64-- | Resolve a 'ByteString' into 'Text' and a continuation that can handle further 'ByteStrings'. 67-- Resolve a 'ByteString' into 'Text' and a continuation that can handle further 'ByteStrings'.
65streamDecodeUtf8 :: ByteString -> Decoding 68streamDecodeUtf8 :: ByteString -> Decoding
66streamDecodeUtf8 = decodeChunkUtf8 B.empty 0 0 69streamDecodeUtf8 = decodeChunkUtf8 B.empty 0 0
67 where 70 where
@@ -95,7 +98,7 @@ streamDecodeUtf8 = decodeChunkUtf8 B.empty 0 0
95 {-# INLINE decodeChunkUtf8 #-} 98 {-# INLINE decodeChunkUtf8 #-}
96{-# INLINE streamDecodeUtf8 #-} 99{-# INLINE streamDecodeUtf8 #-}
97 100
98-- | Resolve a ByteString into an initial segment of intelligible 'Text' and whatever is unintelligble 101-- Resolve a ByteString into an initial segment of intelligible 'Text' and whatever is unintelligble
99decodeSomeUtf8 :: ByteString -> (Text, ByteString) 102decodeSomeUtf8 :: ByteString -> (Text, ByteString)
100decodeSomeUtf8 bs@(PS fp off len) = runST $ do 103decodeSomeUtf8 bs@(PS fp off len) = runST $ do
101 dest <- A.new (len+1) 104 dest <- A.new (len+1)