{-# OPTIONS_GHC -Wno-orphans #-}

module LawfulConversions.Relations.ByteStringAndLazyText where

import qualified Data.ByteString.Lazy
import qualified Data.Text.Encoding.Error
import qualified Data.Text.Lazy
import qualified Data.Text.Lazy.Encoding
import LawfulConversions.Classes
import LawfulConversions.Prelude

-- | UTF-8 codec.
instance IsSome ByteString Data.Text.Lazy.Text where
  to :: Text -> ByteString
to = LazyByteString -> ByteString
Data.ByteString.Lazy.toStrict (LazyByteString -> ByteString)
-> (Text -> LazyByteString) -> Text -> ByteString
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
. Text -> LazyByteString
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
. LazyByteString -> Either UnicodeException Text
Data.Text.Lazy.Encoding.decodeUtf8' (LazyByteString -> Either UnicodeException Text)
-> (ByteString -> LazyByteString)
-> ByteString
-> Either UnicodeException 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 -> LazyByteString
Data.ByteString.Lazy.fromStrict

-- | Lenient UTF-8 decoding.
instance IsMany ByteString Data.Text.Lazy.Text where
  from :: ByteString -> Text
from = OnDecodeError -> LazyByteString -> Text
Data.Text.Lazy.Encoding.decodeUtf8With OnDecodeError
Data.Text.Encoding.Error.lenientDecode (LazyByteString -> Text)
-> (ByteString -> LazyByteString) -> ByteString -> 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 -> LazyByteString
Data.ByteString.Lazy.fromStrict