{-# language OverloadedStrings #-}
{-# language ScopedTypeVariables #-}
module Data.Sv.Decode.Error (
DecodeError (..)
, DecodeErrors (..)
, decodeError
, unexpectedEndOfRow
, expectedEndOfRow
, unknownCategoricalValue
, missingColumn
, missingHeader
, badConfig
, badParse
, badDecode
, displayErrors
, displayErrors'
, dieOnError
, dieOnError'
, validateEither
, validateEitherWith
, validateMaybe
, validateTrifectaResult
, bindValidation
) where
import Data.ByteString (ByteString)
import qualified Data.ByteString.Char8 as Char8
import Data.Foldable (toList)
import Data.List (intersperse)
import Data.Semigroup (Semigroup ((<>)))
import Data.Semigroup.Foldable (Foldable1 (foldMap1))
import Data.String (IsString)
import qualified Data.Text.Encoding as T
import qualified Data.Text.Lazy as LT
import qualified Data.Text.Lazy.IO as LT
import Data.Text.Lazy.Builder (Builder)
import qualified Data.Text.Lazy.Builder as Builder
import Data.Validation (Validation (Failure), bindValidation)
import Data.Vector (Vector)
import qualified Text.Trifecta.Result as Trifecta
import System.Exit (exitFailure)
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
displayErrors :: DecodeErrors ByteString -> LT.Text
displayErrors = displayErrors' buildBytestring
displayErrors' :: forall e. (e -> Builder) -> DecodeErrors e -> LT.Text
displayErrors' build (DecodeErrors errs) =
let
indent :: Builder -> Builder
indent x = " " <> x
displayErr :: DecodeError e -> Builder
displayErr e = indent $ case e of
BadParse msg -> "Parsing the document failed. The error was: " <> build msg
UnexpectedEndOfRow -> "Expected more fields, but the row ended."
ExpectedEndOfRow extras ->
"Expected fewer fields in the row. The extra fields contained: " <>
commaSep (bquote <$> toList extras)
UnknownCategoricalValue found required ->
"Unknown categorical value found: " <> bquote found <> ". Expected one of: " <>
(commaSep . fmap bquote . mconcat) required
MissingColumn name -> "Could not find required column " <> bquote name
MissingHeader -> "A header row was required, but one was not found."
BadConfig msg -> "sv was misconfigured: " <> build msg
BadDecode msg -> "Decoding a field failed: " <> build msg
displayAndCount = count . displayErr
Counted body c = foldMap1 displayAndCount errs
spaceSep = mconcat . intersperse " "
commaSep = mconcat . intersperse ", "
quote s = "\"" <> s <> "\""
bquote = quote . build
pluralise n s =
if n == 1
then s
else Builder.fromString (show n) <> " " <> s <> "s"
heading = spaceSep ["The following", pluralise c "error", "occurred:"]
in
Builder.toLazyText $ heading <> "\n" <> body
dieOnError :: DecodeValidation ByteString a -> IO a
dieOnError = dieOnError' buildBytestring
dieOnError' :: (e -> Builder) -> DecodeValidation e a -> IO a
dieOnError' build e = case e of
Failure errs -> do
LT.putStrLn $ displayErrors' build errs
exitFailure
Success a -> pure a
buildBytestring :: ByteString -> Builder
buildBytestring bs = case T.decodeUtf8' bs of
Left _ -> Builder.fromString $ Char8.unpack bs
Right b -> Builder.fromText b
data Counted e = Counted e Integer
count :: e -> Counted e
count e = Counted e 1
instance (Semigroup e, IsString e) => Semigroup (Counted e) where
Counted b c <> Counted b' c' =
Counted (b <> "\n" <> b') (c+c')