2021-04-11 17:04:53 +03:00
|
|
|
{-# OPTIONS_GHC -Wno-orphans #-}
|
2021-04-17 21:33:29 +03:00
|
|
|
{-# LANGUAGE AllowAmbiguousTypes #-}
|
2021-04-11 23:17:22 +03:00
|
|
|
{-# LANGUAGE FlexibleInstances #-}
|
2021-04-11 17:04:53 +03:00
|
|
|
{-# LANGUAGE MultiParamTypeClasses #-}
|
2021-04-17 21:33:29 +03:00
|
|
|
{-# LANGUAGE ScopedTypeVariables #-}
|
|
|
|
{-# LANGUAGE TypeApplications #-}
|
2021-04-11 17:04:53 +03:00
|
|
|
|
|
|
|
module Witch.Instances where
|
|
|
|
|
2021-04-23 05:47:04 +03:00
|
|
|
import qualified Control.Exception as Exception
|
2021-04-11 17:04:53 +03:00
|
|
|
import qualified Data.Bits as Bits
|
2021-04-18 18:03:05 +03:00
|
|
|
import qualified Data.ByteString as ByteString
|
|
|
|
import qualified Data.ByteString.Lazy as LazyByteString
|
|
|
|
import qualified Data.ByteString.Short as ShortByteString
|
2021-04-11 23:29:15 +03:00
|
|
|
import qualified Data.Complex as Complex
|
2021-04-11 23:23:17 +03:00
|
|
|
import qualified Data.Fixed as Fixed
|
2021-04-18 17:50:39 +03:00
|
|
|
import qualified Data.Foldable as Foldable
|
2021-04-11 17:04:53 +03:00
|
|
|
import qualified Data.Int as Int
|
2021-04-18 17:50:39 +03:00
|
|
|
import qualified Data.IntMap as IntMap
|
|
|
|
import qualified Data.IntSet as IntSet
|
2021-04-11 17:04:53 +03:00
|
|
|
import qualified Data.List.NonEmpty as NonEmpty
|
2021-04-18 17:50:39 +03:00
|
|
|
import qualified Data.Map as Map
|
2021-04-11 23:17:22 +03:00
|
|
|
import qualified Data.Ratio as Ratio
|
2021-04-18 17:50:39 +03:00
|
|
|
import qualified Data.Sequence as Seq
|
|
|
|
import qualified Data.Set as Set
|
2021-04-18 18:08:47 +03:00
|
|
|
import qualified Data.Text as Text
|
2021-04-18 21:51:19 +03:00
|
|
|
import qualified Data.Text.Encoding as Text
|
2021-04-18 18:08:47 +03:00
|
|
|
import qualified Data.Text.Lazy as LazyText
|
2021-04-18 21:51:19 +03:00
|
|
|
import qualified Data.Text.Lazy.Encoding as LazyText
|
2021-04-23 05:11:04 +03:00
|
|
|
import qualified Data.Typeable as Typeable
|
2021-04-11 17:04:53 +03:00
|
|
|
import qualified Data.Word as Word
|
|
|
|
import qualified Numeric.Natural as Natural
|
|
|
|
import qualified Witch.Cast as Cast
|
|
|
|
import qualified Witch.TryCast as TryCast
|
|
|
|
import qualified Witch.TryCastException as TryCastException
|
2021-04-18 21:39:23 +03:00
|
|
|
import qualified Witch.Utility as Utility
|
2021-04-11 17:04:53 +03:00
|
|
|
|
|
|
|
-- Int8
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance Cast.Cast Int.Int8 Int.Int16 where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance Cast.Cast Int.Int8 Int.Int32 where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance Cast.Cast Int.Int8 Int.Int64 where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance Cast.Cast Int.Int8 Int where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance Cast.Cast Int.Int8 Integer where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Int.Int8 Word.Word8 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Int.Int8 Word.Word16 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Int.Int8 Word.Word32 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Int.Int8 Word.Word64 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Int.Int8 Word where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-23 15:27:27 +03:00
|
|
|
-- | Uses 'fromIntegral' when the input is not negative.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Int.Int8 Natural.Natural where
|
2021-04-23 15:29:18 +03:00
|
|
|
tryCast = Utility.eitherTryCast fromNonNegativeIntegral
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-17 19:31:16 +03:00
|
|
|
instance Cast.Cast Int.Int8 Float where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-17 19:31:16 +03:00
|
|
|
instance Cast.Cast Int.Int8 Double where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-11 17:04:53 +03:00
|
|
|
-- Int16
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance TryCast.TryCast Int.Int16 Int.Int8 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 17:04:53 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance Cast.Cast Int.Int16 Int.Int32 where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance Cast.Cast Int.Int16 Int.Int64 where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance Cast.Cast Int.Int16 Int where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance Cast.Cast Int.Int16 Integer where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Int.Int16 Word.Word8 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Int.Int16 Word.Word16 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Int.Int16 Word.Word32 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Int.Int16 Word.Word64 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Int.Int16 Word where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-23 15:27:27 +03:00
|
|
|
-- | Uses 'fromIntegral' when the input is not negative.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Int.Int16 Natural.Natural where
|
2021-04-23 15:29:18 +03:00
|
|
|
tryCast = Utility.eitherTryCast fromNonNegativeIntegral
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-17 19:31:16 +03:00
|
|
|
instance Cast.Cast Int.Int16 Float where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-17 19:31:16 +03:00
|
|
|
instance Cast.Cast Int.Int16 Double where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-11 17:04:53 +03:00
|
|
|
-- Int32
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance TryCast.TryCast Int.Int32 Int.Int8 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 17:04:53 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance TryCast.TryCast Int.Int32 Int.Int16 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 17:04:53 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance Cast.Cast Int.Int32 Int.Int64 where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance TryCast.TryCast Int.Int32 Int where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 17:04:53 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance Cast.Cast Int.Int32 Integer where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Int.Int32 Word.Word8 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Int.Int32 Word.Word16 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Int.Int32 Word.Word32 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Int.Int32 Word.Word64 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Int.Int32 Word where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-23 15:27:27 +03:00
|
|
|
-- | Uses 'fromIntegral' when the input is not negative.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Int.Int32 Natural.Natural where
|
2021-04-23 15:29:18 +03:00
|
|
|
tryCast = Utility.eitherTryCast fromNonNegativeIntegral
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral' when the input is between -16,777,215 and 16,777,215
|
|
|
|
-- inclusive.
|
2021-04-17 19:31:16 +03:00
|
|
|
instance TryCast.TryCast Int.Int32 Float where
|
2021-04-23 16:01:03 +03:00
|
|
|
tryCast = Utility.eitherTryCast $ \s -> if s < -maxFloat
|
|
|
|
then Left Exception.Underflow
|
|
|
|
else if s > maxFloat
|
|
|
|
then Left Exception.Overflow
|
|
|
|
else Right $ fromIntegral s
|
2021-04-17 19:31:16 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-17 19:31:16 +03:00
|
|
|
instance Cast.Cast Int.Int32 Double where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-11 17:04:53 +03:00
|
|
|
-- Int64
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance TryCast.TryCast Int.Int64 Int.Int8 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 17:04:53 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance TryCast.TryCast Int.Int64 Int.Int16 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 17:04:53 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance TryCast.TryCast Int.Int64 Int.Int32 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 17:04:53 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance TryCast.TryCast Int.Int64 Int where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 17:04:53 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance Cast.Cast Int.Int64 Integer where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Int.Int64 Word.Word8 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Int.Int64 Word.Word16 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Int.Int64 Word.Word32 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Int.Int64 Word.Word64 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Int.Int64 Word where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-23 15:27:27 +03:00
|
|
|
-- | Uses 'fromIntegral' when the input is not negative.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Int.Int64 Natural.Natural where
|
2021-04-23 15:29:18 +03:00
|
|
|
tryCast = Utility.eitherTryCast fromNonNegativeIntegral
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral' when the input is between -16,777,215 and 16,777,215
|
|
|
|
-- inclusive.
|
2021-04-17 19:31:16 +03:00
|
|
|
instance TryCast.TryCast Int.Int64 Float where
|
2021-04-23 16:01:03 +03:00
|
|
|
tryCast = Utility.eitherTryCast $ \s -> if s < -maxFloat
|
|
|
|
then Left Exception.Underflow
|
|
|
|
else if s > maxFloat
|
|
|
|
then Left Exception.Overflow
|
|
|
|
else Right $ fromIntegral s
|
2021-04-17 19:31:16 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral' when the input is between -9,007,199,254,740,991 and
|
|
|
|
-- 9,007,199,254,740,991 inclusive.
|
2021-04-17 19:31:16 +03:00
|
|
|
instance TryCast.TryCast Int.Int64 Double where
|
2021-04-23 16:01:03 +03:00
|
|
|
tryCast = Utility.eitherTryCast $ \s -> if s < -maxDouble
|
|
|
|
then Left Exception.Underflow
|
|
|
|
else if s > maxDouble
|
|
|
|
then Left Exception.Overflow
|
|
|
|
else Right $ fromIntegral s
|
2021-04-17 19:31:16 +03:00
|
|
|
|
2021-04-11 17:04:53 +03:00
|
|
|
-- Int
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance TryCast.TryCast Int Int.Int8 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 17:04:53 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance TryCast.TryCast Int Int.Int16 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 17:04:53 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance TryCast.TryCast Int Int.Int32 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 17:04:53 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance Cast.Cast Int Int.Int64 where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance Cast.Cast Int Integer where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Int Word.Word8 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Int Word.Word16 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Int Word.Word32 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Int Word.Word64 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Int Word where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-23 15:27:27 +03:00
|
|
|
-- | Uses 'fromIntegral' when the input is not negative.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Int Natural.Natural where
|
2021-04-23 15:29:18 +03:00
|
|
|
tryCast = Utility.eitherTryCast fromNonNegativeIntegral
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral' when the input is between -16,777,215 and 16,777,215
|
|
|
|
-- inclusive.
|
2021-04-17 19:31:16 +03:00
|
|
|
instance TryCast.TryCast Int Float where
|
2021-04-23 16:01:03 +03:00
|
|
|
tryCast = Utility.eitherTryCast $ \s -> if s < -maxFloat
|
|
|
|
then Left Exception.Underflow
|
|
|
|
else if s > maxFloat
|
|
|
|
then Left Exception.Overflow
|
|
|
|
else Right $ fromIntegral s
|
2021-04-17 19:31:16 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral' when the input is between -9,007,199,254,740,991 and
|
|
|
|
-- 9,007,199,254,740,991 inclusive.
|
2021-04-17 19:31:16 +03:00
|
|
|
instance TryCast.TryCast Int Double where
|
2021-04-23 15:14:53 +03:00
|
|
|
tryCast = Utility.eitherTryCast $ \s ->
|
2021-04-23 16:01:03 +03:00
|
|
|
if toInteger (maxBound :: Int) <= maxDouble
|
|
|
|
then Right $ fromIntegral s
|
|
|
|
else if s < -maxDouble
|
|
|
|
then Left Exception.Underflow
|
|
|
|
else if s > maxDouble
|
|
|
|
then Left Exception.Overflow
|
|
|
|
else Right $ fromIntegral s
|
2021-04-17 19:31:16 +03:00
|
|
|
|
2021-04-11 17:04:53 +03:00
|
|
|
-- Integer
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance TryCast.TryCast Integer Int.Int8 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 17:04:53 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance TryCast.TryCast Integer Int.Int16 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 17:04:53 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance TryCast.TryCast Integer Int.Int32 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 17:04:53 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance TryCast.TryCast Integer Int.Int64 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 17:04:53 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance TryCast.TryCast Integer Int where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 17:04:53 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Integer Word.Word8 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Integer Word.Word16 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Integer Word.Word32 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Integer Word.Word64 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Integer Word where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-23 15:27:27 +03:00
|
|
|
-- | Uses 'fromInteger' when the input is not negative.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Integer Natural.Natural where
|
2021-04-23 15:29:18 +03:00
|
|
|
-- This should use @eitherTryCast fromNonNegativeIntegral@, but that causes
|
|
|
|
-- a bug in GHC 9.0.1. By inlining @fromNonNegativeIntegral@ and replacing
|
2021-04-11 22:19:13 +03:00
|
|
|
-- @fromIntegral@ with @fromInteger@, we can work around the bug.
|
|
|
|
-- https://mail.haskell.org/pipermail/haskell-cafe/2021-March/133540.html
|
2021-04-23 16:01:03 +03:00
|
|
|
tryCast = Utility.eitherTryCast
|
|
|
|
$ \s -> if s < 0 then Left Exception.Underflow else Right $ fromInteger s
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral' when the input is between -16,777,215 and 16,777,215
|
|
|
|
-- inclusive.
|
2021-04-17 19:31:16 +03:00
|
|
|
instance TryCast.TryCast Integer Float where
|
2021-04-23 16:01:03 +03:00
|
|
|
tryCast = Utility.eitherTryCast $ \s -> if s < -maxFloat
|
|
|
|
then Left Exception.Underflow
|
|
|
|
else if s > maxFloat
|
|
|
|
then Left Exception.Overflow
|
|
|
|
else Right $ fromIntegral s
|
2021-04-17 19:31:16 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral' when the input is between -9,007,199,254,740,991 and
|
|
|
|
-- 9,007,199,254,740,991 inclusive.
|
2021-04-17 19:31:16 +03:00
|
|
|
instance TryCast.TryCast Integer Double where
|
2021-04-23 16:01:03 +03:00
|
|
|
tryCast = Utility.eitherTryCast $ \s -> if s < -maxDouble
|
|
|
|
then Left Exception.Underflow
|
|
|
|
else if s > maxDouble
|
|
|
|
then Left Exception.Overflow
|
|
|
|
else Right $ fromIntegral s
|
2021-04-17 19:31:16 +03:00
|
|
|
|
2021-04-11 17:04:53 +03:00
|
|
|
-- Word8
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance Cast.Cast Word.Word8 Word.Word16 where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance Cast.Cast Word.Word8 Word.Word32 where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance Cast.Cast Word.Word8 Word.Word64 where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance Cast.Cast Word.Word8 Word where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance Cast.Cast Word.Word8 Natural.Natural where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Word.Word8 Int.Int8 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance Cast.Cast Word.Word8 Int.Int16 where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance Cast.Cast Word.Word8 Int.Int32 where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance Cast.Cast Word.Word8 Int.Int64 where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance Cast.Cast Word.Word8 Int where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance Cast.Cast Word.Word8 Integer where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-17 19:31:16 +03:00
|
|
|
instance Cast.Cast Word.Word8 Float where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-17 19:31:16 +03:00
|
|
|
instance Cast.Cast Word.Word8 Double where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-11 17:04:53 +03:00
|
|
|
-- Word16
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance TryCast.TryCast Word.Word16 Word.Word8 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 17:04:53 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance Cast.Cast Word.Word16 Word.Word32 where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance Cast.Cast Word.Word16 Word.Word64 where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance Cast.Cast Word.Word16 Word where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance Cast.Cast Word.Word16 Natural.Natural where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Word.Word16 Int.Int8 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Word.Word16 Int.Int16 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance Cast.Cast Word.Word16 Int.Int32 where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance Cast.Cast Word.Word16 Int.Int64 where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance Cast.Cast Word.Word16 Int where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance Cast.Cast Word.Word16 Integer where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-17 19:31:16 +03:00
|
|
|
instance Cast.Cast Word.Word16 Float where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-17 19:31:16 +03:00
|
|
|
instance Cast.Cast Word.Word16 Double where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-11 17:04:53 +03:00
|
|
|
-- Word32
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance TryCast.TryCast Word.Word32 Word.Word8 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 17:04:53 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance TryCast.TryCast Word.Word32 Word.Word16 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 17:04:53 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance Cast.Cast Word.Word32 Word.Word64 where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance TryCast.TryCast Word.Word32 Word where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 17:04:53 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance Cast.Cast Word.Word32 Natural.Natural where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Word.Word32 Int.Int8 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Word.Word32 Int.Int16 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Word.Word32 Int.Int32 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance Cast.Cast Word.Word32 Int.Int64 where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Word.Word32 Int where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance Cast.Cast Word.Word32 Integer where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-23 15:27:27 +03:00
|
|
|
-- | Uses 'fromIntegral' when the input is less than or equal to 16,777,215.
|
2021-04-17 19:31:16 +03:00
|
|
|
instance TryCast.TryCast Word.Word32 Float where
|
2021-04-23 16:01:03 +03:00
|
|
|
tryCast = Utility.eitherTryCast $ \s ->
|
|
|
|
if s <= maxFloat then Right $ fromIntegral s else Left Exception.Overflow
|
2021-04-17 19:31:16 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-17 19:31:16 +03:00
|
|
|
instance Cast.Cast Word.Word32 Double where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-11 17:04:53 +03:00
|
|
|
-- Word64
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance TryCast.TryCast Word.Word64 Word.Word8 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 17:04:53 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance TryCast.TryCast Word.Word64 Word.Word16 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 17:04:53 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance TryCast.TryCast Word.Word64 Word.Word32 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 17:04:53 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance TryCast.TryCast Word.Word64 Word where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 17:04:53 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance Cast.Cast Word.Word64 Natural.Natural where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Word.Word64 Int.Int8 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Word.Word64 Int.Int16 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Word.Word64 Int.Int32 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Word.Word64 Int.Int64 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Word.Word64 Int where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance Cast.Cast Word.Word64 Integer where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-23 15:27:27 +03:00
|
|
|
-- | Uses 'fromIntegral' when the input is less than or equal to 16,777,215.
|
2021-04-17 19:31:16 +03:00
|
|
|
instance TryCast.TryCast Word.Word64 Float where
|
2021-04-23 16:01:03 +03:00
|
|
|
tryCast = Utility.eitherTryCast $ \s ->
|
|
|
|
if s <= maxFloat then Right $ fromIntegral s else Left Exception.Overflow
|
2021-04-17 19:31:16 +03:00
|
|
|
|
2021-04-23 15:27:27 +03:00
|
|
|
-- | Uses 'fromIntegral' when the input is less than or equal to
|
|
|
|
-- 9,007,199,254,740,991.
|
2021-04-17 19:31:16 +03:00
|
|
|
instance TryCast.TryCast Word.Word64 Double where
|
2021-04-23 16:01:03 +03:00
|
|
|
tryCast = Utility.eitherTryCast $ \s -> if s <= maxDouble
|
|
|
|
then Right $ fromIntegral s
|
|
|
|
else Left Exception.Overflow
|
2021-04-17 19:31:16 +03:00
|
|
|
|
2021-04-11 17:04:53 +03:00
|
|
|
-- Word
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance TryCast.TryCast Word Word.Word8 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 17:04:53 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance TryCast.TryCast Word Word.Word16 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 17:04:53 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance TryCast.TryCast Word Word.Word32 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 17:04:53 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance Cast.Cast Word Word.Word64 where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance Cast.Cast Word Natural.Natural where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Word Int.Int8 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Word Int.Int16 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Word Int.Int32 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Word Int.Int64 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Word Int where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance Cast.Cast Word Integer where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-23 15:27:27 +03:00
|
|
|
-- | Uses 'fromIntegral' when the input is less than or equal to 16,777,215.
|
2021-04-17 19:31:16 +03:00
|
|
|
instance TryCast.TryCast Word Float where
|
2021-04-23 16:01:03 +03:00
|
|
|
tryCast = Utility.eitherTryCast $ \s ->
|
|
|
|
if s <= maxFloat then Right $ fromIntegral s else Left Exception.Overflow
|
2021-04-17 19:31:16 +03:00
|
|
|
|
2021-04-23 15:27:27 +03:00
|
|
|
-- | Uses 'fromIntegral' when the input is less than or equal to
|
|
|
|
-- 9,007,199,254,740,991.
|
2021-04-17 19:31:16 +03:00
|
|
|
instance TryCast.TryCast Word Double where
|
2021-04-23 15:29:18 +03:00
|
|
|
tryCast = Utility.eitherTryCast $ \s ->
|
2021-04-18 18:28:02 +03:00
|
|
|
if (toInteger (maxBound :: Word) <= maxDouble) || (s <= maxDouble)
|
2021-04-23 15:29:18 +03:00
|
|
|
then Right $ fromIntegral s
|
|
|
|
else Left Exception.Overflow
|
2021-04-17 19:31:16 +03:00
|
|
|
|
2021-04-11 17:04:53 +03:00
|
|
|
-- Natural
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance TryCast.TryCast Natural.Natural Word.Word8 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 17:04:53 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance TryCast.TryCast Natural.Natural Word.Word16 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 17:04:53 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance TryCast.TryCast Natural.Natural Word.Word32 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 17:04:53 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance TryCast.TryCast Natural.Natural Word.Word64 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 17:04:53 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 17:04:53 +03:00
|
|
|
instance TryCast.TryCast Natural.Natural Word where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 17:04:53 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Natural.Natural Int.Int8 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Natural.Natural Int.Int16 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Natural.Natural Int.Int32 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Natural.Natural Int.Int64 where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Bits.toIntegralSized'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance TryCast.TryCast Natural.Natural Int where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast Bits.toIntegralSized
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromIntegral'.
|
2021-04-11 21:06:17 +03:00
|
|
|
instance Cast.Cast Natural.Natural Integer where
|
|
|
|
cast = fromIntegral
|
|
|
|
|
2021-04-23 15:27:27 +03:00
|
|
|
-- | Uses 'fromIntegral' when the input is less than or equal to 16,777,215.
|
2021-04-17 19:31:16 +03:00
|
|
|
instance TryCast.TryCast Natural.Natural Float where
|
2021-04-23 16:01:03 +03:00
|
|
|
tryCast = Utility.eitherTryCast $ \s ->
|
|
|
|
if s <= maxFloat then Right $ fromIntegral s else Left Exception.Overflow
|
2021-04-17 19:31:16 +03:00
|
|
|
|
2021-04-23 15:27:27 +03:00
|
|
|
-- | Uses 'fromIntegral' when the input is less than or equal to
|
|
|
|
-- 9,007,199,254,740,991.
|
2021-04-17 19:31:16 +03:00
|
|
|
instance TryCast.TryCast Natural.Natural Double where
|
2021-04-23 16:01:03 +03:00
|
|
|
tryCast = Utility.eitherTryCast $ \s -> if s <= maxDouble
|
|
|
|
then Right $ fromIntegral s
|
|
|
|
else Left Exception.Overflow
|
2021-04-17 21:33:29 +03:00
|
|
|
|
|
|
|
-- Float
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Converts via 'Integer'.
|
2021-04-17 21:33:29 +03:00
|
|
|
instance TryCast.TryCast Float Int.Int8 where
|
2021-04-18 21:39:23 +03:00
|
|
|
tryCast = Utility.tryVia @Integer
|
2021-04-17 21:33:29 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Converts via 'Integer'.
|
2021-04-17 21:33:29 +03:00
|
|
|
instance TryCast.TryCast Float Int.Int16 where
|
2021-04-18 21:39:23 +03:00
|
|
|
tryCast = Utility.tryVia @Integer
|
2021-04-17 21:33:29 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Converts via 'Integer'.
|
2021-04-17 21:33:29 +03:00
|
|
|
instance TryCast.TryCast Float Int.Int32 where
|
2021-04-18 21:39:23 +03:00
|
|
|
tryCast = Utility.tryVia @Integer
|
2021-04-17 21:33:29 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Converts via 'Integer'.
|
2021-04-17 21:33:29 +03:00
|
|
|
instance TryCast.TryCast Float Int.Int64 where
|
2021-04-18 21:39:23 +03:00
|
|
|
tryCast = Utility.tryVia @Integer
|
2021-04-17 21:33:29 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Converts via 'Integer'.
|
2021-04-17 21:33:29 +03:00
|
|
|
instance TryCast.TryCast Float Int where
|
2021-04-18 21:39:23 +03:00
|
|
|
tryCast = Utility.tryVia @Integer
|
2021-04-17 21:33:29 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Converts via 'Rational' when the input is between -16,777,215 and
|
|
|
|
-- 16,777,215 inclusive.
|
2021-04-17 21:33:29 +03:00
|
|
|
instance TryCast.TryCast Float Integer where
|
2021-04-23 15:14:53 +03:00
|
|
|
tryCast = Utility.eitherTryCast $ \s -> case Utility.tryVia @Rational s of
|
|
|
|
Left e -> Left $ Exception.toException e
|
2021-04-23 05:47:04 +03:00
|
|
|
Right t
|
2021-04-23 15:14:53 +03:00
|
|
|
| t < -maxFloat -> Left $ Exception.toException Exception.Underflow
|
|
|
|
| t > maxFloat -> Left $ Exception.toException Exception.Overflow
|
2021-04-23 05:47:04 +03:00
|
|
|
| otherwise -> Right t
|
2021-04-17 21:33:29 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Converts via 'Integer'.
|
2021-04-17 21:33:29 +03:00
|
|
|
instance TryCast.TryCast Float Word.Word8 where
|
2021-04-18 21:39:23 +03:00
|
|
|
tryCast = Utility.tryVia @Integer
|
2021-04-17 21:33:29 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Converts via 'Integer'.
|
2021-04-17 21:33:29 +03:00
|
|
|
instance TryCast.TryCast Float Word.Word16 where
|
2021-04-18 21:39:23 +03:00
|
|
|
tryCast = Utility.tryVia @Integer
|
2021-04-17 21:33:29 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Converts via 'Integer'.
|
2021-04-17 21:33:29 +03:00
|
|
|
instance TryCast.TryCast Float Word.Word32 where
|
2021-04-18 21:39:23 +03:00
|
|
|
tryCast = Utility.tryVia @Integer
|
2021-04-17 21:33:29 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Converts via 'Integer'.
|
2021-04-17 21:33:29 +03:00
|
|
|
instance TryCast.TryCast Float Word.Word64 where
|
2021-04-18 21:39:23 +03:00
|
|
|
tryCast = Utility.tryVia @Integer
|
2021-04-17 21:33:29 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Converts via 'Integer'.
|
2021-04-17 21:33:29 +03:00
|
|
|
instance TryCast.TryCast Float Word where
|
2021-04-18 21:39:23 +03:00
|
|
|
tryCast = Utility.tryVia @Integer
|
2021-04-17 21:33:29 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Converts via 'Integer'.
|
2021-04-17 21:33:29 +03:00
|
|
|
instance TryCast.TryCast Float Natural.Natural where
|
2021-04-18 21:39:23 +03:00
|
|
|
tryCast = Utility.tryVia @Integer
|
2021-04-17 21:33:29 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'toRational' when the input is not NaN or infinity.
|
2021-04-17 21:33:29 +03:00
|
|
|
instance TryCast.TryCast Float Rational where
|
2021-04-23 16:01:03 +03:00
|
|
|
tryCast = Utility.eitherTryCast $ \s -> if isNaN s
|
|
|
|
then Left Exception.LossOfPrecision
|
|
|
|
else if isInfinite s
|
|
|
|
then if s > 0 then Left Exception.Overflow else Left Exception.Underflow
|
|
|
|
else Right $ toRational s
|
2021-04-17 19:31:16 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'realToFrac'.
|
2021-04-17 21:55:56 +03:00
|
|
|
instance Cast.Cast Float Double where
|
|
|
|
cast = realToFrac
|
|
|
|
|
|
|
|
-- Double
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Converts via 'Integer'.
|
2021-04-17 21:55:56 +03:00
|
|
|
instance TryCast.TryCast Double Int.Int8 where
|
2021-04-18 21:39:23 +03:00
|
|
|
tryCast = Utility.tryVia @Integer
|
2021-04-17 21:55:56 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Converts via 'Integer'.
|
2021-04-17 21:55:56 +03:00
|
|
|
instance TryCast.TryCast Double Int.Int16 where
|
2021-04-18 21:39:23 +03:00
|
|
|
tryCast = Utility.tryVia @Integer
|
2021-04-17 21:55:56 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Converts via 'Integer'.
|
2021-04-17 21:55:56 +03:00
|
|
|
instance TryCast.TryCast Double Int.Int32 where
|
2021-04-18 21:39:23 +03:00
|
|
|
tryCast = Utility.tryVia @Integer
|
2021-04-17 21:55:56 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Converts via 'Integer'.
|
2021-04-17 21:55:56 +03:00
|
|
|
instance TryCast.TryCast Double Int.Int64 where
|
2021-04-18 21:39:23 +03:00
|
|
|
tryCast = Utility.tryVia @Integer
|
2021-04-17 21:55:56 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Converts via 'Integer'.
|
2021-04-17 21:55:56 +03:00
|
|
|
instance TryCast.TryCast Double Int where
|
2021-04-18 21:39:23 +03:00
|
|
|
tryCast = Utility.tryVia @Integer
|
2021-04-17 21:55:56 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Converts via 'Rational' when the input is between -9,007,199,254,740,991
|
|
|
|
-- and 9,007,199,254,740,991 inclusive.
|
2021-04-17 21:55:56 +03:00
|
|
|
instance TryCast.TryCast Double Integer where
|
2021-04-23 15:14:53 +03:00
|
|
|
tryCast = Utility.eitherTryCast $ \s -> case Utility.tryVia @Rational s of
|
|
|
|
Left e -> Left $ Exception.toException e
|
2021-04-23 05:47:04 +03:00
|
|
|
Right t
|
2021-04-23 15:14:53 +03:00
|
|
|
| t < -maxDouble -> Left $ Exception.toException Exception.Underflow
|
|
|
|
| t > maxDouble -> Left $ Exception.toException Exception.Overflow
|
2021-04-23 05:47:04 +03:00
|
|
|
| otherwise -> Right t
|
2021-04-17 21:55:56 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Converts via 'Integer'.
|
2021-04-17 21:55:56 +03:00
|
|
|
instance TryCast.TryCast Double Word.Word8 where
|
2021-04-18 21:39:23 +03:00
|
|
|
tryCast = Utility.tryVia @Integer
|
2021-04-17 21:55:56 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Converts via 'Integer'.
|
2021-04-17 21:55:56 +03:00
|
|
|
instance TryCast.TryCast Double Word.Word16 where
|
2021-04-18 21:39:23 +03:00
|
|
|
tryCast = Utility.tryVia @Integer
|
2021-04-17 21:55:56 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Converts via 'Integer'.
|
2021-04-17 21:55:56 +03:00
|
|
|
instance TryCast.TryCast Double Word.Word32 where
|
2021-04-18 21:39:23 +03:00
|
|
|
tryCast = Utility.tryVia @Integer
|
2021-04-17 21:55:56 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Converts via 'Integer'.
|
2021-04-17 21:55:56 +03:00
|
|
|
instance TryCast.TryCast Double Word.Word64 where
|
2021-04-18 21:39:23 +03:00
|
|
|
tryCast = Utility.tryVia @Integer
|
2021-04-17 21:55:56 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Converts via 'Integer'.
|
2021-04-17 21:55:56 +03:00
|
|
|
instance TryCast.TryCast Double Word where
|
2021-04-18 21:39:23 +03:00
|
|
|
tryCast = Utility.tryVia @Integer
|
2021-04-17 21:55:56 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Converts via 'Integer'.
|
2021-04-17 21:55:56 +03:00
|
|
|
instance TryCast.TryCast Double Natural.Natural where
|
2021-04-18 21:39:23 +03:00
|
|
|
tryCast = Utility.tryVia @Integer
|
2021-04-17 21:55:56 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'toRational' when the input is not NaN or infinity.
|
2021-04-17 21:55:56 +03:00
|
|
|
instance TryCast.TryCast Double Rational where
|
2021-04-23 16:01:03 +03:00
|
|
|
tryCast = Utility.eitherTryCast $ \s -> if isNaN s
|
|
|
|
then Left Exception.LossOfPrecision
|
|
|
|
else if isInfinite s
|
|
|
|
then if s > 0 then Left Exception.Overflow else Left Exception.Underflow
|
|
|
|
else Right $ toRational s
|
2021-04-17 21:55:56 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'realToFrac'. This necessarily loses some precision.
|
2021-04-18 17:37:02 +03:00
|
|
|
instance Cast.Cast Double Float where
|
|
|
|
cast = realToFrac
|
|
|
|
|
2021-04-11 23:17:22 +03:00
|
|
|
-- Ratio
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses '(Ratio.%)' with a denominator of 1.
|
2021-04-11 23:17:22 +03:00
|
|
|
instance Integral a => Cast.Cast a (Ratio.Ratio a) where
|
|
|
|
cast = (Ratio.% 1)
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Ratio.numerator' when the denominator is 1.
|
2021-04-11 23:31:13 +03:00
|
|
|
instance (Eq a, Num a) => TryCast.TryCast (Ratio.Ratio a) a where
|
2021-04-23 16:01:03 +03:00
|
|
|
tryCast = Utility.eitherTryCast $ \s -> if Ratio.denominator s == 1
|
|
|
|
then Right $ Ratio.numerator s
|
|
|
|
else Left Exception.LossOfPrecision
|
2021-04-11 23:17:22 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromRational'. This necessarily loses some precision.
|
2021-04-18 17:37:02 +03:00
|
|
|
instance Cast.Cast Rational Float where
|
|
|
|
cast = fromRational
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'fromRational'. This necessarily loses some precision.
|
2021-04-18 17:37:02 +03:00
|
|
|
instance Cast.Cast Rational Double where
|
|
|
|
cast = fromRational
|
|
|
|
|
2021-04-11 23:23:17 +03:00
|
|
|
-- Fixed
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Fixed.MkFixed'. This means @cast 2 :: Centi@ is @0.02@ rather than
|
|
|
|
-- @2.00@.
|
2021-04-11 23:23:17 +03:00
|
|
|
instance Cast.Cast Integer (Fixed.Fixed a) where
|
|
|
|
cast = Fixed.MkFixed
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Fixed.MkFixed'. This means @cast (3.00 :: Centi)@ is @300@ rather
|
|
|
|
-- than @3@.
|
2021-04-11 23:23:17 +03:00
|
|
|
instance Cast.Cast (Fixed.Fixed a) Integer where
|
|
|
|
cast (Fixed.MkFixed t) = t
|
|
|
|
|
2021-04-11 23:29:15 +03:00
|
|
|
-- Complex
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses '(Complex.:+)' with an imaginary part of 0.
|
2021-04-11 23:29:15 +03:00
|
|
|
instance Num a => Cast.Cast a (Complex.Complex a) where
|
|
|
|
cast = (Complex.:+ 0)
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Complex.realPart' when the imaginary part is 0.
|
2021-04-11 23:29:15 +03:00
|
|
|
instance (Eq a, Num a) => TryCast.TryCast (Complex.Complex a) a where
|
2021-04-23 16:01:03 +03:00
|
|
|
tryCast = Utility.eitherTryCast $ \s -> if Complex.imagPart s == 0
|
|
|
|
then Right $ Complex.realPart s
|
|
|
|
else Left Exception.LossOfPrecision
|
2021-04-11 23:29:15 +03:00
|
|
|
|
2021-04-18 17:50:39 +03:00
|
|
|
-- NonEmpty
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'NonEmpty.nonEmpty'.
|
2021-04-18 17:50:39 +03:00
|
|
|
instance TryCast.TryCast [a] (NonEmpty.NonEmpty a) where
|
2021-04-23 14:39:20 +03:00
|
|
|
tryCast = Utility.maybeTryCast NonEmpty.nonEmpty
|
2021-04-18 17:50:39 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'NonEmpty.toList'.
|
2021-04-18 17:50:39 +03:00
|
|
|
instance Cast.Cast (NonEmpty.NonEmpty a) [a] where
|
|
|
|
cast = NonEmpty.toList
|
|
|
|
|
|
|
|
-- Set
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Set.fromList'.
|
2021-04-18 17:50:39 +03:00
|
|
|
instance Ord a => Cast.Cast [a] (Set.Set a) where
|
|
|
|
cast = Set.fromList
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Set.toAscList'.
|
2021-04-18 17:50:39 +03:00
|
|
|
instance Cast.Cast (Set.Set a) [a] where
|
|
|
|
cast = Set.toAscList
|
|
|
|
|
|
|
|
-- IntSet
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'IntSet.fromList'.
|
2021-04-18 17:50:39 +03:00
|
|
|
instance Cast.Cast [Int] IntSet.IntSet where
|
|
|
|
cast = IntSet.fromList
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'IntSet.toAscList'.
|
2021-04-18 17:50:39 +03:00
|
|
|
instance Cast.Cast IntSet.IntSet [Int] where
|
|
|
|
cast = IntSet.toAscList
|
|
|
|
|
|
|
|
-- Map
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Map.fromList'. If there are duplicate keys, later values will
|
|
|
|
-- overwrite earlier ones.
|
2021-04-18 17:50:39 +03:00
|
|
|
instance Ord k => Cast.Cast [(k, v)] (Map.Map k v) where
|
|
|
|
cast = Map.fromList
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Map.toAscList'.
|
2021-04-18 17:50:39 +03:00
|
|
|
instance Cast.Cast (Map.Map k v) [(k, v)] where
|
|
|
|
cast = Map.toAscList
|
|
|
|
|
|
|
|
-- IntMap
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'IntMap.fromList'. If there are duplicate keys, later values will
|
|
|
|
-- overwrite earlier ones.
|
2021-04-18 17:50:39 +03:00
|
|
|
instance Cast.Cast [(Int, v)] (IntMap.IntMap v) where
|
|
|
|
cast = IntMap.fromList
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'IntMap.toAscList'.
|
2021-04-18 17:50:39 +03:00
|
|
|
instance Cast.Cast (IntMap.IntMap v) [(Int, v)] where
|
|
|
|
cast = IntMap.toAscList
|
|
|
|
|
|
|
|
-- Seq
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Seq.fromList'.
|
2021-04-18 17:50:39 +03:00
|
|
|
instance Cast.Cast [a] (Seq.Seq a) where
|
|
|
|
cast = Seq.fromList
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Foldable.toList'.
|
2021-04-18 17:50:39 +03:00
|
|
|
instance Cast.Cast (Seq.Seq a) [a] where
|
|
|
|
cast = Foldable.toList
|
|
|
|
|
2021-04-18 18:03:05 +03:00
|
|
|
-- ByteString
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'ByteString.pack'.
|
2021-04-18 18:03:05 +03:00
|
|
|
instance Cast.Cast [Word.Word8] ByteString.ByteString where
|
|
|
|
cast = ByteString.pack
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'ByteString.unpack'.
|
2021-04-18 18:03:05 +03:00
|
|
|
instance Cast.Cast ByteString.ByteString [Word.Word8] where
|
|
|
|
cast = ByteString.unpack
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'LazyByteString.fromStrict'.
|
2021-04-18 18:03:05 +03:00
|
|
|
instance Cast.Cast ByteString.ByteString LazyByteString.ByteString where
|
|
|
|
cast = LazyByteString.fromStrict
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'ShortByteString.toShort'.
|
2021-04-18 18:03:05 +03:00
|
|
|
instance Cast.Cast ByteString.ByteString ShortByteString.ShortByteString where
|
|
|
|
cast = ShortByteString.toShort
|
|
|
|
|
2021-04-18 21:51:19 +03:00
|
|
|
-- | Uses 'Text.decodeUtf8''.
|
|
|
|
instance TryCast.TryCast ByteString.ByteString Text.Text where
|
2021-04-23 15:14:53 +03:00
|
|
|
tryCast = Utility.eitherTryCast Text.decodeUtf8'
|
2021-04-18 21:51:19 +03:00
|
|
|
|
2021-04-18 18:03:05 +03:00
|
|
|
-- LazyByteString
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'LazyByteString.pack'.
|
2021-04-18 18:03:05 +03:00
|
|
|
instance Cast.Cast [Word.Word8] LazyByteString.ByteString where
|
|
|
|
cast = LazyByteString.pack
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'LazyByteString.unpack'.
|
2021-04-18 18:03:05 +03:00
|
|
|
instance Cast.Cast LazyByteString.ByteString [Word.Word8] where
|
|
|
|
cast = LazyByteString.unpack
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'LazyByteString.toStrict'.
|
2021-04-18 18:03:05 +03:00
|
|
|
instance Cast.Cast LazyByteString.ByteString ByteString.ByteString where
|
|
|
|
cast = LazyByteString.toStrict
|
|
|
|
|
2021-04-18 21:51:19 +03:00
|
|
|
-- | Uses 'LazyText.decodeUtf8''.
|
|
|
|
instance TryCast.TryCast LazyByteString.ByteString LazyText.Text where
|
2021-04-23 15:14:53 +03:00
|
|
|
tryCast = Utility.eitherTryCast LazyText.decodeUtf8'
|
2021-04-18 21:51:19 +03:00
|
|
|
|
2021-04-18 18:03:05 +03:00
|
|
|
-- ShortByteString
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'ShortByteString.pack'.
|
2021-04-18 18:03:05 +03:00
|
|
|
instance Cast.Cast [Word.Word8] ShortByteString.ShortByteString where
|
|
|
|
cast = ShortByteString.pack
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'ShortByteString.unpack'.
|
2021-04-18 18:03:05 +03:00
|
|
|
instance Cast.Cast ShortByteString.ShortByteString [Word.Word8] where
|
|
|
|
cast = ShortByteString.unpack
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'ShortByteString.fromShort'.
|
2021-04-18 18:03:05 +03:00
|
|
|
instance Cast.Cast ShortByteString.ShortByteString ByteString.ByteString where
|
|
|
|
cast = ShortByteString.fromShort
|
|
|
|
|
2021-04-18 18:08:47 +03:00
|
|
|
-- Text
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Text.pack'. Some 'Char' values cannot be represented in 'Text.Text'
|
2021-04-18 22:44:05 +03:00
|
|
|
-- and will be replaced with @'\\xFFFD'@.
|
2021-04-18 18:08:47 +03:00
|
|
|
instance Cast.Cast String Text.Text where
|
|
|
|
cast = Text.pack
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'Text.unpack'.
|
2021-04-18 18:08:47 +03:00
|
|
|
instance Cast.Cast Text.Text String where
|
|
|
|
cast = Text.unpack
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'LazyText.fromStrict'.
|
2021-04-18 18:08:47 +03:00
|
|
|
instance Cast.Cast Text.Text LazyText.Text where
|
|
|
|
cast = LazyText.fromStrict
|
|
|
|
|
2021-04-18 21:51:19 +03:00
|
|
|
-- | Uses 'Text.encodeUtf8'.
|
|
|
|
instance Cast.Cast Text.Text ByteString.ByteString where
|
|
|
|
cast = Text.encodeUtf8
|
|
|
|
|
2021-04-18 18:08:47 +03:00
|
|
|
-- LazyText
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'LazyText.pack'. Some 'Char' values cannot be represented in
|
2021-04-18 22:44:05 +03:00
|
|
|
-- 'LazyText.Text' and will be replaced with @'\\xFFFD'@.
|
2021-04-18 18:08:47 +03:00
|
|
|
instance Cast.Cast String LazyText.Text where
|
|
|
|
cast = LazyText.pack
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'LazyText.unpack'.
|
2021-04-18 18:08:47 +03:00
|
|
|
instance Cast.Cast LazyText.Text String where
|
|
|
|
cast = LazyText.unpack
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | Uses 'LazyText.toStrict'.
|
2021-04-18 18:08:47 +03:00
|
|
|
instance Cast.Cast LazyText.Text Text.Text where
|
|
|
|
cast = LazyText.toStrict
|
|
|
|
|
2021-04-18 21:51:19 +03:00
|
|
|
-- | Uses 'LazyText.encodeUtf8'.
|
|
|
|
instance Cast.Cast LazyText.Text LazyByteString.ByteString where
|
|
|
|
cast = LazyText.encodeUtf8
|
|
|
|
|
2021-04-23 05:11:04 +03:00
|
|
|
-- TryCastException
|
|
|
|
|
2021-04-19 17:10:43 +03:00
|
|
|
instance Cast.Cast (TryCastException.TryCastException s t0) (TryCastException.TryCastException s t1)
|
|
|
|
|
2021-04-23 05:11:04 +03:00
|
|
|
instance
|
|
|
|
( Show s
|
|
|
|
, Typeable.Typeable s
|
|
|
|
, Typeable.Typeable t
|
|
|
|
) => Cast.Cast (TryCastException.TryCastException s t) String where
|
|
|
|
cast = show
|
|
|
|
|
|
|
|
instance
|
|
|
|
( Show s
|
|
|
|
, Typeable.Typeable s
|
|
|
|
, Typeable.Typeable t
|
|
|
|
) => Cast.Cast (TryCastException.TryCastException s t) Text.Text where
|
|
|
|
cast = Utility.via @String
|
|
|
|
|
|
|
|
instance
|
|
|
|
( Show s
|
|
|
|
, Typeable.Typeable s
|
|
|
|
, Typeable.Typeable t
|
|
|
|
) => Cast.Cast (TryCastException.TryCastException s t) LazyText.Text where
|
|
|
|
cast = Utility.via @String
|
|
|
|
|
2021-04-23 16:01:03 +03:00
|
|
|
fromNonNegativeIntegral
|
|
|
|
:: (Integral s, Num t) => s -> Either Exception.ArithException t
|
|
|
|
fromNonNegativeIntegral x =
|
|
|
|
if x < 0 then Left Exception.Underflow else Right $ fromIntegral x
|
2021-04-11 21:06:17 +03:00
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | The maximum integral value that can be unambiguously represented as a
|
|
|
|
-- 'Float'. Equal to 16,777,215.
|
2021-04-18 16:12:40 +03:00
|
|
|
maxFloat :: Num a => a
|
|
|
|
maxFloat = 16777215
|
|
|
|
|
2021-04-18 21:39:23 +03:00
|
|
|
-- | The maximum integral value that can be unambiguously represented as a
|
|
|
|
-- 'Double'. Equal to 9,007,199,254,740,991.
|
2021-04-18 16:12:40 +03:00
|
|
|
maxDouble :: Num a => a
|
|
|
|
maxDouble = 9007199254740991
|