{-# OPTIONS_GHC -Wno-orphans #-}

module IsomorphismClass.Relations.LazyTextAndString where

import qualified Data.Text.Lazy
import IsomorphismClass.Classes
import IsomorphismClass.Prelude
import IsomorphismClass.Relations.StringAndText ()

instance IsSome String Data.Text.Lazy.Text where
  to :: Text -> String
to = Text -> String
Data.Text.Lazy.unpack
  maybeFrom :: String -> Maybe Text
maybeFrom = (StrictText -> Text) -> Maybe StrictText -> Maybe Text
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap StrictText -> Text
Data.Text.Lazy.fromStrict (Maybe StrictText -> Maybe Text)
-> (String -> Maybe StrictText) -> String -> 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
. String -> Maybe StrictText
forall sup sub. IsSome sup sub => sup -> Maybe sub
maybeFrom