module Data.Sv.Decode.Error (
DecodeError (..)
, DecodeErrors (..)
, decodeError
, unexpectedEndOfRow
, expectedEndOfRow
, unknownCategoricalValue
, badParse
, badDecode
, validateEither
, validateEither'
, validateMaybe
, validateMaybe'
, trifectaResultToEither
, validateTrifectaResult
, bindValidation
) where
import Data.Validation (Validation (Failure), bindValidation)
import Data.Vector (Vector)
import qualified Text.Trifecta as Trifecta (Result (Success, Failure), _errDoc)
import Data.Sv.Decode.Type
import Data.Sv.Syntax.Field
decodeError :: DecodeError e -> DecodeValidation e a
decodeError = Failure . DecodeErrors . pure
unexpectedEndOfRow :: DecodeValidation e a
unexpectedEndOfRow = decodeError UnexpectedEndOfRow
expectedEndOfRow :: Vector (SpacedField e) -> DecodeValidation e a
expectedEndOfRow = decodeError . ExpectedEndOfRow
unknownCategoricalValue :: e -> [[e]] -> DecodeValidation e a
unknownCategoricalValue unknown valids =
decodeError (UnknownCategoricalValue unknown valids)
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 = validateEither' id
validateEither' :: (e -> DecodeError e') -> Either e a -> DecodeValidation e' a
validateEither' f = either (decodeError . f) pure
validateMaybe :: DecodeError e -> Maybe b -> DecodeValidation e b
validateMaybe e = maybe (decodeError e) pure
validateMaybe' :: (a -> Maybe b) -> DecodeError e -> a -> DecodeValidation e b
validateMaybe' ab e a = validateMaybe e (ab a)
trifectaResultToEither :: Trifecta.Result a -> Either String a
trifectaResultToEither result = case result of
Trifecta.Success a -> Right a
Trifecta.Failure e -> Left . show . Trifecta._errDoc $ e
validateTrifectaResult :: (String -> DecodeError e) -> Trifecta.Result a -> DecodeValidation e a
validateTrifectaResult f = validateEither' f . trifectaResultToEither