module IsomorphismClass
(
IsomorphicTo (..),
from,
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
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 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 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 = forall l. IsList l => l -> [Item l]
toList
instance IsomorphicTo [Word8] TextArray.Array where
to :: Array -> [Word8]
to = forall a b. IsomorphicTo a b => b -> a
to 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 @ByteStringShort.ShortByteString
instance IsomorphicTo [a] [a] where
to :: [a] -> [a]
to = forall {k} (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance IsomorphicTo [a] (Vector a) where
to :: Vector a -> [a]
to = forall l. IsList l => l -> [Item l]
toList
instance IsomorphicTo [a] (Seq a) where
to :: Seq a -> [a]
to = forall l. IsList l => l -> [Item l]
toList
instance IsomorphicTo Text Text where
to :: Text -> Text
to = forall {k} (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
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 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 = forall {k} (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
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 = forall {k} (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
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 = 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 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 = forall a b. IsomorphicTo a b => b -> a
to 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 @ByteStringShort.ShortByteString
instance IsomorphicTo ByteString TextArray.Array where
to :: Array -> ByteString
to = forall a b. IsomorphicTo a b => b -> a
to 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 @ByteStringShort.ShortByteString
instance IsomorphicTo ByteStringLazy.ByteString ByteStringLazy.ByteString where
to :: ByteString -> ByteString
to = 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 a b. IsomorphicTo b a => a -> b
from @ByteString 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
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 = forall a b. IsomorphicTo a b => b -> a
to 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 @ByteStringShort.ShortByteString
instance IsomorphicTo ByteStringLazy.ByteString TextArray.Array where
to :: Array -> ByteString
to = forall a b. IsomorphicTo a b => b -> a
to 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 @ByteStringShort.ShortByteString
instance IsomorphicTo ByteStringShort.ShortByteString ByteStringShort.ShortByteString where
to :: ShortByteString -> ShortByteString
to = 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 = forall a b. IsomorphicTo a b => b -> a
to 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 @ByteString
instance IsomorphicTo ByteStringShort.ShortByteString ByteStringBuilder.Builder where
to :: Builder -> ShortByteString
to = forall a b. IsomorphicTo a b => b -> a
to 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 @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 = forall {k} (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance IsomorphicTo ByteStringBuilder.Builder [Word8] where
to :: [Word8] -> Builder
to = forall a b. IsomorphicTo a b => b -> a
to 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 @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 = forall a b. IsomorphicTo a b => b -> a
to 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 @ByteStringShort.ShortByteString
instance IsomorphicTo ByteStringBuilder.Builder TextArray.Array where
to :: Array -> Builder
to = forall a b. IsomorphicTo a b => b -> a
to 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 @ByteStringShort.ShortByteString
instance IsomorphicTo PrimitiveByteArray.ByteArray PrimitiveByteArray.ByteArray where
to :: ByteArray -> ByteArray
to = forall {k} (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance IsomorphicTo PrimitiveByteArray.ByteArray [Word8] where
to :: [Word8] -> ByteArray
to = 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 = forall a b. IsomorphicTo a b => b -> a
to 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 @ByteStringShort.ShortByteString
instance IsomorphicTo PrimitiveByteArray.ByteArray ByteStringLazy.ByteString where
to :: ByteString -> ByteArray
to = forall a b. IsomorphicTo a b => b -> a
to 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 @ByteStringShort.ShortByteString
instance IsomorphicTo PrimitiveByteArray.ByteArray ByteStringBuilder.Builder where
to :: Builder -> ByteArray
to = forall a b. IsomorphicTo a b => b -> a
to 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 @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 = forall a b. IsomorphicTo a b => b -> a
to 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 @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 = forall a b. IsomorphicTo a b => b -> a
to 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 @ByteStringShort.ShortByteString
instance IsomorphicTo TextArray.Array ByteStringLazy.ByteString where
to :: ByteString -> Array
to = forall a b. IsomorphicTo a b => b -> a
to 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 @ByteStringShort.ShortByteString
instance IsomorphicTo TextArray.Array ByteStringBuilder.Builder where
to :: Builder -> Array
to = forall a b. IsomorphicTo a b => b -> a
to 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 @ByteStringShort.ShortByteString
instance IsomorphicTo (Vector a) (Vector a) where
to :: Vector a -> Vector a
to = forall {k} (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance IsomorphicTo (Vector a) [a] where
to :: [a] -> Vector a
to = forall a. [a] -> Vector a
Vector.fromList
instance IsomorphicTo (Vector a) (Seq a) where
to :: Seq a -> Vector a
to = forall a b. IsomorphicTo b a => a -> b
from @[a] 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
instance IsomorphicTo (Seq a) (Seq a) where
to :: Seq a -> Seq a
to = forall {k} (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance IsomorphicTo (Seq a) [a] where
to :: [a] -> Seq a
to = forall a. [a] -> Seq a
Seq.fromList
instance IsomorphicTo (Seq a) (Vector a) where
to :: Vector a -> Seq a
to = forall a b. IsomorphicTo b a => a -> b
from @[a] 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
instance IsomorphicTo (Set a) (Set a) where
to :: Set a -> Set a
to = forall {k} (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance IsomorphicTo (Set Int) IntSet where
to :: IntSet -> Set Int
to = forall l. IsList l => [Item l] -> l
fromList forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall l. IsList l => l -> [Item l]
toList
instance IsomorphicTo IntSet IntSet where
to :: IntSet -> IntSet
to = forall {k} (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance IsomorphicTo IntSet (Set Int) where
to :: Set Int -> IntSet
to = forall l. IsList l => [Item l] -> l
fromList forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. 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 = 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 = forall l. IsList l => [Item l] -> l
fromList forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall l. IsList l => l -> [Item l]
toList
instance IsomorphicTo (IntMap a) (IntMap a) where
to :: IntMap a -> IntMap a
to = 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 = forall l. IsList l => [Item l] -> l
fromList forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall l. IsList l => l -> [Item l]
toList
instance IsomorphicTo (Maybe a) (Maybe a) where to :: Maybe a -> Maybe a
to = 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 = 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 = 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 = 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 = 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 = forall {k} (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance IsomorphicTo Bool Bool where to :: Bool -> Bool
to = forall {k} (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance IsomorphicTo Char Char where to :: Char -> Char
to = forall {k} (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance IsomorphicTo Double Double where to :: Double -> Double
to = forall {k} (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance IsomorphicTo Float Float where to :: Float -> Float
to = forall {k} (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance IsomorphicTo Int Int where to :: Int -> Int
to = forall {k} (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance IsomorphicTo Int Word where to :: Word -> Int
to = forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance IsomorphicTo Int16 Int16 where to :: Int16 -> Int16
to = forall {k} (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance IsomorphicTo Int16 Word16 where to :: Word16 -> Int16
to = forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance IsomorphicTo Int32 Int32 where to :: Int32 -> Int32
to = forall {k} (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance IsomorphicTo Int32 Word32 where to :: Word32 -> Int32
to = forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance IsomorphicTo Int64 Int64 where to :: Int64 -> Int64
to = forall {k} (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance IsomorphicTo Int64 Word64 where to :: Word64 -> Int64
to = forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance IsomorphicTo Int8 Int8 where to :: Int8 -> Int8
to = forall {k} (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance IsomorphicTo Int8 Word8 where to :: Word8 -> Int8
to = forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance IsomorphicTo Integer Integer where to :: Integer -> Integer
to = forall {k} (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance IsomorphicTo Rational Rational where to :: Rational -> Rational
to = forall {k} (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance IsomorphicTo Word Int where to :: Int -> Word
to = forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance IsomorphicTo Word Word where to :: Word -> Word
to = forall {k} (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance IsomorphicTo Word16 Int16 where to :: Int16 -> Word16
to = forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance IsomorphicTo Word16 Word16 where to :: Word16 -> Word16
to = forall {k} (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance IsomorphicTo Word32 Int32 where to :: Int32 -> Word32
to = forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance IsomorphicTo Word32 Word32 where to :: Word32 -> Word32
to = forall {k} (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance IsomorphicTo Word64 Int64 where to :: Int64 -> Word64
to = forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance IsomorphicTo Word64 Word64 where to :: Word64 -> Word64
to = forall {k} (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
instance IsomorphicTo Word8 Int8 where to :: Int8 -> Word8
to = forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance IsomorphicTo Word8 Word8 where to :: Word8 -> Word8
to = forall {k} (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id
from :: forall a b. IsomorphicTo b a => a -> b
from :: forall a b. IsomorphicTo b a => a -> b
from = forall a b. IsomorphicTo a b => b -> a
to
{-# INLINE thru #-}
thru :: (IsomorphicTo a b, IsomorphicTo a c) => Proxy a -> b -> c
thru :: forall a b c.
(IsomorphicTo a b, IsomorphicTo a c) =>
Proxy a -> b -> c
thru Proxy a
proxy = forall a b. IsomorphicTo b a => a -> b
from 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 c. (a -> b -> c) -> b -> a -> c
flip forall a (proxy :: * -> *). a -> proxy a -> a
asProxyTypeOf Proxy a
proxy 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
{-# INLINE thruString #-}
thruString :: (IsomorphicTo String a, IsomorphicTo String b) => a -> b
thruString :: forall a b.
(IsomorphicTo String a, IsomorphicTo String b) =>
a -> b
thruString = forall a b. IsomorphicTo b a => a -> b
from @String 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
{-# INLINE thruText #-}
thruText :: (IsomorphicTo Text a, IsomorphicTo Text b) => a -> b
thruText :: forall a b. (IsomorphicTo Text a, IsomorphicTo Text b) => a -> b
thruText = forall a b. IsomorphicTo b a => a -> b
from @Text 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
{-# INLINE thruList #-}
thruList :: forall a f g. (IsomorphicTo [a] (f a), IsomorphicTo [a] (g a)) => f a -> g a
thruList :: forall a (f :: * -> *) (g :: * -> *).
(IsomorphicTo [a] (f a), IsomorphicTo [a] (g a)) =>
f a -> g a
thruList = forall a b. IsomorphicTo b a => a -> b
from @[a] 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
showAs :: forall b a. (IsomorphicTo String b, Show a) => a -> b
showAs :: forall b a. (IsomorphicTo String b, Show a) => a -> b
showAs = forall a b. IsomorphicTo b a => a -> b
from forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a. Show a => a -> String
show