{-| Module : Pipes.KeyValueCsv.Csv Copyright : (c) Marcin Mrotek, 2015 License : BSD3 Maintainer : marcin.jan.mrotek@gmail.com Stability : experimental Abstract types. -} {-# LANGUAGE GeneralizedNewtypeDeriving #-} module Pipes.KeyValueCsv.Internal.Types where import Data.Text (Text) import Pipes import Pipes.Group (FreeT) -- |A wrapped 'Char' that has the explicit puropse of delimiting cells. newtype Delimiter = Delimiter { getDelimiter :: Char } -- |A single line. Internally, a stream of text. newtype Line m r = Line { unLine :: Producer Text m r } deriving (Functor, Applicative, Monad) -- |A stream of lines. newtype Lines m r = Lines { unLines :: FreeT (Line m) m r } deriving (Functor, Applicative, Monad) -- |A single cell. Internally, a stream of text. newtype Cell m r = Cell { unCell :: Producer Text m r } deriving (Functor, Applicative, Monad) -- |A stream of cells. newtype Cells m r = Cells { unCells :: FreeT (Cell m) m r } deriving (Functor, Applicative, Monad)