module Data.Sv.Decode (
  
  Decode (..)
, Decode'
, Validation (..)
, DecodeValidation
, DecodeError (..)
, DecodeErrors (..)
  
, decode
, parseDecode
, parseDecode'
, parseDecodeFromFile
, parseDecodeFromFile'
, decodeMay
, decodeEither
, decodeEither'
, mapErrors
, alterInput
, contents
, untrimmed
, raw
, char
, byteString
, utf8
, lazyUtf8
, lazyByteString
, string
, int
, integer
, float
, double
, boolean
, boolean'
, ignore
, replace
, exactly
, emptyField
, row
, rowWithSpacing
, choice
, element
, optionalField
, ignoreFailure
, orEmpty
, either
, orElse
, orElseE
, categorical
, categorical'
, (>>==)
, (==<<)
, bindDecode
, decodeRead
, decodeRead'
, decodeReadWithMsg
, withTrifecta
, withAttoparsec
, withParsec
, onError
, decodeError
, unexpectedEndOfRow
, expectedEndOfRow
, unknownCategoricalValue
, badParse
, badDecode
, validateEither
, validateEither'
, validateMaybe
, validateMaybe'
, runDecode
, buildDecode
, mkDecode
, mkDecodeWithQuotes
, mkDecodeWithSpaces
, promote
) where
import Prelude hiding (either)
import qualified Prelude
import Control.Lens (alaf, view)
import Control.Monad.IO.Class (MonadIO)
import Control.Monad.Reader (ReaderT (ReaderT))
import Control.Monad.State (state)
import Data.Attoparsec.ByteString (parseOnly)
import qualified Data.Attoparsec.ByteString as A (Parser)
import Data.Bifunctor (first, second)
import Data.ByteString (ByteString)
import qualified Data.ByteString.UTF8 as UTF8
import qualified Data.ByteString.Lazy as LBS
import Data.Char (toUpper)
import Data.Foldable (toList)
import Data.Functor.Alt (Alt ((<!>)))
import Data.Functor.Compose (Compose (Compose, getCompose))
import Data.List.NonEmpty (NonEmpty ((:|)))
import Data.Monoid (First (First))
import Data.Profunctor (lmap)
import Data.Readable (Readable (fromBS))
import Data.Semigroup (Semigroup ((<>)), sconcat)
import Data.Semigroup.Foldable (asum1)
import Data.Set (Set, fromList, member)
import Data.String (IsString (fromString))
import Data.Text (Text)
import Data.Text.Encoding (decodeUtf8')
import qualified Data.Text.Lazy as LT
import Data.Validation (_Validation)
import Data.Vector (Vector, (!))
import qualified Data.Vector as V
import Text.Parsec (Parsec)
import qualified Text.Parsec as P (parse)
import qualified Text.Trifecta as Tri
import Data.Sv.Decode.Error
import Data.Sv.Decode.Type
import qualified Data.Sv.Parse as P
import Data.Sv.Parse.Options (ParseOptions)
import Data.Sv.Syntax.Field (Field (Unquoted, Quoted), fieldContents, SpacedField, Spaced (Spaced))
import Data.Sv.Syntax.Record (Record, _fields)
import Data.Sv.Syntax.Sv (Sv, recordList)
import Text.Space (HorizontalSpace, Spaced (_value), spacedValue)
decode :: Decode' s a -> Sv s -> DecodeValidation s [a]
decode f = traverse (promote f) . recordList
parseDecode ::
  Decode' ByteString a
  -> ParseOptions ByteString
  -> ByteString
  -> DecodeValidation ByteString [a]
parseDecode = parseDecode' P.trifecta
parseDecode' ::
  P.SvParser s
  -> Decode' s a
  -> ParseOptions s
  -> s
  -> DecodeValidation s [a]
parseDecode' svp d opts s =
  Prelude.either badDecode pure (P.parseSv' svp opts s) `bindValidation` decode d
parseDecodeFromFile ::
  MonadIO m
  => Decode' ByteString a
  -> ParseOptions ByteString
  -> FilePath
  -> m (DecodeValidation ByteString [a])
parseDecodeFromFile = parseDecodeFromFile' P.trifecta
parseDecodeFromFile' ::
  MonadIO m
  => P.SvParser s
  -> Decode' s a
  -> ParseOptions s
  -> FilePath
  -> m (DecodeValidation s [a])
parseDecodeFromFile' svp d opts fp = do
  sv <- P.parseSvFromFile' svp opts fp
  pure (Prelude.either badDecode pure sv `bindValidation` decode d)
decodeMay :: DecodeError e -> (s -> Maybe a) -> Decode e s a
decodeMay e f = mkDecode (validateMaybe e . f)
decodeEither :: (s -> Either (DecodeError e) a) -> Decode e s a
decodeEither f = mkDecode (validateEither . f)
decodeEither' :: (e -> DecodeError e') -> (s -> Either e a) -> Decode e' s a
decodeEither' e f = mkDecode (validateEither' e . f)
raw :: Decode e s (SpacedField s)
raw = mkDecodeWithSpaces pure
untrimmed :: Monoid s => (HorizontalSpace -> s) -> Decode e s s
untrimmed fromSpace =
  let sp = foldMap fromSpace
      spaceIfNecessary (Spaced b a f) = case f of
        Unquoted s -> mconcat [sp b, s, sp a]
        Quoted _ _ -> view fieldContents f
  in  fmap spaceIfNecessary raw
contents :: Decode e s s
contents = mkDecode pure
row :: Decode e s (Vector s)
row = (fmap . fmap) (view (spacedValue.fieldContents)) rowWithSpacing
rowWithSpacing :: Decode e s (Vector (SpacedField s))
rowWithSpacing =
  Decode . Compose . DecodeState . ReaderT $ \v ->
    state (const (pure v, Ind (V.length v)))
char :: Decode' ByteString Char
char = string >>== \cs -> case cs of
  [] -> badDecode "Expected single char but got empty string"
  (c:[]) -> pure c
  (_:_:_) -> badDecode ("Expected single char but got " <> UTF8.fromString cs)
byteString :: Decode' ByteString ByteString
byteString = contents
utf8 :: Decode' ByteString Text
utf8 = contents >>==
  Prelude.either (badDecode . UTF8.fromString . show) pure . decodeUtf8'
lazyUtf8 :: Decode' ByteString LT.Text
lazyUtf8 = LT.fromStrict <$> utf8
lazyByteString :: Decode' ByteString LBS.ByteString
lazyByteString = LBS.fromStrict <$> contents
string :: Decode' ByteString String
string = UTF8.toString <$> contents
ignore :: Decode e s ()
ignore = replace ()
replace :: a -> Decode e s a
replace a = a <$ contents
exactly :: (Semigroup s, Eq s, IsString s) => s -> Decode' s s
exactly s = contents >>== \z ->
  if s == z
  then pure s
  else badDecode (sconcat ("'":|[z,"' was not equal to '",s,"'"]))
int :: Decode' ByteString Int
int = named "int"
integer :: Decode' ByteString Integer
integer = named "integer"
float :: Decode' ByteString Float
float = named "float"
double :: Decode' ByteString Double
double = named "double"
boolean :: (IsString s, Ord s) => Decode' s Bool
boolean = boolean' fromString
boolean' :: Ord s => (String -> s) -> Decode' s Bool
boolean' s =
  categorical' [
    (False, fmap s ["false", "False", "FALSE", "f", "F", "0", "n", "N", "no", "No", "NO", "off", "Off", "OFF"])
  , (True, fmap s ["true", "True", "TRUE", "t", "T", "1", "y", "Y", "yes", "Yes", "YES", "on", "On", "ON"])
  ]
emptyField :: (Eq s, IsString s, Semigroup s) => Decode' s ()
emptyField = contents >>== \c ->
  if c == fromString "" then
    pure ()
  else
    badDecode ("Expected emptiness but got: " <> c)
choice :: Decode e s a -> Decode e s a -> Decode e s a
choice = (<!>)
element :: NonEmpty (Decode e s a) -> Decode e s a
element = asum1
ignoreFailure :: Decode e s a -> Decode e s (Maybe a)
ignoreFailure a = Just <$> a <!> Nothing <$ ignore
orEmpty :: (Eq s, IsString s, Semigroup s) => Decode' s a -> Decode' s (Maybe a)
orEmpty a = Nothing <$ emptyField <!> Just <$> a
optionalField :: Decode e s a -> Decode e s (Maybe a)
optionalField a = Just <$> a <!> pure Nothing
either :: Decode e s a -> Decode e s b -> Decode e s (Either a b)
either a b = fmap Left a <!> fmap Right b
orElse :: Decode e s a -> a -> Decode e s a
orElse f a = f <!> replace a
orElseE :: Decode e s b -> a -> Decode e s (Either a b)
orElseE b a = fmap Right b <!> replace (Left a)
categorical :: (Ord s, Show a) => [(a, s)] -> Decode' s a
categorical = categorical' . fmap (fmap pure)
categorical' :: forall s a . (Ord s, Show a) => [(a, [s])] -> Decode' s a
categorical' as =
  let as' :: [(a, Set s)]
      as' = fmap (second fromList) as
      go :: s -> (a, Set s) -> Maybe a
      go s (a, set) =
        if s `member` set
        then Just a
        else Nothing
  in  contents >>== \s ->
    validateMaybe (UnknownCategoricalValue s (fmap snd as)) $
      alaf First foldMap (go s) as'
decodeRead :: Readable a => Decode' ByteString a
decodeRead = decodeReadWithMsg (mappend "Couldn't parse ")
decodeRead' :: Readable a => ByteString -> Decode' ByteString a
decodeRead' e = decodeReadWithMsg (const e)
decodeReadWithMsg :: Readable a => (ByteString -> e) -> Decode e ByteString a
decodeReadWithMsg e = contents >>== \c ->
  maybe (badDecode (e c)) pure . fromBS $ c
named :: Readable a => ByteString -> Decode' ByteString a
named name =
  let vs' = ['a','e','i','o','u']
      vs  = fmap toUpper vs' ++ vs'
      n c = if c `elem` vs then "n" else ""
      n' = foldMap (n . fst) . UTF8.uncons
      n'' = n' name
      space = " "
  in  decodeReadWithMsg $ \bs ->
        mconcat ["Couldn't parse \"", bs, "\" as a", n'', space, name]
mapErrors :: (e -> x) -> Decode e s a -> Decode x s a
mapErrors f (Decode (Compose r)) = Decode (Compose (fmap (first (fmap f)) r))
alterInput :: (e -> x) -> (t -> s) -> Decode e s a -> Decode x t a
alterInput f g = mapErrors f . lmap g
withTrifecta :: Tri.Parser a -> Decode' ByteString a
withTrifecta =
  mkParserFunction
    (validateTrifectaResult (BadDecode . UTF8.fromString))
    (flip Tri.parseByteString mempty)
withAttoparsec :: A.Parser a -> Decode' ByteString a
withAttoparsec =
  mkParserFunction
    (validateEither' (BadDecode . fromString))
    parseOnly
withParsec :: Parsec ByteString () a -> Decode' ByteString a
withParsec =
  
  
  let dropPos = drop 1 . dropWhile (/= ':')
  in  mkParserFunction
    (validateEither' (BadDecode . UTF8.fromString . dropPos . show))
    (\p s -> P.parse p mempty s)
mkParserFunction ::
  Tri.CharParsing p
  => (f a -> DecodeValidation ByteString a)
  -> (p a -> ByteString -> f a)
  -> p a
  -> Decode' ByteString a
mkParserFunction err run p =
  let p' = p <* Tri.eof
  in  byteString >>== (err . run p')
runDecode :: Decode e s a -> Vector (SpacedField s) -> Ind -> (DecodeValidation e a, Ind)
runDecode = runDecodeState . getCompose . unwrapDecode
(>>==) :: Decode e s a -> (a -> DecodeValidation e b) -> Decode e s b
(>>==) = flip (==<<)
infixl 1 >>==
(==<<) :: (a -> DecodeValidation e b) -> Decode e s a -> Decode e s b
(==<<) f (Decode c) =
  Decode (rmapC (`bindValidation` (view _Validation . f)) c)
    where
      rmapC g (Compose fga) = Compose (fmap g fga)
infixr 1 ==<<
bindDecode :: Decode e s a -> (a -> Decode e s b) -> Decode e s b
bindDecode d f =
  buildDecode $ \v i ->
    case runDecode d v i of
      (Failure e, i') -> (Failure e, i')
      (Success a, i') -> runDecode (f a) v i'
onError :: Decode e s a -> (DecodeErrors e -> Decode e s a) -> Decode e s a
onError d f =
  buildDecode $ \v i ->
    case runDecode d v i of
      (Failure e, i') -> runDecode (f e) v i'
      (Success a, i') -> (Success a, i')
mkDecode :: (s -> DecodeValidation e a) -> Decode e s a
mkDecode f = mkDecodeWithQuotes (f . view fieldContents)
mkDecodeWithQuotes :: (Field s -> DecodeValidation e a) -> Decode e s a
mkDecodeWithQuotes f = mkDecodeWithSpaces (f . _value)
mkDecodeWithSpaces :: (SpacedField s -> DecodeValidation e a) -> Decode e s a
mkDecodeWithSpaces f =
  Decode . Compose . DecodeState . ReaderT $ \v -> state $ \(Ind i) ->
    if i >= length v
    then (unexpectedEndOfRow, Ind i)
    else (f (v ! i), Ind (i+1))
promote :: Decode' s a -> Record s -> DecodeValidation s a
promote dec rs =
  let vec = V.fromList . toList . _fields $ rs
      len = length vec
  in  case runDecode dec vec (Ind 0) of
    (d, Ind i) ->
      if i >= len
      then d
      else d *> expectedEndOfRow (V.force (V.drop i vec))