{-# OPTIONS_GHC -Wno-orphans #-}

module IsomorphismClass.Relations.ByteArrayAndByteString where

import qualified Data.ByteString.Short
import qualified Data.Primitive.ByteArray
import IsomorphismClass.Classes
import IsomorphismClass.Prelude
import IsomorphismClass.Relations.ByteArrayAndShortByteString ()
import IsomorphismClass.Relations.ByteStringAndShortByteString ()

instance IsSome Data.Primitive.ByteArray.ByteArray ByteString where
  to :: ByteString -> ByteArray
to = ShortByteString -> ByteArray
forall sup sub. IsSome sup sub => sub -> sup
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 sup sub. IsSome sup sub => sub -> sup
to @Data.ByteString.Short.ShortByteString

instance IsSome ByteString Data.Primitive.ByteArray.ByteArray where
  to :: ByteArray -> ByteString
to = ShortByteString -> ByteString
forall sup sub. IsSome sup sub => sub -> sup
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 sup sub. IsSome sup sub => sub -> sup
to @Data.ByteString.Short.ShortByteString

instance Is Data.Primitive.ByteArray.ByteArray ByteString

instance Is ByteString Data.Primitive.ByteArray.ByteArray