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