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