]> git.immae.eu Git - github/fretlink/text-pipes.git/commitdiff
little Haddock notes on Internal material
authormichaelt <what_is_it_to_do_anything@yahoo.com>
Wed, 5 Feb 2014 05:20:11 +0000 (00:20 -0500)
committermichaelt <what_is_it_to_do_anything@yahoo.com>
Wed, 5 Feb 2014 05:20:11 +0000 (00:20 -0500)
Pipes/Text/Internal/Codec.hs
Pipes/Text/Internal/Decoding.hs

index 4b9367fcd97866bdfeca878babe734460c5a1628..63cbd740b77195946a06940ff73c144466e20745 100644 (file)
@@ -3,8 +3,12 @@
 -- |
 -- Copyright: 2014 Michael Thompson, 2011 Michael Snoyman, 2010-2011 John Millikin
 -- License: MIT
---
--- Parts of this code were taken from enumerator and conduits, and adapted for pipes.
+--  This Parts of this code were taken from enumerator and conduits, and adapted for pipes
+{- | This module follows the model of the enumerator and conduits libraries, and defines
+     'Codec' s for various encodings. Note that we do not export a 'Codec' for ascii and 
+     iso8859_1. A 'Lens' in the sense of the pipes library cannot be defined for these, so
+     special functions appear in @Pipes.Text@
+-}
 
 module Pipes.Text.Internal.Codec
     ( Decoding(..)
@@ -41,12 +45,11 @@ import Data.Maybe (catMaybes)
 import Pipes.Text.Internal.Decoding
 import Pipes
 -- | A specific character encoding.
---
--- Since 0.3.0
+
 data Codec = Codec
   { codecName :: Text
   , codecEncode :: Text -> (ByteString, Maybe (TextException, Text))
-  , codecDecode :: ByteString -> Decoding -- (Text, Either (TextException, ByteString) ByteString)
+  , codecDecode :: ByteString -> Decoding 
   }
 
 instance Show Codec where
index 531104a992d0c9ad010f5e19f323bc9fa9a65d62..4b4bbe6094899272733bff84eee5b18a3814336e 100644 (file)
@@ -2,9 +2,11 @@
 {-# LANGUAGE GeneralizedNewtypeDeriving, MagicHash, UnliftedFFITypes #-}
 {-# LANGUAGE DeriveDataTypeable, RankNTypes #-}
 
--- This module lifts assorted materials from Brian O'Sullivan's text package 
--- especially Data.Text.Encoding in order to define a pipes-appropriate
--- streamDecodeUtf8
+{- |
+This module lifts assorted materials from Brian O'Sullivan's text package 
+especially @Data.Text.Encoding@ in order to define a pipes-appropriate
+'streamDecodeUtf8'
+-} 
 module Pipes.Text.Internal.Decoding 
     ( Decoding(..)
     , streamDecodeUtf8
@@ -41,9 +43,9 @@ import Data.Maybe (catMaybes)
 
 
 
--- | A stream oriented decoding result.
-data Decoding = Some Text ByteString (ByteString -> Decoding)
-              | Other Text ByteString
+-- | A stream oriented decoding result. Distinct from the similar type in @Data.Text.Encoding@
+data Decoding = Some Text ByteString (ByteString -> Decoding) -- | Text, continuation and any undecoded fragment.
+              | Other Text ByteString  -- | Text followed by an undecodable ByteString
 instance Show Decoding where
     showsPrec d (Some t bs _) = showParen (d > prec) $
                                 showString "Some " . showsPrec prec' t .
@@ -59,6 +61,7 @@ instance Show Decoding where
 newtype CodePoint = CodePoint Word32 deriving (Eq, Show, Num, Storable)
 newtype DecoderState = DecoderState Word32 deriving (Eq, Show, Num, Storable)
 
+-- | Resolve a 'ByteString' into 'Text' and a continuation that can handle further 'ByteStrings'. 
 streamDecodeUtf8 :: ByteString -> Decoding
 streamDecodeUtf8 = decodeChunkUtf8 B.empty 0 0 
   where
@@ -92,6 +95,7 @@ streamDecodeUtf8 = decodeChunkUtf8 B.empty 0 0
   {-# INLINE decodeChunkUtf8 #-}
 {-# INLINE streamDecodeUtf8 #-}
 
+-- | Resolve a ByteString into an initial segment of intelligible 'Text' and whatever is unintelligble
 decodeSomeUtf8 :: ByteString -> (Text, ByteString)
 decodeSomeUtf8 bs@(PS fp off len) = runST $ do 
   dest <- A.new (len+1)