{-# LANGUAGE CPP #-}
{-# OPTIONS_GHC -Wno-orphans #-}

module IsomorphismClass.Relations.StrictTextBuilderAndString where

#if MIN_VERSION_text(2,0,2)

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

instance IsSome String Data.Text.Encoding.StrictBuilder where
  to :: StrictBuilder -> String
to = Text -> String
forall sup sub. IsSome sup sub => sub -> sup
to (Text -> String)
-> (StrictBuilder -> Text) -> StrictBuilder -> String
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
. StrictBuilder -> Text
Data.Text.Encoding.strictBuilderToText
  maybeFrom :: String -> Maybe StrictBuilder
maybeFrom = (Text -> StrictBuilder) -> Maybe Text -> Maybe StrictBuilder
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> StrictBuilder
Data.Text.Encoding.textToStrictBuilder (Maybe Text -> Maybe StrictBuilder)
-> (String -> Maybe Text) -> String -> Maybe StrictBuilder
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 Text
forall sup sub. IsSome sup sub => sup -> Maybe sub
maybeFrom

#endif