{-# OPTIONS_GHC -Wno-orphans #-} module IsomorphismClass.Relations.ByteArrayAndLazyByteStringBuilder where import qualified Data.ByteString.Builder import qualified Data.ByteString.Short import qualified Data.Primitive.ByteArray import IsomorphismClass.Classes import IsomorphismClass.Prelude import IsomorphismClass.Relations.ByteArrayAndShortByteString () import IsomorphismClass.Relations.LazyByteStringBuilderAndShortByteString () instance IsomorphicTo Data.Primitive.ByteArray.ByteArray Data.ByteString.Builder.Builder where to :: Builder -> ByteArray to = ShortByteString -> ByteArray forall a b. IsomorphicTo a b => b -> a to (ShortByteString -> ByteArray) -> (Builder -> ShortByteString) -> Builder -> ByteArray 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 . forall a b. IsomorphicTo a b => b -> a to @Data.ByteString.Short.ShortByteString instance IsomorphicTo Data.ByteString.Builder.Builder Data.Primitive.ByteArray.ByteArray where to :: ByteArray -> Builder to = ShortByteString -> Builder forall a b. IsomorphicTo a b => b -> a to (ShortByteString -> Builder) -> (ByteArray -> ShortByteString) -> ByteArray -> 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 . forall a b. IsomorphicTo a b => b -> a to @Data.ByteString.Short.ShortByteString