{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE UndecidableInstances #-} module Data.NestedText.Decode where import Data.Bifunctor (first) import qualified Data.Text.Lazy as TL import Generic.Data import Data.NestedText.From import Data.NestedText.Parse data DecodeError a = DecodeError'ParseError ParseError | DecodeError'FromItemError (FromItemError a) deriving ((forall x. DecodeError a -> Rep (DecodeError a) x) -> (forall x. Rep (DecodeError a) x -> DecodeError a) -> Generic (DecodeError a) forall x. Rep (DecodeError a) x -> DecodeError a forall x. DecodeError a -> Rep (DecodeError a) x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a forall a x. Rep (DecodeError a) x -> DecodeError a forall a x. DecodeError a -> Rep (DecodeError a) x $cfrom :: forall a x. DecodeError a -> Rep (DecodeError a) x from :: forall x. DecodeError a -> Rep (DecodeError a) x $cto :: forall a x. Rep (DecodeError a) x -> DecodeError a to :: forall x. Rep (DecodeError a) x -> DecodeError a Generic) instance Eq (FromItemError a) => Eq (DecodeError a) where == :: DecodeError a -> DecodeError a -> Bool (==) = DecodeError a -> DecodeError a -> Bool forall a. (Generic a, Eq (Rep a ())) => a -> a -> Bool geq instance Show (FromItemError a) => Show (DecodeError a) where showsPrec :: Int -> DecodeError a -> ShowS showsPrec = Int -> DecodeError a -> ShowS forall a. (Generic a, GShow0 (Rep a)) => Int -> a -> ShowS gshowsPrec decode :: FromItem a => TL.Text -> Either (DecodeError a) a decode :: forall a. FromItem a => Text -> Either (DecodeError a) a decode Text ts = do Item item <- (ParseError -> DecodeError a) -> Either ParseError Item -> Either (DecodeError a) Item forall a b c. (a -> b) -> Either a c -> Either b c forall (p :: * -> * -> *) a b c. Bifunctor p => (a -> b) -> p a c -> p b c first ParseError -> DecodeError a forall a. ParseError -> DecodeError a DecodeError'ParseError (Either ParseError Item -> Either (DecodeError a) Item) -> Either ParseError Item -> Either (DecodeError a) Item forall a b. (a -> b) -> a -> b $ Text -> Either ParseError Item parse Text ts (FromItemError a -> DecodeError a) -> Either (FromItemError a) a -> Either (DecodeError a) a forall a b c. (a -> b) -> Either a c -> Either b c forall (p :: * -> * -> *) a b c. Bifunctor p => (a -> b) -> p a c -> p b c first FromItemError a -> DecodeError a forall a. FromItemError a -> DecodeError a DecodeError'FromItemError (Either (FromItemError a) a -> Either (DecodeError a) a) -> Either (FromItemError a) a -> Either (DecodeError a) a forall a b. (a -> b) -> a -> b $ Item -> Either (FromItemError a) a forall a. FromItem a => Item -> Either (FromItemError a) a fromItem Item item