module Data.Sv.Decode.Error (
DecodeError (..)
, DecodeErrors (..)
, decodeError
, unexpectedEndOfRow
, expectedEndOfRow
, unknownCategoricalValue
, missingColumn
, missingHeader
, badConfig
, badParse
, badDecode
, validateEither
, validateEitherWith
, validateMaybe
, validateTrifectaResult
, bindValidation
) where
import Data.Validation (Validation (Failure), bindValidation)
import Data.Vector (Vector)
import qualified Text.Trifecta.Result as Trifecta
import Data.Sv.Decode.Type
decodeError :: DecodeError e -> DecodeValidation e a
decodeError = Failure . DecodeErrors . pure
unexpectedEndOfRow :: DecodeValidation e a
unexpectedEndOfRow = decodeError UnexpectedEndOfRow
expectedEndOfRow :: Vector e -> DecodeValidation e a
expectedEndOfRow = decodeError . ExpectedEndOfRow
unknownCategoricalValue :: e -> [[e]] -> DecodeValidation e a
unknownCategoricalValue unknown valids =
decodeError (UnknownCategoricalValue unknown valids)
missingColumn :: e -> DecodeValidation e a
missingColumn = decodeError . MissingColumn
missingHeader :: DecodeValidation e a
missingHeader = decodeError MissingHeader
badConfig :: e -> DecodeValidation e a
badConfig = decodeError . BadConfig
badParse :: e -> DecodeValidation e a
badParse = decodeError . BadParse
badDecode :: e -> DecodeValidation e a
badDecode = decodeError . BadDecode
validateEither :: Either (DecodeError e) a -> DecodeValidation e a
validateEither = validateEitherWith id
validateEitherWith :: (e -> DecodeError e') -> Either e a -> DecodeValidation e' a
validateEitherWith f = either (decodeError . f) pure
validateMaybe :: DecodeError e -> Maybe b -> DecodeValidation e b
validateMaybe e = maybe (decodeError e) pure
validateTrifectaResult :: (String -> DecodeError e) -> Trifecta.Result a -> DecodeValidation e a
validateTrifectaResult f =
validateEitherWith f . trifectaResultToEither
where
trifectaResultToEither r = case r of
Trifecta.Failure e -> Left . show . Trifecta._errDoc $ e
Trifecta.Success a -> Right a