{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE TupleSections #-}
module Data.Sv.Decode.Type (
Decode (..)
, Decode'
, buildDecode
, NameDecode (..)
, NameDecode'
, DecodeState (..)
, runDecodeState
, Ind (..)
, DecodeError (..)
, DecodeErrors (..)
, DecodeValidation
, Validation (..)
) where
import Control.Applicative (liftA2)
import Control.DeepSeq (NFData)
import Control.Monad.Reader (ReaderT (ReaderT, runReaderT), MonadReader, withReaderT)
import Control.Monad.State (State, runState, state, MonadState)
import Control.Monad.Writer.Strict (Writer, writer, runWriter)
import Data.Functor.Alt (Alt ((<!>)))
import Data.Functor.Apply (Apply)
import Data.Functor.Bind (Bind ((>>-)))
import Data.Functor.Compose (Compose (Compose, getCompose))
import Data.List.NonEmpty (NonEmpty)
import Data.Map.Strict (Map)
import Data.Monoid (Last)
import Data.Semigroup (Semigroup ((<>)))
import Data.Semigroupoid (Semigroupoid (o))
import Data.Profunctor (Profunctor (lmap, rmap))
import Data.Validation (Validation (Success, Failure))
import Data.Vector (Vector)
import GHC.Generics (Generic)
newtype Decode e s a =
Decode { unwrapDecode :: Compose (DecodeState s) (Compose (Writer (Last Bool)) (DecodeValidation e)) a }
deriving (Functor, Apply, Applicative)
type Decode' s = Decode s s
instance Alt (Decode e s) where
Decode (Compose as) <!> Decode (Compose bs) =
buildDecode $ \v i ->
case runDecodeState as v i of
(a, j) -> case runDecodeState bs v i of
(b, k) ->
let a' = fmap (,j) a
b' = fmap (,k) b
in case runWriter $ liftA2 (<!>) (getCompose a') (getCompose b') of
(Failure e, l) -> (Failure e, l, k)
(Success (z, m), l) -> (Success z, l, m)
instance Profunctor (Decode e) where
lmap f (Decode (Compose dec)) = Decode (Compose (lmap f dec))
rmap = fmap
instance Semigroupoid (Decode e) where
r `o` s = case r of
Decode (Compose (DecodeState (ReaderT r'))) -> case s of
Decode (Compose (DecodeState (ReaderT s'))) ->
buildDecode $ \vec ind -> case runState (s' vec) ind of
(v,ind') -> case runWriter (getCompose v) of
(Failure e, l) -> (Failure e, l, ind')
(Success x, l) ->
case runWriter $ getCompose $ fst (runState (r' (pure x)) (Ind 0)) of
(y, l') -> (y, l <> l', ind')
newtype DecodeState s a =
DecodeState { getDecodeState :: ReaderT (Vector s) (State Ind) a }
deriving (Functor, Apply, Applicative, Monad, MonadReader (Vector s), MonadState Ind)
instance Bind (DecodeState s) where
(>>-) = (>>=)
instance Profunctor DecodeState where
lmap f (DecodeState s) = DecodeState (withReaderT (fmap f) s)
rmap = fmap
buildDecode :: (Vector s -> Ind -> (DecodeValidation e a, Last Bool, Ind)) -> Decode e s a
buildDecode f =
Decode . Compose . DecodeState . ReaderT $ \v -> state $ \i ->
case f v i of
(va, l, i') -> (Compose (writer (va, l)), i')
runDecodeState :: DecodeState s a -> Vector s -> Ind -> (a, Ind)
runDecodeState = fmap runState . runReaderT . getDecodeState
newtype Ind = Ind Int deriving (Eq, Ord, Show)
data DecodeError e =
UnexpectedEndOfRow
| ExpectedEndOfRow (Vector e)
| UnknownCategoricalValue e [[e]]
| MissingColumn e
| MissingHeader
| BadConfig e
| BadParse e
| BadDecode e
deriving (Eq, Ord, Show, Generic)
instance Functor DecodeError where
fmap f d = case d of
UnexpectedEndOfRow -> UnexpectedEndOfRow
ExpectedEndOfRow v -> ExpectedEndOfRow (fmap f v)
UnknownCategoricalValue e ess -> UnknownCategoricalValue (f e) (fmap (fmap f) ess)
MissingColumn e -> MissingColumn (f e)
MissingHeader -> MissingHeader
BadConfig e -> BadConfig (f e)
BadParse e -> BadParse (f e)
BadDecode e -> BadDecode (f e)
instance NFData e => NFData (DecodeError e)
newtype DecodeErrors e =
DecodeErrors (NonEmpty (DecodeError e))
deriving (Eq, Ord, Show, Semigroup, Generic)
instance Functor DecodeErrors where
fmap f (DecodeErrors nel) = DecodeErrors (fmap (fmap f) nel)
instance NFData e => NFData (DecodeErrors e)
type DecodeValidation e = Validation (DecodeErrors e)
newtype NameDecode e s a =
Named {
unNamed :: ReaderT (Map s Ind) (Compose (DecodeValidation e) (Decode e s)) a
}
deriving (Functor, Applicative)
type NameDecode' s = NameDecode s s
instance Alt (NameDecode e s) where
Named f <!> Named g = Named (f <!> g)