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

Automated parsing of single cells.
-}

{-# LANGUAGE 
    FlexibleContexts
  , FlexibleInstances
  , GeneralizedNewtypeDeriving
  , PolyKinds
  , RankNTypes 
  , TypeSynonymInstances
  #-}

module Pipes.KeyValueCsv.Cell where

import Pipes.KeyValueCsv.Internal

import Data.Text (Text)
import qualified Data.Text.Lazy as Lazy
import Data.Text.Lazy.Read
import Data.Vinyl.Functor
import Pipes.Parse (Parser)
import Pipes.Parse.Tutorial()

-- |Parse a single cell. For more information about parsing with Pipes, see "Pipes.Parse.Tutorial".
class FromCell c where
  fromCell :: Monad m => Parser Text m (Either String c)

instance FromCell Text where
  fromCell = Right . Lazy.toStrict <$> drawText

instance FromCell String where
  fromCell = Right . Lazy.unpack <$> drawText

instance FromCell Integer where
  fromCell = fmap fst . signed decimal <$> (skipSpace >> build)

instance FromCell Int where
  fromCell = fmap fst . signed decimal <$> (skipSpace >> build)

instance FromCell Double where
  fromCell = fmap fst . double <$> (skipSpace >> build)

instance FromCell a => FromCell (Identity a) where
  fromCell = fmap Identity <$> fromCell

instance FromCell (f (g a)) => FromCell (Compose f g a) where
  fromCell = fmap Compose <$> fromCell

instance FromCell a => FromCell (Thunk a) where
  fromCell = fmap Thunk <$> fromCell