{-# OPTIONS_GHC -Wno-orphans #-} module IsomorphismClass.Relations.LazyByteStringAndLazyText where import qualified Data.ByteString.Lazy import qualified Data.Text.Lazy import qualified Data.Text.Lazy.Encoding import IsomorphismClass.Classes import IsomorphismClass.Prelude instance IsSome Data.ByteString.Lazy.ByteString Data.Text.Lazy.Text where to :: Text -> ByteString to = Text -> ByteString Data.Text.Lazy.Encoding.encodeUtf8 maybeFrom :: ByteString -> Maybe Text maybeFrom = (UnicodeException -> Maybe Text) -> (Text -> Maybe Text) -> Either UnicodeException Text -> Maybe Text forall a c b. (a -> c) -> (b -> c) -> Either a b -> c either (Maybe Text -> UnicodeException -> Maybe Text forall a b. a -> b -> a const Maybe Text forall a. Maybe a Nothing) Text -> Maybe Text forall a. a -> Maybe a Just (Either UnicodeException Text -> Maybe Text) -> (ByteString -> Either UnicodeException Text) -> ByteString -> Maybe Text forall b c a. (b -> c) -> (a -> b) -> a -> c forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . ByteString -> Either UnicodeException Text Data.Text.Lazy.Encoding.decodeUtf8'