witch/src/lib/Witch/Instances.hs

1266 lines
39 KiB
Haskell
Raw Normal View History

{-# OPTIONS_GHC -Wno-orphans #-}
2021-04-11 23:17:22 +03:00
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
module Witch.Instances where
import qualified Control.Exception as Exception
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
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
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
import qualified Data.Time as Time
import qualified Data.Time.Clock.POSIX as Time
import qualified Data.Time.Clock.System as Time
import qualified Data.Time.Clock.TAI as Time
import qualified Data.Word as Word
import qualified GHC.Float as Float
import qualified Numeric.Natural as Natural
2021-05-11 02:22:57 +03:00
import qualified Witch.From as From
2021-05-11 02:31:18 +03:00
import qualified Witch.TryFrom as TryFrom
import qualified Witch.TryFromException as TryFromException
2021-04-18 21:39:23 +03:00
import qualified Witch.Utility as Utility
2021-05-28 23:51:26 +03:00
-- | Uses 'id'.
instance From.From a a where
from = id
-- Int8
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Int.Int8 Int.Int16 where
from = fromIntegral
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Int.Int8 Int.Int32 where
from = fromIntegral
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Int.Int8 Int.Int64 where
from = fromIntegral
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Int.Int8 Int where
from = fromIntegral
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Int.Int8 Integer where
from = fromIntegral
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Int.Int8 Word.Word8 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Int.Int8 Word.Word16 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Int.Int8 Word.Word32 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Int.Int8 Word.Word64 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Int.Int8 Word where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-23 15:27:27 +03:00
-- | Uses 'fromIntegral' when the input is not negative.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Int.Int8 Natural.Natural where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.eitherTryFrom fromNonNegativeIntegral
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Int.Int8 Float where
from = fromIntegral
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Int.Int8 Double where
from = fromIntegral
-- Int16
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Int.Int16 Int.Int8 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Int.Int16 Int.Int32 where
from = fromIntegral
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Int.Int16 Int.Int64 where
from = fromIntegral
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Int.Int16 Int where
from = fromIntegral
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Int.Int16 Integer where
from = fromIntegral
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Int.Int16 Word.Word8 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Int.Int16 Word.Word16 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Int.Int16 Word.Word32 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Int.Int16 Word.Word64 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Int.Int16 Word where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-23 15:27:27 +03:00
-- | Uses 'fromIntegral' when the input is not negative.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Int.Int16 Natural.Natural where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.eitherTryFrom fromNonNegativeIntegral
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Int.Int16 Float where
from = fromIntegral
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Int.Int16 Double where
from = fromIntegral
-- Int32
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Int.Int32 Int.Int8 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Int.Int32 Int.Int16 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Int.Int32 Int.Int64 where
from = fromIntegral
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Int.Int32 Int where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Int.Int32 Integer where
from = fromIntegral
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Int.Int32 Word.Word8 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Int.Int32 Word.Word16 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Int.Int32 Word.Word32 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Int.Int32 Word.Word64 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Int.Int32 Word where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-23 15:27:27 +03:00
-- | Uses 'fromIntegral' when the input is not negative.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Int.Int32 Natural.Natural where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.eitherTryFrom fromNonNegativeIntegral
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral' when the input is between -16,777,215 and 16,777,215
-- inclusive.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Int.Int32 Float where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.eitherTryFrom $ \s -> if s < -maxFloat
2021-04-23 16:01:03 +03:00
then Left Exception.Underflow
else if s > maxFloat
then Left Exception.Overflow
else Right $ fromIntegral s
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Int.Int32 Double where
from = fromIntegral
-- Int64
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Int.Int64 Int.Int8 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Int.Int64 Int.Int16 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Int.Int64 Int.Int32 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Int.Int64 Int where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Int.Int64 Integer where
from = fromIntegral
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Int.Int64 Word.Word8 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Int.Int64 Word.Word16 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Int.Int64 Word.Word32 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Int.Int64 Word.Word64 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Int.Int64 Word where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-23 15:27:27 +03:00
-- | Uses 'fromIntegral' when the input is not negative.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Int.Int64 Natural.Natural where
2021-05-28 21:57:15 +03:00
-- This should use @eitherTryFrom fromNonNegativeIntegral@, but that causes
-- a bug in GHC 9.0.1.
-- https://mail.haskell.org/pipermail/haskell-cafe/2021-March/133540.html
2021-05-28 23:03:47 +03:00
tryFrom = Utility.eitherTryFrom $ \ s -> TryFrom.tryFrom (From.from s :: Integer)
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral' when the input is between -16,777,215 and 16,777,215
-- inclusive.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Int.Int64 Float where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.eitherTryFrom $ \s -> if s < -maxFloat
2021-04-23 16:01:03 +03:00
then Left Exception.Underflow
else if s > maxFloat
then Left Exception.Overflow
else Right $ fromIntegral s
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-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Int.Int64 Double where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.eitherTryFrom $ \s -> if s < -maxDouble
2021-04-23 16:01:03 +03:00
then Left Exception.Underflow
else if s > maxDouble
then Left Exception.Overflow
else Right $ fromIntegral s
-- Int
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Int Int.Int8 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Int Int.Int16 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Int Int.Int32 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Int Int.Int64 where
from = fromIntegral
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Int Integer where
from = fromIntegral
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Int Word.Word8 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Int Word.Word16 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Int Word.Word32 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Int Word.Word64 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Int Word where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-23 15:27:27 +03:00
-- | Uses 'fromIntegral' when the input is not negative.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Int Natural.Natural where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.eitherTryFrom fromNonNegativeIntegral
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral' when the input is between -16,777,215 and 16,777,215
-- inclusive.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Int Float where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.eitherTryFrom $ \s -> if s < -maxFloat
2021-04-23 16:01:03 +03:00
then Left Exception.Underflow
else if s > maxFloat
then Left Exception.Overflow
else Right $ fromIntegral s
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-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Int Double where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.eitherTryFrom $ \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
-- Integer
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Integer Int.Int8 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Integer Int.Int16 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Integer Int.Int32 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Integer Int.Int64 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Integer Int where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Integer Word.Word8 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Integer Word.Word16 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Integer Word.Word32 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Integer Word.Word64 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Integer Word where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-23 15:27:27 +03:00
-- | Uses 'fromInteger' when the input is not negative.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Integer Natural.Natural where
2021-05-11 04:04:51 +03:00
-- This should use @eitherTryFrom fromNonNegativeIntegral@, but that causes
2021-04-23 15:29:18 +03:00
-- 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-05-11 04:04:51 +03:00
tryFrom = Utility.eitherTryFrom
2021-04-23 16:01:03 +03:00
$ \s -> if s < 0 then Left Exception.Underflow else Right $ fromInteger s
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral' when the input is between -16,777,215 and 16,777,215
-- inclusive.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Integer Float where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.eitherTryFrom $ \s -> if s < -maxFloat
2021-04-23 16:01:03 +03:00
then Left Exception.Underflow
else if s > maxFloat
then Left Exception.Overflow
else Right $ fromIntegral s
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-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Integer Double where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.eitherTryFrom $ \s -> if s < -maxDouble
2021-04-23 16:01:03 +03:00
then Left Exception.Underflow
else if s > maxDouble
then Left Exception.Overflow
else Right $ fromIntegral s
-- Word8
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Word.Word8 Word.Word16 where
from = fromIntegral
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Word.Word8 Word.Word32 where
from = fromIntegral
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Word.Word8 Word.Word64 where
from = fromIntegral
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Word.Word8 Word where
from = fromIntegral
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Word.Word8 Natural.Natural where
from = fromIntegral
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Word.Word8 Int.Int8 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Word.Word8 Int.Int16 where
from = fromIntegral
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Word.Word8 Int.Int32 where
from = fromIntegral
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Word.Word8 Int.Int64 where
from = fromIntegral
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Word.Word8 Int where
from = fromIntegral
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Word.Word8 Integer where
from = fromIntegral
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Word.Word8 Float where
from = fromIntegral
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Word.Word8 Double where
from = fromIntegral
-- Word16
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Word.Word16 Word.Word8 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Word.Word16 Word.Word32 where
from = fromIntegral
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Word.Word16 Word.Word64 where
from = fromIntegral
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Word.Word16 Word where
from = fromIntegral
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Word.Word16 Natural.Natural where
from = fromIntegral
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Word.Word16 Int.Int8 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Word.Word16 Int.Int16 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Word.Word16 Int.Int32 where
from = fromIntegral
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Word.Word16 Int.Int64 where
from = fromIntegral
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Word.Word16 Int where
from = fromIntegral
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Word.Word16 Integer where
from = fromIntegral
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Word.Word16 Float where
from = fromIntegral
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Word.Word16 Double where
from = fromIntegral
-- Word32
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Word.Word32 Word.Word8 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Word.Word32 Word.Word16 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Word.Word32 Word.Word64 where
from = fromIntegral
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Word.Word32 Word where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Word.Word32 Natural.Natural where
from = fromIntegral
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Word.Word32 Int.Int8 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Word.Word32 Int.Int16 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Word.Word32 Int.Int32 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Word.Word32 Int.Int64 where
from = fromIntegral
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Word.Word32 Int where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Word.Word32 Integer where
from = fromIntegral
2021-04-23 15:27:27 +03:00
-- | Uses 'fromIntegral' when the input is less than or equal to 16,777,215.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Word.Word32 Float where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.eitherTryFrom $ \s ->
2021-04-23 16:01:03 +03:00
if s <= maxFloat then Right $ fromIntegral s else Left Exception.Overflow
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Word.Word32 Double where
from = fromIntegral
-- Word64
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Word.Word64 Word.Word8 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Word.Word64 Word.Word16 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Word.Word64 Word.Word32 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Word.Word64 Word where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Word.Word64 Natural.Natural where
2021-05-28 21:57:15 +03:00
-- This should use @fromIntegral@, but that causes a bug in GHC 9.0.1.
-- https://mail.haskell.org/pipermail/haskell-cafe/2021-March/133540.html
from s = Utility.unsafeFrom (From.from s :: Integer)
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Word.Word64 Int.Int8 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Word.Word64 Int.Int16 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Word.Word64 Int.Int32 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Word.Word64 Int.Int64 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Word.Word64 Int where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Word.Word64 Integer where
from = fromIntegral
2021-04-23 15:27:27 +03:00
-- | Uses 'fromIntegral' when the input is less than or equal to 16,777,215.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Word.Word64 Float where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.eitherTryFrom $ \s ->
2021-04-23 16:01:03 +03:00
if s <= maxFloat then Right $ fromIntegral s else Left Exception.Overflow
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-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Word.Word64 Double where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.eitherTryFrom $ \s -> if s <= maxDouble
2021-04-23 16:01:03 +03:00
then Right $ fromIntegral s
else Left Exception.Overflow
-- Word
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Word Word.Word8 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Word Word.Word16 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Word Word.Word32 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Word Word.Word64 where
from = fromIntegral
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Word Natural.Natural where
from = fromIntegral
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Word Int.Int8 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Word Int.Int16 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Word Int.Int32 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Word Int.Int64 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Word Int where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Word Integer where
from = fromIntegral
2021-04-23 15:27:27 +03:00
-- | Uses 'fromIntegral' when the input is less than or equal to 16,777,215.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Word Float where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.eitherTryFrom $ \s ->
2021-04-23 16:01:03 +03:00
if s <= maxFloat then Right $ fromIntegral s else Left Exception.Overflow
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-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Word Double where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.eitherTryFrom $ \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
-- Natural
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Natural.Natural Word.Word8 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Natural.Natural Word.Word16 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Natural.Natural Word.Word32 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Natural.Natural Word.Word64 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Natural.Natural Word where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Natural.Natural Int.Int8 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Natural.Natural Int.Int16 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Natural.Natural Int.Int32 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Natural.Natural Int.Int64 where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'Bits.toIntegralSized'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Natural.Natural Int where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom Bits.toIntegralSized
2021-04-18 21:39:23 +03:00
-- | Uses 'fromIntegral'.
2021-05-11 02:22:57 +03:00
instance From.From Natural.Natural Integer where
from = fromIntegral
2021-04-23 15:27:27 +03:00
-- | Uses 'fromIntegral' when the input is less than or equal to 16,777,215.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Natural.Natural Float where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.eitherTryFrom $ \s ->
2021-04-23 16:01:03 +03:00
if s <= maxFloat then Right $ fromIntegral s else Left Exception.Overflow
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-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Natural.Natural Double where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.eitherTryFrom $ \s -> if s <= maxDouble
2021-04-23 16:01:03 +03:00
then Right $ fromIntegral s
else Left Exception.Overflow
-- Float
2021-04-18 21:39:23 +03:00
-- | Converts via 'Integer'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Float Int.Int8 where
tryFrom = Utility.tryVia @Integer
2021-04-18 21:39:23 +03:00
-- | Converts via 'Integer'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Float Int.Int16 where
tryFrom = Utility.tryVia @Integer
2021-04-18 21:39:23 +03:00
-- | Converts via 'Integer'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Float Int.Int32 where
tryFrom = Utility.tryVia @Integer
2021-04-18 21:39:23 +03:00
-- | Converts via 'Integer'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Float Int.Int64 where
tryFrom = Utility.tryVia @Integer
2021-04-18 21:39:23 +03:00
-- | Converts via 'Integer'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Float Int where
tryFrom = Utility.tryVia @Integer
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-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Float Integer where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.eitherTryFrom $ \s -> case Utility.tryVia @Rational s of
2021-04-23 15:14:53 +03:00
Left e -> Left $ Exception.toException e
Right t
2021-04-23 15:14:53 +03:00
| t < -maxFloat -> Left $ Exception.toException Exception.Underflow
| t > maxFloat -> Left $ Exception.toException Exception.Overflow
| otherwise -> Right t
2021-04-18 21:39:23 +03:00
-- | Converts via 'Integer'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Float Word.Word8 where
tryFrom = Utility.tryVia @Integer
2021-04-18 21:39:23 +03:00
-- | Converts via 'Integer'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Float Word.Word16 where
tryFrom = Utility.tryVia @Integer
2021-04-18 21:39:23 +03:00
-- | Converts via 'Integer'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Float Word.Word32 where
tryFrom = Utility.tryVia @Integer
2021-04-18 21:39:23 +03:00
-- | Converts via 'Integer'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Float Word.Word64 where
tryFrom = Utility.tryVia @Integer
2021-04-18 21:39:23 +03:00
-- | Converts via 'Integer'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Float Word where
tryFrom = Utility.tryVia @Integer
2021-04-18 21:39:23 +03:00
-- | Converts via 'Integer'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Float Natural.Natural where
tryFrom = Utility.tryVia @Integer
2021-04-18 21:39:23 +03:00
-- | Uses 'toRational' when the input is not NaN or infinity.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Float Rational where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.eitherTryFrom $ \s -> if isNaN s
2021-04-23 16:01:03 +03:00
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-26 15:34:05 +03:00
-- | Uses 'Float.float2Double'.
2021-05-11 02:22:57 +03:00
instance From.From Float Double where
from = Float.float2Double
-- Double
2021-04-18 21:39:23 +03:00
-- | Converts via 'Integer'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Double Int.Int8 where
tryFrom = Utility.tryVia @Integer
2021-04-18 21:39:23 +03:00
-- | Converts via 'Integer'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Double Int.Int16 where
tryFrom = Utility.tryVia @Integer
2021-04-18 21:39:23 +03:00
-- | Converts via 'Integer'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Double Int.Int32 where
tryFrom = Utility.tryVia @Integer
2021-04-18 21:39:23 +03:00
-- | Converts via 'Integer'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Double Int.Int64 where
tryFrom = Utility.tryVia @Integer
2021-04-18 21:39:23 +03:00
-- | Converts via 'Integer'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Double Int where
tryFrom = Utility.tryVia @Integer
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-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Double Integer where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.eitherTryFrom $ \s -> case Utility.tryVia @Rational s of
2021-04-23 15:14:53 +03:00
Left e -> Left $ Exception.toException e
Right t
2021-04-23 15:14:53 +03:00
| t < -maxDouble -> Left $ Exception.toException Exception.Underflow
| t > maxDouble -> Left $ Exception.toException Exception.Overflow
| otherwise -> Right t
2021-04-18 21:39:23 +03:00
-- | Converts via 'Integer'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Double Word.Word8 where
tryFrom = Utility.tryVia @Integer
2021-04-18 21:39:23 +03:00
-- | Converts via 'Integer'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Double Word.Word16 where
tryFrom = Utility.tryVia @Integer
2021-04-18 21:39:23 +03:00
-- | Converts via 'Integer'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Double Word.Word32 where
tryFrom = Utility.tryVia @Integer
2021-04-18 21:39:23 +03:00
-- | Converts via 'Integer'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Double Word.Word64 where
tryFrom = Utility.tryVia @Integer
2021-04-18 21:39:23 +03:00
-- | Converts via 'Integer'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Double Word where
tryFrom = Utility.tryVia @Integer
2021-04-18 21:39:23 +03:00
-- | Converts via 'Integer'.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Double Natural.Natural where
tryFrom = Utility.tryVia @Integer
2021-04-18 21:39:23 +03:00
-- | Uses 'toRational' when the input is not NaN or infinity.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom Double Rational where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.eitherTryFrom $ \s -> if isNaN s
2021-04-23 16:01:03 +03:00
then Left Exception.LossOfPrecision
else if isInfinite s
then if s > 0 then Left Exception.Overflow else Left Exception.Underflow
else Right $ toRational s
-- | Uses 'Float.double2Float'. This necessarily loses some precision.
2021-05-11 02:22:57 +03:00
instance From.From Double Float where
from = Float.double2Float
2021-04-18 17:37:02 +03:00
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-05-11 02:22:57 +03:00
instance Integral a => From.From a (Ratio.Ratio a) where
from = (Ratio.% 1)
2021-04-11 23:17:22 +03:00
2021-04-18 21:39:23 +03:00
-- | Uses 'Ratio.numerator' when the denominator is 1.
2021-05-11 02:31:18 +03:00
instance (Eq a, Num a) => TryFrom.TryFrom (Ratio.Ratio a) a where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.eitherTryFrom $ \s -> if Ratio.denominator s == 1
2021-04-23 16:01:03 +03:00
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-05-11 02:22:57 +03:00
instance From.From Rational Float where
from = fromRational
2021-04-18 17:37:02 +03:00
2021-04-18 21:39:23 +03:00
-- | Uses 'fromRational'. This necessarily loses some precision.
2021-05-11 02:22:57 +03:00
instance From.From Rational Double where
from = fromRational
2021-04-18 17:37:02 +03:00
2021-07-10 22:29:58 +03:00
-- | Uses `fromRational` as long as there isn't a loss of precision.
instance Fixed.HasResolution a => TryFrom.TryFrom Rational (Fixed.Fixed a) where
tryFrom = Utility.eitherTryFrom $ \s ->
2021-07-10 22:36:17 +03:00
let
t :: Fixed.Fixed a
t = fromRational s
in if toRational t == s
then Right t
else Left Exception.LossOfPrecision
2021-04-11 23:23:17 +03:00
-- Fixed
2021-05-11 04:56:28 +03:00
-- | Uses 'Fixed.MkFixed'. This means @from \@Integer \@Centi 2@ is @0.02@
-- rather than @2.00@.
2021-05-11 02:22:57 +03:00
instance From.From Integer (Fixed.Fixed a) where
from = Fixed.MkFixed
2021-04-11 23:23:17 +03:00
2021-05-11 04:56:28 +03:00
-- | Uses 'Fixed.MkFixed'. This means @from \@Centi \@Integer 3.00@ is @300@
-- rather than @3@.
2021-05-11 02:22:57 +03:00
instance From.From (Fixed.Fixed a) Integer where
from (Fixed.MkFixed t) = t
2021-04-11 23:23:17 +03:00
-- | Uses 'toRational'.
instance Fixed.HasResolution a => From.From (Fixed.Fixed a) Rational where
from = toRational
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-05-11 02:22:57 +03:00
instance Num a => From.From a (Complex.Complex a) where
from = (Complex.:+ 0)
2021-04-11 23:29:15 +03:00
2021-04-18 21:39:23 +03:00
-- | Uses 'Complex.realPart' when the imaginary part is 0.
2021-05-11 02:31:18 +03:00
instance (Eq a, Num a) => TryFrom.TryFrom (Complex.Complex a) a where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.eitherTryFrom $ \s -> if Complex.imagPart s == 0
2021-04-23 16:01:03 +03:00
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-05-11 02:31:18 +03:00
instance TryFrom.TryFrom [a] (NonEmpty.NonEmpty a) where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.maybeTryFrom NonEmpty.nonEmpty
2021-04-18 17:50:39 +03:00
2021-04-18 21:39:23 +03:00
-- | Uses 'NonEmpty.toList'.
2021-05-11 02:22:57 +03:00
instance From.From (NonEmpty.NonEmpty a) [a] where
from = NonEmpty.toList
2021-04-18 17:50:39 +03:00
-- Set
2021-04-18 21:39:23 +03:00
-- | Uses 'Set.fromList'.
2021-05-11 02:22:57 +03:00
instance Ord a => From.From [a] (Set.Set a) where
from = Set.fromList
2021-04-18 17:50:39 +03:00
2021-04-18 21:39:23 +03:00
-- | Uses 'Set.toAscList'.
2021-05-11 02:22:57 +03:00
instance From.From (Set.Set a) [a] where
from = Set.toAscList
2021-04-18 17:50:39 +03:00
-- IntSet
2021-04-18 21:39:23 +03:00
-- | Uses 'IntSet.fromList'.
2021-05-11 02:22:57 +03:00
instance From.From [Int] IntSet.IntSet where
from = IntSet.fromList
2021-04-18 17:50:39 +03:00
2021-04-18 21:39:23 +03:00
-- | Uses 'IntSet.toAscList'.
2021-05-11 02:22:57 +03:00
instance From.From IntSet.IntSet [Int] where
from = IntSet.toAscList
2021-04-18 17:50:39 +03:00
-- Map
2021-04-18 21:39:23 +03:00
-- | Uses 'Map.fromList'. If there are duplicate keys, later values will
-- overwrite earlier ones.
2021-05-11 02:22:57 +03:00
instance Ord k => From.From [(k, v)] (Map.Map k v) where
from = Map.fromList
2021-04-18 17:50:39 +03:00
2021-04-18 21:39:23 +03:00
-- | Uses 'Map.toAscList'.
2021-05-11 02:22:57 +03:00
instance From.From (Map.Map k v) [(k, v)] where
from = Map.toAscList
2021-04-18 17:50:39 +03:00
-- IntMap
2021-04-18 21:39:23 +03:00
-- | Uses 'IntMap.fromList'. If there are duplicate keys, later values will
-- overwrite earlier ones.
2021-05-11 02:22:57 +03:00
instance From.From [(Int, v)] (IntMap.IntMap v) where
from = IntMap.fromList
2021-04-18 17:50:39 +03:00
2021-04-18 21:39:23 +03:00
-- | Uses 'IntMap.toAscList'.
2021-05-11 02:22:57 +03:00
instance From.From (IntMap.IntMap v) [(Int, v)] where
from = IntMap.toAscList
2021-04-18 17:50:39 +03:00
-- Seq
2021-04-18 21:39:23 +03:00
-- | Uses 'Seq.fromList'.
2021-05-11 02:22:57 +03:00
instance From.From [a] (Seq.Seq a) where
from = Seq.fromList
2021-04-18 17:50:39 +03:00
2021-04-18 21:39:23 +03:00
-- | Uses 'Foldable.toList'.
2021-05-11 02:22:57 +03:00
instance From.From (Seq.Seq a) [a] where
from = Foldable.toList
2021-04-18 17:50:39 +03:00
2021-04-18 18:03:05 +03:00
-- ByteString
2021-04-18 21:39:23 +03:00
-- | Uses 'ByteString.pack'.
2021-05-11 02:22:57 +03:00
instance From.From [Word.Word8] ByteString.ByteString where
from = ByteString.pack
2021-04-18 18:03:05 +03:00
2021-04-18 21:39:23 +03:00
-- | Uses 'ByteString.unpack'.
2021-05-11 02:22:57 +03:00
instance From.From ByteString.ByteString [Word.Word8] where
from = ByteString.unpack
2021-04-18 18:03:05 +03:00
2021-04-18 21:39:23 +03:00
-- | Uses 'LazyByteString.fromStrict'.
2021-05-11 02:22:57 +03:00
instance From.From ByteString.ByteString LazyByteString.ByteString where
from = LazyByteString.fromStrict
2021-04-18 18:03:05 +03:00
2021-04-18 21:39:23 +03:00
-- | Uses 'ShortByteString.toShort'.
2021-05-11 02:22:57 +03:00
instance From.From ByteString.ByteString ShortByteString.ShortByteString where
from = ShortByteString.toShort
2021-04-18 18:03:05 +03:00
2021-04-18 21:51:19 +03:00
-- | Uses 'Text.decodeUtf8''.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom ByteString.ByteString Text.Text where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.eitherTryFrom Text.decodeUtf8'
2021-04-18 21:51:19 +03:00
2021-05-29 15:22:29 +03:00
-- | Converts via 'Text.Text'.
instance TryFrom.TryFrom ByteString.ByteString LazyText.Text where
tryFrom = Utility.eitherTryFrom $ fmap (Utility.into @LazyText.Text) . Utility.tryInto @Text.Text
-- | Converts via 'Text.Text'.
instance TryFrom.TryFrom ByteString.ByteString String where
tryFrom = Utility.eitherTryFrom $ fmap (Utility.into @String) . Utility.tryInto @Text.Text
2021-04-18 18:03:05 +03:00
-- LazyByteString
2021-04-18 21:39:23 +03:00
-- | Uses 'LazyByteString.pack'.
2021-05-11 02:22:57 +03:00
instance From.From [Word.Word8] LazyByteString.ByteString where
from = LazyByteString.pack
2021-04-18 18:03:05 +03:00
2021-04-18 21:39:23 +03:00
-- | Uses 'LazyByteString.unpack'.
2021-05-11 02:22:57 +03:00
instance From.From LazyByteString.ByteString [Word.Word8] where
from = LazyByteString.unpack
2021-04-18 18:03:05 +03:00
2021-04-18 21:39:23 +03:00
-- | Uses 'LazyByteString.toStrict'.
2021-05-11 02:22:57 +03:00
instance From.From LazyByteString.ByteString ByteString.ByteString where
from = LazyByteString.toStrict
2021-04-18 18:03:05 +03:00
2021-04-18 21:51:19 +03:00
-- | Uses 'LazyText.decodeUtf8''.
2021-05-11 02:31:18 +03:00
instance TryFrom.TryFrom LazyByteString.ByteString LazyText.Text where
2021-05-11 04:04:51 +03:00
tryFrom = Utility.eitherTryFrom LazyText.decodeUtf8'
2021-04-18 21:51:19 +03:00
2021-05-29 15:22:29 +03:00
-- | Converts via 'LazyText.Text'.
instance TryFrom.TryFrom LazyByteString.ByteString Text.Text where
tryFrom = Utility.eitherTryFrom $ fmap (Utility.into @Text.Text) . Utility.tryInto @LazyText.Text
-- | Converts via 'LazyText.Text'.
instance TryFrom.TryFrom LazyByteString.ByteString String where
tryFrom = Utility.eitherTryFrom $ fmap (Utility.into @String) . Utility.tryInto @LazyText.Text
2021-04-18 18:03:05 +03:00
-- ShortByteString
2021-04-18 21:39:23 +03:00
-- | Uses 'ShortByteString.pack'.
2021-05-11 02:22:57 +03:00
instance From.From [Word.Word8] ShortByteString.ShortByteString where
from = ShortByteString.pack
2021-04-18 18:03:05 +03:00
2021-04-18 21:39:23 +03:00
-- | Uses 'ShortByteString.unpack'.
2021-05-11 02:22:57 +03:00
instance From.From ShortByteString.ShortByteString [Word.Word8] where
from = ShortByteString.unpack
2021-04-18 18:03:05 +03:00
2021-04-18 21:39:23 +03:00
-- | Uses 'ShortByteString.fromShort'.
2021-05-11 02:22:57 +03:00
instance From.From ShortByteString.ShortByteString ByteString.ByteString where
from = ShortByteString.fromShort
2021-04-18 18:03:05 +03:00
2021-04-18 18:08:47 +03:00
-- Text
2021-04-18 21:39:23 +03:00
-- | Uses 'LazyText.fromStrict'.
2021-05-11 02:22:57 +03:00
instance From.From Text.Text LazyText.Text where
from = LazyText.fromStrict
2021-04-18 18:08:47 +03:00
2021-04-18 21:51:19 +03:00
-- | Uses 'Text.encodeUtf8'.
2021-05-11 02:22:57 +03:00
instance From.From Text.Text ByteString.ByteString where
from = Text.encodeUtf8
2021-04-18 21:51:19 +03:00
2021-05-29 15:22:29 +03:00
-- | Converts via 'ByteString.ByteString'.
instance From.From Text.Text LazyByteString.ByteString where
from = Utility.via @ByteString.ByteString
2021-04-18 18:08:47 +03:00
-- LazyText
2021-05-29 14:49:20 +03:00
-- | Uses 'LazyText.toStrict'.
instance From.From LazyText.Text Text.Text where
from = LazyText.toStrict
-- | Uses 'LazyText.encodeUtf8'.
instance From.From LazyText.Text LazyByteString.ByteString where
from = LazyText.encodeUtf8
2021-05-29 15:22:29 +03:00
-- | Converts via 'LazyByteString.ByteString'.
instance From.From LazyText.Text ByteString.ByteString where
from = Utility.via @LazyByteString.ByteString
2021-05-29 14:49:20 +03:00
-- String
-- | Uses 'Text.pack'. Some 'Char' values cannot be represented in 'Text.Text'
-- and will be replaced with @'\\xFFFD'@.
instance From.From String Text.Text where
from = Text.pack
-- | Uses 'Text.unpack'.
instance From.From Text.Text String where
from = Text.unpack
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-05-11 02:22:57 +03:00
instance From.From String LazyText.Text where
from = LazyText.pack
2021-04-18 18:08:47 +03:00
2021-04-18 21:39:23 +03:00
-- | Uses 'LazyText.unpack'.
2021-05-11 02:22:57 +03:00
instance From.From LazyText.Text String where
from = LazyText.unpack
2021-04-18 18:08:47 +03:00
2021-05-29 15:22:29 +03:00
-- | Converts via 'Text.Text'.
instance From.From String ByteString.ByteString where
from = Utility.via @Text.Text
-- | Converts via 'LazyText.Text'.
instance From.From String LazyByteString.ByteString where
from = Utility.via @LazyText.Text
-- TryFromException
-- | Uses @coerce@.
2021-05-11 02:22:57 +03:00
instance From.From
(TryFromException.TryFromException s u)
(TryFromException.TryFromException s t)
-- Day
-- | Uses 'Time.ModifiedJulianDay'.
instance From.From Integer Time.Day where
from = Time.ModifiedJulianDay
2021-05-15 18:20:47 +03:00
-- | Uses 'Time.toModifiedJulianDay'.
instance From.From Time.Day Integer where
from = Time.toModifiedJulianDay
-- DayOfWeek
-- | Uses 'Time.dayOfWeek'.
instance From.From Time.Day Time.DayOfWeek where
from = Time.dayOfWeek
-- UniversalTime
-- | Uses 'Time.ModJulianDate'.
instance From.From Rational Time.UniversalTime where
from = Time.ModJulianDate
-- | Uses 'Time.getModJulianDate'.
instance From.From Time.UniversalTime Rational where
from = Time.getModJulianDate
-- DiffTime
-- | Uses 'realToFrac'.
instance From.From Fixed.Pico Time.DiffTime where
from = realToFrac
-- | Uses 'realToFrac'.
instance From.From Time.DiffTime Fixed.Pico where
from = realToFrac
-- NominalDiffTime
-- | Uses 'Time.secondsToNominalDiffTime'.
instance From.From Fixed.Pico Time.NominalDiffTime where
from = Time.secondsToNominalDiffTime
-- | Uses 'Time.nominalDiffTimeToSeconds'.
instance From.From Time.NominalDiffTime Fixed.Pico where
from = Time.nominalDiffTimeToSeconds
-- POSIXTime
-- | Uses 'Time.systemToPOSIXTime'.
instance From.From Time.SystemTime Time.POSIXTime where
from = Time.systemToPOSIXTime
-- | Uses 'Time.utcTimeToPOSIXSeconds'.
instance From.From Time.UTCTime Time.POSIXTime where
from = Time.utcTimeToPOSIXSeconds
-- | Uses 'Time.posixSecondsToUTCTime'.
instance From.From Time.POSIXTime Time.UTCTime where
from = Time.posixSecondsToUTCTime
-- SystemTime
-- | Uses 'Time.utcToSystemTime'.
instance From.From Time.UTCTime Time.SystemTime where
from = Time.utcToSystemTime
-- | Uses 'Time.systemToTAITime'.
instance From.From Time.SystemTime Time.AbsoluteTime where
from = Time.systemToTAITime
-- | Uses 'Time.systemToUTCTime'.
instance From.From Time.SystemTime Time.UTCTime where
from = Time.systemToUTCTime
-- TimeOfDay
-- | Uses 'Time.timeToTimeOfDay'.
instance From.From Time.DiffTime Time.TimeOfDay where
from = Time.timeToTimeOfDay
-- | Uses 'Time.dayFractionToTimeOfDay'.
instance From.From Rational Time.TimeOfDay where
from = Time.dayFractionToTimeOfDay
-- | Uses 'Time.timeOfDayToTime'.
instance From.From Time.TimeOfDay Time.DiffTime where
from = Time.timeOfDayToTime
-- | Uses 'Time.timeOfDayToDayFraction'.
instance From.From Time.TimeOfDay Rational where
from = Time.timeOfDayToDayFraction
-- CalendarDiffTime
-- | Uses 'Time.calendarTimeDays'.
instance From.From Time.CalendarDiffDays Time.CalendarDiffTime where
from = Time.calendarTimeDays
-- | Uses 'Time.calendarTimeTime'.
instance From.From Time.NominalDiffTime Time.CalendarDiffTime where
from = Time.calendarTimeTime
-- ZonedTime
-- | Uses 'Time.zonedTimeToUTC'.
instance From.From Time.ZonedTime Time.UTCTime where
from = Time.zonedTimeToUTC
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-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