{-|
Module      : Pipes.KeyValueCsv.Types.KeyValue
Copyright   : (c) Marcin Mrotek, 2015
License     : BSD3
Maintainer  : marcin.jan.mrotek@gmail.com
Stability   : experimental

Types used by the key-value part of the library.
-}

{-# LANGUAGE 
    DataKinds
  , PolyKinds
  , TemplateHaskell 
  , UndecidableInstances
  #-}

module Pipes.KeyValueCsv.Types.KeyValue where

import Pipes.KeyValueCsv.Cell
import Pipes.KeyValueCsv.Common
import Pipes.KeyValueCsv.Names
import Pipes.KeyValueCsv.Types.Common 

import Control.Lens hiding (Const)
import Data.Default.Class
import Data.Typeable
import Data.Vinyl
import Data.Vinyl.Functor
import Data.Vinyl.TypeLevel
import Data.Validation

-- |An error that occured during the parsing of the header.
data KeyValueError 
  = MissingValue             -- ^A value is missing in the header.
  | MultipleValues           -- ^A value is given multiple times.
  | ValueParsingError String -- ^Parsing error as returned by "Data.Text.Lazy.Read".
 deriving (Show, Eq)

-- |Shorthand for functions that can return 'KeyValueError's.
type WithKeyValueError = Validation [KeyValueError]

data KeyValueOptions (m :: * -> *) (f :: k -> *) (rs :: [k]) = KeyValueOptions
  { _kvParser  :: Rec (CellParser m f) rs
  , _keyNames  :: Rec (Const Text) rs
  }

makeLenses ''KeyValueOptions

instance ( RecAll f rs FromCell
         , FieldAll rs Typeable
         , Record rs
         , Monad m
         ) => Default (KeyValueOptions m f rs) where
  def = KeyValueOptions 
        { _kvParser = defaultParser
        , _keyNames = names
        }