{-| Module : Pipes.KeyValueCsv.Types.Csv Copyright : (c) Marcin Mrotek, 2015 License : BSD3 Maintainer : marcin.jan.mrotek@gmail.com Stability : experimental Types used by the CSV part of the library. -} {-# LANGUAGE DataKinds , GADTs , RankNTypes , PolyKinds , UndecidableInstances #-} module Pipes.KeyValueCsv.Types.Csv where import Pipes.KeyValueCsv.Cell import Pipes.KeyValueCsv.Common import Pipes.KeyValueCsv.Types.Common import Control.Lens import Data.Vinyl import Data.Vinyl.TypeLevel import Data.Vinyl.Utils.Proxy import Data.Default.Class import Data.Validation data CsvOptions (m :: * -> *) (f :: k -> *) (rs :: [k]) = CsvOptions { _csvParser :: Rec (CellParser m f) rs } csvParser :: forall (m :: * -> *) (f :: k -> *) (rs :: [k]) . Lens' (CsvOptions m f rs) (Rec (CellParser m f) rs) csvParser = lens _csvParser $ \o p -> o {_csvParser = p} instance (RecAll f rs FromCell, Record rs, Monad m) => Default (CsvOptions m f rs) where def = CsvOptions defaultParser -- |An error that occurred during the parsing of a row. data CsvError = CellParseError String -- ^Error as returned by "Text.Read". | MissingCell deriving (Show, Eq) -- |Shorthand for functions that can return 'CsvError's. type WithCsvError = Validation [CsvError]