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

module IsomorphismClass.Relations.LazyByteStringBuilderAndTextArray where

#if !MIN_VERSION_text(2,1,0)

import qualified Data.ByteString.Builder
import qualified Data.ByteString.Lazy
import qualified Data.ByteString.Short
import qualified Data.Text.Array
import IsomorphismClass.Classes
import IsomorphismClass.Prelude
import qualified IsomorphismClass.TextCompat.Array

instance IsomorphicTo Data.ByteString.Builder.Builder Data.Text.Array.Array where
  to :: Array -> Builder
to = ShortByteString -> Builder
Data.ByteString.Builder.shortByteString (ShortByteString -> Builder)
-> (Array -> ShortByteString) -> Array -> Builder
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
. Array -> ShortByteString
IsomorphismClass.TextCompat.Array.toShortByteString

instance IsomorphicTo Data.Text.Array.Array Data.ByteString.Builder.Builder where
  to :: Builder -> Array
to =
    ShortByteString -> Array
IsomorphismClass.TextCompat.Array.fromShortByteString
      (ShortByteString -> Array)
-> (Builder -> ShortByteString) -> Builder -> Array
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 -> ShortByteString
Data.ByteString.Short.toShort
      (ByteString -> ShortByteString)
-> (Builder -> ByteString) -> Builder -> ShortByteString
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 -> ByteString
Data.ByteString.Lazy.toStrict
      (ByteString -> ByteString)
-> (Builder -> ByteString) -> Builder -> 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
. Builder -> ByteString
Data.ByteString.Builder.toLazyByteString

#endif