-- |
-- Isomorphism law as a lawful solution to the conversion problem.
--
-- = Conversion problem
--
-- Have you ever looked for a @toString@ function? How often do you
-- import @Data.Text.Lazy@ only to call its 'Data.Text.Lazy.fromStrict'? How
-- about importing @Data.Text@ only to to call its 'Data.Text.unpack'? How
-- about going thru the always fun sequence of
-- importing @Data.ByteString.Builder@ only to to call its
-- 'Data.ByteString.Builder.toLazyByteString' and then importing
-- @Data.ByteString.Lazy@ only to call its 'Data.ByteString.Lazy.toStrict'?
--
-- Those all are instances of one pattern. They are conversions between
-- representations of the same information. Codebases that don't attempt to
-- abstract over this pattern tend to be sprawling with this type of
-- boilerplate. It's noise to the codereader, it's a burden to the
-- implementor and the maintainer.
--
-- = Why another conversion library?
--
-- Many libraries exist that approach the conversion problem. However all of
-- them provide lawless typeclasses leaving it up to the author of the
-- instance to define what makes a proper conversion. This results in
-- inconsistencies across instances and their behaviour being not evident to
-- the user.
--
-- This library tackles this problem with a lawful typeclass, making it
-- evident what any of its instances do.
--
-- = The law
--
-- The key insight of this library is that if you add a requirement for the
-- conversion to be lossless and to have a mirror conversion in the opposite
-- direction, there usually appears to be only one way of defining it. That
-- makes it very clear what the conversion does to the user and how to define
-- it to the author of the conversion.
--
-- That insight itself stems from an observation that almost all of the
-- practical conversions in Haskell share a property: you can restore the
-- original data from its converted form. E.g., you can get a bytestring from
-- a builder and you can create a builder from a bytestring, you can convert
-- a text into a list of chars and vice-versa, bytestring to\/from bytearray,
-- strict bytestring to\/from lazy, list to\/from sequence, sequence to/from
-- vector, set of ints to\/from int-set. In other words, it's always a two-way
-- street with them and there's a lot of instances of this pattern.
--
-- = UX
--
-- A few other accidental findings like encoding this property with recursive
-- typeclass constraints and fine-tuning for the use of
-- the @TypeApplications@ extension resulted in a very terse yet clear API.
--
-- Essentially the whole API is just two functions: 'to' and 'from'. Both
-- perform a conversion between two types. The only difference between them
-- is in what the first type application parameter specifies. E.g.:
--
-- > fromString = from @String
--
-- > toText = to @Text
--
-- In other words 'to' and 'from' let you explicitly specify either the source
-- or the target type of a conversion when you need to help the type
-- inferencer.
--
-- Here are more practical examples:
--
-- @
-- renderNameAndHeight :: 'Text' -> 'Int' -> 'Text'
-- renderNameAndHeight name height =
--   'from' @'TextLazyBuilder.Builder' $
--     "Height of " <> 'to' name <> " is " <> 'showAs' height
-- @
--
-- @
-- combineEncodings :: 'ByteStringShort.ShortByteString' -> 'PrimitiveByteArray.ByteArray' -> 'ByteString' -> [Word8]
-- combineEncodings a b c =
--   'from' @'ByteStringBuilder.Builder' $
--     'to' a <> 'to' b <> 'to' c
-- @
module IsomorphismClass
  ( -- * Typeclass
    IsomorphicTo (..),
    from,

    -- * Common Utilities
    showAs,
  )
where

import qualified Data.ByteString as ByteString
import qualified Data.ByteString.Builder as ByteStringBuilder
import qualified Data.ByteString.Lazy as ByteStringLazy
import qualified Data.ByteString.Short as ByteStringShort
import qualified Data.ByteString.Short.Internal as ByteStringShortInternal
import qualified Data.Primitive.ByteArray as PrimitiveByteArray
import qualified Data.Sequence as Seq
import qualified Data.Set as Set
import qualified Data.Text as Text
import qualified Data.Text.Array as TextArray
import qualified Data.Text.Lazy as TextLazy
import qualified Data.Text.Lazy.Builder as TextLazyBuilder
import qualified Data.Vector as Vector
import qualified Data.Vector.Generic as VectorGeneric
import IsomorphismClass.Prelude
import qualified IsomorphismClass.TextCompat.Array as TextCompatArray

-- | Bidirectional conversion between two types with no loss of information.
-- The bidirectionality is encoded via a recursive dependency with arguments
-- flipped.
--
-- You can read the signature @IsomorphicTo a b@ as \"/B/ is isomorphic to /A/\".
--
-- __Laws__
--
-- /A/ is isomorphic to /B/ if and only if there exists a conversion from /A/
-- to /B/ ('to') and a conversion from /B/ to /A/ ('from') such that:
--
-- - @'from' . 'to' = 'id'@ - For all values of /A/ converting from /A/ to /B/
--     and then converting from /B/ to /A/ produces a value that is identical
--     to the original.
--
-- - @'to' . 'from' = 'id'@ - For all values of /B/ converting from /B/ to /A/
--     and then converting from /A/ to /B/ produces a value that is identical
--     to the original.
--
-- __Usage__
--
-- This class is particularly easy to use in combination with
-- the @TypeApplications@ extension making it clear to the reader what sort
-- of conversion he sees. E.g.,
--
-- > fromString = from @String
--
-- > toText = to @Text
--
-- The types are also self-evident:
--
-- > > :t from @String
-- > from @String :: IsomorphicTo b String => String -> b
--
-- > > :t to @Text
-- > to @Text :: IsomorphicTo Text b => b -> Text
--
-- __Instance Definition__
--
-- For each pair of isomorphic types (/A/ and /B/) the compiler will require
-- you to define two instances, namely: @IsomorphicTo A B@ and @IsomorphicTo
-- B A@.
class IsomorphicTo b a => IsomorphicTo a b where
  to :: b -> a

--

instance IsomorphicTo String Text where
  to :: Text -> String
to = Text -> String
Text.unpack

instance IsomorphicTo String TextLazy.Text where
  to :: Text -> String
to = Text -> String
TextLazy.unpack

instance IsomorphicTo String TextLazyBuilder.Builder where
  to :: Builder -> String
to = Text -> String
TextLazy.unpack (Text -> String) -> (Builder -> Text) -> Builder -> String
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Builder -> Text
TextLazyBuilder.toLazyText

--

instance IsomorphicTo [Word8] ByteString where
  to :: ByteString -> [Word8]
to = ByteString -> [Word8]
ByteString.unpack

instance IsomorphicTo [Word8] ByteStringLazy.ByteString where
  to :: ByteString -> [Word8]
to = ByteString -> [Word8]
ByteStringLazy.unpack

instance IsomorphicTo [Word8] ByteStringShort.ShortByteString where
  to :: ShortByteString -> [Word8]
to = ShortByteString -> [Word8]
ByteStringShort.unpack

instance IsomorphicTo [Word8] ByteStringBuilder.Builder where
  to :: Builder -> [Word8]
to = ByteString -> [Word8]
ByteStringLazy.unpack (ByteString -> [Word8])
-> (Builder -> ByteString) -> Builder -> [Word8]
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Builder -> ByteString
ByteStringBuilder.toLazyByteString

instance IsomorphicTo [Word8] PrimitiveByteArray.ByteArray where
  to :: ByteArray -> [Word8]
to = ByteArray -> [Word8]
forall l. IsList l => l -> [Item l]
toList

instance IsomorphicTo [Word8] TextArray.Array where
  to :: Array -> [Word8]
to = ShortByteString -> [Word8]
forall a b. IsomorphicTo a b => b -> a
to (ShortByteString -> [Word8])
-> (Array -> ShortByteString) -> Array -> [Word8]
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall b. IsomorphicTo ShortByteString b => b -> ShortByteString
forall a b. IsomorphicTo a b => b -> a
to @ByteStringShort.ShortByteString

--

instance IsomorphicTo [a] [a] where
  to :: [a] -> [a]
to = [a] -> [a]
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id

instance IsomorphicTo [a] (Vector a) where
  to :: Vector a -> [a]
to = Vector a -> [a]
forall l. IsList l => l -> [Item l]
toList

instance IsomorphicTo [a] (Seq a) where
  to :: Seq a -> [a]
to = Seq a -> [a]
forall l. IsList l => l -> [Item l]
toList

--

instance IsomorphicTo Text Text where
  to :: Text -> Text
to = Text -> Text
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id

-- | Performs replacement on invalid Unicode chars in the string.
instance IsomorphicTo Text String where
  to :: String -> Text
to = String -> Text
Text.pack

instance IsomorphicTo Text TextLazy.Text where
  to :: Text -> Text
to = Text -> Text
TextLazy.toStrict

instance IsomorphicTo Text TextLazyBuilder.Builder where
  to :: Builder -> Text
to = Text -> Text
TextLazy.toStrict (Text -> Text) -> (Builder -> Text) -> Builder -> Text
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Builder -> Text
TextLazyBuilder.toLazyText

--

instance IsomorphicTo TextLazy.Text TextLazy.Text where
  to :: Text -> Text
to = Text -> Text
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id

-- | Performs replacement on invalid Unicode chars in the string.
instance IsomorphicTo TextLazy.Text String where
  to :: String -> Text
to = String -> Text
TextLazy.pack

instance IsomorphicTo TextLazy.Text Text where
  to :: Text -> Text
to = Text -> Text
TextLazy.fromStrict

instance IsomorphicTo TextLazy.Text TextLazyBuilder.Builder where
  to :: Builder -> Text
to = Builder -> Text
TextLazyBuilder.toLazyText

--

instance IsomorphicTo TextLazyBuilder.Builder TextLazyBuilder.Builder where
  to :: Builder -> Builder
to = Builder -> Builder
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id

-- | Performs replacement on invalid Unicode chars in the string.
instance IsomorphicTo TextLazyBuilder.Builder String where
  to :: String -> Builder
to = String -> Builder
TextLazyBuilder.fromString

instance IsomorphicTo TextLazyBuilder.Builder Text where
  to :: Text -> Builder
to = Text -> Builder
TextLazyBuilder.fromText

instance IsomorphicTo TextLazyBuilder.Builder TextLazy.Text where
  to :: Text -> Builder
to = Text -> Builder
TextLazyBuilder.fromLazyText

--

instance IsomorphicTo ByteString ByteString where
  to :: ByteString -> ByteString
to = ByteString -> ByteString
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id

instance IsomorphicTo ByteString [Word8] where
  to :: [Word8] -> ByteString
to = [Word8] -> ByteString
ByteString.pack

instance IsomorphicTo ByteString ByteStringLazy.ByteString where
  to :: ByteString -> ByteString
to = ByteString -> ByteString
ByteStringLazy.toStrict

instance IsomorphicTo ByteString ByteStringShort.ShortByteString where
  to :: ShortByteString -> ByteString
to = ShortByteString -> ByteString
ByteStringShort.fromShort

instance IsomorphicTo ByteString ByteStringBuilder.Builder where
  to :: Builder -> ByteString
to = ByteString -> ByteString
ByteStringLazy.toStrict (ByteString -> ByteString)
-> (Builder -> ByteString) -> Builder -> ByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Builder -> ByteString
ByteStringBuilder.toLazyByteString

instance IsomorphicTo ByteString PrimitiveByteArray.ByteArray where
  to :: ByteArray -> ByteString
to = ShortByteString -> ByteString
forall a b. IsomorphicTo a b => b -> a
to (ShortByteString -> ByteString)
-> (ByteArray -> ShortByteString) -> ByteArray -> ByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall b. IsomorphicTo ShortByteString b => b -> ShortByteString
forall a b. IsomorphicTo a b => b -> a
to @ByteStringShort.ShortByteString

instance IsomorphicTo ByteString TextArray.Array where
  to :: Array -> ByteString
to = ShortByteString -> ByteString
forall a b. IsomorphicTo a b => b -> a
to (ShortByteString -> ByteString)
-> (Array -> ShortByteString) -> Array -> ByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall b. IsomorphicTo ShortByteString b => b -> ShortByteString
forall a b. IsomorphicTo a b => b -> a
to @ByteStringShort.ShortByteString

--

instance IsomorphicTo ByteStringLazy.ByteString ByteStringLazy.ByteString where
  to :: ByteString -> ByteString
to = ByteString -> ByteString
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id

instance IsomorphicTo ByteStringLazy.ByteString [Word8] where
  to :: [Word8] -> ByteString
to = [Word8] -> ByteString
ByteStringLazy.pack

instance IsomorphicTo ByteStringLazy.ByteString ByteString where
  to :: ByteString -> ByteString
to = ByteString -> ByteString
ByteStringLazy.fromStrict

instance IsomorphicTo ByteStringLazy.ByteString ByteStringShort.ShortByteString where
  to :: ShortByteString -> ByteString
to = forall b. IsomorphicTo b ByteString => ByteString -> b
forall a b. IsomorphicTo b a => a -> b
from @ByteString (ByteString -> ByteString)
-> (ShortByteString -> ByteString) -> ShortByteString -> ByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ShortByteString -> ByteString
forall a b. IsomorphicTo a b => b -> a
to

instance IsomorphicTo ByteStringLazy.ByteString ByteStringBuilder.Builder where
  to :: Builder -> ByteString
to = Builder -> ByteString
ByteStringBuilder.toLazyByteString

instance IsomorphicTo ByteStringLazy.ByteString PrimitiveByteArray.ByteArray where
  to :: ByteArray -> ByteString
to = ShortByteString -> ByteString
forall a b. IsomorphicTo a b => b -> a
to (ShortByteString -> ByteString)
-> (ByteArray -> ShortByteString) -> ByteArray -> ByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall b. IsomorphicTo ShortByteString b => b -> ShortByteString
forall a b. IsomorphicTo a b => b -> a
to @ByteStringShort.ShortByteString

instance IsomorphicTo ByteStringLazy.ByteString TextArray.Array where
  to :: Array -> ByteString
to = ShortByteString -> ByteString
forall a b. IsomorphicTo a b => b -> a
to (ShortByteString -> ByteString)
-> (Array -> ShortByteString) -> Array -> ByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall b. IsomorphicTo ShortByteString b => b -> ShortByteString
forall a b. IsomorphicTo a b => b -> a
to @ByteStringShort.ShortByteString

--

instance IsomorphicTo ByteStringShort.ShortByteString ByteStringShort.ShortByteString where
  to :: ShortByteString -> ShortByteString
to = ShortByteString -> ShortByteString
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id

instance IsomorphicTo ByteStringShort.ShortByteString [Word8] where
  to :: [Word8] -> ShortByteString
to = [Word8] -> ShortByteString
ByteStringShort.pack

instance IsomorphicTo ByteStringShort.ShortByteString ByteString where
  to :: ByteString -> ShortByteString
to = ByteString -> ShortByteString
ByteStringShort.toShort

instance IsomorphicTo ByteStringShort.ShortByteString ByteStringLazy.ByteString where
  to :: ByteString -> ShortByteString
to = ByteString -> ShortByteString
forall a b. IsomorphicTo a b => b -> a
to (ByteString -> ShortByteString)
-> (ByteString -> ByteString) -> ByteString -> ShortByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall b. IsomorphicTo ByteString b => b -> ByteString
forall a b. IsomorphicTo a b => b -> a
to @ByteString

instance IsomorphicTo ByteStringShort.ShortByteString ByteStringBuilder.Builder where
  to :: Builder -> ShortByteString
to = ByteString -> ShortByteString
forall a b. IsomorphicTo a b => b -> a
to (ByteString -> ShortByteString)
-> (Builder -> ByteString) -> Builder -> ShortByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall b. IsomorphicTo ByteString b => b -> ByteString
forall a b. IsomorphicTo a b => b -> a
to @ByteStringLazy.ByteString

instance IsomorphicTo ByteStringShort.ShortByteString PrimitiveByteArray.ByteArray where
  to :: ByteArray -> ShortByteString
to (PrimitiveByteArray.ByteArray ByteArray#
array) = ByteArray# -> ShortByteString
ByteStringShortInternal.SBS ByteArray#
array

instance IsomorphicTo ByteStringShort.ShortByteString TextArray.Array where
  to :: Array -> ShortByteString
to Array
a = ByteArray# -> ShortByteString
ByteStringShortInternal.SBS (Array -> ByteArray#
TextCompatArray.toUnliftedByteArray Array
a)

--

instance IsomorphicTo ByteStringBuilder.Builder ByteStringBuilder.Builder where
  to :: Builder -> Builder
to = Builder -> Builder
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id

instance IsomorphicTo ByteStringBuilder.Builder [Word8] where
  to :: [Word8] -> Builder
to = ByteString -> Builder
forall a b. IsomorphicTo a b => b -> a
to (ByteString -> Builder)
-> ([Word8] -> ByteString) -> [Word8] -> Builder
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall b. IsomorphicTo ByteString b => b -> ByteString
forall a b. IsomorphicTo a b => b -> a
to @ByteString

instance IsomorphicTo ByteStringBuilder.Builder ByteString where
  to :: ByteString -> Builder
to = ByteString -> Builder
ByteStringBuilder.byteString

instance IsomorphicTo ByteStringBuilder.Builder ByteStringLazy.ByteString where
  to :: ByteString -> Builder
to = ByteString -> Builder
ByteStringBuilder.lazyByteString

instance IsomorphicTo ByteStringBuilder.Builder ByteStringShort.ShortByteString where
  to :: ShortByteString -> Builder
to = ShortByteString -> Builder
ByteStringBuilder.shortByteString

instance IsomorphicTo ByteStringBuilder.Builder PrimitiveByteArray.ByteArray where
  to :: ByteArray -> Builder
to = ShortByteString -> Builder
forall a b. IsomorphicTo a b => b -> a
to (ShortByteString -> Builder)
-> (ByteArray -> ShortByteString) -> ByteArray -> Builder
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall b. IsomorphicTo ShortByteString b => b -> ShortByteString
forall a b. IsomorphicTo a b => b -> a
to @ByteStringShort.ShortByteString

instance IsomorphicTo ByteStringBuilder.Builder TextArray.Array where
  to :: Array -> Builder
to = ShortByteString -> Builder
forall a b. IsomorphicTo a b => b -> a
to (ShortByteString -> Builder)
-> (Array -> ShortByteString) -> Array -> Builder
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall b. IsomorphicTo ShortByteString b => b -> ShortByteString
forall a b. IsomorphicTo a b => b -> a
to @ByteStringShort.ShortByteString

--

instance IsomorphicTo PrimitiveByteArray.ByteArray PrimitiveByteArray.ByteArray where
  to :: ByteArray -> ByteArray
to = ByteArray -> ByteArray
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id

instance IsomorphicTo PrimitiveByteArray.ByteArray [Word8] where
  to :: [Word8] -> ByteArray
to = [Word8] -> ByteArray
forall l. IsList l => [Item l] -> l
fromList

instance IsomorphicTo PrimitiveByteArray.ByteArray ByteStringShort.ShortByteString where
  to :: ShortByteString -> ByteArray
to (ByteStringShortInternal.SBS ByteArray#
array) = ByteArray# -> ByteArray
PrimitiveByteArray.ByteArray ByteArray#
array

instance IsomorphicTo PrimitiveByteArray.ByteArray ByteString where
  to :: ByteString -> ByteArray
to = ShortByteString -> ByteArray
forall a b. IsomorphicTo a b => b -> a
to (ShortByteString -> ByteArray)
-> (ByteString -> ShortByteString) -> ByteString -> ByteArray
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall b. IsomorphicTo ShortByteString b => b -> ShortByteString
forall a b. IsomorphicTo a b => b -> a
to @ByteStringShort.ShortByteString

instance IsomorphicTo PrimitiveByteArray.ByteArray ByteStringLazy.ByteString where
  to :: ByteString -> ByteArray
to = ShortByteString -> ByteArray
forall a b. IsomorphicTo a b => b -> a
to (ShortByteString -> ByteArray)
-> (ByteString -> ShortByteString) -> ByteString -> ByteArray
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall b. IsomorphicTo ShortByteString b => b -> ShortByteString
forall a b. IsomorphicTo a b => b -> a
to @ByteStringShort.ShortByteString

instance IsomorphicTo PrimitiveByteArray.ByteArray ByteStringBuilder.Builder where
  to :: Builder -> ByteArray
to = ShortByteString -> ByteArray
forall a b. IsomorphicTo a b => b -> a
to (ShortByteString -> ByteArray)
-> (Builder -> ShortByteString) -> Builder -> ByteArray
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall b. IsomorphicTo ShortByteString b => b -> ShortByteString
forall a b. IsomorphicTo a b => b -> a
to @ByteStringShort.ShortByteString

instance IsomorphicTo PrimitiveByteArray.ByteArray TextArray.Array where
  to :: Array -> ByteArray
to Array
a = ByteArray# -> ByteArray
PrimitiveByteArray.ByteArray (Array -> ByteArray#
TextCompatArray.toUnliftedByteArray Array
a)

--

instance IsomorphicTo TextArray.Array [Word8] where
  to :: [Word8] -> Array
to = ShortByteString -> Array
forall a b. IsomorphicTo a b => b -> a
to (ShortByteString -> Array)
-> ([Word8] -> ShortByteString) -> [Word8] -> Array
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall b. IsomorphicTo ShortByteString b => b -> ShortByteString
forall a b. IsomorphicTo a b => b -> a
to @ByteStringShort.ShortByteString

instance IsomorphicTo TextArray.Array PrimitiveByteArray.ByteArray where
  to :: ByteArray -> Array
to (PrimitiveByteArray.ByteArray ByteArray#
arr) = ByteArray# -> Array
TextCompatArray.fromUnliftedByteArray ByteArray#
arr

instance IsomorphicTo TextArray.Array ByteStringShort.ShortByteString where
  to :: ShortByteString -> Array
to (ByteStringShortInternal.SBS ByteArray#
arr) = ByteArray# -> Array
TextCompatArray.fromUnliftedByteArray ByteArray#
arr

instance IsomorphicTo TextArray.Array ByteString where
  to :: ByteString -> Array
to = ShortByteString -> Array
forall a b. IsomorphicTo a b => b -> a
to (ShortByteString -> Array)
-> (ByteString -> ShortByteString) -> ByteString -> Array
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall b. IsomorphicTo ShortByteString b => b -> ShortByteString
forall a b. IsomorphicTo a b => b -> a
to @ByteStringShort.ShortByteString

instance IsomorphicTo TextArray.Array ByteStringLazy.ByteString where
  to :: ByteString -> Array
to = ShortByteString -> Array
forall a b. IsomorphicTo a b => b -> a
to (ShortByteString -> Array)
-> (ByteString -> ShortByteString) -> ByteString -> Array
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall b. IsomorphicTo ShortByteString b => b -> ShortByteString
forall a b. IsomorphicTo a b => b -> a
to @ByteStringShort.ShortByteString

instance IsomorphicTo TextArray.Array ByteStringBuilder.Builder where
  to :: Builder -> Array
to = ShortByteString -> Array
forall a b. IsomorphicTo a b => b -> a
to (ShortByteString -> Array)
-> (Builder -> ShortByteString) -> Builder -> Array
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall b. IsomorphicTo ShortByteString b => b -> ShortByteString
forall a b. IsomorphicTo a b => b -> a
to @ByteStringShort.ShortByteString

--

instance IsomorphicTo (Vector a) (Vector a) where
  to :: Vector a -> Vector a
to = Vector a -> Vector a
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id

instance IsomorphicTo (Vector a) [a] where
  to :: [a] -> Vector a
to = [a] -> Vector a
forall a. [a] -> Vector a
Vector.fromList

instance IsomorphicTo (Vector a) (Seq a) where
  to :: Seq a -> Vector a
to = forall b. IsomorphicTo b [a] => [a] -> b
forall a b. IsomorphicTo b a => a -> b
from @[a] ([a] -> Vector a) -> (Seq a -> [a]) -> Seq a -> Vector a
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Seq a -> [a]
forall a b. IsomorphicTo a b => b -> a
to

--

instance IsomorphicTo (Seq a) (Seq a) where
  to :: Seq a -> Seq a
to = Seq a -> Seq a
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id

instance IsomorphicTo (Seq a) [a] where
  to :: [a] -> Seq a
to = [a] -> Seq a
forall a. [a] -> Seq a
Seq.fromList

instance IsomorphicTo (Seq a) (Vector a) where
  to :: Vector a -> Seq a
to = forall b. IsomorphicTo b [a] => [a] -> b
forall a b. IsomorphicTo b a => a -> b
from @[a] ([a] -> Seq a) -> (Vector a -> [a]) -> Vector a -> Seq a
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Vector a -> [a]
forall a b. IsomorphicTo a b => b -> a
to

--

instance IsomorphicTo (Set a) (Set a) where
  to :: Set a -> Set a
to = Set a -> Set a
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id

instance IsomorphicTo (Set Int) IntSet where
  to :: IntSet -> Set Int
to = [Int] -> Set Int
forall l. IsList l => [Item l] -> l
fromList ([Int] -> Set Int) -> (IntSet -> [Int]) -> IntSet -> Set Int
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. IntSet -> [Int]
forall l. IsList l => l -> [Item l]
toList

--

instance IsomorphicTo IntSet IntSet where
  to :: IntSet -> IntSet
to = IntSet -> IntSet
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id

instance IsomorphicTo IntSet (Set Int) where
  to :: Set Int -> IntSet
to = [Int] -> IntSet
forall l. IsList l => [Item l] -> l
fromList ([Int] -> IntSet) -> (Set Int -> [Int]) -> Set Int -> IntSet
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Set Int -> [Int]
forall l. IsList l => l -> [Item l]
toList

--

instance IsomorphicTo (Map k v) (Map k v) where
  to :: Map k v -> Map k v
to = Map k v -> Map k v
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id

instance IsomorphicTo (Map Int v) (IntMap v) where
  to :: IntMap v -> Map Int v
to = [(Int, v)] -> Map Int v
forall l. IsList l => [Item l] -> l
fromList ([(Int, v)] -> Map Int v)
-> (IntMap v -> [(Int, v)]) -> IntMap v -> Map Int v
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. IntMap v -> [(Int, v)]
forall l. IsList l => l -> [Item l]
toList

--

instance IsomorphicTo (IntMap a) (IntMap a) where
  to :: IntMap a -> IntMap a
to = IntMap a -> IntMap a
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id

instance IsomorphicTo (IntMap v) (Map Int v) where
  to :: Map Int v -> IntMap v
to = [(Int, v)] -> IntMap v
forall l. IsList l => [Item l] -> l
fromList ([(Int, v)] -> IntMap v)
-> (Map Int v -> [(Int, v)]) -> Map Int v -> IntMap v
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Map Int v -> [(Int, v)]
forall l. IsList l => l -> [Item l]
toList

--

instance IsomorphicTo (Maybe a) (Maybe a) where to :: Maybe a -> Maybe a
to = Maybe a -> Maybe a
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id

instance IsomorphicTo (Either a b) (Either a b) where to :: Either a b -> Either a b
to = Either a b -> Either a b
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id

instance IsomorphicTo (First a) (First a) where to :: First a -> First a
to = First a -> First a
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id

instance IsomorphicTo (Last a) (Last a) where to :: Last a -> Last a
to = Last a -> Last a
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id

instance IsomorphicTo (Product a) (Product a) where to :: Product a -> Product a
to = Product a -> Product a
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id

instance IsomorphicTo (Sum a) (Sum a) where to :: Sum a -> Sum a
to = Sum a -> Sum a
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id

--

instance IsomorphicTo Bool Bool where to :: Bool -> Bool
to = Bool -> Bool
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id

instance IsomorphicTo Char Char where to :: Char -> Char
to = Char -> Char
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id

instance IsomorphicTo Double Double where to :: Double -> Double
to = Double -> Double
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id

instance IsomorphicTo Float Float where to :: Float -> Float
to = Float -> Float
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id

instance IsomorphicTo Int Int where to :: Int -> Int
to = Int -> Int
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id

instance IsomorphicTo Int Word where to :: Word -> Int
to = Word -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral

instance IsomorphicTo Int16 Int16 where to :: Int16 -> Int16
to = Int16 -> Int16
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id

instance IsomorphicTo Int16 Word16 where to :: Word16 -> Int16
to = Word16 -> Int16
forall a b. (Integral a, Num b) => a -> b
fromIntegral

instance IsomorphicTo Int32 Int32 where to :: Int32 -> Int32
to = Int32 -> Int32
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id

instance IsomorphicTo Int32 Word32 where to :: Word32 -> Int32
to = Word32 -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral

instance IsomorphicTo Int64 Int64 where to :: Int64 -> Int64
to = Int64 -> Int64
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id

instance IsomorphicTo Int64 Word64 where to :: Word64 -> Int64
to = Word64 -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral

instance IsomorphicTo Int8 Int8 where to :: Int8 -> Int8
to = Int8 -> Int8
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id

instance IsomorphicTo Int8 Word8 where to :: Word8 -> Int8
to = Word8 -> Int8
forall a b. (Integral a, Num b) => a -> b
fromIntegral

instance IsomorphicTo Integer Integer where to :: Integer -> Integer
to = Integer -> Integer
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id

instance IsomorphicTo Rational Rational where to :: Rational -> Rational
to = Rational -> Rational
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id

instance IsomorphicTo Word Int where to :: Int -> Word
to = Int -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral

instance IsomorphicTo Word Word where to :: Word -> Word
to = Word -> Word
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id

instance IsomorphicTo Word16 Int16 where to :: Int16 -> Word16
to = Int16 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral

instance IsomorphicTo Word16 Word16 where to :: Word16 -> Word16
to = Word16 -> Word16
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id

instance IsomorphicTo Word32 Int32 where to :: Int32 -> Word32
to = Int32 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral

instance IsomorphicTo Word32 Word32 where to :: Word32 -> Word32
to = Word32 -> Word32
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id

instance IsomorphicTo Word64 Int64 where to :: Int64 -> Word64
to = Int64 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral

instance IsomorphicTo Word64 Word64 where to :: Word64 -> Word64
to = Word64 -> Word64
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id

instance IsomorphicTo Word8 Int8 where to :: Int8 -> Word8
to = Int8 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral

instance IsomorphicTo Word8 Word8 where to :: Word8 -> Word8
to = Word8 -> Word8
forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id

--

-- |
-- 'to' in reverse direction.
--
-- Particularly useful in combination with the @TypeApplications@ extension,
-- where it allows to specify the input type, e.g.:
--
-- > fromString :: IsomorphicTo a String => String -> a
-- > fromString = from @String
--
-- The first type application of the 'to' function on the other hand specifies
-- the output data type.
from :: forall a b. IsomorphicTo b a => a -> b
from :: a -> b
from = a -> b
forall a b. IsomorphicTo a b => b -> a
to

-- |
-- Ideally there should be a direct instance and this function
-- should merely serve as a helper for defining instances
-- by merely composing from other instances.
--
-- E.g.,
--
-- > thru @String Proxy
--
-- captures the following pattern:
--
-- > from @String . to
--
-- However it is advised to use the conversion functions directly,
-- since it makes the intent clearer and is actually shorter.
{-# INLINE thru #-}
thru :: (IsomorphicTo a b, IsomorphicTo a c) => Proxy a -> b -> c
thru :: Proxy a -> b -> c
thru Proxy a
proxy = a -> c
forall a b. IsomorphicTo b a => a -> b
from (a -> c) -> (b -> a) -> b -> c
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (a -> Proxy a -> a) -> Proxy a -> a -> a
forall a b c. (a -> b -> c) -> b -> a -> c
flip a -> Proxy a -> a
forall a (proxy :: * -> *). a -> proxy a -> a
asProxyTypeOf Proxy a
proxy (a -> a) -> (b -> a) -> b -> a
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. b -> a
forall a b. IsomorphicTo a b => b -> a
to

{-# INLINE thruString #-}
thruString :: (IsomorphicTo String a, IsomorphicTo String b) => a -> b
thruString :: a -> b
thruString = forall b. IsomorphicTo b String => String -> b
forall a b. IsomorphicTo b a => a -> b
from @String (String -> b) -> (a -> String) -> a -> b
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. a -> String
forall a b. IsomorphicTo a b => b -> a
to

{-# INLINE thruText #-}
thruText :: (IsomorphicTo Text a, IsomorphicTo Text b) => a -> b
thruText :: a -> b
thruText = forall b. IsomorphicTo b Text => Text -> b
forall a b. IsomorphicTo b a => a -> b
from @Text (Text -> b) -> (a -> Text) -> a -> b
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. a -> Text
forall a b. IsomorphicTo a b => b -> a
to

{-# INLINE thruList #-}
thruList :: forall a f g. (IsomorphicTo [a] (f a), IsomorphicTo [a] (g a)) => f a -> g a
thruList :: f a -> g a
thruList = forall b. IsomorphicTo b [a] => [a] -> b
forall a b. IsomorphicTo b a => a -> b
from @[a] ([a] -> g a) -> (f a -> [a]) -> f a -> g a
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. f a -> [a]
forall a b. IsomorphicTo a b => b -> a
to

-- | A utility, which uses the 'Show' instance to produce a value
-- that 'String' is isomorphic to.
--
-- It lets you generalize over the functions like the following:
--
-- > showAsText :: Show a => a -> Text
-- > showAsText = showAs @Text
--
-- > showAsBuilder :: Show a => a -> Builder
-- > showAsBuilder = showAs @Builder
showAs :: forall b a. (IsomorphicTo String b, Show a) => a -> b
showAs :: a -> b
showAs = String -> b
forall a b. IsomorphicTo b a => a -> b
from (String -> b) -> (a -> String) -> a -> b
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. a -> String
forall a. Show a => a -> String
show