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

module IsomorphismClass.Relations.LazyTextAndStrictTextBuilder where

#if MIN_VERSION_text(2,0,2)

import qualified Data.Text.Encoding
import qualified Data.Text.Lazy
import IsomorphismClass.Classes
import IsomorphismClass.Prelude

instance IsomorphicTo Data.Text.Lazy.Text Data.Text.Encoding.StrictBuilder where
  to :: StrictBuilder -> Text
to = Text -> Text
Data.Text.Lazy.fromStrict (Text -> Text) -> (StrictBuilder -> Text) -> StrictBuilder -> 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
. StrictBuilder -> Text
Data.Text.Encoding.strictBuilderToText

instance IsomorphicTo Data.Text.Encoding.StrictBuilder Data.Text.Lazy.Text where
  to :: Text -> StrictBuilder
to = Text -> StrictBuilder
Data.Text.Encoding.textToStrictBuilder (Text -> StrictBuilder) -> (Text -> Text) -> Text -> 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
. Text -> Text
Data.Text.Lazy.toStrict

#endif