{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE UndecidableInstances #-} module Data.NestedText.Encode where import Data.Bifunctor (first) import qualified Data.Text.Lazy as TL import Generic.Data import Data.NestedText.To import Data.NestedText.Serialize data EncodeError a = EncodeError'ToItemError (ToItemError a) deriving ((forall x. EncodeError a -> Rep (EncodeError a) x) -> (forall x. Rep (EncodeError a) x -> EncodeError a) -> Generic (EncodeError a) forall x. Rep (EncodeError a) x -> EncodeError a forall x. EncodeError a -> Rep (EncodeError a) x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a forall a x. Rep (EncodeError a) x -> EncodeError a forall a x. EncodeError a -> Rep (EncodeError a) x $cfrom :: forall a x. EncodeError a -> Rep (EncodeError a) x from :: forall x. EncodeError a -> Rep (EncodeError a) x $cto :: forall a x. Rep (EncodeError a) x -> EncodeError a to :: forall x. Rep (EncodeError a) x -> EncodeError a Generic) instance Eq (ToItemError a) => Eq (EncodeError a) where == :: EncodeError a -> EncodeError a -> Bool (==) = EncodeError a -> EncodeError a -> Bool forall a. (Generic a, Eq (Rep a ())) => a -> a -> Bool geq instance Show (ToItemError a) => Show (EncodeError a) where showsPrec :: Int -> EncodeError a -> ShowS showsPrec = Int -> EncodeError a -> ShowS forall a. (Generic a, GShow0 (Rep a)) => Int -> a -> ShowS gshowsPrec encode :: ToItem a => a -> Either (EncodeError a) TL.Text encode :: forall a. ToItem a => a -> Either (EncodeError a) Text encode = (Item -> Text) -> Either (EncodeError a) Item -> Either (EncodeError a) Text forall a b. (a -> b) -> Either (EncodeError a) a -> Either (EncodeError a) b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap (Int -> Item -> Text serialize Int 2) (Either (EncodeError a) Item -> Either (EncodeError a) Text) -> (a -> Either (EncodeError a) Item) -> a -> Either (EncodeError a) Text forall b c a. (b -> c) -> (a -> b) -> a -> c . (ToItemError a -> EncodeError a) -> Either (ToItemError a) Item -> Either (EncodeError 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 ToItemError a -> EncodeError a forall a. ToItemError a -> EncodeError a EncodeError'ToItemError (Either (ToItemError a) Item -> Either (EncodeError a) Item) -> (a -> Either (ToItemError a) Item) -> a -> Either (EncodeError a) Item forall b c a. (b -> c) -> (a -> b) -> a -> c . a -> Either (ToItemError a) Item forall a. ToItem a => a -> Either (ToItemError a) Item toItem