{-# LANGUAGE BangPatterns, CPP, OverloadedStrings #-}

module Data.Csv.Util
    ( (<$!>)
    , blankLine
    , liftM2'
    , endOfLine
    , doubleQuote
    , newline
    , cr
    , toStrict
    ) where

import Control.Applicative ((<|>))
import Data.Word (Word8)
import Data.Attoparsec.ByteString.Char8 (string)
import qualified Data.Attoparsec.ByteString as A
import qualified Data.ByteString as B
import qualified Data.Vector as V
import Data.Attoparsec.ByteString (Parser)

#if !MIN_VERSION_base(4,8,0)
import Control.Applicative ((*>))
#endif

#if MIN_VERSION_bytestring(0,10,0)
import Data.ByteString.Lazy (toStrict)
#else
import qualified Data.ByteString.Lazy as L

toStrict :: L.ByteString -> B.ByteString
toStrict = B.concat . L.toChunks
#endif

-- | A strict version of 'Data.Functor.<$>' for monads.
(<$!>) :: Monad m => (a -> b) -> m a -> m b
a -> b
f <$!> :: (a -> b) -> m a -> m b
<$!> m a
m = do
    a
a <- m a
m
    b -> m b
forall (m :: * -> *) a. Monad m => a -> m a
return (b -> m b) -> b -> m b
forall a b. (a -> b) -> a -> b
$! a -> b
f a
a
{-# INLINE (<$!>) #-}

infixl 4 <$!>

-- | Is this an empty record (i.e. a blank line)?
blankLine :: V.Vector B.ByteString -> Bool
blankLine :: Vector ByteString -> Bool
blankLine Vector ByteString
v = Vector ByteString -> Int
forall a. Vector a -> Int
V.length Vector ByteString
v Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1 Bool -> Bool -> Bool
&& (ByteString -> Bool
B.null (Vector ByteString -> ByteString
forall a. Vector a -> a
V.head Vector ByteString
v))

-- | A version of 'liftM2' that is strict in the result of its first
-- action.
liftM2' :: (Monad m) => (a -> b -> c) -> m a -> m b -> m c
liftM2' :: (a -> b -> c) -> m a -> m b -> m c
liftM2' a -> b -> c
f m a
a m b
b = do
    !a
x <- m a
a
    b
y <- m b
b
    c -> m c
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> b -> c
f a
x b
y)
{-# INLINE liftM2' #-}


-- | Match either a single newline character @\'\\n\'@, or a carriage
-- return followed by a newline character @\"\\r\\n\"@, or a single
-- carriage return @\'\\r\'@.
endOfLine :: Parser ()
endOfLine :: Parser ()
endOfLine = (Word8 -> Parser Word8
A.word8 Word8
newline Parser Word8 -> Parser () -> Parser ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> () -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()) Parser () -> Parser () -> Parser ()
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (ByteString -> Parser ByteString
string ByteString
"\r\n" Parser ByteString -> Parser () -> Parser ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> () -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()) Parser () -> Parser () -> Parser ()
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Word8 -> Parser Word8
A.word8 Word8
cr Parser Word8 -> Parser () -> Parser ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> () -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
return ())
{-# INLINE endOfLine #-}

doubleQuote, newline, cr :: Word8
doubleQuote :: Word8
doubleQuote = Word8
34
newline :: Word8
newline = Word8
10
cr :: Word8
cr = Word8
13