{-# OPTIONS_GHC -Wno-orphans #-}

module IsomorphismClass.Relations.LazyTextBuilderAndText where

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

instance IsomorphicTo Data.Text.Lazy.Builder.Builder Text where
  to :: Text -> Builder
to = Text -> Builder
Data.Text.Lazy.Builder.fromText

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