{-| Module : Pipes.KeyValueCsv Copyright : (c) Marcin Mrotek, 2015 License : BSD3 Maintainer : marcin.jan.mrotek@gmail.com Stability : experimental Parse CSV files with key-value headers. -} {-# LANGUAGE DataKinds , ExplicitForAll , PolyKinds , TypeOperators #-} module Pipes.KeyValueCsv ( breakLines , parseKeyValueCsv , module Pipes.KeyValueCsv.Csv , module Pipes.KeyValueCsv.KeyValue , module Pipes.KeyValueCsv.Types , Record (..) -- * Re-exports , AccValidation(..) ) where import Prelude hiding (lines) import Pipes.KeyValueCsv.Internal import Pipes.KeyValueCsv.Internal.Types import Pipes.KeyValueCsv.Common import Pipes.KeyValueCsv.Csv import Pipes.KeyValueCsv.KeyValue import Pipes.KeyValueCsv.Types import Control.Lens import Data.Validation import Data.Vinyl import Data.Vinyl.Functor import Data.Vinyl.Utils.Proxy breakLines :: Monad m => (Text -> Bool) -> Lines m r -> Lines m (Lines m r) {-^ Break a stream of lines into two parts, on a line that satisfies the given predicate. All input lines up to the breaking one will be fully read, and each (not including the breaking one) will be re-'yield'ed. -} breakLines p (Lines l) = Lines $ Lines <$> breakLines' p l parseKeyValueCsv :: forall (m :: * -> *) (f :: k -> *) (g :: j -> *) (hs :: [k]) (rs :: [j]) (r :: *) . ( Monad m , Record hs ) => Options m f g hs rs -> Producer Text m r -> m ( Rec (WithKeyValueError :. f) hs , Producer (Rec (WithCsvError :. g) rs) m r ) -- ^Read a CSV file preceded by key-value pairs. parseKeyValueCsv options producer = useDelimiter (options^.delimiter) $ do (hdr, remaining) <- parseKeyValues (options^.kvOptions) . breakLines (options^.predicate) $ lines producer pure (hdr, parseCsv (options^.csvOptions) remaining)