Rename "cast" to "from"

This commit is contained in:
Taylor Fausak 2021-05-10 19:22:57 -04:00
parent 99d601b222
commit 7c5e93182d
7 changed files with 421 additions and 437 deletions

View File

@ -6,14 +6,13 @@
-- >>> import Witch -- >>> import Witch
-- --
-- In typical usage, you will most likely use 'Witch.Utility.into' for -- In typical usage, you will most likely use 'Witch.Utility.into' for
-- 'Witch.Cast.Cast' instances and 'With.Utility.tryInto' for -- 'Witch.From.From' instances and 'With.Utility.tryInto' for
-- 'Witch.TryCast.TryCast' instances. -- 'Witch.TryCast.TryCast' instances.
module Witch module Witch
( -- * Type classes ( -- * Type classes
-- ** Cast -- ** From
Witch.Cast.Cast(cast) Witch.From.From(from)
, Witch.Utility.from
, Witch.Utility.into , Witch.Utility.into
-- ** TryCast -- ** TryCast
@ -34,7 +33,7 @@ module Witch
-- a conversion is safe even though you can't prove it to the compiler, and -- a conversion is safe even though you can't prove it to the compiler, and
-- when you're alright with your program crashing if the conversion fails. -- when you're alright with your program crashing if the conversion fails.
-- In all other cases you should prefer the normal conversion functions like -- In all other cases you should prefer the normal conversion functions like
-- 'Witch.Cast.cast'. And if you're converting a literal value, consider -- 'Witch.From.from'. And if you're converting a literal value, consider
-- using the Template Haskell conversion functions like -- using the Template Haskell conversion functions like
-- 'Witch.Lift.liftedCast'. -- 'Witch.Lift.liftedCast'.
, Witch.Utility.unsafeCast , Witch.Utility.unsafeCast
@ -65,7 +64,7 @@ module Witch
-- pitfalls to watch out for. -- pitfalls to watch out for.
-- --
-- This library tries to address that problem by providing a common -- This library tries to address that problem by providing a common
-- interface for converting between types. The 'Witch.Cast.Cast' type class -- interface for converting between types. The 'Witch.From.From' type class
-- is for conversions that cannot fail, and the 'Witch.TryCast.TryCast' type -- is for conversions that cannot fail, and the 'Witch.TryCast.TryCast' type
-- class is for conversions that can fail. These type classes are inspired -- class is for conversions that can fail. These type classes are inspired
-- by the [@From@](https://doc.rust-lang.org/std/convert/trait.From.html) -- by the [@From@](https://doc.rust-lang.org/std/convert/trait.From.html)
@ -120,7 +119,7 @@ module Witch
-- negative 'Int' into a 'Word' will overflow, which may be surprising. -- negative 'Int' into a 'Word' will overflow, which may be surprising.
-- ** Instances -- ** Instances
-- | When should you add a 'Witch.Cast.Cast' (or 'Witch.TryCast.TryCast') -- | When should you add a 'Witch.From.From' (or 'Witch.TryCast.TryCast')
-- instance for some pair of types? This is a surprisingly tricky question -- instance for some pair of types? This is a surprisingly tricky question
-- to answer precisely. Instances are driven more by guidelines than rules. -- to answer precisely. Instances are driven more by guidelines than rules.
-- --
@ -129,39 +128,39 @@ module Witch
-- --
-- - Conversions should be unambiguous. If there are multiple reasonable -- - Conversions should be unambiguous. If there are multiple reasonable
-- ways to convert from @a@ to @b@, then you probably should not add a -- ways to convert from @a@ to @b@, then you probably should not add a
-- @Cast@ instance for them. -- 'Witch.From.From' instance for them.
-- --
-- - Conversions should be lossless. If you have @Cast a b@ then no two @a@ -- - Conversions should be lossless. If you have @From a b@ then no two @a@
-- values should be converted to the same @b@ value. -- values should be converted to the same @b@ value.
-- --
-- - Some conversions necessarily lose information, like converting from a -- - Some conversions necessarily lose information, like converting from a
-- list into a set. -- list into a set.
-- --
-- - If you have both @Cast a b@ and @Cast b a@, then -- - If you have both @From a b@ and @From b a@, then
-- @cast \@b \@a . cast \@a \@b@ should be the same as 'id'. In other -- @from \@b \@a . from \@a \@b@ should be the same as 'id'. In other
-- words, @a@ and @b@ are isomorphic. -- words, @a@ and @b@ are isomorphic.
-- --
-- - This often true, but not always. For example, converting a list into -- - This often true, but not always. For example, converting a list into
-- a set will remove duplicates. And then converting back into a list -- a set will remove duplicates. And then converting back into a list
-- will put the elements in ascending order. -- will put the elements in ascending order.
-- --
-- - If you have both @Cast a b@ and @Cast b c@, then you could also have -- - If you have both @From a b@ and @From b c@, then you could also have
-- @Cast a c@ and it should be the same as @cast \@b \@c . cast \@a \@b@. -- @From a c@ and it should be the same as @from \@b \@c . from \@a \@b@.
-- In other words, @Cast@ is transitive. -- In other words, @From@ is transitive.
-- --
-- - This is not always true. For example an @Int8@ may be represented as -- - This is not always true. For example an @Int8@ may be represented as
-- a number in JSON, whereas an @Int64@ might be represented as a -- a number in JSON, whereas an @Int64@ might be represented as a
-- string. That means @into \@JSON (into \@Int64 int8)@ would not be the -- string. That means @into \@JSON (into \@Int64 int8)@ would not be the
-- same as @into \@JSON int8@. -- same as @into \@JSON int8@.
-- --
-- In general if @s@ /is/ a @t@, then you should add a 'Witch.Cast.Cast' -- In general if @s@ /is/ a @t@, then you should add a 'Witch.From.From'
-- instance for it. But if @s@ merely /can be/ a @t@, then you could add a -- instance for it. But if @s@ merely /can be/ a @t@, then you could add a
-- 'Witch.TryCast.TryCast' instance for it. And if it is technically -- 'Witch.TryCast.TryCast' instance for it. And if it is technically
-- possible to convert from @s@ to @t@ but there are a lot of caveats, you -- possible to convert from @s@ to @t@ but there are a lot of caveats, you
-- probably should not write any instances at all. -- probably should not write any instances at all.
) where ) where
import qualified Witch.Cast import qualified Witch.From
import Witch.Instances () import Witch.Instances ()
import qualified Witch.Lift import qualified Witch.Lift
import qualified Witch.TryCast import qualified Witch.TryCast

View File

@ -1,18 +1,18 @@
{-# LANGUAGE DefaultSignatures #-} {-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE MultiParamTypeClasses #-}
module Witch.Cast where module Witch.From where
import qualified Data.Coerce as Coerce import qualified Data.Coerce as Coerce
-- | This type class is for converting values from some @source@ type into -- | This type class is for converting values from some @source@ type into
-- some other @target@ type. The constraint @Cast source target@ measn that -- some other @target@ type. The constraint @From source target@ measn that
-- you can convert from a value of type @source@ into a value of type -- you can convert from a value of type @source@ into a value of type
-- @target@. -- @target@.
-- --
-- This type class is for conversions that cannot fail. If your conversion can -- This type class is for conversions that cannot fail. If your conversion can
-- fail, consider implementing @TryCast@ instead. -- fail, consider implementing @TryCast@ instead.
class Cast source target where class From source target where
-- | This method implements the conversion of a value between types. At call -- | This method implements the conversion of a value between types. At call
-- sites you will usually want to use @from@ or @into@ instead of this -- sites you will usually want to use @from@ or @into@ instead of this
-- method. -- method.
@ -23,9 +23,9 @@ class Cast source target where
-- all. For example: -- all. For example:
-- --
-- >>> newtype Name = Name String -- >>> newtype Name = Name String
-- >>> instance Cast Name String -- >>> instance From Name String
-- >>> instance Cast String Name -- >>> instance From String Name
cast :: source -> target from :: source -> target
default cast :: Coerce.Coercible source target => source -> target default from :: Coerce.Coercible source target => source -> target
cast = Coerce.coerce from = Coerce.coerce

View File

@ -29,7 +29,7 @@ import qualified Data.Typeable as Typeable
import qualified Data.Word as Word import qualified Data.Word as Word
import qualified GHC.Float as Float import qualified GHC.Float as Float
import qualified Numeric.Natural as Natural import qualified Numeric.Natural as Natural
import qualified Witch.Cast as Cast import qualified Witch.From as From
import qualified Witch.TryCast as TryCast import qualified Witch.TryCast as TryCast
import qualified Witch.TryCastException as TryCastException import qualified Witch.TryCastException as TryCastException
import qualified Witch.Utility as Utility import qualified Witch.Utility as Utility
@ -37,24 +37,24 @@ import qualified Witch.Utility as Utility
-- Int8 -- Int8
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Int.Int8 Int.Int16 where instance From.From Int.Int8 Int.Int16 where
cast = fromIntegral from = fromIntegral
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Int.Int8 Int.Int32 where instance From.From Int.Int8 Int.Int32 where
cast = fromIntegral from = fromIntegral
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Int.Int8 Int.Int64 where instance From.From Int.Int8 Int.Int64 where
cast = fromIntegral from = fromIntegral
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Int.Int8 Int where instance From.From Int.Int8 Int where
cast = fromIntegral from = fromIntegral
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Int.Int8 Integer where instance From.From Int.Int8 Integer where
cast = fromIntegral from = fromIntegral
-- | Uses 'Bits.toIntegralSized'. -- | Uses 'Bits.toIntegralSized'.
instance TryCast.TryCast Int.Int8 Word.Word8 where instance TryCast.TryCast Int.Int8 Word.Word8 where
@ -81,12 +81,12 @@ instance TryCast.TryCast Int.Int8 Natural.Natural where
tryCast = Utility.eitherTryCast fromNonNegativeIntegral tryCast = Utility.eitherTryCast fromNonNegativeIntegral
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Int.Int8 Float where instance From.From Int.Int8 Float where
cast = fromIntegral from = fromIntegral
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Int.Int8 Double where instance From.From Int.Int8 Double where
cast = fromIntegral from = fromIntegral
-- Int16 -- Int16
@ -95,20 +95,20 @@ instance TryCast.TryCast Int.Int16 Int.Int8 where
tryCast = Utility.maybeTryCast Bits.toIntegralSized tryCast = Utility.maybeTryCast Bits.toIntegralSized
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Int.Int16 Int.Int32 where instance From.From Int.Int16 Int.Int32 where
cast = fromIntegral from = fromIntegral
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Int.Int16 Int.Int64 where instance From.From Int.Int16 Int.Int64 where
cast = fromIntegral from = fromIntegral
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Int.Int16 Int where instance From.From Int.Int16 Int where
cast = fromIntegral from = fromIntegral
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Int.Int16 Integer where instance From.From Int.Int16 Integer where
cast = fromIntegral from = fromIntegral
-- | Uses 'Bits.toIntegralSized'. -- | Uses 'Bits.toIntegralSized'.
instance TryCast.TryCast Int.Int16 Word.Word8 where instance TryCast.TryCast Int.Int16 Word.Word8 where
@ -135,12 +135,12 @@ instance TryCast.TryCast Int.Int16 Natural.Natural where
tryCast = Utility.eitherTryCast fromNonNegativeIntegral tryCast = Utility.eitherTryCast fromNonNegativeIntegral
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Int.Int16 Float where instance From.From Int.Int16 Float where
cast = fromIntegral from = fromIntegral
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Int.Int16 Double where instance From.From Int.Int16 Double where
cast = fromIntegral from = fromIntegral
-- Int32 -- Int32
@ -153,16 +153,16 @@ instance TryCast.TryCast Int.Int32 Int.Int16 where
tryCast = Utility.maybeTryCast Bits.toIntegralSized tryCast = Utility.maybeTryCast Bits.toIntegralSized
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Int.Int32 Int.Int64 where instance From.From Int.Int32 Int.Int64 where
cast = fromIntegral from = fromIntegral
-- | Uses 'Bits.toIntegralSized'. -- | Uses 'Bits.toIntegralSized'.
instance TryCast.TryCast Int.Int32 Int where instance TryCast.TryCast Int.Int32 Int where
tryCast = Utility.maybeTryCast Bits.toIntegralSized tryCast = Utility.maybeTryCast Bits.toIntegralSized
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Int.Int32 Integer where instance From.From Int.Int32 Integer where
cast = fromIntegral from = fromIntegral
-- | Uses 'Bits.toIntegralSized'. -- | Uses 'Bits.toIntegralSized'.
instance TryCast.TryCast Int.Int32 Word.Word8 where instance TryCast.TryCast Int.Int32 Word.Word8 where
@ -198,8 +198,8 @@ instance TryCast.TryCast Int.Int32 Float where
else Right $ fromIntegral s else Right $ fromIntegral s
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Int.Int32 Double where instance From.From Int.Int32 Double where
cast = fromIntegral from = fromIntegral
-- Int64 -- Int64
@ -220,8 +220,8 @@ instance TryCast.TryCast Int.Int64 Int where
tryCast = Utility.maybeTryCast Bits.toIntegralSized tryCast = Utility.maybeTryCast Bits.toIntegralSized
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Int.Int64 Integer where instance From.From Int.Int64 Integer where
cast = fromIntegral from = fromIntegral
-- | Uses 'Bits.toIntegralSized'. -- | Uses 'Bits.toIntegralSized'.
instance TryCast.TryCast Int.Int64 Word.Word8 where instance TryCast.TryCast Int.Int64 Word.Word8 where
@ -280,12 +280,12 @@ instance TryCast.TryCast Int Int.Int32 where
tryCast = Utility.maybeTryCast Bits.toIntegralSized tryCast = Utility.maybeTryCast Bits.toIntegralSized
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Int Int.Int64 where instance From.From Int Int.Int64 where
cast = fromIntegral from = fromIntegral
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Int Integer where instance From.From Int Integer where
cast = fromIntegral from = fromIntegral
-- | Uses 'Bits.toIntegralSized'. -- | Uses 'Bits.toIntegralSized'.
instance TryCast.TryCast Int Word.Word8 where instance TryCast.TryCast Int Word.Word8 where
@ -404,56 +404,56 @@ instance TryCast.TryCast Integer Double where
-- Word8 -- Word8
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Word.Word8 Word.Word16 where instance From.From Word.Word8 Word.Word16 where
cast = fromIntegral from = fromIntegral
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Word.Word8 Word.Word32 where instance From.From Word.Word8 Word.Word32 where
cast = fromIntegral from = fromIntegral
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Word.Word8 Word.Word64 where instance From.From Word.Word8 Word.Word64 where
cast = fromIntegral from = fromIntegral
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Word.Word8 Word where instance From.From Word.Word8 Word where
cast = fromIntegral from = fromIntegral
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Word.Word8 Natural.Natural where instance From.From Word.Word8 Natural.Natural where
cast = fromIntegral from = fromIntegral
-- | Uses 'Bits.toIntegralSized'. -- | Uses 'Bits.toIntegralSized'.
instance TryCast.TryCast Word.Word8 Int.Int8 where instance TryCast.TryCast Word.Word8 Int.Int8 where
tryCast = Utility.maybeTryCast Bits.toIntegralSized tryCast = Utility.maybeTryCast Bits.toIntegralSized
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Word.Word8 Int.Int16 where instance From.From Word.Word8 Int.Int16 where
cast = fromIntegral from = fromIntegral
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Word.Word8 Int.Int32 where instance From.From Word.Word8 Int.Int32 where
cast = fromIntegral from = fromIntegral
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Word.Word8 Int.Int64 where instance From.From Word.Word8 Int.Int64 where
cast = fromIntegral from = fromIntegral
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Word.Word8 Int where instance From.From Word.Word8 Int where
cast = fromIntegral from = fromIntegral
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Word.Word8 Integer where instance From.From Word.Word8 Integer where
cast = fromIntegral from = fromIntegral
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Word.Word8 Float where instance From.From Word.Word8 Float where
cast = fromIntegral from = fromIntegral
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Word.Word8 Double where instance From.From Word.Word8 Double where
cast = fromIntegral from = fromIntegral
-- Word16 -- Word16
@ -462,20 +462,20 @@ instance TryCast.TryCast Word.Word16 Word.Word8 where
tryCast = Utility.maybeTryCast Bits.toIntegralSized tryCast = Utility.maybeTryCast Bits.toIntegralSized
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Word.Word16 Word.Word32 where instance From.From Word.Word16 Word.Word32 where
cast = fromIntegral from = fromIntegral
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Word.Word16 Word.Word64 where instance From.From Word.Word16 Word.Word64 where
cast = fromIntegral from = fromIntegral
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Word.Word16 Word where instance From.From Word.Word16 Word where
cast = fromIntegral from = fromIntegral
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Word.Word16 Natural.Natural where instance From.From Word.Word16 Natural.Natural where
cast = fromIntegral from = fromIntegral
-- | Uses 'Bits.toIntegralSized'. -- | Uses 'Bits.toIntegralSized'.
instance TryCast.TryCast Word.Word16 Int.Int8 where instance TryCast.TryCast Word.Word16 Int.Int8 where
@ -486,28 +486,28 @@ instance TryCast.TryCast Word.Word16 Int.Int16 where
tryCast = Utility.maybeTryCast Bits.toIntegralSized tryCast = Utility.maybeTryCast Bits.toIntegralSized
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Word.Word16 Int.Int32 where instance From.From Word.Word16 Int.Int32 where
cast = fromIntegral from = fromIntegral
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Word.Word16 Int.Int64 where instance From.From Word.Word16 Int.Int64 where
cast = fromIntegral from = fromIntegral
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Word.Word16 Int where instance From.From Word.Word16 Int where
cast = fromIntegral from = fromIntegral
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Word.Word16 Integer where instance From.From Word.Word16 Integer where
cast = fromIntegral from = fromIntegral
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Word.Word16 Float where instance From.From Word.Word16 Float where
cast = fromIntegral from = fromIntegral
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Word.Word16 Double where instance From.From Word.Word16 Double where
cast = fromIntegral from = fromIntegral
-- Word32 -- Word32
@ -520,16 +520,16 @@ instance TryCast.TryCast Word.Word32 Word.Word16 where
tryCast = Utility.maybeTryCast Bits.toIntegralSized tryCast = Utility.maybeTryCast Bits.toIntegralSized
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Word.Word32 Word.Word64 where instance From.From Word.Word32 Word.Word64 where
cast = fromIntegral from = fromIntegral
-- | Uses 'Bits.toIntegralSized'. -- | Uses 'Bits.toIntegralSized'.
instance TryCast.TryCast Word.Word32 Word where instance TryCast.TryCast Word.Word32 Word where
tryCast = Utility.maybeTryCast Bits.toIntegralSized tryCast = Utility.maybeTryCast Bits.toIntegralSized
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Word.Word32 Natural.Natural where instance From.From Word.Word32 Natural.Natural where
cast = fromIntegral from = fromIntegral
-- | Uses 'Bits.toIntegralSized'. -- | Uses 'Bits.toIntegralSized'.
instance TryCast.TryCast Word.Word32 Int.Int8 where instance TryCast.TryCast Word.Word32 Int.Int8 where
@ -544,16 +544,16 @@ instance TryCast.TryCast Word.Word32 Int.Int32 where
tryCast = Utility.maybeTryCast Bits.toIntegralSized tryCast = Utility.maybeTryCast Bits.toIntegralSized
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Word.Word32 Int.Int64 where instance From.From Word.Word32 Int.Int64 where
cast = fromIntegral from = fromIntegral
-- | Uses 'Bits.toIntegralSized'. -- | Uses 'Bits.toIntegralSized'.
instance TryCast.TryCast Word.Word32 Int where instance TryCast.TryCast Word.Word32 Int where
tryCast = Utility.maybeTryCast Bits.toIntegralSized tryCast = Utility.maybeTryCast Bits.toIntegralSized
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Word.Word32 Integer where instance From.From Word.Word32 Integer where
cast = fromIntegral from = fromIntegral
-- | Uses 'fromIntegral' when the input is less than or equal to 16,777,215. -- | Uses 'fromIntegral' when the input is less than or equal to 16,777,215.
instance TryCast.TryCast Word.Word32 Float where instance TryCast.TryCast Word.Word32 Float where
@ -561,8 +561,8 @@ instance TryCast.TryCast Word.Word32 Float where
if s <= maxFloat then Right $ fromIntegral s else Left Exception.Overflow if s <= maxFloat then Right $ fromIntegral s else Left Exception.Overflow
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Word.Word32 Double where instance From.From Word.Word32 Double where
cast = fromIntegral from = fromIntegral
-- Word64 -- Word64
@ -583,8 +583,8 @@ instance TryCast.TryCast Word.Word64 Word where
tryCast = Utility.maybeTryCast Bits.toIntegralSized tryCast = Utility.maybeTryCast Bits.toIntegralSized
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Word.Word64 Natural.Natural where instance From.From Word.Word64 Natural.Natural where
cast = fromIntegral from = fromIntegral
-- | Uses 'Bits.toIntegralSized'. -- | Uses 'Bits.toIntegralSized'.
instance TryCast.TryCast Word.Word64 Int.Int8 where instance TryCast.TryCast Word.Word64 Int.Int8 where
@ -607,8 +607,8 @@ instance TryCast.TryCast Word.Word64 Int where
tryCast = Utility.maybeTryCast Bits.toIntegralSized tryCast = Utility.maybeTryCast Bits.toIntegralSized
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Word.Word64 Integer where instance From.From Word.Word64 Integer where
cast = fromIntegral from = fromIntegral
-- | Uses 'fromIntegral' when the input is less than or equal to 16,777,215. -- | Uses 'fromIntegral' when the input is less than or equal to 16,777,215.
instance TryCast.TryCast Word.Word64 Float where instance TryCast.TryCast Word.Word64 Float where
@ -637,12 +637,12 @@ instance TryCast.TryCast Word Word.Word32 where
tryCast = Utility.maybeTryCast Bits.toIntegralSized tryCast = Utility.maybeTryCast Bits.toIntegralSized
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Word Word.Word64 where instance From.From Word Word.Word64 where
cast = fromIntegral from = fromIntegral
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Word Natural.Natural where instance From.From Word Natural.Natural where
cast = fromIntegral from = fromIntegral
-- | Uses 'Bits.toIntegralSized'. -- | Uses 'Bits.toIntegralSized'.
instance TryCast.TryCast Word Int.Int8 where instance TryCast.TryCast Word Int.Int8 where
@ -665,8 +665,8 @@ instance TryCast.TryCast Word Int where
tryCast = Utility.maybeTryCast Bits.toIntegralSized tryCast = Utility.maybeTryCast Bits.toIntegralSized
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Word Integer where instance From.From Word Integer where
cast = fromIntegral from = fromIntegral
-- | Uses 'fromIntegral' when the input is less than or equal to 16,777,215. -- | Uses 'fromIntegral' when the input is less than or equal to 16,777,215.
instance TryCast.TryCast Word Float where instance TryCast.TryCast Word Float where
@ -724,8 +724,8 @@ instance TryCast.TryCast Natural.Natural Int where
tryCast = Utility.maybeTryCast Bits.toIntegralSized tryCast = Utility.maybeTryCast Bits.toIntegralSized
-- | Uses 'fromIntegral'. -- | Uses 'fromIntegral'.
instance Cast.Cast Natural.Natural Integer where instance From.From Natural.Natural Integer where
cast = fromIntegral from = fromIntegral
-- | Uses 'fromIntegral' when the input is less than or equal to 16,777,215. -- | Uses 'fromIntegral' when the input is less than or equal to 16,777,215.
instance TryCast.TryCast Natural.Natural Float where instance TryCast.TryCast Natural.Natural Float where
@ -804,8 +804,8 @@ instance TryCast.TryCast Float Rational where
else Right $ toRational s else Right $ toRational s
-- | Uses 'Float.float2Double'. -- | Uses 'Float.float2Double'.
instance Cast.Cast Float Double where instance From.From Float Double where
cast = Float.float2Double from = Float.float2Double
-- Double -- Double
@ -872,14 +872,14 @@ instance TryCast.TryCast Double Rational where
else Right $ toRational s else Right $ toRational s
-- | Uses 'Float.double2Float'. This necessarily loses some precision. -- | Uses 'Float.double2Float'. This necessarily loses some precision.
instance Cast.Cast Double Float where instance From.From Double Float where
cast = Float.double2Float from = Float.double2Float
-- Ratio -- Ratio
-- | Uses '(Ratio.%)' with a denominator of 1. -- | Uses '(Ratio.%)' with a denominator of 1.
instance Integral a => Cast.Cast a (Ratio.Ratio a) where instance Integral a => From.From a (Ratio.Ratio a) where
cast = (Ratio.% 1) from = (Ratio.% 1)
-- | Uses 'Ratio.numerator' when the denominator is 1. -- | Uses 'Ratio.numerator' when the denominator is 1.
instance (Eq a, Num a) => TryCast.TryCast (Ratio.Ratio a) a where instance (Eq a, Num a) => TryCast.TryCast (Ratio.Ratio a) a where
@ -888,30 +888,30 @@ instance (Eq a, Num a) => TryCast.TryCast (Ratio.Ratio a) a where
else Left Exception.LossOfPrecision else Left Exception.LossOfPrecision
-- | Uses 'fromRational'. This necessarily loses some precision. -- | Uses 'fromRational'. This necessarily loses some precision.
instance Cast.Cast Rational Float where instance From.From Rational Float where
cast = fromRational from = fromRational
-- | Uses 'fromRational'. This necessarily loses some precision. -- | Uses 'fromRational'. This necessarily loses some precision.
instance Cast.Cast Rational Double where instance From.From Rational Double where
cast = fromRational from = fromRational
-- Fixed -- Fixed
-- | Uses 'Fixed.MkFixed'. This means @cast 2 :: Centi@ is @0.02@ rather than -- | Uses 'Fixed.MkFixed'. This means @from 2 :: Centi@ is @0.02@ rather than
-- @2.00@. -- @2.00@.
instance Cast.Cast Integer (Fixed.Fixed a) where instance From.From Integer (Fixed.Fixed a) where
cast = Fixed.MkFixed from = Fixed.MkFixed
-- | Uses 'Fixed.MkFixed'. This means @cast (3.00 :: Centi)@ is @300@ rather -- | Uses 'Fixed.MkFixed'. This means @from (3.00 :: Centi)@ is @300@ rather
-- than @3@. -- than @3@.
instance Cast.Cast (Fixed.Fixed a) Integer where instance From.From (Fixed.Fixed a) Integer where
cast (Fixed.MkFixed t) = t from (Fixed.MkFixed t) = t
-- Complex -- Complex
-- | Uses '(Complex.:+)' with an imaginary part of 0. -- | Uses '(Complex.:+)' with an imaginary part of 0.
instance Num a => Cast.Cast a (Complex.Complex a) where instance Num a => From.From a (Complex.Complex a) where
cast = (Complex.:+ 0) from = (Complex.:+ 0)
-- | Uses 'Complex.realPart' when the imaginary part is 0. -- | Uses 'Complex.realPart' when the imaginary part is 0.
instance (Eq a, Num a) => TryCast.TryCast (Complex.Complex a) a where instance (Eq a, Num a) => TryCast.TryCast (Complex.Complex a) a where
@ -926,78 +926,78 @@ instance TryCast.TryCast [a] (NonEmpty.NonEmpty a) where
tryCast = Utility.maybeTryCast NonEmpty.nonEmpty tryCast = Utility.maybeTryCast NonEmpty.nonEmpty
-- | Uses 'NonEmpty.toList'. -- | Uses 'NonEmpty.toList'.
instance Cast.Cast (NonEmpty.NonEmpty a) [a] where instance From.From (NonEmpty.NonEmpty a) [a] where
cast = NonEmpty.toList from = NonEmpty.toList
-- Set -- Set
-- | Uses 'Set.fromList'. -- | Uses 'Set.fromList'.
instance Ord a => Cast.Cast [a] (Set.Set a) where instance Ord a => From.From [a] (Set.Set a) where
cast = Set.fromList from = Set.fromList
-- | Uses 'Set.toAscList'. -- | Uses 'Set.toAscList'.
instance Cast.Cast (Set.Set a) [a] where instance From.From (Set.Set a) [a] where
cast = Set.toAscList from = Set.toAscList
-- IntSet -- IntSet
-- | Uses 'IntSet.fromList'. -- | Uses 'IntSet.fromList'.
instance Cast.Cast [Int] IntSet.IntSet where instance From.From [Int] IntSet.IntSet where
cast = IntSet.fromList from = IntSet.fromList
-- | Uses 'IntSet.toAscList'. -- | Uses 'IntSet.toAscList'.
instance Cast.Cast IntSet.IntSet [Int] where instance From.From IntSet.IntSet [Int] where
cast = IntSet.toAscList from = IntSet.toAscList
-- Map -- Map
-- | Uses 'Map.fromList'. If there are duplicate keys, later values will -- | Uses 'Map.fromList'. If there are duplicate keys, later values will
-- overwrite earlier ones. -- overwrite earlier ones.
instance Ord k => Cast.Cast [(k, v)] (Map.Map k v) where instance Ord k => From.From [(k, v)] (Map.Map k v) where
cast = Map.fromList from = Map.fromList
-- | Uses 'Map.toAscList'. -- | Uses 'Map.toAscList'.
instance Cast.Cast (Map.Map k v) [(k, v)] where instance From.From (Map.Map k v) [(k, v)] where
cast = Map.toAscList from = Map.toAscList
-- IntMap -- IntMap
-- | Uses 'IntMap.fromList'. If there are duplicate keys, later values will -- | Uses 'IntMap.fromList'. If there are duplicate keys, later values will
-- overwrite earlier ones. -- overwrite earlier ones.
instance Cast.Cast [(Int, v)] (IntMap.IntMap v) where instance From.From [(Int, v)] (IntMap.IntMap v) where
cast = IntMap.fromList from = IntMap.fromList
-- | Uses 'IntMap.toAscList'. -- | Uses 'IntMap.toAscList'.
instance Cast.Cast (IntMap.IntMap v) [(Int, v)] where instance From.From (IntMap.IntMap v) [(Int, v)] where
cast = IntMap.toAscList from = IntMap.toAscList
-- Seq -- Seq
-- | Uses 'Seq.fromList'. -- | Uses 'Seq.fromList'.
instance Cast.Cast [a] (Seq.Seq a) where instance From.From [a] (Seq.Seq a) where
cast = Seq.fromList from = Seq.fromList
-- | Uses 'Foldable.toList'. -- | Uses 'Foldable.toList'.
instance Cast.Cast (Seq.Seq a) [a] where instance From.From (Seq.Seq a) [a] where
cast = Foldable.toList from = Foldable.toList
-- ByteString -- ByteString
-- | Uses 'ByteString.pack'. -- | Uses 'ByteString.pack'.
instance Cast.Cast [Word.Word8] ByteString.ByteString where instance From.From [Word.Word8] ByteString.ByteString where
cast = ByteString.pack from = ByteString.pack
-- | Uses 'ByteString.unpack'. -- | Uses 'ByteString.unpack'.
instance Cast.Cast ByteString.ByteString [Word.Word8] where instance From.From ByteString.ByteString [Word.Word8] where
cast = ByteString.unpack from = ByteString.unpack
-- | Uses 'LazyByteString.fromStrict'. -- | Uses 'LazyByteString.fromStrict'.
instance Cast.Cast ByteString.ByteString LazyByteString.ByteString where instance From.From ByteString.ByteString LazyByteString.ByteString where
cast = LazyByteString.fromStrict from = LazyByteString.fromStrict
-- | Uses 'ShortByteString.toShort'. -- | Uses 'ShortByteString.toShort'.
instance Cast.Cast ByteString.ByteString ShortByteString.ShortByteString where instance From.From ByteString.ByteString ShortByteString.ShortByteString where
cast = ShortByteString.toShort from = ShortByteString.toShort
-- | Uses 'Text.decodeUtf8''. -- | Uses 'Text.decodeUtf8''.
instance TryCast.TryCast ByteString.ByteString Text.Text where instance TryCast.TryCast ByteString.ByteString Text.Text where
@ -1006,16 +1006,16 @@ instance TryCast.TryCast ByteString.ByteString Text.Text where
-- LazyByteString -- LazyByteString
-- | Uses 'LazyByteString.pack'. -- | Uses 'LazyByteString.pack'.
instance Cast.Cast [Word.Word8] LazyByteString.ByteString where instance From.From [Word.Word8] LazyByteString.ByteString where
cast = LazyByteString.pack from = LazyByteString.pack
-- | Uses 'LazyByteString.unpack'. -- | Uses 'LazyByteString.unpack'.
instance Cast.Cast LazyByteString.ByteString [Word.Word8] where instance From.From LazyByteString.ByteString [Word.Word8] where
cast = LazyByteString.unpack from = LazyByteString.unpack
-- | Uses 'LazyByteString.toStrict'. -- | Uses 'LazyByteString.toStrict'.
instance Cast.Cast LazyByteString.ByteString ByteString.ByteString where instance From.From LazyByteString.ByteString ByteString.ByteString where
cast = LazyByteString.toStrict from = LazyByteString.toStrict
-- | Uses 'LazyText.decodeUtf8''. -- | Uses 'LazyText.decodeUtf8''.
instance TryCast.TryCast LazyByteString.ByteString LazyText.Text where instance TryCast.TryCast LazyByteString.ByteString LazyText.Text where
@ -1024,59 +1024,59 @@ instance TryCast.TryCast LazyByteString.ByteString LazyText.Text where
-- ShortByteString -- ShortByteString
-- | Uses 'ShortByteString.pack'. -- | Uses 'ShortByteString.pack'.
instance Cast.Cast [Word.Word8] ShortByteString.ShortByteString where instance From.From [Word.Word8] ShortByteString.ShortByteString where
cast = ShortByteString.pack from = ShortByteString.pack
-- | Uses 'ShortByteString.unpack'. -- | Uses 'ShortByteString.unpack'.
instance Cast.Cast ShortByteString.ShortByteString [Word.Word8] where instance From.From ShortByteString.ShortByteString [Word.Word8] where
cast = ShortByteString.unpack from = ShortByteString.unpack
-- | Uses 'ShortByteString.fromShort'. -- | Uses 'ShortByteString.fromShort'.
instance Cast.Cast ShortByteString.ShortByteString ByteString.ByteString where instance From.From ShortByteString.ShortByteString ByteString.ByteString where
cast = ShortByteString.fromShort from = ShortByteString.fromShort
-- Text -- Text
-- | Uses 'Text.pack'. Some 'Char' values cannot be represented in 'Text.Text' -- | Uses 'Text.pack'. Some 'Char' values cannot be represented in 'Text.Text'
-- and will be replaced with @'\\xFFFD'@. -- and will be replaced with @'\\xFFFD'@.
instance Cast.Cast String Text.Text where instance From.From String Text.Text where
cast = Text.pack from = Text.pack
-- | Uses 'Text.unpack'. -- | Uses 'Text.unpack'.
instance Cast.Cast Text.Text String where instance From.From Text.Text String where
cast = Text.unpack from = Text.unpack
-- | Uses 'LazyText.fromStrict'. -- | Uses 'LazyText.fromStrict'.
instance Cast.Cast Text.Text LazyText.Text where instance From.From Text.Text LazyText.Text where
cast = LazyText.fromStrict from = LazyText.fromStrict
-- | Uses 'Text.encodeUtf8'. -- | Uses 'Text.encodeUtf8'.
instance Cast.Cast Text.Text ByteString.ByteString where instance From.From Text.Text ByteString.ByteString where
cast = Text.encodeUtf8 from = Text.encodeUtf8
-- LazyText -- LazyText
-- | Uses 'LazyText.pack'. Some 'Char' values cannot be represented in -- | Uses 'LazyText.pack'. Some 'Char' values cannot be represented in
-- 'LazyText.Text' and will be replaced with @'\\xFFFD'@. -- 'LazyText.Text' and will be replaced with @'\\xFFFD'@.
instance Cast.Cast String LazyText.Text where instance From.From String LazyText.Text where
cast = LazyText.pack from = LazyText.pack
-- | Uses 'LazyText.unpack'. -- | Uses 'LazyText.unpack'.
instance Cast.Cast LazyText.Text String where instance From.From LazyText.Text String where
cast = LazyText.unpack from = LazyText.unpack
-- | Uses 'LazyText.toStrict'. -- | Uses 'LazyText.toStrict'.
instance Cast.Cast LazyText.Text Text.Text where instance From.From LazyText.Text Text.Text where
cast = LazyText.toStrict from = LazyText.toStrict
-- | Uses 'LazyText.encodeUtf8'. -- | Uses 'LazyText.encodeUtf8'.
instance Cast.Cast LazyText.Text LazyByteString.ByteString where instance From.From LazyText.Text LazyByteString.ByteString where
cast = LazyText.encodeUtf8 from = LazyText.encodeUtf8
-- TryCastException -- TryCastException
-- | Uses @coerce@. -- | Uses @coerce@.
instance Cast.Cast instance From.From
(TryCastException.TryCastException s u) (TryCastException.TryCastException s u)
(TryCastException.TryCastException s t) (TryCastException.TryCastException s t)
@ -1085,24 +1085,24 @@ instance
( Show s ( Show s
, Typeable.Typeable s , Typeable.Typeable s
, Typeable.Typeable t , Typeable.Typeable t
) => Cast.Cast (TryCastException.TryCastException s t) String where ) => From.From (TryCastException.TryCastException s t) String where
cast = show from = show
-- | Converts via 'String'. -- | Converts via 'String'.
instance instance
( Show s ( Show s
, Typeable.Typeable s , Typeable.Typeable s
, Typeable.Typeable t , Typeable.Typeable t
) => Cast.Cast (TryCastException.TryCastException s t) Text.Text where ) => From.From (TryCastException.TryCastException s t) Text.Text where
cast = Utility.via @String from = Utility.via @String
-- | Converts via 'String'. -- | Converts via 'String'.
instance instance
( Show s ( Show s
, Typeable.Typeable s , Typeable.Typeable s
, Typeable.Typeable t , Typeable.Typeable t
) => Cast.Cast (TryCastException.TryCastException s t) LazyText.Text where ) => From.From (TryCastException.TryCastException s t) LazyText.Text where
cast = Utility.via @String from = Utility.via @String
fromNonNegativeIntegral fromNonNegativeIntegral
:: (Integral s, Num t) => s -> Either Exception.ArithException t :: (Integral s, Num t) => s -> Either Exception.ArithException t

View File

@ -10,7 +10,7 @@ import qualified Witch.TryCastException as TryCastException
-- type @target@, but that conversion may fail at runtime. -- type @target@, but that conversion may fail at runtime.
-- --
-- This type class is for conversions that can fail. If your conversion cannot -- This type class is for conversions that can fail. If your conversion cannot
-- fail, consider implementing @Cast@ instead. -- fail, consider implementing @From@ instead.
class TryCast source target where class TryCast source target where
-- | This method implements the conversion of a value between types. At call -- | This method implements the conversion of a value between types. At call
-- sites you will usually want to use @tryFrom@ or @tryInto@ instead of this -- sites you will usually want to use @tryFrom@ or @tryInto@ instead of this

View File

@ -6,7 +6,7 @@ module Witch.Utility where
import qualified Control.Exception as Exception import qualified Control.Exception as Exception
import qualified Data.Typeable as Typeable import qualified Data.Typeable as Typeable
import qualified GHC.Stack as Stack import qualified GHC.Stack as Stack
import qualified Witch.Cast as Cast import qualified Witch.From as From
import qualified Witch.TryCast as TryCast import qualified Witch.TryCast as TryCast
import qualified Witch.TryCastException as TryCastException import qualified Witch.TryCastException as TryCastException
@ -22,35 +22,20 @@ import qualified Witch.TryCastException as TryCastException
as :: forall source . source -> source as :: forall source . source -> source
as = id as = id
-- | This is the same as 'Cast.cast' except that it requires a type -- | This is the same as 'From.from' except that it requires a type
-- application for the @source@ type.
--
-- > -- Avoid this:
-- > cast (x :: s)
-- >
-- > -- Prefer this:
-- > from @s x
from
:: forall source target
. Cast.Cast source target
=> source
-> target
from = Cast.cast
-- | This is the same as 'Cast.cast' except that it requires a type
-- application for the @target@ type. -- application for the @target@ type.
-- --
-- > -- Avoid this: -- > -- Avoid this:
-- > cast x :: t -- > from x :: t
-- > -- >
-- > -- Prefer this: -- > -- Prefer this:
-- > into @t x -- > into @t x
into into
:: forall target source :: forall target source
. Cast.Cast source target . From.From source target
=> source => source
-> target -> target
into = Cast.cast into = From.from
-- | This function converts from some @source@ type into some @target@ type, -- | This function converts from some @source@ type into some @target@ type,
-- applies the given function, then converts back into the @source@ type. This -- applies the given function, then converts back into the @source@ type. This
@ -64,17 +49,17 @@ into = Cast.cast
-- > over @t f -- > over @t f
over over
:: forall target source :: forall target source
. ( Cast.Cast source target . ( From.From source target
, Cast.Cast target source , From.From target source
) )
=> (target -> target) => (target -> target)
-> source -> source
-> source -> source
over f = Cast.cast . f . Cast.cast over f = From.from . f . From.from
-- | This function first converts from some @source@ type into some @through@ -- | This function first converts from some @source@ type into some @through@
-- type, and then converts that into some @target@ type. Usually this is used -- type, and then converts that into some @target@ type. Usually this is used
-- when writing 'Cast.Cast' instances. Sometimes this can be used to work -- when writing 'From.From' instances. Sometimes this can be used to work
-- around the lack of an instance that should probably exist. -- around the lack of an instance that should probably exist.
-- --
-- > -- Avoid this: -- > -- Avoid this:
@ -84,12 +69,12 @@ over f = Cast.cast . f . Cast.cast
-- > via @u -- > via @u
via via
:: forall through source target :: forall through source target
. ( Cast.Cast source through . ( From.From source through
, Cast.Cast through target , From.From through target
) )
=> source => source
-> target -> target
via = Cast.cast . (\x -> x :: through) . Cast.cast via = From.from . (\x -> x :: through) . From.from
-- | This is the same as 'TryCast.tryCast' except that it requires a type -- | This is the same as 'TryCast.tryCast' except that it requires a type
-- application for the @source@ type. -- application for the @source@ type.
@ -191,7 +176,7 @@ eitherTryCast f s = case f s of
-- impure exception if the conversion fails. -- impure exception if the conversion fails.
-- --
-- > -- Avoid this: -- > -- Avoid this:
-- > either throw id . cast -- > either throw id . from
-- > -- >
-- > -- Prefer this: -- > -- Prefer this:
-- > unsafeCast -- > unsafeCast

View File

@ -27,10 +27,10 @@ import qualified Witch
main :: IO () main :: IO ()
main = Hspec.hspec . Hspec.describe "Witch" $ do main = Hspec.hspec . Hspec.describe "Witch" $ do
Hspec.describe "Cast" $ do Hspec.describe "From" $ do
Hspec.describe "cast" $ do Hspec.describe "from" $ do
test $ Witch.cast (1 :: Int.Int8) `Hspec.shouldBe` (1 :: Int.Int16) test $ Witch.from (1 :: Int.Int8) `Hspec.shouldBe` (1 :: Int.Int16)
Hspec.describe "TryCast" $ do Hspec.describe "TryCast" $ do
@ -87,32 +87,32 @@ main = Hspec.hspec . Hspec.describe "Witch" $ do
-- Int8 -- Int8
Hspec.describe "Cast Int8 Int16" $ do Hspec.describe "From Int8 Int16" $ do
let f = Witch.cast @Int.Int8 @Int.Int16 let f = Witch.from @Int.Int8 @Int.Int16
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f 127 `Hspec.shouldBe` 127 test $ f 127 `Hspec.shouldBe` 127
test $ f (-128) `Hspec.shouldBe` (-128) test $ f (-128) `Hspec.shouldBe` (-128)
Hspec.describe "Cast Int8 Int32" $ do Hspec.describe "From Int8 Int32" $ do
let f = Witch.cast @Int.Int8 @Int.Int32 let f = Witch.from @Int.Int8 @Int.Int32
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f 127 `Hspec.shouldBe` 127 test $ f 127 `Hspec.shouldBe` 127
test $ f (-128) `Hspec.shouldBe` (-128) test $ f (-128) `Hspec.shouldBe` (-128)
Hspec.describe "Cast Int8 Int64" $ do Hspec.describe "From Int8 Int64" $ do
let f = Witch.cast @Int.Int8 @Int.Int64 let f = Witch.from @Int.Int8 @Int.Int64
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f 127 `Hspec.shouldBe` 127 test $ f 127 `Hspec.shouldBe` 127
test $ f (-128) `Hspec.shouldBe` (-128) test $ f (-128) `Hspec.shouldBe` (-128)
Hspec.describe "Cast Int8 Int" $ do Hspec.describe "From Int8 Int" $ do
let f = Witch.cast @Int.Int8 @Int let f = Witch.from @Int.Int8 @Int
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f 127 `Hspec.shouldBe` 127 test $ f 127 `Hspec.shouldBe` 127
test $ f (-128) `Hspec.shouldBe` (-128) test $ f (-128) `Hspec.shouldBe` (-128)
Hspec.describe "Cast Int8 Integer" $ do Hspec.describe "From Int8 Integer" $ do
let f = Witch.cast @Int.Int8 @Integer let f = Witch.from @Int.Int8 @Integer
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f 127 `Hspec.shouldBe` 127 test $ f 127 `Hspec.shouldBe` 127
test $ f (-128) `Hspec.shouldBe` (-128) test $ f (-128) `Hspec.shouldBe` (-128)
@ -153,14 +153,14 @@ main = Hspec.hspec . Hspec.describe "Witch" $ do
test $ f 127 `Hspec.shouldBe` Just 127 test $ f 127 `Hspec.shouldBe` Just 127
test $ f (-1) `Hspec.shouldBe` Nothing test $ f (-1) `Hspec.shouldBe` Nothing
Hspec.describe "Cast Int8 Float" $ do Hspec.describe "From Int8 Float" $ do
let f = Witch.cast @Int.Int8 @Float let f = Witch.from @Int.Int8 @Float
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f 127 `Hspec.shouldBe` 127 test $ f 127 `Hspec.shouldBe` 127
test $ f (-128) `Hspec.shouldBe` (-128) test $ f (-128) `Hspec.shouldBe` (-128)
Hspec.describe "Cast Int8 Double" $ do Hspec.describe "From Int8 Double" $ do
let f = Witch.cast @Int.Int8 @Double let f = Witch.from @Int.Int8 @Double
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f 127 `Hspec.shouldBe` 127 test $ f 127 `Hspec.shouldBe` 127
test $ f (-128) `Hspec.shouldBe` (-128) test $ f (-128) `Hspec.shouldBe` (-128)
@ -175,26 +175,26 @@ main = Hspec.hspec . Hspec.describe "Witch" $ do
test $ f (-128) `Hspec.shouldBe` Just (-128) test $ f (-128) `Hspec.shouldBe` Just (-128)
test $ f (-129) `Hspec.shouldBe` Nothing test $ f (-129) `Hspec.shouldBe` Nothing
Hspec.describe "Cast Int16 Int32" $ do Hspec.describe "From Int16 Int32" $ do
let f = Witch.cast @Int.Int16 @Int.Int32 let f = Witch.from @Int.Int16 @Int.Int32
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f 32767 `Hspec.shouldBe` 32767 test $ f 32767 `Hspec.shouldBe` 32767
test $ f (-32768) `Hspec.shouldBe` (-32768) test $ f (-32768) `Hspec.shouldBe` (-32768)
Hspec.describe "Cast Int16 Int64" $ do Hspec.describe "From Int16 Int64" $ do
let f = Witch.cast @Int.Int16 @Int.Int64 let f = Witch.from @Int.Int16 @Int.Int64
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f 32767 `Hspec.shouldBe` 32767 test $ f 32767 `Hspec.shouldBe` 32767
test $ f (-32768) `Hspec.shouldBe` (-32768) test $ f (-32768) `Hspec.shouldBe` (-32768)
Hspec.describe "Cast Int16 Int" $ do Hspec.describe "From Int16 Int" $ do
let f = Witch.cast @Int.Int16 @Int let f = Witch.from @Int.Int16 @Int
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f 32767 `Hspec.shouldBe` 32767 test $ f 32767 `Hspec.shouldBe` 32767
test $ f (-32768) `Hspec.shouldBe` (-32768) test $ f (-32768) `Hspec.shouldBe` (-32768)
Hspec.describe "Cast Int16 Integer" $ do Hspec.describe "From Int16 Integer" $ do
let f = Witch.cast @Int.Int16 @Integer let f = Witch.from @Int.Int16 @Integer
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f 32767 `Hspec.shouldBe` 32767 test $ f 32767 `Hspec.shouldBe` 32767
test $ f (-32768) `Hspec.shouldBe` (-32768) test $ f (-32768) `Hspec.shouldBe` (-32768)
@ -236,14 +236,14 @@ main = Hspec.hspec . Hspec.describe "Witch" $ do
test $ f 32767 `Hspec.shouldBe` Just 32767 test $ f 32767 `Hspec.shouldBe` Just 32767
test $ f (-1) `Hspec.shouldBe` Nothing test $ f (-1) `Hspec.shouldBe` Nothing
Hspec.describe "Cast Int16 Float" $ do Hspec.describe "From Int16 Float" $ do
let f = Witch.cast @Int.Int16 @Float let f = Witch.from @Int.Int16 @Float
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f 32767 `Hspec.shouldBe` 32767 test $ f 32767 `Hspec.shouldBe` 32767
test $ f (-32768) `Hspec.shouldBe` (-32768) test $ f (-32768) `Hspec.shouldBe` (-32768)
Hspec.describe "Cast Int16 Double" $ do Hspec.describe "From Int16 Double" $ do
let f = Witch.cast @Int.Int16 @Double let f = Witch.from @Int.Int16 @Double
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f 32767 `Hspec.shouldBe` 32767 test $ f 32767 `Hspec.shouldBe` 32767
test $ f (-32768) `Hspec.shouldBe` (-32768) test $ f (-32768) `Hspec.shouldBe` (-32768)
@ -266,8 +266,8 @@ main = Hspec.hspec . Hspec.describe "Witch" $ do
test $ f (-32768) `Hspec.shouldBe` Just (-32768) test $ f (-32768) `Hspec.shouldBe` Just (-32768)
test $ f (-32769) `Hspec.shouldBe` Nothing test $ f (-32769) `Hspec.shouldBe` Nothing
Hspec.describe "Cast Int32 Int64" $ do Hspec.describe "From Int32 Int64" $ do
let f = Witch.cast @Int.Int32 @Int.Int64 let f = Witch.from @Int.Int32 @Int.Int64
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f 2147483647 `Hspec.shouldBe` 2147483647 test $ f 2147483647 `Hspec.shouldBe` 2147483647
test $ f (-2147483648) `Hspec.shouldBe` (-2147483648) test $ f (-2147483648) `Hspec.shouldBe` (-2147483648)
@ -279,8 +279,8 @@ main = Hspec.hspec . Hspec.describe "Witch" $ do
test $ f 2147483647 `Hspec.shouldBe` Just 2147483647 test $ f 2147483647 `Hspec.shouldBe` Just 2147483647
test $ f (-2147483648) `Hspec.shouldBe` Just (-2147483648) test $ f (-2147483648) `Hspec.shouldBe` Just (-2147483648)
Hspec.describe "Cast Int32 Integer" $ do Hspec.describe "From Int32 Integer" $ do
let f = Witch.cast @Int.Int32 @Integer let f = Witch.from @Int.Int32 @Integer
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f 2147483647 `Hspec.shouldBe` 2147483647 test $ f 2147483647 `Hspec.shouldBe` 2147483647
test $ f (-2147483648) `Hspec.shouldBe` (-2147483648) test $ f (-2147483648) `Hspec.shouldBe` (-2147483648)
@ -332,8 +332,8 @@ main = Hspec.hspec . Hspec.describe "Witch" $ do
test $ f (-16777215) `Hspec.shouldBe` Just (-16777215) test $ f (-16777215) `Hspec.shouldBe` Just (-16777215)
test $ f (-16777216) `Hspec.shouldBe` Nothing test $ f (-16777216) `Hspec.shouldBe` Nothing
Hspec.describe "Cast Int32 Double" $ do Hspec.describe "From Int32 Double" $ do
let f = Witch.cast @Int.Int32 @Double let f = Witch.from @Int.Int32 @Double
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f 2147483647 `Hspec.shouldBe` 2147483647 test $ f 2147483647 `Hspec.shouldBe` 2147483647
test $ f (-2147483648) `Hspec.shouldBe` (-2147483648) test $ f (-2147483648) `Hspec.shouldBe` (-2147483648)
@ -371,8 +371,8 @@ main = Hspec.hspec . Hspec.describe "Witch" $ do
test $ f 9223372036854775807 `Hspec.shouldBe` Just 9223372036854775807 test $ f 9223372036854775807 `Hspec.shouldBe` Just 9223372036854775807
test $ f (-9223372036854775808) `Hspec.shouldBe` Just (-9223372036854775808) test $ f (-9223372036854775808) `Hspec.shouldBe` Just (-9223372036854775808)
Hspec.describe "Cast Int64 Integer" $ do Hspec.describe "From Int64 Integer" $ do
let f = Witch.cast @Int.Int64 @Integer let f = Witch.from @Int.Int64 @Integer
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f 9223372036854775807 `Hspec.shouldBe` 9223372036854775807 test $ f 9223372036854775807 `Hspec.shouldBe` 9223372036854775807
test $ f (-9223372036854775808) `Hspec.shouldBe` (-9223372036854775808) test $ f (-9223372036854775808) `Hspec.shouldBe` (-9223372036854775808)
@ -459,14 +459,14 @@ main = Hspec.hspec . Hspec.describe "Witch" $ do
test $ f (-2147483648) `Hspec.shouldBe` Just (-2147483648) test $ f (-2147483648) `Hspec.shouldBe` Just (-2147483648)
test $ f (-2147483649) `Hspec.shouldBe` Nothing test $ f (-2147483649) `Hspec.shouldBe` Nothing
Hspec.describe "Cast Int Int64" $ do Hspec.describe "From Int Int64" $ do
let f = Witch.cast @Int @Int.Int64 let f = Witch.from @Int @Int.Int64
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f maxBound `Hspec.shouldBe` fromIntegral (maxBound :: Int) test $ f maxBound `Hspec.shouldBe` fromIntegral (maxBound :: Int)
test $ f minBound `Hspec.shouldBe` fromIntegral (minBound :: Int) test $ f minBound `Hspec.shouldBe` fromIntegral (minBound :: Int)
Hspec.describe "Cast Int Integer" $ do Hspec.describe "From Int Integer" $ do
let f = Witch.cast @Int @Integer let f = Witch.from @Int @Integer
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f maxBound `Hspec.shouldBe` fromIntegral (maxBound :: Int) test $ f maxBound `Hspec.shouldBe` fromIntegral (maxBound :: Int)
test $ f minBound `Hspec.shouldBe` fromIntegral (minBound :: Int) test $ f minBound `Hspec.shouldBe` fromIntegral (minBound :: Int)
@ -629,28 +629,28 @@ main = Hspec.hspec . Hspec.describe "Witch" $ do
-- Word8 -- Word8
Hspec.describe "Cast Word8 Word16" $ do Hspec.describe "From Word8 Word16" $ do
let f = Witch.cast @Word.Word8 @Word.Word16 let f = Witch.from @Word.Word8 @Word.Word16
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f 255 `Hspec.shouldBe` 255 test $ f 255 `Hspec.shouldBe` 255
Hspec.describe "Cast Word8 Word32" $ do Hspec.describe "From Word8 Word32" $ do
let f = Witch.cast @Word.Word8 @Word.Word32 let f = Witch.from @Word.Word8 @Word.Word32
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f 255 `Hspec.shouldBe` 255 test $ f 255 `Hspec.shouldBe` 255
Hspec.describe "Cast Word8 Word64" $ do Hspec.describe "From Word8 Word64" $ do
let f = Witch.cast @Word.Word8 @Word.Word64 let f = Witch.from @Word.Word8 @Word.Word64
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f 255 `Hspec.shouldBe` 255 test $ f 255 `Hspec.shouldBe` 255
Hspec.describe "Cast Word8 Word" $ do Hspec.describe "From Word8 Word" $ do
let f = Witch.cast @Word.Word8 @Word let f = Witch.from @Word.Word8 @Word
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f 255 `Hspec.shouldBe` 255 test $ f 255 `Hspec.shouldBe` 255
Hspec.describe "Cast Word8 Natural" $ do Hspec.describe "From Word8 Natural" $ do
let f = Witch.cast @Word.Word8 @Natural.Natural let f = Witch.from @Word.Word8 @Natural.Natural
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f 255 `Hspec.shouldBe` 255 test $ f 255 `Hspec.shouldBe` 255
@ -660,38 +660,38 @@ main = Hspec.hspec . Hspec.describe "Witch" $ do
test $ f 127 `Hspec.shouldBe` Just 127 test $ f 127 `Hspec.shouldBe` Just 127
test $ f 128 `Hspec.shouldBe` Nothing test $ f 128 `Hspec.shouldBe` Nothing
Hspec.describe "Cast Word8 Int16" $ do Hspec.describe "From Word8 Int16" $ do
let f = Witch.cast @Word.Word8 @Int.Int16 let f = Witch.from @Word.Word8 @Int.Int16
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f 255 `Hspec.shouldBe` 255 test $ f 255 `Hspec.shouldBe` 255
Hspec.describe "Cast Word8 Int32" $ do Hspec.describe "From Word8 Int32" $ do
let f = Witch.cast @Word.Word8 @Int.Int32 let f = Witch.from @Word.Word8 @Int.Int32
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f 255 `Hspec.shouldBe` 255 test $ f 255 `Hspec.shouldBe` 255
Hspec.describe "Cast Word8 Int64" $ do Hspec.describe "From Word8 Int64" $ do
let f = Witch.cast @Word.Word8 @Int.Int64 let f = Witch.from @Word.Word8 @Int.Int64
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f 255 `Hspec.shouldBe` 255 test $ f 255 `Hspec.shouldBe` 255
Hspec.describe "Cast Word8 Int" $ do Hspec.describe "From Word8 Int" $ do
let f = Witch.cast @Word.Word8 @Int let f = Witch.from @Word.Word8 @Int
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f 255 `Hspec.shouldBe` 255 test $ f 255 `Hspec.shouldBe` 255
Hspec.describe "Cast Word8 Integer" $ do Hspec.describe "From Word8 Integer" $ do
let f = Witch.cast @Word.Word8 @Integer let f = Witch.from @Word.Word8 @Integer
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f 255 `Hspec.shouldBe` 255 test $ f 255 `Hspec.shouldBe` 255
Hspec.describe "Cast Word8 Float" $ do Hspec.describe "From Word8 Float" $ do
let f = Witch.cast @Word.Word8 @Float let f = Witch.from @Word.Word8 @Float
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f 255 `Hspec.shouldBe` 255 test $ f 255 `Hspec.shouldBe` 255
Hspec.describe "Cast Word8 Double" $ do Hspec.describe "From Word8 Double" $ do
let f = Witch.cast @Word.Word8 @Double let f = Witch.from @Word.Word8 @Double
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f 255 `Hspec.shouldBe` 255 test $ f 255 `Hspec.shouldBe` 255
@ -703,23 +703,23 @@ main = Hspec.hspec . Hspec.describe "Witch" $ do
test $ f 255 `Hspec.shouldBe` Just 255 test $ f 255 `Hspec.shouldBe` Just 255
test $ f 256 `Hspec.shouldBe` Nothing test $ f 256 `Hspec.shouldBe` Nothing
Hspec.describe "Cast Word16 Word32" $ do Hspec.describe "From Word16 Word32" $ do
let f = Witch.cast @Word.Word16 @Word.Word32 let f = Witch.from @Word.Word16 @Word.Word32
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f 65535 `Hspec.shouldBe` 65535 test $ f 65535 `Hspec.shouldBe` 65535
Hspec.describe "Cast Word16 Word64" $ do Hspec.describe "From Word16 Word64" $ do
let f = Witch.cast @Word.Word16 @Word.Word64 let f = Witch.from @Word.Word16 @Word.Word64
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f 65535 `Hspec.shouldBe` 65535 test $ f 65535 `Hspec.shouldBe` 65535
Hspec.describe "Cast Word16 Word" $ do Hspec.describe "From Word16 Word" $ do
let f = Witch.cast @Word.Word16 @Word let f = Witch.from @Word.Word16 @Word
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f 65535 `Hspec.shouldBe` 65535 test $ f 65535 `Hspec.shouldBe` 65535
Hspec.describe "Cast Word16 Natural" $ do Hspec.describe "From Word16 Natural" $ do
let f = Witch.cast @Word.Word16 @Natural.Natural let f = Witch.from @Word.Word16 @Natural.Natural
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f 65535 `Hspec.shouldBe` 65535 test $ f 65535 `Hspec.shouldBe` 65535
@ -735,33 +735,33 @@ main = Hspec.hspec . Hspec.describe "Witch" $ do
test $ f 32767 `Hspec.shouldBe` Just 32767 test $ f 32767 `Hspec.shouldBe` Just 32767
test $ f 32768 `Hspec.shouldBe` Nothing test $ f 32768 `Hspec.shouldBe` Nothing
Hspec.describe "Cast Word16 Int32" $ do Hspec.describe "From Word16 Int32" $ do
let f = Witch.cast @Word.Word16 @Int.Int32 let f = Witch.from @Word.Word16 @Int.Int32
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f 65535 `Hspec.shouldBe` 65535 test $ f 65535 `Hspec.shouldBe` 65535
Hspec.describe "Cast Word16 Int64" $ do Hspec.describe "From Word16 Int64" $ do
let f = Witch.cast @Word.Word16 @Int.Int64 let f = Witch.from @Word.Word16 @Int.Int64
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f 65535 `Hspec.shouldBe` 65535 test $ f 65535 `Hspec.shouldBe` 65535
Hspec.describe "Cast Word16 Int" $ do Hspec.describe "From Word16 Int" $ do
let f = Witch.cast @Word.Word16 @Int let f = Witch.from @Word.Word16 @Int
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f 65535 `Hspec.shouldBe` 65535 test $ f 65535 `Hspec.shouldBe` 65535
Hspec.describe "Cast Word16 Integer" $ do Hspec.describe "From Word16 Integer" $ do
let f = Witch.cast @Word.Word16 @Integer let f = Witch.from @Word.Word16 @Integer
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f 65535 `Hspec.shouldBe` 65535 test $ f 65535 `Hspec.shouldBe` 65535
Hspec.describe "Cast Word16 Float" $ do Hspec.describe "From Word16 Float" $ do
let f = Witch.cast @Word.Word16 @Float let f = Witch.from @Word.Word16 @Float
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f 65535 `Hspec.shouldBe` 65535 test $ f 65535 `Hspec.shouldBe` 65535
Hspec.describe "Cast Word16 Double" $ do Hspec.describe "From Word16 Double" $ do
let f = Witch.cast @Word.Word16 @Double let f = Witch.from @Word.Word16 @Double
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f 65535 `Hspec.shouldBe` 65535 test $ f 65535 `Hspec.shouldBe` 65535
@ -779,8 +779,8 @@ main = Hspec.hspec . Hspec.describe "Witch" $ do
test $ f 65535 `Hspec.shouldBe` Just 65535 test $ f 65535 `Hspec.shouldBe` Just 65535
test $ f 65536 `Hspec.shouldBe` Nothing test $ f 65536 `Hspec.shouldBe` Nothing
Hspec.describe "Cast Word32 Word64" $ do Hspec.describe "From Word32 Word64" $ do
let f = Witch.cast @Word.Word32 @Word.Word64 let f = Witch.from @Word.Word32 @Word.Word64
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f 4294967295 `Hspec.shouldBe` 4294967295 test $ f 4294967295 `Hspec.shouldBe` 4294967295
@ -790,8 +790,8 @@ main = Hspec.hspec . Hspec.describe "Witch" $ do
test $ f 0 `Hspec.shouldBe` Just 0 test $ f 0 `Hspec.shouldBe` Just 0
test $ f 4294967295 `Hspec.shouldBe` Just 4294967295 test $ f 4294967295 `Hspec.shouldBe` Just 4294967295
Hspec.describe "Cast Word32 Natural" $ do Hspec.describe "From Word32 Natural" $ do
let f = Witch.cast @Word.Word32 @Natural.Natural let f = Witch.from @Word.Word32 @Natural.Natural
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f 4294967295 `Hspec.shouldBe` 4294967295 test $ f 4294967295 `Hspec.shouldBe` 4294967295
@ -813,8 +813,8 @@ main = Hspec.hspec . Hspec.describe "Witch" $ do
test $ f 2147483647 `Hspec.shouldBe` Just 2147483647 test $ f 2147483647 `Hspec.shouldBe` Just 2147483647
test $ f 2147483648 `Hspec.shouldBe` Nothing test $ f 2147483648 `Hspec.shouldBe` Nothing
Hspec.describe "Cast Word32 Int64" $ do Hspec.describe "From Word32 Int64" $ do
let f = Witch.cast @Word.Word32 @Int.Int64 let f = Witch.from @Word.Word32 @Int.Int64
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f 4294967295 `Hspec.shouldBe` 4294967295 test $ f 4294967295 `Hspec.shouldBe` 4294967295
@ -824,8 +824,8 @@ main = Hspec.hspec . Hspec.describe "Witch" $ do
test $ f 0 `Hspec.shouldBe` Just 0 test $ f 0 `Hspec.shouldBe` Just 0
test $ f 4294967295 `Hspec.shouldBe` Just 4294967295 test $ f 4294967295 `Hspec.shouldBe` Just 4294967295
Hspec.describe "Cast Word32 Integer" $ do Hspec.describe "From Word32 Integer" $ do
let f = Witch.cast @Word.Word32 @Integer let f = Witch.from @Word.Word32 @Integer
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f 4294967295 `Hspec.shouldBe` 4294967295 test $ f 4294967295 `Hspec.shouldBe` 4294967295
@ -835,8 +835,8 @@ main = Hspec.hspec . Hspec.describe "Witch" $ do
test $ f 16777215 `Hspec.shouldBe` Just 16777215 test $ f 16777215 `Hspec.shouldBe` Just 16777215
test $ f 16777216 `Hspec.shouldBe` Nothing test $ f 16777216 `Hspec.shouldBe` Nothing
Hspec.describe "Cast Word32 Double" $ do Hspec.describe "From Word32 Double" $ do
let f = Witch.cast @Word.Word32 @Double let f = Witch.from @Word.Word32 @Double
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f 4294967295 `Hspec.shouldBe` 4294967295 test $ f 4294967295 `Hspec.shouldBe` 4294967295
@ -866,8 +866,8 @@ main = Hspec.hspec . Hspec.describe "Witch" $ do
test $ f 0 `Hspec.shouldBe` Just 0 test $ f 0 `Hspec.shouldBe` Just 0
test $ f 18446744073709551615 `Hspec.shouldBe` Just 18446744073709551615 test $ f 18446744073709551615 `Hspec.shouldBe` Just 18446744073709551615
Hspec.describe "Cast Word64 Natural" $ do Hspec.describe "From Word64 Natural" $ do
let f = Witch.cast @Word.Word64 @Natural.Natural let f = Witch.from @Word.Word64 @Natural.Natural
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f 18446744073709551615 `Hspec.shouldBe` 18446744073709551615 test $ f 18446744073709551615 `Hspec.shouldBe` 18446744073709551615
@ -901,8 +901,8 @@ main = Hspec.hspec . Hspec.describe "Witch" $ do
test $ let x = maxBound :: Int in hush (Witch.tryCast @Word.Word64 @Int (fromIntegral x)) `Hspec.shouldBe` Just x test $ let x = maxBound :: Int in hush (Witch.tryCast @Word.Word64 @Int (fromIntegral x)) `Hspec.shouldBe` Just x
test $ let x = fromIntegral (maxBound :: Int) + 1 :: Word.Word64 in hush (Witch.tryCast @Word.Word64 @Int x) `Hspec.shouldBe` Nothing test $ let x = fromIntegral (maxBound :: Int) + 1 :: Word.Word64 in hush (Witch.tryCast @Word.Word64 @Int x) `Hspec.shouldBe` Nothing
Hspec.describe "Cast Word64 Integer" $ do Hspec.describe "From Word64 Integer" $ do
let f = Witch.cast @Word.Word64 @Integer let f = Witch.from @Word.Word64 @Integer
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f 18446744073709551615 `Hspec.shouldBe` 18446744073709551615 test $ f 18446744073709551615 `Hspec.shouldBe` 18446744073709551615
@ -939,13 +939,13 @@ main = Hspec.hspec . Hspec.describe "Witch" $ do
test $ f 4294967295 `Hspec.shouldBe` Just 4294967295 test $ f 4294967295 `Hspec.shouldBe` Just 4294967295
test $ f 4294967296 `Hspec.shouldBe` Nothing test $ f 4294967296 `Hspec.shouldBe` Nothing
Hspec.describe "Cast Word Word64" $ do Hspec.describe "From Word Word64" $ do
let f = Witch.cast @Word @Word.Word64 let f = Witch.from @Word @Word.Word64
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f maxBound `Hspec.shouldBe` fromIntegral (maxBound :: Word) test $ f maxBound `Hspec.shouldBe` fromIntegral (maxBound :: Word)
Hspec.describe "Cast Word Natural" $ do Hspec.describe "From Word Natural" $ do
let f = Witch.cast @Word @Natural.Natural let f = Witch.from @Word @Natural.Natural
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f maxBound `Hspec.shouldBe` fromIntegral (maxBound :: Word) test $ f maxBound `Hspec.shouldBe` fromIntegral (maxBound :: Word)
@ -981,8 +981,8 @@ main = Hspec.hspec . Hspec.describe "Witch" $ do
test $ let x = maxBound :: Int in hush (Witch.tryCast @Word @Int (fromIntegral x)) `Hspec.shouldBe` Just x test $ let x = maxBound :: Int in hush (Witch.tryCast @Word @Int (fromIntegral x)) `Hspec.shouldBe` Just x
test $ let x = fromIntegral (maxBound :: Int) + 1 :: Word in hush (Witch.tryCast @Word @Int x) `Hspec.shouldBe` Nothing test $ let x = fromIntegral (maxBound :: Int) + 1 :: Word in hush (Witch.tryCast @Word @Int x) `Hspec.shouldBe` Nothing
Hspec.describe "Cast Word Integer" $ do Hspec.describe "From Word Integer" $ do
let f = Witch.cast @Word @Integer let f = Witch.from @Word @Integer
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f maxBound `Hspec.shouldBe` fromIntegral (maxBound :: Word) test $ f maxBound `Hspec.shouldBe` fromIntegral (maxBound :: Word)
@ -1061,8 +1061,8 @@ main = Hspec.hspec . Hspec.describe "Witch" $ do
test $ let x = maxBound :: Int in hush (Witch.tryCast @Natural.Natural @Int (fromIntegral x)) `Hspec.shouldBe` Just x test $ let x = maxBound :: Int in hush (Witch.tryCast @Natural.Natural @Int (fromIntegral x)) `Hspec.shouldBe` Just x
test $ let x = fromIntegral (maxBound :: Int) + 1 :: Natural.Natural in hush (Witch.tryCast @Natural.Natural @Int x) `Hspec.shouldBe` Nothing test $ let x = fromIntegral (maxBound :: Int) + 1 :: Natural.Natural in hush (Witch.tryCast @Natural.Natural @Int x) `Hspec.shouldBe` Nothing
Hspec.describe "Cast Natural Integer" $ do Hspec.describe "From Natural Integer" $ do
let f = Witch.cast @Natural.Natural @Integer let f = Witch.from @Natural.Natural @Integer
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f 9223372036854775808 `Hspec.shouldBe` 9223372036854775808 test $ f 9223372036854775808 `Hspec.shouldBe` 9223372036854775808
@ -1214,8 +1214,8 @@ main = Hspec.hspec . Hspec.describe "Witch" $ do
test $ f (1 / 0) `Hspec.shouldBe` Nothing test $ f (1 / 0) `Hspec.shouldBe` Nothing
test $ f (-1 / 0) `Hspec.shouldBe` Nothing test $ f (-1 / 0) `Hspec.shouldBe` Nothing
Hspec.describe "Cast Float Double" $ do Hspec.describe "From Float Double" $ do
let f = Witch.cast @Float @Double let f = Witch.from @Float @Double
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f 0.5 `Hspec.shouldBe` 0.5 test $ f 0.5 `Hspec.shouldBe` 0.5
test $ f (-0.5) `Hspec.shouldBe` (-0.5) test $ f (-0.5) `Hspec.shouldBe` (-0.5)
@ -1361,8 +1361,8 @@ main = Hspec.hspec . Hspec.describe "Witch" $ do
test $ f (1 / 0) `Hspec.shouldBe` Nothing test $ f (1 / 0) `Hspec.shouldBe` Nothing
test $ f (-1 / 0) `Hspec.shouldBe` Nothing test $ f (-1 / 0) `Hspec.shouldBe` Nothing
Hspec.describe "Cast Double Float" $ do Hspec.describe "From Double Float" $ do
let f = Witch.cast @Double @Float let f = Witch.from @Double @Float
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f 0.5 `Hspec.shouldBe` 0.5 test $ f 0.5 `Hspec.shouldBe` 0.5
test $ f (-0.5) `Hspec.shouldBe` (-0.5) test $ f (-0.5) `Hspec.shouldBe` (-0.5)
@ -1372,9 +1372,9 @@ main = Hspec.hspec . Hspec.describe "Witch" $ do
-- Ratio -- Ratio
Hspec.describe "Cast a (Ratio a)" $ do Hspec.describe "From a (Ratio a)" $ do
test $ Witch.cast @Integer @Rational 0 `Hspec.shouldBe` 0 test $ Witch.from @Integer @Rational 0 `Hspec.shouldBe` 0
let f = Witch.cast @Int @(Ratio.Ratio Int) let f = Witch.from @Int @(Ratio.Ratio Int)
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
Hspec.describe "TryCast (Ratio a) a" $ do Hspec.describe "TryCast (Ratio a) a" $ do
@ -1384,35 +1384,35 @@ main = Hspec.hspec . Hspec.describe "Witch" $ do
test $ f 0 `Hspec.shouldBe` Just 0 test $ f 0 `Hspec.shouldBe` Just 0
test $ f 0.5 `Hspec.shouldBe` Nothing test $ f 0.5 `Hspec.shouldBe` Nothing
Hspec.describe "Cast Rational Float" $ do Hspec.describe "From Rational Float" $ do
let f = Witch.cast @Rational @Float let f = Witch.from @Rational @Float
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f 0.5 `Hspec.shouldBe` 0.5 test $ f 0.5 `Hspec.shouldBe` 0.5
test $ f (-0.5) `Hspec.shouldBe` (-0.5) test $ f (-0.5) `Hspec.shouldBe` (-0.5)
Hspec.describe "Cast Rational Double" $ do Hspec.describe "From Rational Double" $ do
let f = Witch.cast @Rational @Double let f = Witch.from @Rational @Double
test $ f 0 `Hspec.shouldBe` 0 test $ f 0 `Hspec.shouldBe` 0
test $ f 0.5 `Hspec.shouldBe` 0.5 test $ f 0.5 `Hspec.shouldBe` 0.5
test $ f (-0.5) `Hspec.shouldBe` (-0.5) test $ f (-0.5) `Hspec.shouldBe` (-0.5)
-- Fixed -- Fixed
Hspec.describe "Cast Integer (Fixed a)" $ do Hspec.describe "From Integer (Fixed a)" $ do
test $ Witch.cast @Integer @Fixed.Uni 1 `Hspec.shouldBe` 1 test $ Witch.from @Integer @Fixed.Uni 1 `Hspec.shouldBe` 1
let f = Witch.cast @Integer @Fixed.Deci let f = Witch.from @Integer @Fixed.Deci
test $ f 1 `Hspec.shouldBe` 0.1 test $ f 1 `Hspec.shouldBe` 0.1
Hspec.describe "Cast (Fixed a) Integer" $ do Hspec.describe "From (Fixed a) Integer" $ do
test $ Witch.cast @Fixed.Uni @Integer 1 `Hspec.shouldBe` 1 test $ Witch.from @Fixed.Uni @Integer 1 `Hspec.shouldBe` 1
let f = Witch.cast @Fixed.Deci @Integer let f = Witch.from @Fixed.Deci @Integer
test $ f 1 `Hspec.shouldBe` 10 test $ f 1 `Hspec.shouldBe` 10
-- Complex -- Complex
Hspec.describe "Cast a (Complex a)" $ do Hspec.describe "From a (Complex a)" $ do
test $ Witch.cast @Double @(Complex.Complex Double) 1 `Hspec.shouldBe` 1 test $ Witch.from @Double @(Complex.Complex Double) 1 `Hspec.shouldBe` 1
let f = Witch.cast @Float @(Complex.Complex Float) let f = Witch.from @Float @(Complex.Complex Float)
test $ f 1 `Hspec.shouldBe` 1 test $ f 1 `Hspec.shouldBe` 1
Hspec.describe "TryCast (Complex a) a" $ do Hspec.describe "TryCast (Complex a) a" $ do
@ -1430,106 +1430,106 @@ main = Hspec.hspec . Hspec.describe "Witch" $ do
test $ f [1] `Hspec.shouldBe` Just (1 NonEmpty.:| []) test $ f [1] `Hspec.shouldBe` Just (1 NonEmpty.:| [])
test $ f [1, 2] `Hspec.shouldBe` Just (1 NonEmpty.:| [2]) test $ f [1, 2] `Hspec.shouldBe` Just (1 NonEmpty.:| [2])
Hspec.describe "Cast (NonEmpty a) [a]" $ do Hspec.describe "From (NonEmpty a) [a]" $ do
let f = Witch.cast @(NonEmpty.NonEmpty Int) @[Int] let f = Witch.from @(NonEmpty.NonEmpty Int) @[Int]
test $ f (1 NonEmpty.:| []) `Hspec.shouldBe` [1] test $ f (1 NonEmpty.:| []) `Hspec.shouldBe` [1]
test $ f (1 NonEmpty.:| [2]) `Hspec.shouldBe` [1, 2] test $ f (1 NonEmpty.:| [2]) `Hspec.shouldBe` [1, 2]
-- Set -- Set
Hspec.describe "Cast [a] (Set a)" $ do Hspec.describe "From [a] (Set a)" $ do
let f = Witch.cast @[Char] @(Set.Set Char) let f = Witch.from @[Char] @(Set.Set Char)
test $ f [] `Hspec.shouldBe` Set.fromList [] test $ f [] `Hspec.shouldBe` Set.fromList []
test $ f ['a'] `Hspec.shouldBe` Set.fromList ['a'] test $ f ['a'] `Hspec.shouldBe` Set.fromList ['a']
test $ f ['a', 'b'] `Hspec.shouldBe` Set.fromList ['a', 'b'] test $ f ['a', 'b'] `Hspec.shouldBe` Set.fromList ['a', 'b']
test $ f ['a', 'a'] `Hspec.shouldBe` Set.fromList ['a'] test $ f ['a', 'a'] `Hspec.shouldBe` Set.fromList ['a']
Hspec.describe "Cast (Set a) [a]" $ do Hspec.describe "From (Set a) [a]" $ do
let f = Witch.cast @(Set.Set Char) @[Char] let f = Witch.from @(Set.Set Char) @[Char]
test $ f (Set.fromList []) `Hspec.shouldBe` [] test $ f (Set.fromList []) `Hspec.shouldBe` []
test $ f (Set.fromList ['a']) `Hspec.shouldBe` ['a'] test $ f (Set.fromList ['a']) `Hspec.shouldBe` ['a']
test $ f (Set.fromList ['a', 'b']) `Hspec.shouldBe` ['a', 'b'] test $ f (Set.fromList ['a', 'b']) `Hspec.shouldBe` ['a', 'b']
-- IntSet -- IntSet
Hspec.describe "Cast [Int] IntSet" $ do Hspec.describe "From [Int] IntSet" $ do
let f = Witch.cast @[Int] @IntSet.IntSet let f = Witch.from @[Int] @IntSet.IntSet
test $ f [] `Hspec.shouldBe` IntSet.fromList [] test $ f [] `Hspec.shouldBe` IntSet.fromList []
test $ f [1] `Hspec.shouldBe` IntSet.fromList [1] test $ f [1] `Hspec.shouldBe` IntSet.fromList [1]
test $ f [1, 2] `Hspec.shouldBe` IntSet.fromList [1, 2] test $ f [1, 2] `Hspec.shouldBe` IntSet.fromList [1, 2]
Hspec.describe "Cast IntSet [Int]" $ do Hspec.describe "From IntSet [Int]" $ do
let f = Witch.cast @IntSet.IntSet @[Int] let f = Witch.from @IntSet.IntSet @[Int]
test $ f (IntSet.fromList []) `Hspec.shouldBe` [] test $ f (IntSet.fromList []) `Hspec.shouldBe` []
test $ f (IntSet.fromList [1]) `Hspec.shouldBe` [1] test $ f (IntSet.fromList [1]) `Hspec.shouldBe` [1]
test $ f (IntSet.fromList [1, 2]) `Hspec.shouldBe` [1, 2] test $ f (IntSet.fromList [1, 2]) `Hspec.shouldBe` [1, 2]
-- Map -- Map
Hspec.describe "Cast [(k, v)] (Map k v)" $ do Hspec.describe "From [(k, v)] (Map k v)" $ do
let f = Witch.cast @[(Char, Int)] @(Map.Map Char Int) let f = Witch.from @[(Char, Int)] @(Map.Map Char Int)
test $ f [] `Hspec.shouldBe` Map.empty test $ f [] `Hspec.shouldBe` Map.empty
test $ f [('a', 1)] `Hspec.shouldBe` Map.fromList [('a', 1)] test $ f [('a', 1)] `Hspec.shouldBe` Map.fromList [('a', 1)]
test $ f [('a', 1), ('b', 2)] `Hspec.shouldBe` Map.fromList [('a', 1), ('b', 2)] test $ f [('a', 1), ('b', 2)] `Hspec.shouldBe` Map.fromList [('a', 1), ('b', 2)]
test $ f [('a', 1), ('a', 2)] `Hspec.shouldBe` Map.fromList [('a', 2)] test $ f [('a', 1), ('a', 2)] `Hspec.shouldBe` Map.fromList [('a', 2)]
Hspec.describe "Cast (Map k v) [(k, v)]" $ do Hspec.describe "From (Map k v) [(k, v)]" $ do
let f = Witch.cast @(Map.Map Char Int) @[(Char, Int)] let f = Witch.from @(Map.Map Char Int) @[(Char, Int)]
test $ f Map.empty `Hspec.shouldBe` [] test $ f Map.empty `Hspec.shouldBe` []
test $ f (Map.fromList [('a', 1)]) `Hspec.shouldBe` [('a', 1)] test $ f (Map.fromList [('a', 1)]) `Hspec.shouldBe` [('a', 1)]
test $ f (Map.fromList [('a', 1), ('b', 2)]) `Hspec.shouldBe` [('a', 1), ('b', 2)] test $ f (Map.fromList [('a', 1), ('b', 2)]) `Hspec.shouldBe` [('a', 1), ('b', 2)]
-- IntMap -- IntMap
Hspec.describe "Cast [(Int, v)] (IntMap v)" $ do Hspec.describe "From [(Int, v)] (IntMap v)" $ do
let f = Witch.cast @[(Int, Char)] @(IntMap.IntMap Char) let f = Witch.from @[(Int, Char)] @(IntMap.IntMap Char)
test $ f [] `Hspec.shouldBe` IntMap.fromList [] test $ f [] `Hspec.shouldBe` IntMap.fromList []
test $ f [(1, 'a')] `Hspec.shouldBe` IntMap.fromList [(1, 'a')] test $ f [(1, 'a')] `Hspec.shouldBe` IntMap.fromList [(1, 'a')]
test $ f [(1, 'a'), (2, 'b')] `Hspec.shouldBe` IntMap.fromList [(1, 'a'), (2, 'b')] test $ f [(1, 'a'), (2, 'b')] `Hspec.shouldBe` IntMap.fromList [(1, 'a'), (2, 'b')]
test $ f [(1, 'a'), (1, 'b')] `Hspec.shouldBe` IntMap.fromList [(1, 'b')] test $ f [(1, 'a'), (1, 'b')] `Hspec.shouldBe` IntMap.fromList [(1, 'b')]
Hspec.describe "Cast (IntMap v) [(Int, v)]" $ do Hspec.describe "From (IntMap v) [(Int, v)]" $ do
let f = Witch.cast @(IntMap.IntMap Char) @[(Int, Char)] let f = Witch.from @(IntMap.IntMap Char) @[(Int, Char)]
test $ f (IntMap.fromList []) `Hspec.shouldBe` [] test $ f (IntMap.fromList []) `Hspec.shouldBe` []
test $ f (IntMap.fromList [(1, 'a')]) `Hspec.shouldBe` [(1, 'a')] test $ f (IntMap.fromList [(1, 'a')]) `Hspec.shouldBe` [(1, 'a')]
test $ f (IntMap.fromList [(1, 'a'), (2, 'b')]) `Hspec.shouldBe` [(1, 'a'), (2, 'b')] test $ f (IntMap.fromList [(1, 'a'), (2, 'b')]) `Hspec.shouldBe` [(1, 'a'), (2, 'b')]
-- Seq -- Seq
Hspec.describe "Cast [a] (Seq a)" $ do Hspec.describe "From [a] (Seq a)" $ do
let f = Witch.cast @[Int] @(Seq.Seq Int) let f = Witch.from @[Int] @(Seq.Seq Int)
test $ f [] `Hspec.shouldBe` Seq.fromList [] test $ f [] `Hspec.shouldBe` Seq.fromList []
test $ f [1] `Hspec.shouldBe` Seq.fromList [1] test $ f [1] `Hspec.shouldBe` Seq.fromList [1]
test $ f [1, 2] `Hspec.shouldBe` Seq.fromList [1, 2] test $ f [1, 2] `Hspec.shouldBe` Seq.fromList [1, 2]
Hspec.describe "Cast (Seq a) [a]" $ do Hspec.describe "From (Seq a) [a]" $ do
let f = Witch.cast @(Seq.Seq Int) @[Int] let f = Witch.from @(Seq.Seq Int) @[Int]
test $ f (Seq.fromList []) `Hspec.shouldBe` [] test $ f (Seq.fromList []) `Hspec.shouldBe` []
test $ f (Seq.fromList [1]) `Hspec.shouldBe` [1] test $ f (Seq.fromList [1]) `Hspec.shouldBe` [1]
test $ f (Seq.fromList [1, 2]) `Hspec.shouldBe` [1, 2] test $ f (Seq.fromList [1, 2]) `Hspec.shouldBe` [1, 2]
-- ByteString -- ByteString
Hspec.describe "Cast [Word8] ByteString" $ do Hspec.describe "From [Word8] ByteString" $ do
let f = Witch.cast @[Word.Word8] @ByteString.ByteString let f = Witch.from @[Word.Word8] @ByteString.ByteString
test $ f [] `Hspec.shouldBe` ByteString.pack [] test $ f [] `Hspec.shouldBe` ByteString.pack []
test $ f [0x00] `Hspec.shouldBe` ByteString.pack [0x00] test $ f [0x00] `Hspec.shouldBe` ByteString.pack [0x00]
test $ f [0x0f, 0xf0] `Hspec.shouldBe` ByteString.pack [0x0f, 0xf0] test $ f [0x0f, 0xf0] `Hspec.shouldBe` ByteString.pack [0x0f, 0xf0]
Hspec.describe "Cast ByteString [Word8]" $ do Hspec.describe "From ByteString [Word8]" $ do
let f = Witch.cast @ByteString.ByteString @[Word.Word8] let f = Witch.from @ByteString.ByteString @[Word.Word8]
test $ f (ByteString.pack []) `Hspec.shouldBe` [] test $ f (ByteString.pack []) `Hspec.shouldBe` []
test $ f (ByteString.pack [0x00]) `Hspec.shouldBe` [0x00] test $ f (ByteString.pack [0x00]) `Hspec.shouldBe` [0x00]
test $ f (ByteString.pack [0x0f, 0xf0]) `Hspec.shouldBe` [0x0f, 0xf0] test $ f (ByteString.pack [0x0f, 0xf0]) `Hspec.shouldBe` [0x0f, 0xf0]
Hspec.describe "Cast ByteString LazyByteString" $ do Hspec.describe "From ByteString LazyByteString" $ do
let f = Witch.cast @ByteString.ByteString @LazyByteString.ByteString let f = Witch.from @ByteString.ByteString @LazyByteString.ByteString
test $ f (ByteString.pack []) `Hspec.shouldBe` LazyByteString.pack [] test $ f (ByteString.pack []) `Hspec.shouldBe` LazyByteString.pack []
test $ f (ByteString.pack [0x00]) `Hspec.shouldBe` LazyByteString.pack [0x00] test $ f (ByteString.pack [0x00]) `Hspec.shouldBe` LazyByteString.pack [0x00]
test $ f (ByteString.pack [0x0f, 0xf0]) `Hspec.shouldBe` LazyByteString.pack [0x0f, 0xf0] test $ f (ByteString.pack [0x0f, 0xf0]) `Hspec.shouldBe` LazyByteString.pack [0x0f, 0xf0]
Hspec.describe "Cast ByteString ShortByteString" $ do Hspec.describe "From ByteString ShortByteString" $ do
let f = Witch.cast @ByteString.ByteString @ShortByteString.ShortByteString let f = Witch.from @ByteString.ByteString @ShortByteString.ShortByteString
test $ f (ByteString.pack []) `Hspec.shouldBe` ShortByteString.pack [] test $ f (ByteString.pack []) `Hspec.shouldBe` ShortByteString.pack []
test $ f (ByteString.pack [0x00]) `Hspec.shouldBe` ShortByteString.pack [0x00] test $ f (ByteString.pack [0x00]) `Hspec.shouldBe` ShortByteString.pack [0x00]
test $ f (ByteString.pack [0x0f, 0xf0]) `Hspec.shouldBe` ShortByteString.pack [0x0f, 0xf0] test $ f (ByteString.pack [0x0f, 0xf0]) `Hspec.shouldBe` ShortByteString.pack [0x0f, 0xf0]
@ -1542,20 +1542,20 @@ main = Hspec.hspec . Hspec.describe "Witch" $ do
-- LazyByteString -- LazyByteString
Hspec.describe "Cast [Word8] LazyByteString" $ do Hspec.describe "From [Word8] LazyByteString" $ do
let f = Witch.cast @[Word.Word8] @LazyByteString.ByteString let f = Witch.from @[Word.Word8] @LazyByteString.ByteString
test $ f [] `Hspec.shouldBe` LazyByteString.pack [] test $ f [] `Hspec.shouldBe` LazyByteString.pack []
test $ f [0x00] `Hspec.shouldBe` LazyByteString.pack [0x00] test $ f [0x00] `Hspec.shouldBe` LazyByteString.pack [0x00]
test $ f [0x0f, 0xf0] `Hspec.shouldBe` LazyByteString.pack [0x0f, 0xf0] test $ f [0x0f, 0xf0] `Hspec.shouldBe` LazyByteString.pack [0x0f, 0xf0]
Hspec.describe "Cast LazyByteString [Word8]" $ do Hspec.describe "From LazyByteString [Word8]" $ do
let f = Witch.cast @LazyByteString.ByteString @[Word.Word8] let f = Witch.from @LazyByteString.ByteString @[Word.Word8]
test $ f (LazyByteString.pack []) `Hspec.shouldBe` [] test $ f (LazyByteString.pack []) `Hspec.shouldBe` []
test $ f (LazyByteString.pack [0x00]) `Hspec.shouldBe` [0x00] test $ f (LazyByteString.pack [0x00]) `Hspec.shouldBe` [0x00]
test $ f (LazyByteString.pack [0x0f, 0xf0]) `Hspec.shouldBe` [0x0f, 0xf0] test $ f (LazyByteString.pack [0x0f, 0xf0]) `Hspec.shouldBe` [0x0f, 0xf0]
Hspec.describe "Cast LazyByteString ByteString" $ do Hspec.describe "From LazyByteString ByteString" $ do
let f = Witch.cast @LazyByteString.ByteString @ByteString.ByteString let f = Witch.from @LazyByteString.ByteString @ByteString.ByteString
test $ f (LazyByteString.pack []) `Hspec.shouldBe` ByteString.pack [] test $ f (LazyByteString.pack []) `Hspec.shouldBe` ByteString.pack []
test $ f (LazyByteString.pack [0x00]) `Hspec.shouldBe` ByteString.pack [0x00] test $ f (LazyByteString.pack [0x00]) `Hspec.shouldBe` ByteString.pack [0x00]
test $ f (LazyByteString.pack [0x0f, 0xf0]) `Hspec.shouldBe` ByteString.pack [0x0f, 0xf0] test $ f (LazyByteString.pack [0x0f, 0xf0]) `Hspec.shouldBe` ByteString.pack [0x0f, 0xf0]
@ -1568,90 +1568,90 @@ main = Hspec.hspec . Hspec.describe "Witch" $ do
-- ShortByteString -- ShortByteString
Hspec.describe "Cast [Word8] ShortByteString" $ do Hspec.describe "From [Word8] ShortByteString" $ do
let f = Witch.cast @[Word.Word8] @ShortByteString.ShortByteString let f = Witch.from @[Word.Word8] @ShortByteString.ShortByteString
test $ f [] `Hspec.shouldBe` ShortByteString.pack [] test $ f [] `Hspec.shouldBe` ShortByteString.pack []
test $ f [0x00] `Hspec.shouldBe` ShortByteString.pack [0x00] test $ f [0x00] `Hspec.shouldBe` ShortByteString.pack [0x00]
test $ f [0x0f, 0xf0] `Hspec.shouldBe` ShortByteString.pack [0x0f, 0xf0] test $ f [0x0f, 0xf0] `Hspec.shouldBe` ShortByteString.pack [0x0f, 0xf0]
Hspec.describe "Cast ShortByteString [Word8]" $ do Hspec.describe "From ShortByteString [Word8]" $ do
let f = Witch.cast @ShortByteString.ShortByteString @[Word.Word8] let f = Witch.from @ShortByteString.ShortByteString @[Word.Word8]
test $ f (ShortByteString.pack []) `Hspec.shouldBe` [] test $ f (ShortByteString.pack []) `Hspec.shouldBe` []
test $ f (ShortByteString.pack [0x00]) `Hspec.shouldBe` [0x00] test $ f (ShortByteString.pack [0x00]) `Hspec.shouldBe` [0x00]
test $ f (ShortByteString.pack [0x0f, 0xf0]) `Hspec.shouldBe` [0x0f, 0xf0] test $ f (ShortByteString.pack [0x0f, 0xf0]) `Hspec.shouldBe` [0x0f, 0xf0]
Hspec.describe "Cast ShortByteString ByteString" $ do Hspec.describe "From ShortByteString ByteString" $ do
let f = Witch.cast @ShortByteString.ShortByteString @ByteString.ByteString let f = Witch.from @ShortByteString.ShortByteString @ByteString.ByteString
test $ f (ShortByteString.pack []) `Hspec.shouldBe` ByteString.pack [] test $ f (ShortByteString.pack []) `Hspec.shouldBe` ByteString.pack []
test $ f (ShortByteString.pack [0x00]) `Hspec.shouldBe` ByteString.pack [0x00] test $ f (ShortByteString.pack [0x00]) `Hspec.shouldBe` ByteString.pack [0x00]
test $ f (ShortByteString.pack [0x0f, 0xf0]) `Hspec.shouldBe` ByteString.pack [0x0f, 0xf0] test $ f (ShortByteString.pack [0x0f, 0xf0]) `Hspec.shouldBe` ByteString.pack [0x0f, 0xf0]
-- Text -- Text
Hspec.describe "Cast String Text" $ do Hspec.describe "From String Text" $ do
let f = Witch.cast @String @Text.Text let f = Witch.from @String @Text.Text
test $ f "" `Hspec.shouldBe` Text.pack "" test $ f "" `Hspec.shouldBe` Text.pack ""
test $ f "a" `Hspec.shouldBe` Text.pack "a" test $ f "a" `Hspec.shouldBe` Text.pack "a"
test $ f "ab" `Hspec.shouldBe` Text.pack "ab" test $ f "ab" `Hspec.shouldBe` Text.pack "ab"
Hspec.describe "Cast Text String" $ do Hspec.describe "From Text String" $ do
let f = Witch.cast @Text.Text @String let f = Witch.from @Text.Text @String
test $ f (Text.pack "") `Hspec.shouldBe` "" test $ f (Text.pack "") `Hspec.shouldBe` ""
test $ f (Text.pack "a") `Hspec.shouldBe` "a" test $ f (Text.pack "a") `Hspec.shouldBe` "a"
test $ f (Text.pack "ab") `Hspec.shouldBe` "ab" test $ f (Text.pack "ab") `Hspec.shouldBe` "ab"
Hspec.describe "Cast Text LazyText" $ do Hspec.describe "From Text LazyText" $ do
let f = Witch.cast @Text.Text @LazyText.Text let f = Witch.from @Text.Text @LazyText.Text
test $ f (Text.pack "") `Hspec.shouldBe` LazyText.pack "" test $ f (Text.pack "") `Hspec.shouldBe` LazyText.pack ""
test $ f (Text.pack "a") `Hspec.shouldBe` LazyText.pack "a" test $ f (Text.pack "a") `Hspec.shouldBe` LazyText.pack "a"
test $ f (Text.pack "ab") `Hspec.shouldBe` LazyText.pack "ab" test $ f (Text.pack "ab") `Hspec.shouldBe` LazyText.pack "ab"
Hspec.describe "Cast Text ByteString" $ do Hspec.describe "From Text ByteString" $ do
let f = Witch.cast @Text.Text @ByteString.ByteString let f = Witch.from @Text.Text @ByteString.ByteString
test $ f (Text.pack "") `Hspec.shouldBe` ByteString.pack [] test $ f (Text.pack "") `Hspec.shouldBe` ByteString.pack []
test $ f (Text.pack "a") `Hspec.shouldBe` ByteString.pack [0x61] test $ f (Text.pack "a") `Hspec.shouldBe` ByteString.pack [0x61]
-- LazyText -- LazyText
Hspec.describe "Cast String LazyText" $ do Hspec.describe "From String LazyText" $ do
let f = Witch.cast @String @LazyText.Text let f = Witch.from @String @LazyText.Text
test $ f "" `Hspec.shouldBe` LazyText.pack "" test $ f "" `Hspec.shouldBe` LazyText.pack ""
test $ f "a" `Hspec.shouldBe` LazyText.pack "a" test $ f "a" `Hspec.shouldBe` LazyText.pack "a"
test $ f "ab" `Hspec.shouldBe` LazyText.pack "ab" test $ f "ab" `Hspec.shouldBe` LazyText.pack "ab"
Hspec.describe "Cast LazyText String" $ do Hspec.describe "From LazyText String" $ do
let f = Witch.cast @LazyText.Text @String let f = Witch.from @LazyText.Text @String
test $ f (LazyText.pack "") `Hspec.shouldBe` "" test $ f (LazyText.pack "") `Hspec.shouldBe` ""
test $ f (LazyText.pack "a") `Hspec.shouldBe` "a" test $ f (LazyText.pack "a") `Hspec.shouldBe` "a"
test $ f (LazyText.pack "ab") `Hspec.shouldBe` "ab" test $ f (LazyText.pack "ab") `Hspec.shouldBe` "ab"
Hspec.describe "Cast LazyText Text" $ do Hspec.describe "From LazyText Text" $ do
let f = Witch.cast @LazyText.Text @Text.Text let f = Witch.from @LazyText.Text @Text.Text
test $ f (LazyText.pack "") `Hspec.shouldBe` Text.pack "" test $ f (LazyText.pack "") `Hspec.shouldBe` Text.pack ""
test $ f (LazyText.pack "a") `Hspec.shouldBe` Text.pack "a" test $ f (LazyText.pack "a") `Hspec.shouldBe` Text.pack "a"
test $ f (LazyText.pack "ab") `Hspec.shouldBe` Text.pack "ab" test $ f (LazyText.pack "ab") `Hspec.shouldBe` Text.pack "ab"
Hspec.describe "Cast LazyText LazyByteString" $ do Hspec.describe "From LazyText LazyByteString" $ do
let f = Witch.cast @LazyText.Text @LazyByteString.ByteString let f = Witch.from @LazyText.Text @LazyByteString.ByteString
test $ f (LazyText.pack "") `Hspec.shouldBe` LazyByteString.pack [] test $ f (LazyText.pack "") `Hspec.shouldBe` LazyByteString.pack []
test $ f (LazyText.pack "a") `Hspec.shouldBe` LazyByteString.pack [0x61] test $ f (LazyText.pack "a") `Hspec.shouldBe` LazyByteString.pack [0x61]
-- TryCastException -- TryCastException
Hspec.describe "Cast (TryCastException s t0) (TryCastException s t1)" $ do Hspec.describe "From (TryCastException s t0) (TryCastException s t1)" $ do
Hspec.it "needs tests" Hspec.pending Hspec.it "needs tests" Hspec.pending
Hspec.describe "Cast (TryCastException s t) String" $ do Hspec.describe "From (TryCastException s t) String" $ do
test $ Witch.cast (Witch.TryCastException Nothing Nothing :: Witch.TryCastException (Maybe Bool) (Maybe Int)) `Hspec.shouldBe` "TryCastException @(Maybe Bool) @(Maybe Int) Nothing Nothing" test $ Witch.from (Witch.TryCastException Nothing Nothing :: Witch.TryCastException (Maybe Bool) (Maybe Int)) `Hspec.shouldBe` "TryCastException @(Maybe Bool) @(Maybe Int) Nothing Nothing"
let f = Witch.cast @(Witch.TryCastException Bool Int) @String let f = Witch.from @(Witch.TryCastException Bool Int) @String
test $ f (Witch.TryCastException False Nothing) `Hspec.shouldBe` "TryCastException @Bool @Int False Nothing" test $ f (Witch.TryCastException False Nothing) `Hspec.shouldBe` "TryCastException @Bool @Int False Nothing"
Hspec.describe "Cast (TryCastException s t) Text" $ do Hspec.describe "From (TryCastException s t) Text" $ do
let f = Witch.cast @(Witch.TryCastException Bool Int) @Text.Text let f = Witch.from @(Witch.TryCastException Bool Int) @Text.Text
test $ f (Witch.TryCastException False Nothing) `Hspec.shouldBe` Text.pack "TryCastException @Bool @Int False Nothing" test $ f (Witch.TryCastException False Nothing) `Hspec.shouldBe` Text.pack "TryCastException @Bool @Int False Nothing"
Hspec.describe "Cast (TryCastException s t) LazyText" $ do Hspec.describe "From (TryCastException s t) LazyText" $ do
let f = Witch.cast @(Witch.TryCastException Bool Int) @LazyText.Text let f = Witch.from @(Witch.TryCastException Bool Int) @LazyText.Text
test $ f (Witch.TryCastException False Nothing) `Hspec.shouldBe` LazyText.pack "TryCastException @Bool @Int False Nothing" test $ f (Witch.TryCastException False Nothing) `Hspec.shouldBe` LazyText.pack "TryCastException @Bool @Int False Nothing"
test :: Hspec.Example a => a -> Hspec.SpecWith (Hspec.Arg a) test :: Hspec.Example a => a -> Hspec.SpecWith (Hspec.Arg a)
@ -1673,6 +1673,6 @@ newtype Age
= Age Int.Int8 = Age Int.Int8
deriving (Eq, Show) deriving (Eq, Show)
instance Witch.Cast Age Int.Int8 instance Witch.From Age Int.Int8
instance Witch.Cast Int.Int8 Age instance Witch.From Int.Int8 Age

View File

@ -46,7 +46,7 @@ library
, template-haskell >= 2.15.0 && < 2.18 , template-haskell >= 2.15.0 && < 2.18
exposed-modules: exposed-modules:
Witch Witch
Witch.Cast Witch.From
Witch.Instances Witch.Instances
Witch.Lift Witch.Lift
Witch.TryCast Witch.TryCast