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

module IsomorphismClass.Relations.ByteStringAndTextArray where

#if !MIN_VERSION_text(2,1,0)

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

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

instance IsSome Data.Text.Array.Array ByteString where
  to :: ByteString -> Array
to = ShortByteString -> Array
IsomorphismClass.TextCompat.Array.fromShortByteString (ShortByteString -> Array)
-> (ByteString -> ShortByteString) -> ByteString -> 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

instance Is ByteString Data.Text.Array.Array

instance Is Data.Text.Array.Array ByteString

#endif