add more things
This commit is contained in:
parent
cb11a8bd9a
commit
b8da6c0fab
@ -20,6 +20,7 @@ library
|
||||
Siphon
|
||||
Siphon.Types
|
||||
Siphon.Encoding
|
||||
Siphon.Decoding
|
||||
Siphon.Internal
|
||||
build-depends:
|
||||
base >= 4.7 && < 5
|
||||
|
||||
@ -1,8 +1,22 @@
|
||||
{-# LANGUAGE RankNTypes #-}
|
||||
|
||||
module Siphon.Decoding where
|
||||
|
||||
import Siphon.Types
|
||||
import Siphon.Internal (row,comma)
|
||||
import Data.Text (Text)
|
||||
import Data.ByteString (ByteString)
|
||||
import Pipes (yield,Pipe,Consumer',Producer,await)
|
||||
import Data.Vector (Vector)
|
||||
import qualified Data.Attoparsec.ByteString as AttoByteString
|
||||
import qualified Data.ByteString.Char8 as ByteString
|
||||
import qualified Data.Attoparsec.Types as Atto
|
||||
|
||||
byteStringChar8 :: SiphonDecoding ByteString ByteString
|
||||
byteStringChar8 = SiphonDecoding
|
||||
(AttoByteString.parse (row comma))
|
||||
ByteString.null
|
||||
|
||||
-- unrow :: c1 -> (Vector c2,c1)
|
||||
--
|
||||
-- row :: _
|
||||
@ -10,32 +24,31 @@ import qualified Data.Attoparsec.Types as Atto
|
||||
-- -> Vector c
|
||||
-- -> Either DecodingErrors a
|
||||
|
||||
pipe :: SiphonDecoding c1 c2
|
||||
pipe :: Monad m
|
||||
=> SiphonDecoding c1 c2
|
||||
-> Atto.Parser c1 (WithEnd c2)
|
||||
-> Pipe c1 (Vector c2) m String
|
||||
pipe (SiphonDecoding parse isNull) p = do
|
||||
c1 <- awaitSkip isNull
|
||||
case parse p c1 of
|
||||
pipe (SiphonDecoding parse isNull) p = go1 where
|
||||
go1 = do
|
||||
c1 <- awaitSkip isNull
|
||||
handleResult (parse c1)
|
||||
go2 c1 = handleResult (parse c1)
|
||||
go3 k = do
|
||||
c1 <- awaitSkip isNull
|
||||
handleResult (k c1)
|
||||
handleResult r = case r of
|
||||
Atto.Fail _ _ _ -> error "ahh"
|
||||
Atto.Done c1 v -> do
|
||||
yield v
|
||||
if isNull c1 then go1 else go2 c1
|
||||
Atto.Partial k -> go3 k
|
||||
|
||||
awaitSkip :: (a -> Bool)
|
||||
awaitSkip :: Monad m
|
||||
=> (a -> Bool)
|
||||
-> Consumer' a m a
|
||||
awaitSkip f = go where
|
||||
go = do
|
||||
a <- await
|
||||
if f a then go else return a
|
||||
|
||||
nextSkipEmpty
|
||||
:: (Monad m, Eq a, Monoid a)
|
||||
=> Producer a m r
|
||||
-> m (Either r (a, Producer a m r))
|
||||
nextSkipEmpty = go where
|
||||
go p0 = do
|
||||
x <- next p0
|
||||
case x of
|
||||
Left _ -> return x
|
||||
Right (a,p1)
|
||||
| a == mempty -> go p1
|
||||
| otherwise -> return x
|
||||
{-# INLINABLE nextSkipEmpty #-}
|
||||
|
||||
|
||||
|
||||
@ -92,9 +92,14 @@ sepByEndOfLine1' p = liftM2' (:) p loop
|
||||
-- this parser.
|
||||
row :: Word8 -- ^ Field delimiter
|
||||
-> AL.Parser (Vector ByteString)
|
||||
row !delim = V.fromList <$!> field delim `sepByDelim1'` delim <* endOfLine
|
||||
row !delim = rowNoNewline delim <* endOfLine
|
||||
{-# INLINE row #-}
|
||||
|
||||
rowNoNewline :: Word8 -- ^ Field delimiter
|
||||
-> AL.Parser (Vector ByteString)
|
||||
rowNoNewline !delim = V.fromList <$!> field delim `sepByDelim1'` delim
|
||||
{-# INLINE rowNoNewline #-}
|
||||
|
||||
removeBlankLines :: [Vector ByteString] -> [Vector ByteString]
|
||||
removeBlankLines = filter (not . blankLine)
|
||||
|
||||
@ -181,8 +186,9 @@ endOfLine :: A.Parser ()
|
||||
endOfLine = (A.word8 newline *> return ()) <|> (string (BC8.pack "\r\n") *> return ()) <|> (A.word8 cr *> return ())
|
||||
{-# INLINE endOfLine #-}
|
||||
|
||||
doubleQuote, newline, cr :: Word8
|
||||
doubleQuote, newline, cr, comma :: Word8
|
||||
doubleQuote = 34
|
||||
newline = 10
|
||||
cr = 13
|
||||
comma = 44
|
||||
|
||||
|
||||
@ -14,7 +14,7 @@ data Siphon c1 c2 = Siphon
|
||||
}
|
||||
|
||||
data SiphonDecoding c1 c2 = SiphonDecoding
|
||||
{ siphonDecodingParse :: Atto.Parser c1 c2 -> c1 -> Atto.IResult c1 c2
|
||||
{ siphonDecodingParse :: c1 -> Atto.IResult c1 (Vector c2)
|
||||
, siphonDecodingNull :: c1 -> Bool
|
||||
}
|
||||
|
||||
|
||||
Loading…
Reference in New Issue
Block a user