{-# OPTIONS_GHC -Wno-orphans #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
module Witch.Instances where
import qualified Control.Exception as Exception
import qualified Data.Bits as Bits
import qualified Data.ByteString as ByteString
import qualified Data.ByteString.Lazy as LazyByteString
import qualified Data.ByteString.Short as ShortByteString
import qualified Data.Complex as Complex
import qualified Data.Fixed as Fixed
import qualified Data.Foldable as Foldable
import qualified Data.Int as Int
import qualified Data.IntMap as IntMap
import qualified Data.IntSet as IntSet
import qualified Data.List as List
import qualified Data.List.NonEmpty as NonEmpty
import qualified Data.Map as Map
import qualified Data.Ratio as Ratio
import qualified Data.Sequence as Seq
import qualified Data.Set as Set
import qualified Data.Text as Text
import qualified Data.Text.Encoding as Text
import qualified Data.Text.Lazy as LazyText
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
import qualified Numeric.Natural as Natural
import qualified Witch.From as From
import qualified Witch.TryFrom as TryFrom
import qualified Witch.TryFromException as TryFromException
import qualified Witch.Utility as Utility
instance From.From a a where
from :: a -> a
from = a -> a
forall a. a -> a
id
instance From.From Int.Int8 Int.Int16 where
from :: Int8 -> Int16
from = Int8 -> Int16
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance From.From Int.Int8 Int.Int32 where
from :: Int8 -> Int32
from = Int8 -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance From.From Int.Int8 Int.Int64 where
from :: Int8 -> Int64
from = Int8 -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance From.From Int.Int8 Int where
from :: Int8 -> Int
from = Int8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance From.From Int.Int8 Integer where
from :: Int8 -> Integer
from = Int8 -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance TryFrom.TryFrom Int.Int8 Word.Word8 where
tryFrom :: Int8 -> Either (TryFromException Int8 Word8) Word8
tryFrom = (Int8 -> Maybe Word8)
-> Int8 -> Either (TryFromException Int8 Word8) Word8
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Int8 -> Maybe Word8
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Int.Int8 Word.Word16 where
tryFrom :: Int8 -> Either (TryFromException Int8 Word16) Word16
tryFrom = (Int8 -> Maybe Word16)
-> Int8 -> Either (TryFromException Int8 Word16) Word16
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Int8 -> Maybe Word16
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Int.Int8 Word.Word32 where
tryFrom :: Int8 -> Either (TryFromException Int8 Word32) Word32
tryFrom = (Int8 -> Maybe Word32)
-> Int8 -> Either (TryFromException Int8 Word32) Word32
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Int8 -> Maybe Word32
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Int.Int8 Word.Word64 where
tryFrom :: Int8 -> Either (TryFromException Int8 Word64) Word64
tryFrom = (Int8 -> Maybe Word64)
-> Int8 -> Either (TryFromException Int8 Word64) Word64
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Int8 -> Maybe Word64
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Int.Int8 Word where
tryFrom :: Int8 -> Either (TryFromException Int8 Word) Word
tryFrom = (Int8 -> Maybe Word)
-> Int8 -> Either (TryFromException Int8 Word) Word
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Int8 -> Maybe Word
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Int.Int8 Natural.Natural where
tryFrom :: Int8 -> Either (TryFromException Int8 Natural) Natural
tryFrom = (Int8 -> Either ArithException Natural)
-> Int8 -> Either (TryFromException Int8 Natural) Natural
forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom Int8 -> Either ArithException Natural
forall s t. (Integral s, Num t) => s -> Either ArithException t
fromNonNegativeIntegral
instance From.From Int.Int8 Float where
from :: Int8 -> Float
from = Int8 -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance From.From Int.Int8 Double where
from :: Int8 -> Double
from = Int8 -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance TryFrom.TryFrom Int.Int16 Int.Int8 where
tryFrom :: Int16 -> Either (TryFromException Int16 Int8) Int8
tryFrom = (Int16 -> Maybe Int8)
-> Int16 -> Either (TryFromException Int16 Int8) Int8
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Int16 -> Maybe Int8
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance From.From Int.Int16 Int.Int32 where
from :: Int16 -> Int32
from = Int16 -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance From.From Int.Int16 Int.Int64 where
from :: Int16 -> Int64
from = Int16 -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance From.From Int.Int16 Int where
from :: Int16 -> Int
from = Int16 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance From.From Int.Int16 Integer where
from :: Int16 -> Integer
from = Int16 -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance TryFrom.TryFrom Int.Int16 Word.Word8 where
tryFrom :: Int16 -> Either (TryFromException Int16 Word8) Word8
tryFrom = (Int16 -> Maybe Word8)
-> Int16 -> Either (TryFromException Int16 Word8) Word8
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Int16 -> Maybe Word8
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Int.Int16 Word.Word16 where
tryFrom :: Int16 -> Either (TryFromException Int16 Word16) Word16
tryFrom = (Int16 -> Maybe Word16)
-> Int16 -> Either (TryFromException Int16 Word16) Word16
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Int16 -> Maybe Word16
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Int.Int16 Word.Word32 where
tryFrom :: Int16 -> Either (TryFromException Int16 Word32) Word32
tryFrom = (Int16 -> Maybe Word32)
-> Int16 -> Either (TryFromException Int16 Word32) Word32
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Int16 -> Maybe Word32
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Int.Int16 Word.Word64 where
tryFrom :: Int16 -> Either (TryFromException Int16 Word64) Word64
tryFrom = (Int16 -> Maybe Word64)
-> Int16 -> Either (TryFromException Int16 Word64) Word64
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Int16 -> Maybe Word64
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Int.Int16 Word where
tryFrom :: Int16 -> Either (TryFromException Int16 Word) Word
tryFrom = (Int16 -> Maybe Word)
-> Int16 -> Either (TryFromException Int16 Word) Word
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Int16 -> Maybe Word
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Int.Int16 Natural.Natural where
tryFrom :: Int16 -> Either (TryFromException Int16 Natural) Natural
tryFrom = (Int16 -> Either ArithException Natural)
-> Int16 -> Either (TryFromException Int16 Natural) Natural
forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom Int16 -> Either ArithException Natural
forall s t. (Integral s, Num t) => s -> Either ArithException t
fromNonNegativeIntegral
instance From.From Int.Int16 Float where
from :: Int16 -> Float
from = Int16 -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance From.From Int.Int16 Double where
from :: Int16 -> Double
from = Int16 -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance TryFrom.TryFrom Int.Int32 Int.Int8 where
tryFrom :: Int32 -> Either (TryFromException Int32 Int8) Int8
tryFrom = (Int32 -> Maybe Int8)
-> Int32 -> Either (TryFromException Int32 Int8) Int8
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Int32 -> Maybe Int8
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Int.Int32 Int.Int16 where
tryFrom :: Int32 -> Either (TryFromException Int32 Int16) Int16
tryFrom = (Int32 -> Maybe Int16)
-> Int32 -> Either (TryFromException Int32 Int16) Int16
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Int32 -> Maybe Int16
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance From.From Int.Int32 Int.Int64 where
from :: Int32 -> Int64
from = Int32 -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance TryFrom.TryFrom Int.Int32 Int where
tryFrom :: Int32 -> Either (TryFromException Int32 Int) Int
tryFrom = (Int32 -> Maybe Int)
-> Int32 -> Either (TryFromException Int32 Int) Int
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Int32 -> Maybe Int
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance From.From Int.Int32 Integer where
from :: Int32 -> Integer
from = Int32 -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance TryFrom.TryFrom Int.Int32 Word.Word8 where
tryFrom :: Int32 -> Either (TryFromException Int32 Word8) Word8
tryFrom = (Int32 -> Maybe Word8)
-> Int32 -> Either (TryFromException Int32 Word8) Word8
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Int32 -> Maybe Word8
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Int.Int32 Word.Word16 where
tryFrom :: Int32 -> Either (TryFromException Int32 Word16) Word16
tryFrom = (Int32 -> Maybe Word16)
-> Int32 -> Either (TryFromException Int32 Word16) Word16
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Int32 -> Maybe Word16
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Int.Int32 Word.Word32 where
tryFrom :: Int32 -> Either (TryFromException Int32 Word32) Word32
tryFrom = (Int32 -> Maybe Word32)
-> Int32 -> Either (TryFromException Int32 Word32) Word32
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Int32 -> Maybe Word32
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Int.Int32 Word.Word64 where
tryFrom :: Int32 -> Either (TryFromException Int32 Word64) Word64
tryFrom = (Int32 -> Maybe Word64)
-> Int32 -> Either (TryFromException Int32 Word64) Word64
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Int32 -> Maybe Word64
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Int.Int32 Word where
tryFrom :: Int32 -> Either (TryFromException Int32 Word) Word
tryFrom = (Int32 -> Maybe Word)
-> Int32 -> Either (TryFromException Int32 Word) Word
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Int32 -> Maybe Word
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Int.Int32 Natural.Natural where
tryFrom :: Int32 -> Either (TryFromException Int32 Natural) Natural
tryFrom = (Int32 -> Either ArithException Natural)
-> Int32 -> Either (TryFromException Int32 Natural) Natural
forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom Int32 -> Either ArithException Natural
forall s t. (Integral s, Num t) => s -> Either ArithException t
fromNonNegativeIntegral
instance TryFrom.TryFrom Int.Int32 Float where
tryFrom :: Int32 -> Either (TryFromException Int32 Float) Float
tryFrom = (Int32 -> Either ArithException Float)
-> Int32 -> Either (TryFromException Int32 Float) Float
forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom ((Int32 -> Either ArithException Float)
-> Int32 -> Either (TryFromException Int32 Float) Float)
-> (Int32 -> Either ArithException Float)
-> Int32
-> Either (TryFromException Int32 Float) Float
forall a b. (a -> b) -> a -> b
$ \Int32
s -> if Int32
s Int32 -> Int32 -> Bool
forall a. Ord a => a -> a -> Bool
< -Int32
forall a. Num a => a
maxFloat
then ArithException -> Either ArithException Float
forall a b. a -> Either a b
Left ArithException
Exception.Underflow
else if Int32
s Int32 -> Int32 -> Bool
forall a. Ord a => a -> a -> Bool
> Int32
forall a. Num a => a
maxFloat
then ArithException -> Either ArithException Float
forall a b. a -> Either a b
Left ArithException
Exception.Overflow
else Float -> Either ArithException Float
forall a b. b -> Either a b
Right (Float -> Either ArithException Float)
-> Float -> Either ArithException Float
forall a b. (a -> b) -> a -> b
$ Int32 -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int32
s
instance From.From Int.Int32 Double where
from :: Int32 -> Double
from = Int32 -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance TryFrom.TryFrom Int.Int64 Int.Int8 where
tryFrom :: Int64 -> Either (TryFromException Int64 Int8) Int8
tryFrom = (Int64 -> Maybe Int8)
-> Int64 -> Either (TryFromException Int64 Int8) Int8
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Int64 -> Maybe Int8
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Int.Int64 Int.Int16 where
tryFrom :: Int64 -> Either (TryFromException Int64 Int16) Int16
tryFrom = (Int64 -> Maybe Int16)
-> Int64 -> Either (TryFromException Int64 Int16) Int16
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Int64 -> Maybe Int16
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Int.Int64 Int.Int32 where
tryFrom :: Int64 -> Either (TryFromException Int64 Int32) Int32
tryFrom = (Int64 -> Maybe Int32)
-> Int64 -> Either (TryFromException Int64 Int32) Int32
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Int64 -> Maybe Int32
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Int.Int64 Int where
tryFrom :: Int64 -> Either (TryFromException Int64 Int) Int
tryFrom = (Int64 -> Maybe Int)
-> Int64 -> Either (TryFromException Int64 Int) Int
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Int64 -> Maybe Int
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance From.From Int.Int64 Integer where
from :: Int64 -> Integer
from = Int64 -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance TryFrom.TryFrom Int.Int64 Word.Word8 where
tryFrom :: Int64 -> Either (TryFromException Int64 Word8) Word8
tryFrom = (Int64 -> Maybe Word8)
-> Int64 -> Either (TryFromException Int64 Word8) Word8
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Int64 -> Maybe Word8
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Int.Int64 Word.Word16 where
tryFrom :: Int64 -> Either (TryFromException Int64 Word16) Word16
tryFrom = (Int64 -> Maybe Word16)
-> Int64 -> Either (TryFromException Int64 Word16) Word16
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Int64 -> Maybe Word16
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Int.Int64 Word.Word32 where
tryFrom :: Int64 -> Either (TryFromException Int64 Word32) Word32
tryFrom = (Int64 -> Maybe Word32)
-> Int64 -> Either (TryFromException Int64 Word32) Word32
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Int64 -> Maybe Word32
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Int.Int64 Word.Word64 where
tryFrom :: Int64 -> Either (TryFromException Int64 Word64) Word64
tryFrom = (Int64 -> Maybe Word64)
-> Int64 -> Either (TryFromException Int64 Word64) Word64
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Int64 -> Maybe Word64
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Int.Int64 Word where
tryFrom :: Int64 -> Either (TryFromException Int64 Word) Word
tryFrom = (Int64 -> Maybe Word)
-> Int64 -> Either (TryFromException Int64 Word) Word
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Int64 -> Maybe Word
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Int.Int64 Natural.Natural where
tryFrom :: Int64 -> Either (TryFromException Int64 Natural) Natural
tryFrom =
(Int64 -> Either (TryFromException Integer Natural) Natural)
-> Int64 -> Either (TryFromException Int64 Natural) Natural
forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom ((Int64 -> Either (TryFromException Integer Natural) Natural)
-> Int64 -> Either (TryFromException Int64 Natural) Natural)
-> (Int64 -> Either (TryFromException Integer Natural) Natural)
-> Int64
-> Either (TryFromException Int64 Natural) Natural
forall a b. (a -> b) -> a -> b
$ \Int64
s -> Integer -> Either (TryFromException Integer Natural) Natural
forall source target.
TryFrom source target =>
source -> Either (TryFromException source target) target
TryFrom.tryFrom (Int64 -> Integer
forall source target. From source target => source -> target
From.from Int64
s :: Integer)
instance TryFrom.TryFrom Int.Int64 Float where
tryFrom :: Int64 -> Either (TryFromException Int64 Float) Float
tryFrom = (Int64 -> Either ArithException Float)
-> Int64 -> Either (TryFromException Int64 Float) Float
forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom ((Int64 -> Either ArithException Float)
-> Int64 -> Either (TryFromException Int64 Float) Float)
-> (Int64 -> Either ArithException Float)
-> Int64
-> Either (TryFromException Int64 Float) Float
forall a b. (a -> b) -> a -> b
$ \Int64
s -> if Int64
s Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
< -Int64
forall a. Num a => a
maxFloat
then ArithException -> Either ArithException Float
forall a b. a -> Either a b
Left ArithException
Exception.Underflow
else if Int64
s Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
> Int64
forall a. Num a => a
maxFloat
then ArithException -> Either ArithException Float
forall a b. a -> Either a b
Left ArithException
Exception.Overflow
else Float -> Either ArithException Float
forall a b. b -> Either a b
Right (Float -> Either ArithException Float)
-> Float -> Either ArithException Float
forall a b. (a -> b) -> a -> b
$ Int64 -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
s
instance TryFrom.TryFrom Int.Int64 Double where
tryFrom :: Int64 -> Either (TryFromException Int64 Double) Double
tryFrom = (Int64 -> Either ArithException Double)
-> Int64 -> Either (TryFromException Int64 Double) Double
forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom ((Int64 -> Either ArithException Double)
-> Int64 -> Either (TryFromException Int64 Double) Double)
-> (Int64 -> Either ArithException Double)
-> Int64
-> Either (TryFromException Int64 Double) Double
forall a b. (a -> b) -> a -> b
$ \Int64
s -> if Int64
s Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
< -Int64
forall a. Num a => a
maxDouble
then ArithException -> Either ArithException Double
forall a b. a -> Either a b
Left ArithException
Exception.Underflow
else if Int64
s Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
> Int64
forall a. Num a => a
maxDouble
then ArithException -> Either ArithException Double
forall a b. a -> Either a b
Left ArithException
Exception.Overflow
else Double -> Either ArithException Double
forall a b. b -> Either a b
Right (Double -> Either ArithException Double)
-> Double -> Either ArithException Double
forall a b. (a -> b) -> a -> b
$ Int64 -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
s
instance TryFrom.TryFrom Int Int.Int8 where
tryFrom :: Int -> Either (TryFromException Int Int8) Int8
tryFrom = (Int -> Maybe Int8)
-> Int -> Either (TryFromException Int Int8) Int8
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Int -> Maybe Int8
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Int Int.Int16 where
tryFrom :: Int -> Either (TryFromException Int Int16) Int16
tryFrom = (Int -> Maybe Int16)
-> Int -> Either (TryFromException Int Int16) Int16
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Int -> Maybe Int16
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Int Int.Int32 where
tryFrom :: Int -> Either (TryFromException Int Int32) Int32
tryFrom = (Int -> Maybe Int32)
-> Int -> Either (TryFromException Int Int32) Int32
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Int -> Maybe Int32
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance From.From Int Int.Int64 where
from :: Int -> Int64
from = Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance From.From Int Integer where
from :: Int -> Integer
from = Int -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance TryFrom.TryFrom Int Word.Word8 where
tryFrom :: Int -> Either (TryFromException Int Word8) Word8
tryFrom = (Int -> Maybe Word8)
-> Int -> Either (TryFromException Int Word8) Word8
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Int -> Maybe Word8
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Int Word.Word16 where
tryFrom :: Int -> Either (TryFromException Int Word16) Word16
tryFrom = (Int -> Maybe Word16)
-> Int -> Either (TryFromException Int Word16) Word16
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Int -> Maybe Word16
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Int Word.Word32 where
tryFrom :: Int -> Either (TryFromException Int Word32) Word32
tryFrom = (Int -> Maybe Word32)
-> Int -> Either (TryFromException Int Word32) Word32
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Int -> Maybe Word32
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Int Word.Word64 where
tryFrom :: Int -> Either (TryFromException Int Word64) Word64
tryFrom = (Int -> Maybe Word64)
-> Int -> Either (TryFromException Int Word64) Word64
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Int -> Maybe Word64
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Int Word where
tryFrom :: Int -> Either (TryFromException Int Word) Word
tryFrom = (Int -> Maybe Word)
-> Int -> Either (TryFromException Int Word) Word
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Int -> Maybe Word
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Int Natural.Natural where
tryFrom :: Int -> Either (TryFromException Int Natural) Natural
tryFrom = (Int -> Either ArithException Natural)
-> Int -> Either (TryFromException Int Natural) Natural
forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom Int -> Either ArithException Natural
forall s t. (Integral s, Num t) => s -> Either ArithException t
fromNonNegativeIntegral
instance TryFrom.TryFrom Int Float where
tryFrom :: Int -> Either (TryFromException Int Float) Float
tryFrom = (Int -> Either ArithException Float)
-> Int -> Either (TryFromException Int Float) Float
forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom ((Int -> Either ArithException Float)
-> Int -> Either (TryFromException Int Float) Float)
-> (Int -> Either ArithException Float)
-> Int
-> Either (TryFromException Int Float) Float
forall a b. (a -> b) -> a -> b
$ \Int
s -> if Int
s Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< -Int
forall a. Num a => a
maxFloat
then ArithException -> Either ArithException Float
forall a b. a -> Either a b
Left ArithException
Exception.Underflow
else if Int
s Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
forall a. Num a => a
maxFloat
then ArithException -> Either ArithException Float
forall a b. a -> Either a b
Left ArithException
Exception.Overflow
else Float -> Either ArithException Float
forall a b. b -> Either a b
Right (Float -> Either ArithException Float)
-> Float -> Either ArithException Float
forall a b. (a -> b) -> a -> b
$ Int -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
s
instance TryFrom.TryFrom Int Double where
tryFrom :: Int -> Either (TryFromException Int Double) Double
tryFrom = (Int -> Either ArithException Double)
-> Int -> Either (TryFromException Int Double) Double
forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom ((Int -> Either ArithException Double)
-> Int -> Either (TryFromException Int Double) Double)
-> (Int -> Either ArithException Double)
-> Int
-> Either (TryFromException Int Double) Double
forall a b. (a -> b) -> a -> b
$ \Int
s ->
if Int -> Integer
forall a. Integral a => a -> Integer
toInteger (Int
forall a. Bounded a => a
maxBound :: Int) Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= Integer
forall a. Num a => a
maxDouble
then Double -> Either ArithException Double
forall a b. b -> Either a b
Right (Double -> Either ArithException Double)
-> Double -> Either ArithException Double
forall a b. (a -> b) -> a -> b
$ Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
s
else if Int
s Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< -Int
forall a. Num a => a
maxDouble
then ArithException -> Either ArithException Double
forall a b. a -> Either a b
Left ArithException
Exception.Underflow
else if Int
s Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
forall a. Num a => a
maxDouble
then ArithException -> Either ArithException Double
forall a b. a -> Either a b
Left ArithException
Exception.Overflow
else Double -> Either ArithException Double
forall a b. b -> Either a b
Right (Double -> Either ArithException Double)
-> Double -> Either ArithException Double
forall a b. (a -> b) -> a -> b
$ Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
s
instance TryFrom.TryFrom Integer Int.Int8 where
tryFrom :: Integer -> Either (TryFromException Integer Int8) Int8
tryFrom = (Integer -> Maybe Int8)
-> Integer -> Either (TryFromException Integer Int8) Int8
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Integer -> Maybe Int8
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Integer Int.Int16 where
tryFrom :: Integer -> Either (TryFromException Integer Int16) Int16
tryFrom = (Integer -> Maybe Int16)
-> Integer -> Either (TryFromException Integer Int16) Int16
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Integer -> Maybe Int16
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Integer Int.Int32 where
tryFrom :: Integer -> Either (TryFromException Integer Int32) Int32
tryFrom = (Integer -> Maybe Int32)
-> Integer -> Either (TryFromException Integer Int32) Int32
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Integer -> Maybe Int32
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Integer Int.Int64 where
tryFrom :: Integer -> Either (TryFromException Integer Int64) Int64
tryFrom = (Integer -> Maybe Int64)
-> Integer -> Either (TryFromException Integer Int64) Int64
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Integer -> Maybe Int64
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Integer Int where
tryFrom :: Integer -> Either (TryFromException Integer Int) Int
tryFrom = (Integer -> Maybe Int)
-> Integer -> Either (TryFromException Integer Int) Int
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Integer -> Maybe Int
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Integer Word.Word8 where
tryFrom :: Integer -> Either (TryFromException Integer Word8) Word8
tryFrom = (Integer -> Maybe Word8)
-> Integer -> Either (TryFromException Integer Word8) Word8
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Integer -> Maybe Word8
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Integer Word.Word16 where
tryFrom :: Integer -> Either (TryFromException Integer Word16) Word16
tryFrom = (Integer -> Maybe Word16)
-> Integer -> Either (TryFromException Integer Word16) Word16
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Integer -> Maybe Word16
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Integer Word.Word32 where
tryFrom :: Integer -> Either (TryFromException Integer Word32) Word32
tryFrom = (Integer -> Maybe Word32)
-> Integer -> Either (TryFromException Integer Word32) Word32
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Integer -> Maybe Word32
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Integer Word.Word64 where
tryFrom :: Integer -> Either (TryFromException Integer Word64) Word64
tryFrom = (Integer -> Maybe Word64)
-> Integer -> Either (TryFromException Integer Word64) Word64
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Integer -> Maybe Word64
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Integer Word where
tryFrom :: Integer -> Either (TryFromException Integer Word) Word
tryFrom = (Integer -> Maybe Word)
-> Integer -> Either (TryFromException Integer Word) Word
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Integer -> Maybe Word
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Integer Natural.Natural where
tryFrom :: Integer -> Either (TryFromException Integer Natural) Natural
tryFrom = (Integer -> Either ArithException Natural)
-> Integer -> Either (TryFromException Integer Natural) Natural
forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom
((Integer -> Either ArithException Natural)
-> Integer -> Either (TryFromException Integer Natural) Natural)
-> (Integer -> Either ArithException Natural)
-> Integer
-> Either (TryFromException Integer Natural) Natural
forall a b. (a -> b) -> a -> b
$ \Integer
s -> if Integer
s Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
0 then ArithException -> Either ArithException Natural
forall a b. a -> Either a b
Left ArithException
Exception.Underflow else Natural -> Either ArithException Natural
forall a b. b -> Either a b
Right (Natural -> Either ArithException Natural)
-> Natural -> Either ArithException Natural
forall a b. (a -> b) -> a -> b
$ Integer -> Natural
forall a. Num a => Integer -> a
fromInteger Integer
s
instance TryFrom.TryFrom Integer Float where
tryFrom :: Integer -> Either (TryFromException Integer Float) Float
tryFrom = (Integer -> Either ArithException Float)
-> Integer -> Either (TryFromException Integer Float) Float
forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom ((Integer -> Either ArithException Float)
-> Integer -> Either (TryFromException Integer Float) Float)
-> (Integer -> Either ArithException Float)
-> Integer
-> Either (TryFromException Integer Float) Float
forall a b. (a -> b) -> a -> b
$ \Integer
s -> if Integer
s Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< -Integer
forall a. Num a => a
maxFloat
then ArithException -> Either ArithException Float
forall a b. a -> Either a b
Left ArithException
Exception.Underflow
else if Integer
s Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
forall a. Num a => a
maxFloat
then ArithException -> Either ArithException Float
forall a b. a -> Either a b
Left ArithException
Exception.Overflow
else Float -> Either ArithException Float
forall a b. b -> Either a b
Right (Float -> Either ArithException Float)
-> Float -> Either ArithException Float
forall a b. (a -> b) -> a -> b
$ Integer -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
s
instance TryFrom.TryFrom Integer Double where
tryFrom :: Integer -> Either (TryFromException Integer Double) Double
tryFrom = (Integer -> Either ArithException Double)
-> Integer -> Either (TryFromException Integer Double) Double
forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom ((Integer -> Either ArithException Double)
-> Integer -> Either (TryFromException Integer Double) Double)
-> (Integer -> Either ArithException Double)
-> Integer
-> Either (TryFromException Integer Double) Double
forall a b. (a -> b) -> a -> b
$ \Integer
s -> if Integer
s Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< -Integer
forall a. Num a => a
maxDouble
then ArithException -> Either ArithException Double
forall a b. a -> Either a b
Left ArithException
Exception.Underflow
else if Integer
s Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
forall a. Num a => a
maxDouble
then ArithException -> Either ArithException Double
forall a b. a -> Either a b
Left ArithException
Exception.Overflow
else Double -> Either ArithException Double
forall a b. b -> Either a b
Right (Double -> Either ArithException Double)
-> Double -> Either ArithException Double
forall a b. (a -> b) -> a -> b
$ Integer -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
s
instance From.From Word.Word8 Word.Word16 where
from :: Word8 -> Word16
from = Word8 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance From.From Word.Word8 Word.Word32 where
from :: Word8 -> Word32
from = Word8 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance From.From Word.Word8 Word.Word64 where
from :: Word8 -> Word64
from = Word8 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance From.From Word.Word8 Word where
from :: Word8 -> Word
from = Word8 -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance From.From Word.Word8 Natural.Natural where
from :: Word8 -> Natural
from = Word8 -> Natural
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance TryFrom.TryFrom Word.Word8 Int.Int8 where
tryFrom :: Word8 -> Either (TryFromException Word8 Int8) Int8
tryFrom = (Word8 -> Maybe Int8)
-> Word8 -> Either (TryFromException Word8 Int8) Int8
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Word8 -> Maybe Int8
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance From.From Word.Word8 Int.Int16 where
from :: Word8 -> Int16
from = Word8 -> Int16
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance From.From Word.Word8 Int.Int32 where
from :: Word8 -> Int32
from = Word8 -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance From.From Word.Word8 Int.Int64 where
from :: Word8 -> Int64
from = Word8 -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance From.From Word.Word8 Int where
from :: Word8 -> Int
from = Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance From.From Word.Word8 Integer where
from :: Word8 -> Integer
from = Word8 -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance From.From Word.Word8 Float where
from :: Word8 -> Float
from = Word8 -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance From.From Word.Word8 Double where
from :: Word8 -> Double
from = Word8 -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance TryFrom.TryFrom Word.Word16 Word.Word8 where
tryFrom :: Word16 -> Either (TryFromException Word16 Word8) Word8
tryFrom = (Word16 -> Maybe Word8)
-> Word16 -> Either (TryFromException Word16 Word8) Word8
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Word16 -> Maybe Word8
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance From.From Word.Word16 Word.Word32 where
from :: Word16 -> Word32
from = Word16 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance From.From Word.Word16 Word.Word64 where
from :: Word16 -> Word64
from = Word16 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance From.From Word.Word16 Word where
from :: Word16 -> Word
from = Word16 -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance From.From Word.Word16 Natural.Natural where
from :: Word16 -> Natural
from = Word16 -> Natural
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance TryFrom.TryFrom Word.Word16 Int.Int8 where
tryFrom :: Word16 -> Either (TryFromException Word16 Int8) Int8
tryFrom = (Word16 -> Maybe Int8)
-> Word16 -> Either (TryFromException Word16 Int8) Int8
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Word16 -> Maybe Int8
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Word.Word16 Int.Int16 where
tryFrom :: Word16 -> Either (TryFromException Word16 Int16) Int16
tryFrom = (Word16 -> Maybe Int16)
-> Word16 -> Either (TryFromException Word16 Int16) Int16
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Word16 -> Maybe Int16
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance From.From Word.Word16 Int.Int32 where
from :: Word16 -> Int32
from = Word16 -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance From.From Word.Word16 Int.Int64 where
from :: Word16 -> Int64
from = Word16 -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance From.From Word.Word16 Int where
from :: Word16 -> Int
from = Word16 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance From.From Word.Word16 Integer where
from :: Word16 -> Integer
from = Word16 -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance From.From Word.Word16 Float where
from :: Word16 -> Float
from = Word16 -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance From.From Word.Word16 Double where
from :: Word16 -> Double
from = Word16 -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance TryFrom.TryFrom Word.Word32 Word.Word8 where
tryFrom :: Word32 -> Either (TryFromException Word32 Word8) Word8
tryFrom = (Word32 -> Maybe Word8)
-> Word32 -> Either (TryFromException Word32 Word8) Word8
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Word32 -> Maybe Word8
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Word.Word32 Word.Word16 where
tryFrom :: Word32 -> Either (TryFromException Word32 Word16) Word16
tryFrom = (Word32 -> Maybe Word16)
-> Word32 -> Either (TryFromException Word32 Word16) Word16
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Word32 -> Maybe Word16
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance From.From Word.Word32 Word.Word64 where
from :: Word32 -> Word64
from = Word32 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance TryFrom.TryFrom Word.Word32 Word where
tryFrom :: Word32 -> Either (TryFromException Word32 Word) Word
tryFrom = (Word32 -> Maybe Word)
-> Word32 -> Either (TryFromException Word32 Word) Word
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Word32 -> Maybe Word
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance From.From Word.Word32 Natural.Natural where
from :: Word32 -> Natural
from = Word32 -> Natural
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance TryFrom.TryFrom Word.Word32 Int.Int8 where
tryFrom :: Word32 -> Either (TryFromException Word32 Int8) Int8
tryFrom = (Word32 -> Maybe Int8)
-> Word32 -> Either (TryFromException Word32 Int8) Int8
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Word32 -> Maybe Int8
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Word.Word32 Int.Int16 where
tryFrom :: Word32 -> Either (TryFromException Word32 Int16) Int16
tryFrom = (Word32 -> Maybe Int16)
-> Word32 -> Either (TryFromException Word32 Int16) Int16
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Word32 -> Maybe Int16
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Word.Word32 Int.Int32 where
tryFrom :: Word32 -> Either (TryFromException Word32 Int32) Int32
tryFrom = (Word32 -> Maybe Int32)
-> Word32 -> Either (TryFromException Word32 Int32) Int32
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Word32 -> Maybe Int32
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance From.From Word.Word32 Int.Int64 where
from :: Word32 -> Int64
from = Word32 -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance TryFrom.TryFrom Word.Word32 Int where
tryFrom :: Word32 -> Either (TryFromException Word32 Int) Int
tryFrom = (Word32 -> Maybe Int)
-> Word32 -> Either (TryFromException Word32 Int) Int
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Word32 -> Maybe Int
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance From.From Word.Word32 Integer where
from :: Word32 -> Integer
from = Word32 -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance TryFrom.TryFrom Word.Word32 Float where
tryFrom :: Word32 -> Either (TryFromException Word32 Float) Float
tryFrom = (Word32 -> Either ArithException Float)
-> Word32 -> Either (TryFromException Word32 Float) Float
forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom ((Word32 -> Either ArithException Float)
-> Word32 -> Either (TryFromException Word32 Float) Float)
-> (Word32 -> Either ArithException Float)
-> Word32
-> Either (TryFromException Word32 Float) Float
forall a b. (a -> b) -> a -> b
$ \Word32
s ->
if Word32
s Word32 -> Word32 -> Bool
forall a. Ord a => a -> a -> Bool
<= Word32
forall a. Num a => a
maxFloat then Float -> Either ArithException Float
forall a b. b -> Either a b
Right (Float -> Either ArithException Float)
-> Float -> Either ArithException Float
forall a b. (a -> b) -> a -> b
$ Word32 -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
s else ArithException -> Either ArithException Float
forall a b. a -> Either a b
Left ArithException
Exception.Overflow
instance From.From Word.Word32 Double where
from :: Word32 -> Double
from = Word32 -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance TryFrom.TryFrom Word.Word64 Word.Word8 where
tryFrom :: Word64 -> Either (TryFromException Word64 Word8) Word8
tryFrom = (Word64 -> Maybe Word8)
-> Word64 -> Either (TryFromException Word64 Word8) Word8
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Word64 -> Maybe Word8
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Word.Word64 Word.Word16 where
tryFrom :: Word64 -> Either (TryFromException Word64 Word16) Word16
tryFrom = (Word64 -> Maybe Word16)
-> Word64 -> Either (TryFromException Word64 Word16) Word16
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Word64 -> Maybe Word16
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Word.Word64 Word.Word32 where
tryFrom :: Word64 -> Either (TryFromException Word64 Word32) Word32
tryFrom = (Word64 -> Maybe Word32)
-> Word64 -> Either (TryFromException Word64 Word32) Word32
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Word64 -> Maybe Word32
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Word.Word64 Word where
tryFrom :: Word64 -> Either (TryFromException Word64 Word) Word
tryFrom = (Word64 -> Maybe Word)
-> Word64 -> Either (TryFromException Word64 Word) Word
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Word64 -> Maybe Word
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance From.From Word.Word64 Natural.Natural where
from :: Word64 -> Natural
from Word64
s = Integer -> Natural
forall source target.
(HasCallStack, TryFrom source target, Show source, Typeable source,
Typeable target) =>
source -> target
Utility.unsafeFrom (Word64 -> Integer
forall source target. From source target => source -> target
From.from Word64
s :: Integer)
instance TryFrom.TryFrom Word.Word64 Int.Int8 where
tryFrom :: Word64 -> Either (TryFromException Word64 Int8) Int8
tryFrom = (Word64 -> Maybe Int8)
-> Word64 -> Either (TryFromException Word64 Int8) Int8
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Word64 -> Maybe Int8
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Word.Word64 Int.Int16 where
tryFrom :: Word64 -> Either (TryFromException Word64 Int16) Int16
tryFrom = (Word64 -> Maybe Int16)
-> Word64 -> Either (TryFromException Word64 Int16) Int16
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Word64 -> Maybe Int16
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Word.Word64 Int.Int32 where
tryFrom :: Word64 -> Either (TryFromException Word64 Int32) Int32
tryFrom = (Word64 -> Maybe Int32)
-> Word64 -> Either (TryFromException Word64 Int32) Int32
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Word64 -> Maybe Int32
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Word.Word64 Int.Int64 where
tryFrom :: Word64 -> Either (TryFromException Word64 Int64) Int64
tryFrom = (Word64 -> Maybe Int64)
-> Word64 -> Either (TryFromException Word64 Int64) Int64
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Word64 -> Maybe Int64
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Word.Word64 Int where
tryFrom :: Word64 -> Either (TryFromException Word64 Int) Int
tryFrom = (Word64 -> Maybe Int)
-> Word64 -> Either (TryFromException Word64 Int) Int
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Word64 -> Maybe Int
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance From.From Word.Word64 Integer where
from :: Word64 -> Integer
from = Word64 -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance TryFrom.TryFrom Word.Word64 Float where
tryFrom :: Word64 -> Either (TryFromException Word64 Float) Float
tryFrom = (Word64 -> Either ArithException Float)
-> Word64 -> Either (TryFromException Word64 Float) Float
forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom ((Word64 -> Either ArithException Float)
-> Word64 -> Either (TryFromException Word64 Float) Float)
-> (Word64 -> Either ArithException Float)
-> Word64
-> Either (TryFromException Word64 Float) Float
forall a b. (a -> b) -> a -> b
$ \Word64
s ->
if Word64
s Word64 -> Word64 -> Bool
forall a. Ord a => a -> a -> Bool
<= Word64
forall a. Num a => a
maxFloat then Float -> Either ArithException Float
forall a b. b -> Either a b
Right (Float -> Either ArithException Float)
-> Float -> Either ArithException Float
forall a b. (a -> b) -> a -> b
$ Word64 -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
s else ArithException -> Either ArithException Float
forall a b. a -> Either a b
Left ArithException
Exception.Overflow
instance TryFrom.TryFrom Word.Word64 Double where
tryFrom :: Word64 -> Either (TryFromException Word64 Double) Double
tryFrom = (Word64 -> Either ArithException Double)
-> Word64 -> Either (TryFromException Word64 Double) Double
forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom ((Word64 -> Either ArithException Double)
-> Word64 -> Either (TryFromException Word64 Double) Double)
-> (Word64 -> Either ArithException Double)
-> Word64
-> Either (TryFromException Word64 Double) Double
forall a b. (a -> b) -> a -> b
$ \Word64
s -> if Word64
s Word64 -> Word64 -> Bool
forall a. Ord a => a -> a -> Bool
<= Word64
forall a. Num a => a
maxDouble
then Double -> Either ArithException Double
forall a b. b -> Either a b
Right (Double -> Either ArithException Double)
-> Double -> Either ArithException Double
forall a b. (a -> b) -> a -> b
$ Word64 -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
s
else ArithException -> Either ArithException Double
forall a b. a -> Either a b
Left ArithException
Exception.Overflow
instance TryFrom.TryFrom Word Word.Word8 where
tryFrom :: Word -> Either (TryFromException Word Word8) Word8
tryFrom = (Word -> Maybe Word8)
-> Word -> Either (TryFromException Word Word8) Word8
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Word -> Maybe Word8
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Word Word.Word16 where
tryFrom :: Word -> Either (TryFromException Word Word16) Word16
tryFrom = (Word -> Maybe Word16)
-> Word -> Either (TryFromException Word Word16) Word16
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Word -> Maybe Word16
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Word Word.Word32 where
tryFrom :: Word -> Either (TryFromException Word Word32) Word32
tryFrom = (Word -> Maybe Word32)
-> Word -> Either (TryFromException Word Word32) Word32
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Word -> Maybe Word32
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance From.From Word Word.Word64 where
from :: Word -> Word64
from = Word -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance From.From Word Natural.Natural where
from :: Word -> Natural
from = Word -> Natural
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance TryFrom.TryFrom Word Int.Int8 where
tryFrom :: Word -> Either (TryFromException Word Int8) Int8
tryFrom = (Word -> Maybe Int8)
-> Word -> Either (TryFromException Word Int8) Int8
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Word -> Maybe Int8
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Word Int.Int16 where
tryFrom :: Word -> Either (TryFromException Word Int16) Int16
tryFrom = (Word -> Maybe Int16)
-> Word -> Either (TryFromException Word Int16) Int16
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Word -> Maybe Int16
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Word Int.Int32 where
tryFrom :: Word -> Either (TryFromException Word Int32) Int32
tryFrom = (Word -> Maybe Int32)
-> Word -> Either (TryFromException Word Int32) Int32
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Word -> Maybe Int32
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Word Int.Int64 where
tryFrom :: Word -> Either (TryFromException Word Int64) Int64
tryFrom = (Word -> Maybe Int64)
-> Word -> Either (TryFromException Word Int64) Int64
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Word -> Maybe Int64
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Word Int where
tryFrom :: Word -> Either (TryFromException Word Int) Int
tryFrom = (Word -> Maybe Int)
-> Word -> Either (TryFromException Word Int) Int
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Word -> Maybe Int
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance From.From Word Integer where
from :: Word -> Integer
from = Word -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance TryFrom.TryFrom Word Float where
tryFrom :: Word -> Either (TryFromException Word Float) Float
tryFrom = (Word -> Either ArithException Float)
-> Word -> Either (TryFromException Word Float) Float
forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom ((Word -> Either ArithException Float)
-> Word -> Either (TryFromException Word Float) Float)
-> (Word -> Either ArithException Float)
-> Word
-> Either (TryFromException Word Float) Float
forall a b. (a -> b) -> a -> b
$ \Word
s ->
if Word
s Word -> Word -> Bool
forall a. Ord a => a -> a -> Bool
<= Word
forall a. Num a => a
maxFloat then Float -> Either ArithException Float
forall a b. b -> Either a b
Right (Float -> Either ArithException Float)
-> Float -> Either ArithException Float
forall a b. (a -> b) -> a -> b
$ Word -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word
s else ArithException -> Either ArithException Float
forall a b. a -> Either a b
Left ArithException
Exception.Overflow
instance TryFrom.TryFrom Word Double where
tryFrom :: Word -> Either (TryFromException Word Double) Double
tryFrom = (Word -> Either ArithException Double)
-> Word -> Either (TryFromException Word Double) Double
forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom ((Word -> Either ArithException Double)
-> Word -> Either (TryFromException Word Double) Double)
-> (Word -> Either ArithException Double)
-> Word
-> Either (TryFromException Word Double) Double
forall a b. (a -> b) -> a -> b
$ \Word
s ->
if (Word -> Integer
forall a. Integral a => a -> Integer
toInteger (Word
forall a. Bounded a => a
maxBound :: Word) Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= Integer
forall a. Num a => a
maxDouble) Bool -> Bool -> Bool
|| (Word
s Word -> Word -> Bool
forall a. Ord a => a -> a -> Bool
<= Word
forall a. Num a => a
maxDouble)
then Double -> Either ArithException Double
forall a b. b -> Either a b
Right (Double -> Either ArithException Double)
-> Double -> Either ArithException Double
forall a b. (a -> b) -> a -> b
$ Word -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word
s
else ArithException -> Either ArithException Double
forall a b. a -> Either a b
Left ArithException
Exception.Overflow
instance TryFrom.TryFrom Natural.Natural Word.Word8 where
tryFrom :: Natural -> Either (TryFromException Natural Word8) Word8
tryFrom = (Natural -> Maybe Word8)
-> Natural -> Either (TryFromException Natural Word8) Word8
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Natural -> Maybe Word8
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Natural.Natural Word.Word16 where
tryFrom :: Natural -> Either (TryFromException Natural Word16) Word16
tryFrom = (Natural -> Maybe Word16)
-> Natural -> Either (TryFromException Natural Word16) Word16
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Natural -> Maybe Word16
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Natural.Natural Word.Word32 where
tryFrom :: Natural -> Either (TryFromException Natural Word32) Word32
tryFrom = (Natural -> Maybe Word32)
-> Natural -> Either (TryFromException Natural Word32) Word32
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Natural -> Maybe Word32
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Natural.Natural Word.Word64 where
tryFrom :: Natural -> Either (TryFromException Natural Word64) Word64
tryFrom = (Natural -> Maybe Word64)
-> Natural -> Either (TryFromException Natural Word64) Word64
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Natural -> Maybe Word64
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Natural.Natural Word where
tryFrom :: Natural -> Either (TryFromException Natural Word) Word
tryFrom = (Natural -> Maybe Word)
-> Natural -> Either (TryFromException Natural Word) Word
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Natural -> Maybe Word
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Natural.Natural Int.Int8 where
tryFrom :: Natural -> Either (TryFromException Natural Int8) Int8
tryFrom = (Natural -> Maybe Int8)
-> Natural -> Either (TryFromException Natural Int8) Int8
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Natural -> Maybe Int8
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Natural.Natural Int.Int16 where
tryFrom :: Natural -> Either (TryFromException Natural Int16) Int16
tryFrom = (Natural -> Maybe Int16)
-> Natural -> Either (TryFromException Natural Int16) Int16
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Natural -> Maybe Int16
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Natural.Natural Int.Int32 where
tryFrom :: Natural -> Either (TryFromException Natural Int32) Int32
tryFrom = (Natural -> Maybe Int32)
-> Natural -> Either (TryFromException Natural Int32) Int32
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Natural -> Maybe Int32
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Natural.Natural Int.Int64 where
tryFrom :: Natural -> Either (TryFromException Natural Int64) Int64
tryFrom = (Natural -> Maybe Int64)
-> Natural -> Either (TryFromException Natural Int64) Int64
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Natural -> Maybe Int64
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance TryFrom.TryFrom Natural.Natural Int where
tryFrom :: Natural -> Either (TryFromException Natural Int) Int
tryFrom = (Natural -> Maybe Int)
-> Natural -> Either (TryFromException Natural Int) Int
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom Natural -> Maybe Int
forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized
instance From.From Natural.Natural Integer where
from :: Natural -> Integer
from = Natural -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance TryFrom.TryFrom Natural.Natural Float where
tryFrom :: Natural -> Either (TryFromException Natural Float) Float
tryFrom = (Natural -> Either ArithException Float)
-> Natural -> Either (TryFromException Natural Float) Float
forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom ((Natural -> Either ArithException Float)
-> Natural -> Either (TryFromException Natural Float) Float)
-> (Natural -> Either ArithException Float)
-> Natural
-> Either (TryFromException Natural Float) Float
forall a b. (a -> b) -> a -> b
$ \Natural
s ->
if Natural
s Natural -> Natural -> Bool
forall a. Ord a => a -> a -> Bool
<= Natural
forall a. Num a => a
maxFloat then Float -> Either ArithException Float
forall a b. b -> Either a b
Right (Float -> Either ArithException Float)
-> Float -> Either ArithException Float
forall a b. (a -> b) -> a -> b
$ Natural -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral Natural
s else ArithException -> Either ArithException Float
forall a b. a -> Either a b
Left ArithException
Exception.Overflow
instance TryFrom.TryFrom Natural.Natural Double where
tryFrom :: Natural -> Either (TryFromException Natural Double) Double
tryFrom = (Natural -> Either ArithException Double)
-> Natural -> Either (TryFromException Natural Double) Double
forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom ((Natural -> Either ArithException Double)
-> Natural -> Either (TryFromException Natural Double) Double)
-> (Natural -> Either ArithException Double)
-> Natural
-> Either (TryFromException Natural Double) Double
forall a b. (a -> b) -> a -> b
$ \Natural
s -> if Natural
s Natural -> Natural -> Bool
forall a. Ord a => a -> a -> Bool
<= Natural
forall a. Num a => a
maxDouble
then Double -> Either ArithException Double
forall a b. b -> Either a b
Right (Double -> Either ArithException Double)
-> Double -> Either ArithException Double
forall a b. (a -> b) -> a -> b
$ Natural -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Natural
s
else ArithException -> Either ArithException Double
forall a b. a -> Either a b
Left ArithException
Exception.Overflow
instance TryFrom.TryFrom Float Int.Int8 where
tryFrom :: Float -> Either (TryFromException Float Int8) Int8
tryFrom = forall source target.
(TryFrom source Integer, TryFrom Integer target) =>
source -> Either (TryFromException source target) target
forall through source target.
(TryFrom source through, TryFrom through target) =>
source -> Either (TryFromException source target) target
Utility.tryVia @Integer
instance TryFrom.TryFrom Float Int.Int16 where
tryFrom :: Float -> Either (TryFromException Float Int16) Int16
tryFrom = forall source target.
(TryFrom source Integer, TryFrom Integer target) =>
source -> Either (TryFromException source target) target
forall through source target.
(TryFrom source through, TryFrom through target) =>
source -> Either (TryFromException source target) target
Utility.tryVia @Integer
instance TryFrom.TryFrom Float Int.Int32 where
tryFrom :: Float -> Either (TryFromException Float Int32) Int32
tryFrom = forall source target.
(TryFrom source Integer, TryFrom Integer target) =>
source -> Either (TryFromException source target) target
forall through source target.
(TryFrom source through, TryFrom through target) =>
source -> Either (TryFromException source target) target
Utility.tryVia @Integer
instance TryFrom.TryFrom Float Int.Int64 where
tryFrom :: Float -> Either (TryFromException Float Int64) Int64
tryFrom = forall source target.
(TryFrom source Integer, TryFrom Integer target) =>
source -> Either (TryFromException source target) target
forall through source target.
(TryFrom source through, TryFrom through target) =>
source -> Either (TryFromException source target) target
Utility.tryVia @Integer
instance TryFrom.TryFrom Float Int where
tryFrom :: Float -> Either (TryFromException Float Int) Int
tryFrom = forall source target.
(TryFrom source Integer, TryFrom Integer target) =>
source -> Either (TryFromException source target) target
forall through source target.
(TryFrom source through, TryFrom through target) =>
source -> Either (TryFromException source target) target
Utility.tryVia @Integer
instance TryFrom.TryFrom Float Integer where
tryFrom :: Float -> Either (TryFromException Float Integer) Integer
tryFrom = (Float -> Either SomeException Integer)
-> Float -> Either (TryFromException Float Integer) Integer
forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom ((Float -> Either SomeException Integer)
-> Float -> Either (TryFromException Float Integer) Integer)
-> (Float -> Either SomeException Integer)
-> Float
-> Either (TryFromException Float Integer) Integer
forall a b. (a -> b) -> a -> b
$ \Float
s -> case Float -> Either (TryFromException Float Integer) Integer
forall through source target.
(TryFrom source through, TryFrom through target) =>
source -> Either (TryFromException source target) target
Utility.tryVia @Rational Float
s of
Left TryFromException Float Integer
e -> SomeException -> Either SomeException Integer
forall a b. a -> Either a b
Left (SomeException -> Either SomeException Integer)
-> SomeException -> Either SomeException Integer
forall a b. (a -> b) -> a -> b
$ TryFromException Float Integer -> SomeException
forall e. Exception e => e -> SomeException
Exception.toException TryFromException Float Integer
e
Right Integer
t
| Integer
t Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< -Integer
forall a. Num a => a
maxFloat -> SomeException -> Either SomeException Integer
forall a b. a -> Either a b
Left (SomeException -> Either SomeException Integer)
-> SomeException -> Either SomeException Integer
forall a b. (a -> b) -> a -> b
$ ArithException -> SomeException
forall e. Exception e => e -> SomeException
Exception.toException ArithException
Exception.Underflow
| Integer
t Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
forall a. Num a => a
maxFloat -> SomeException -> Either SomeException Integer
forall a b. a -> Either a b
Left (SomeException -> Either SomeException Integer)
-> SomeException -> Either SomeException Integer
forall a b. (a -> b) -> a -> b
$ ArithException -> SomeException
forall e. Exception e => e -> SomeException
Exception.toException ArithException
Exception.Overflow
| Bool
otherwise -> Integer -> Either SomeException Integer
forall a b. b -> Either a b
Right Integer
t
instance TryFrom.TryFrom Float Word.Word8 where
tryFrom :: Float -> Either (TryFromException Float Word8) Word8
tryFrom = forall source target.
(TryFrom source Integer, TryFrom Integer target) =>
source -> Either (TryFromException source target) target
forall through source target.
(TryFrom source through, TryFrom through target) =>
source -> Either (TryFromException source target) target
Utility.tryVia @Integer
instance TryFrom.TryFrom Float Word.Word16 where
tryFrom :: Float -> Either (TryFromException Float Word16) Word16
tryFrom = forall source target.
(TryFrom source Integer, TryFrom Integer target) =>
source -> Either (TryFromException source target) target
forall through source target.
(TryFrom source through, TryFrom through target) =>
source -> Either (TryFromException source target) target
Utility.tryVia @Integer
instance TryFrom.TryFrom Float Word.Word32 where
tryFrom :: Float -> Either (TryFromException Float Word32) Word32
tryFrom = forall source target.
(TryFrom source Integer, TryFrom Integer target) =>
source -> Either (TryFromException source target) target
forall through source target.
(TryFrom source through, TryFrom through target) =>
source -> Either (TryFromException source target) target
Utility.tryVia @Integer
instance TryFrom.TryFrom Float Word.Word64 where
tryFrom :: Float -> Either (TryFromException Float Word64) Word64
tryFrom = forall source target.
(TryFrom source Integer, TryFrom Integer target) =>
source -> Either (TryFromException source target) target
forall through source target.
(TryFrom source through, TryFrom through target) =>
source -> Either (TryFromException source target) target
Utility.tryVia @Integer
instance TryFrom.TryFrom Float Word where
tryFrom :: Float -> Either (TryFromException Float Word) Word
tryFrom = forall source target.
(TryFrom source Integer, TryFrom Integer target) =>
source -> Either (TryFromException source target) target
forall through source target.
(TryFrom source through, TryFrom through target) =>
source -> Either (TryFromException source target) target
Utility.tryVia @Integer
instance TryFrom.TryFrom Float Natural.Natural where
tryFrom :: Float -> Either (TryFromException Float Natural) Natural
tryFrom = forall source target.
(TryFrom source Integer, TryFrom Integer target) =>
source -> Either (TryFromException source target) target
forall through source target.
(TryFrom source through, TryFrom through target) =>
source -> Either (TryFromException source target) target
Utility.tryVia @Integer
instance TryFrom.TryFrom Float Rational where
tryFrom :: Float -> Either (TryFromException Float Rational) Rational
tryFrom = (Float -> Either ArithException Rational)
-> Float -> Either (TryFromException Float Rational) Rational
forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom Float -> Either ArithException Rational
forall s. RealFloat s => s -> Either ArithException Rational
realFloatToRational
instance From.From Float Double where
from :: Float -> Double
from = Float -> Double
Float.float2Double
instance TryFrom.TryFrom Double Int.Int8 where
tryFrom :: Double -> Either (TryFromException Double Int8) Int8
tryFrom = forall source target.
(TryFrom source Integer, TryFrom Integer target) =>
source -> Either (TryFromException source target) target
forall through source target.
(TryFrom source through, TryFrom through target) =>
source -> Either (TryFromException source target) target
Utility.tryVia @Integer
instance TryFrom.TryFrom Double Int.Int16 where
tryFrom :: Double -> Either (TryFromException Double Int16) Int16
tryFrom = forall source target.
(TryFrom source Integer, TryFrom Integer target) =>
source -> Either (TryFromException source target) target
forall through source target.
(TryFrom source through, TryFrom through target) =>
source -> Either (TryFromException source target) target
Utility.tryVia @Integer
instance TryFrom.TryFrom Double Int.Int32 where
tryFrom :: Double -> Either (TryFromException Double Int32) Int32
tryFrom = forall source target.
(TryFrom source Integer, TryFrom Integer target) =>
source -> Either (TryFromException source target) target
forall through source target.
(TryFrom source through, TryFrom through target) =>
source -> Either (TryFromException source target) target
Utility.tryVia @Integer
instance TryFrom.TryFrom Double Int.Int64 where
tryFrom :: Double -> Either (TryFromException Double Int64) Int64
tryFrom = forall source target.
(TryFrom source Integer, TryFrom Integer target) =>
source -> Either (TryFromException source target) target
forall through source target.
(TryFrom source through, TryFrom through target) =>
source -> Either (TryFromException source target) target
Utility.tryVia @Integer
instance TryFrom.TryFrom Double Int where
tryFrom :: Double -> Either (TryFromException Double Int) Int
tryFrom = forall source target.
(TryFrom source Integer, TryFrom Integer target) =>
source -> Either (TryFromException source target) target
forall through source target.
(TryFrom source through, TryFrom through target) =>
source -> Either (TryFromException source target) target
Utility.tryVia @Integer
instance TryFrom.TryFrom Double Integer where
tryFrom :: Double -> Either (TryFromException Double Integer) Integer
tryFrom = (Double -> Either SomeException Integer)
-> Double -> Either (TryFromException Double Integer) Integer
forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom ((Double -> Either SomeException Integer)
-> Double -> Either (TryFromException Double Integer) Integer)
-> (Double -> Either SomeException Integer)
-> Double
-> Either (TryFromException Double Integer) Integer
forall a b. (a -> b) -> a -> b
$ \Double
s -> case Double -> Either (TryFromException Double Integer) Integer
forall through source target.
(TryFrom source through, TryFrom through target) =>
source -> Either (TryFromException source target) target
Utility.tryVia @Rational Double
s of
Left TryFromException Double Integer
e -> SomeException -> Either SomeException Integer
forall a b. a -> Either a b
Left (SomeException -> Either SomeException Integer)
-> SomeException -> Either SomeException Integer
forall a b. (a -> b) -> a -> b
$ TryFromException Double Integer -> SomeException
forall e. Exception e => e -> SomeException
Exception.toException TryFromException Double Integer
e
Right Integer
t
| Integer
t Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< -Integer
forall a. Num a => a
maxDouble -> SomeException -> Either SomeException Integer
forall a b. a -> Either a b
Left (SomeException -> Either SomeException Integer)
-> SomeException -> Either SomeException Integer
forall a b. (a -> b) -> a -> b
$ ArithException -> SomeException
forall e. Exception e => e -> SomeException
Exception.toException ArithException
Exception.Underflow
| Integer
t Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
forall a. Num a => a
maxDouble -> SomeException -> Either SomeException Integer
forall a b. a -> Either a b
Left (SomeException -> Either SomeException Integer)
-> SomeException -> Either SomeException Integer
forall a b. (a -> b) -> a -> b
$ ArithException -> SomeException
forall e. Exception e => e -> SomeException
Exception.toException ArithException
Exception.Overflow
| Bool
otherwise -> Integer -> Either SomeException Integer
forall a b. b -> Either a b
Right Integer
t
instance TryFrom.TryFrom Double Word.Word8 where
tryFrom :: Double -> Either (TryFromException Double Word8) Word8
tryFrom = forall source target.
(TryFrom source Integer, TryFrom Integer target) =>
source -> Either (TryFromException source target) target
forall through source target.
(TryFrom source through, TryFrom through target) =>
source -> Either (TryFromException source target) target
Utility.tryVia @Integer
instance TryFrom.TryFrom Double Word.Word16 where
tryFrom :: Double -> Either (TryFromException Double Word16) Word16
tryFrom = forall source target.
(TryFrom source Integer, TryFrom Integer target) =>
source -> Either (TryFromException source target) target
forall through source target.
(TryFrom source through, TryFrom through target) =>
source -> Either (TryFromException source target) target
Utility.tryVia @Integer
instance TryFrom.TryFrom Double Word.Word32 where
tryFrom :: Double -> Either (TryFromException Double Word32) Word32
tryFrom = forall source target.
(TryFrom source Integer, TryFrom Integer target) =>
source -> Either (TryFromException source target) target
forall through source target.
(TryFrom source through, TryFrom through target) =>
source -> Either (TryFromException source target) target
Utility.tryVia @Integer
instance TryFrom.TryFrom Double Word.Word64 where
tryFrom :: Double -> Either (TryFromException Double Word64) Word64
tryFrom = forall source target.
(TryFrom source Integer, TryFrom Integer target) =>
source -> Either (TryFromException source target) target
forall through source target.
(TryFrom source through, TryFrom through target) =>
source -> Either (TryFromException source target) target
Utility.tryVia @Integer
instance TryFrom.TryFrom Double Word where
tryFrom :: Double -> Either (TryFromException Double Word) Word
tryFrom = forall source target.
(TryFrom source Integer, TryFrom Integer target) =>
source -> Either (TryFromException source target) target
forall through source target.
(TryFrom source through, TryFrom through target) =>
source -> Either (TryFromException source target) target
Utility.tryVia @Integer
instance TryFrom.TryFrom Double Natural.Natural where
tryFrom :: Double -> Either (TryFromException Double Natural) Natural
tryFrom = forall source target.
(TryFrom source Integer, TryFrom Integer target) =>
source -> Either (TryFromException source target) target
forall through source target.
(TryFrom source through, TryFrom through target) =>
source -> Either (TryFromException source target) target
Utility.tryVia @Integer
instance TryFrom.TryFrom Double Rational where
tryFrom :: Double -> Either (TryFromException Double Rational) Rational
tryFrom = (Double -> Either ArithException Rational)
-> Double -> Either (TryFromException Double Rational) Rational
forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom Double -> Either ArithException Rational
forall s. RealFloat s => s -> Either ArithException Rational
realFloatToRational
instance From.From Double Float where
from :: Double -> Float
from = Double -> Float
Float.double2Float
instance Integral a => From.From a (Ratio.Ratio a) where
from :: a -> Ratio a
from = (a -> a -> Ratio a
forall a. Integral a => a -> a -> Ratio a
Ratio.% a
1)
instance (Eq a, Num a) => TryFrom.TryFrom (Ratio.Ratio a) a where
tryFrom :: Ratio a -> Either (TryFromException (Ratio a) a) a
tryFrom = (Ratio a -> Either ArithException a)
-> Ratio a -> Either (TryFromException (Ratio a) a) a
forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom ((Ratio a -> Either ArithException a)
-> Ratio a -> Either (TryFromException (Ratio a) a) a)
-> (Ratio a -> Either ArithException a)
-> Ratio a
-> Either (TryFromException (Ratio a) a) a
forall a b. (a -> b) -> a -> b
$ \Ratio a
s -> if Ratio a -> a
forall a. Ratio a -> a
Ratio.denominator Ratio a
s a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
1
then a -> Either ArithException a
forall a b. b -> Either a b
Right (a -> Either ArithException a) -> a -> Either ArithException a
forall a b. (a -> b) -> a -> b
$ Ratio a -> a
forall a. Ratio a -> a
Ratio.numerator Ratio a
s
else ArithException -> Either ArithException a
forall a b. a -> Either a b
Left ArithException
Exception.LossOfPrecision
instance From.From Rational Float where
from :: Rational -> Float
from = Rational -> Float
forall a. Fractional a => Rational -> a
fromRational
instance From.From Rational Double where
from :: Rational -> Double
from = Rational -> Double
forall a. Fractional a => Rational -> a
fromRational
instance Fixed.HasResolution a => TryFrom.TryFrom Rational (Fixed.Fixed a) where
tryFrom :: Rational -> Either (TryFromException Rational (Fixed a)) (Fixed a)
tryFrom = (Rational -> Either ArithException (Fixed a))
-> Rational
-> Either (TryFromException Rational (Fixed a)) (Fixed a)
forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom ((Rational -> Either ArithException (Fixed a))
-> Rational
-> Either (TryFromException Rational (Fixed a)) (Fixed a))
-> (Rational -> Either ArithException (Fixed a))
-> Rational
-> Either (TryFromException Rational (Fixed a)) (Fixed a)
forall a b. (a -> b) -> a -> b
$ \Rational
s ->
let
t :: Fixed.Fixed a
t :: Fixed a
t = Rational -> Fixed a
forall a. Fractional a => Rational -> a
fromRational Rational
s
in if Fixed a -> Rational
forall a. Real a => a -> Rational
toRational Fixed a
t Rational -> Rational -> Bool
forall a. Eq a => a -> a -> Bool
== Rational
s then Fixed a -> Either ArithException (Fixed a)
forall a b. b -> Either a b
Right Fixed a
t else ArithException -> Either ArithException (Fixed a)
forall a b. a -> Either a b
Left ArithException
Exception.LossOfPrecision
instance From.From Integer (Fixed.Fixed a) where
from :: Integer -> Fixed a
from = Integer -> Fixed a
forall k (a :: k). Integer -> Fixed a
Fixed.MkFixed
instance From.From (Fixed.Fixed a) Integer where
from :: Fixed a -> Integer
from (Fixed.MkFixed Integer
t) = Integer
t
instance Fixed.HasResolution a => From.From (Fixed.Fixed a) Rational where
from :: Fixed a -> Rational
from = Fixed a -> Rational
forall a. Real a => a -> Rational
toRational
instance Num a => From.From a (Complex.Complex a) where
from :: a -> Complex a
from = (a -> a -> Complex a
forall a. a -> a -> Complex a
Complex.:+ a
0)
instance (Eq a, Num a) => TryFrom.TryFrom (Complex.Complex a) a where
tryFrom :: Complex a -> Either (TryFromException (Complex a) a) a
tryFrom = (Complex a -> Either ArithException a)
-> Complex a -> Either (TryFromException (Complex a) a) a
forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom ((Complex a -> Either ArithException a)
-> Complex a -> Either (TryFromException (Complex a) a) a)
-> (Complex a -> Either ArithException a)
-> Complex a
-> Either (TryFromException (Complex a) a) a
forall a b. (a -> b) -> a -> b
$ \Complex a
s -> if Complex a -> a
forall a. Complex a -> a
Complex.imagPart Complex a
s a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
0
then a -> Either ArithException a
forall a b. b -> Either a b
Right (a -> Either ArithException a) -> a -> Either ArithException a
forall a b. (a -> b) -> a -> b
$ Complex a -> a
forall a. Complex a -> a
Complex.realPart Complex a
s
else ArithException -> Either ArithException a
forall a b. a -> Either a b
Left ArithException
Exception.LossOfPrecision
instance TryFrom.TryFrom [a] (NonEmpty.NonEmpty a) where
tryFrom :: [a] -> Either (TryFromException [a] (NonEmpty a)) (NonEmpty a)
tryFrom = ([a] -> Maybe (NonEmpty a))
-> [a] -> Either (TryFromException [a] (NonEmpty a)) (NonEmpty a)
forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom [a] -> Maybe (NonEmpty a)
forall a. [a] -> Maybe (NonEmpty a)
NonEmpty.nonEmpty
instance From.From (NonEmpty.NonEmpty a) [a] where
from :: NonEmpty a -> [a]
from = NonEmpty a -> [a]
forall a. NonEmpty a -> [a]
NonEmpty.toList
instance Ord a => From.From [a] (Set.Set a) where
from :: [a] -> Set a
from = [a] -> Set a
forall a. Ord a => [a] -> Set a
Set.fromList
instance From.From (Set.Set a) [a] where
from :: Set a -> [a]
from = Set a -> [a]
forall a. Set a -> [a]
Set.toAscList
instance From.From [Int] IntSet.IntSet where
from :: [Int] -> IntSet
from = [Int] -> IntSet
IntSet.fromList
instance From.From IntSet.IntSet [Int] where
from :: IntSet -> [Int]
from = IntSet -> [Int]
IntSet.toAscList
instance Ord k => From.From [(k, v)] (Map.Map k v) where
from :: [(k, v)] -> Map k v
from = [(k, v)] -> Map k v
forall k v. Ord k => [(k, v)] -> Map k v
Map.fromList
instance From.From (Map.Map k v) [(k, v)] where
from :: Map k v -> [(k, v)]
from = Map k v -> [(k, v)]
forall k v. Map k v -> [(k, v)]
Map.toAscList
instance From.From [(Int, v)] (IntMap.IntMap v) where
from :: [(Int, v)] -> IntMap v
from = [(Int, v)] -> IntMap v
forall v. [(Int, v)] -> IntMap v
IntMap.fromList
instance From.From (IntMap.IntMap v) [(Int, v)] where
from :: IntMap v -> [(Int, v)]
from = IntMap v -> [(Int, v)]
forall v. IntMap v -> [(Int, v)]
IntMap.toAscList
instance From.From [a] (Seq.Seq a) where
from :: [a] -> Seq a
from = [a] -> Seq a
forall a. [a] -> Seq a
Seq.fromList
instance From.From (Seq.Seq a) [a] where
from :: Seq a -> [a]
from = Seq a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
Foldable.toList
instance From.From [Word.Word8] ByteString.ByteString where
from :: [Word8] -> ByteString
from = [Word8] -> ByteString
ByteString.pack
instance From.From ByteString.ByteString [Word.Word8] where
from :: ByteString -> [Word8]
from = ByteString -> [Word8]
ByteString.unpack
instance From.From ByteString.ByteString LazyByteString.ByteString where
from :: ByteString -> ByteString
from = ByteString -> ByteString
LazyByteString.fromStrict
instance From.From ByteString.ByteString ShortByteString.ShortByteString where
from :: ByteString -> ShortByteString
from = ByteString -> ShortByteString
ShortByteString.toShort
instance TryFrom.TryFrom ByteString.ByteString Text.Text where
tryFrom :: ByteString -> Either (TryFromException ByteString Text) Text
tryFrom = (ByteString -> Either UnicodeException Text)
-> ByteString -> Either (TryFromException ByteString Text) Text
forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom ByteString -> Either UnicodeException Text
Text.decodeUtf8'
instance TryFrom.TryFrom ByteString.ByteString LazyText.Text where
tryFrom :: ByteString -> Either (TryFromException ByteString Text) Text
tryFrom =
(ByteString -> Either (TryFromException ByteString Text) Text)
-> ByteString -> Either (TryFromException ByteString Text) Text
forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom
((ByteString -> Either (TryFromException ByteString Text) Text)
-> ByteString -> Either (TryFromException ByteString Text) Text)
-> (ByteString -> Either (TryFromException ByteString Text) Text)
-> ByteString
-> Either (TryFromException ByteString Text) Text
forall a b. (a -> b) -> a -> b
$ (Text -> Text)
-> Either (TryFromException ByteString Text) Text
-> Either (TryFromException ByteString Text) Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall source. From source Text => source -> Text
forall target source. From source target => source -> target
Utility.into @LazyText.Text)
(Either (TryFromException ByteString Text) Text
-> Either (TryFromException ByteString Text) Text)
-> (ByteString -> Either (TryFromException ByteString Text) Text)
-> ByteString
-> Either (TryFromException ByteString Text) Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall source.
TryFrom source Text =>
source -> Either (TryFromException source Text) Text
forall target source.
TryFrom source target =>
source -> Either (TryFromException source target) target
Utility.tryInto @Text.Text
instance TryFrom.TryFrom ByteString.ByteString String where
tryFrom :: ByteString -> Either (TryFromException ByteString String) String
tryFrom =
(ByteString -> Either (TryFromException ByteString Text) String)
-> ByteString -> Either (TryFromException ByteString String) String
forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom
((ByteString -> Either (TryFromException ByteString Text) String)
-> ByteString
-> Either (TryFromException ByteString String) String)
-> (ByteString -> Either (TryFromException ByteString Text) String)
-> ByteString
-> Either (TryFromException ByteString String) String
forall a b. (a -> b) -> a -> b
$ (Text -> String)
-> Either (TryFromException ByteString Text) Text
-> Either (TryFromException ByteString Text) String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall source. From source String => source -> String
forall target source. From source target => source -> target
Utility.into @String)
(Either (TryFromException ByteString Text) Text
-> Either (TryFromException ByteString Text) String)
-> (ByteString -> Either (TryFromException ByteString Text) Text)
-> ByteString
-> Either (TryFromException ByteString Text) String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall source.
TryFrom source Text =>
source -> Either (TryFromException source Text) Text
forall target source.
TryFrom source target =>
source -> Either (TryFromException source target) target
Utility.tryInto @Text.Text
instance From.From [Word.Word8] LazyByteString.ByteString where
from :: [Word8] -> ByteString
from = [Word8] -> ByteString
LazyByteString.pack
instance From.From LazyByteString.ByteString [Word.Word8] where
from :: ByteString -> [Word8]
from = ByteString -> [Word8]
LazyByteString.unpack
instance From.From LazyByteString.ByteString ByteString.ByteString where
from :: ByteString -> ByteString
from = ByteString -> ByteString
LazyByteString.toStrict
instance TryFrom.TryFrom LazyByteString.ByteString LazyText.Text where
tryFrom :: ByteString -> Either (TryFromException ByteString Text) Text
tryFrom = (ByteString -> Either UnicodeException Text)
-> ByteString -> Either (TryFromException ByteString Text) Text
forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom ByteString -> Either UnicodeException Text
LazyText.decodeUtf8'
instance TryFrom.TryFrom LazyByteString.ByteString Text.Text where
tryFrom :: ByteString -> Either (TryFromException ByteString Text) Text
tryFrom =
(ByteString -> Either (TryFromException ByteString Text) Text)
-> ByteString -> Either (TryFromException ByteString Text) Text
forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom
((ByteString -> Either (TryFromException ByteString Text) Text)
-> ByteString -> Either (TryFromException ByteString Text) Text)
-> (ByteString -> Either (TryFromException ByteString Text) Text)
-> ByteString
-> Either (TryFromException ByteString Text) Text
forall a b. (a -> b) -> a -> b
$ (Text -> Text)
-> Either (TryFromException ByteString Text) Text
-> Either (TryFromException ByteString Text) Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall source. From source Text => source -> Text
forall target source. From source target => source -> target
Utility.into @Text.Text)
(Either (TryFromException ByteString Text) Text
-> Either (TryFromException ByteString Text) Text)
-> (ByteString -> Either (TryFromException ByteString Text) Text)
-> ByteString
-> Either (TryFromException ByteString Text) Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall source.
TryFrom source Text =>
source -> Either (TryFromException source Text) Text
forall target source.
TryFrom source target =>
source -> Either (TryFromException source target) target
Utility.tryInto @LazyText.Text
instance TryFrom.TryFrom LazyByteString.ByteString String where
tryFrom :: ByteString -> Either (TryFromException ByteString String) String
tryFrom =
(ByteString -> Either (TryFromException ByteString Text) String)
-> ByteString -> Either (TryFromException ByteString String) String
forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom
((ByteString -> Either (TryFromException ByteString Text) String)
-> ByteString
-> Either (TryFromException ByteString String) String)
-> (ByteString -> Either (TryFromException ByteString Text) String)
-> ByteString
-> Either (TryFromException ByteString String) String
forall a b. (a -> b) -> a -> b
$ (Text -> String)
-> Either (TryFromException ByteString Text) Text
-> Either (TryFromException ByteString Text) String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall source. From source String => source -> String
forall target source. From source target => source -> target
Utility.into @String)
(Either (TryFromException ByteString Text) Text
-> Either (TryFromException ByteString Text) String)
-> (ByteString -> Either (TryFromException ByteString Text) Text)
-> ByteString
-> Either (TryFromException ByteString Text) String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall source.
TryFrom source Text =>
source -> Either (TryFromException source Text) Text
forall target source.
TryFrom source target =>
source -> Either (TryFromException source target) target
Utility.tryInto @LazyText.Text
instance From.From [Word.Word8] ShortByteString.ShortByteString where
from :: [Word8] -> ShortByteString
from = [Word8] -> ShortByteString
ShortByteString.pack
instance From.From ShortByteString.ShortByteString [Word.Word8] where
from :: ShortByteString -> [Word8]
from = ShortByteString -> [Word8]
ShortByteString.unpack
instance From.From ShortByteString.ShortByteString ByteString.ByteString where
from :: ShortByteString -> ByteString
from = ShortByteString -> ByteString
ShortByteString.fromShort
instance From.From Text.Text LazyText.Text where
from :: Text -> Text
from = Text -> Text
LazyText.fromStrict
instance From.From Text.Text ByteString.ByteString where
from :: Text -> ByteString
from = Text -> ByteString
Text.encodeUtf8
instance From.From Text.Text LazyByteString.ByteString where
from :: Text -> ByteString
from = forall source target.
(From source ByteString, From ByteString target) =>
source -> target
forall through source target.
(From source through, From through target) =>
source -> target
Utility.via @ByteString.ByteString
instance From.From LazyText.Text Text.Text where
from :: Text -> Text
from = Text -> Text
LazyText.toStrict
instance From.From LazyText.Text LazyByteString.ByteString where
from :: Text -> ByteString
from = Text -> ByteString
LazyText.encodeUtf8
instance From.From LazyText.Text ByteString.ByteString where
from :: Text -> ByteString
from = forall source target.
(From source ByteString, From ByteString target) =>
source -> target
forall through source target.
(From source through, From through target) =>
source -> target
Utility.via @LazyByteString.ByteString
instance From.From String Text.Text where
from :: String -> Text
from = String -> Text
Text.pack
instance From.From Text.Text String where
from :: Text -> String
from = Text -> String
Text.unpack
instance From.From String LazyText.Text where
from :: String -> Text
from = String -> Text
LazyText.pack
instance From.From LazyText.Text String where
from :: Text -> String
from = Text -> String
LazyText.unpack
instance From.From String ByteString.ByteString where
from :: String -> ByteString
from = forall source target.
(From source Text, From Text target) =>
source -> target
forall through source target.
(From source through, From through target) =>
source -> target
Utility.via @Text.Text
instance From.From String LazyByteString.ByteString where
from :: String -> ByteString
from = forall source target.
(From source Text, From Text target) =>
source -> target
forall through source target.
(From source through, From through target) =>
source -> target
Utility.via @LazyText.Text
instance From.From
(TryFromException.TryFromException source oldTarget)
(TryFromException.TryFromException source newTarget)
instance From.From Integer Time.Day where
from :: Integer -> Day
from = Integer -> Day
Time.ModifiedJulianDay
instance From.From Time.Day Integer where
from :: Day -> Integer
from = Day -> Integer
Time.toModifiedJulianDay
instance From.From Time.Day Time.DayOfWeek where
from :: Day -> DayOfWeek
from = Day -> DayOfWeek
Time.dayOfWeek
instance From.From Rational Time.UniversalTime where
from :: Rational -> UniversalTime
from = Rational -> UniversalTime
Time.ModJulianDate
instance From.From Time.UniversalTime Rational where
from :: UniversalTime -> Rational
from = UniversalTime -> Rational
Time.getModJulianDate
instance From.From Fixed.Pico Time.DiffTime where
from :: Pico -> DiffTime
from = Pico -> DiffTime
forall a b. (Real a, Fractional b) => a -> b
realToFrac
instance From.From Time.DiffTime Fixed.Pico where
from :: DiffTime -> Pico
from = DiffTime -> Pico
forall a b. (Real a, Fractional b) => a -> b
realToFrac
instance From.From Fixed.Pico Time.NominalDiffTime where
from :: Pico -> NominalDiffTime
from = Pico -> NominalDiffTime
Time.secondsToNominalDiffTime
instance From.From Time.NominalDiffTime Fixed.Pico where
from :: NominalDiffTime -> Pico
from = NominalDiffTime -> Pico
Time.nominalDiffTimeToSeconds
instance From.From Time.SystemTime Time.POSIXTime where
from :: SystemTime -> NominalDiffTime
from = SystemTime -> NominalDiffTime
Time.systemToPOSIXTime
instance From.From Time.UTCTime Time.POSIXTime where
from :: UTCTime -> NominalDiffTime
from = UTCTime -> NominalDiffTime
Time.utcTimeToPOSIXSeconds
instance From.From Time.POSIXTime Time.UTCTime where
from :: NominalDiffTime -> UTCTime
from = NominalDiffTime -> UTCTime
Time.posixSecondsToUTCTime
instance From.From Time.UTCTime Time.SystemTime where
from :: UTCTime -> SystemTime
from = UTCTime -> SystemTime
Time.utcToSystemTime
instance From.From Time.SystemTime Time.AbsoluteTime where
from :: SystemTime -> AbsoluteTime
from = SystemTime -> AbsoluteTime
Time.systemToTAITime
instance From.From Time.SystemTime Time.UTCTime where
from :: SystemTime -> UTCTime
from = SystemTime -> UTCTime
Time.systemToUTCTime
instance From.From Time.DiffTime Time.TimeOfDay where
from :: DiffTime -> TimeOfDay
from = DiffTime -> TimeOfDay
Time.timeToTimeOfDay
instance From.From Rational Time.TimeOfDay where
from :: Rational -> TimeOfDay
from = Rational -> TimeOfDay
Time.dayFractionToTimeOfDay
instance From.From Time.TimeOfDay Time.DiffTime where
from :: TimeOfDay -> DiffTime
from = TimeOfDay -> DiffTime
Time.timeOfDayToTime
instance From.From Time.TimeOfDay Rational where
from :: TimeOfDay -> Rational
from = TimeOfDay -> Rational
Time.timeOfDayToDayFraction
instance From.From Time.CalendarDiffDays Time.CalendarDiffTime where
from :: CalendarDiffDays -> CalendarDiffTime
from = CalendarDiffDays -> CalendarDiffTime
Time.calendarTimeDays
instance From.From Time.NominalDiffTime Time.CalendarDiffTime where
from :: NominalDiffTime -> CalendarDiffTime
from = NominalDiffTime -> CalendarDiffTime
Time.calendarTimeTime
instance From.From Time.ZonedTime Time.UTCTime where
from :: ZonedTime -> UTCTime
from = ZonedTime -> UTCTime
Time.zonedTimeToUTC
realFloatToRational
:: RealFloat s => s -> Either Exception.ArithException Rational
realFloatToRational :: s -> Either ArithException Rational
realFloatToRational s
s
| s -> Bool
forall a. RealFloat a => a -> Bool
isNaN s
s = ArithException -> Either ArithException Rational
forall a b. a -> Either a b
Left ArithException
Exception.LossOfPrecision
| s -> Bool
forall a. RealFloat a => a -> Bool
isInfinite s
s = if s
s s -> s -> Bool
forall a. Ord a => a -> a -> Bool
> s
0
then ArithException -> Either ArithException Rational
forall a b. a -> Either a b
Left ArithException
Exception.Overflow
else ArithException -> Either ArithException Rational
forall a b. a -> Either a b
Left ArithException
Exception.Underflow
| Bool
otherwise = Rational -> Either ArithException Rational
forall a b. b -> Either a b
Right (Rational -> Either ArithException Rational)
-> Rational -> Either ArithException Rational
forall a b. (a -> b) -> a -> b
$ (s -> Rational) -> s -> Rational
forall a b. (Eq a, Num a, Num b) => (a -> b) -> a -> b
overPositive
((Integer -> Integer -> Rational) -> (Integer, Integer) -> Rational
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Integer -> Integer -> Rational
makeRational ((Integer, Integer) -> Rational)
-> (s -> (Integer, Integer)) -> s -> Rational
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Int] -> Int -> (Integer, Integer))
-> ([Int], Int) -> (Integer, Integer)
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry [Int] -> Int -> (Integer, Integer)
fromDigits (([Int], Int) -> (Integer, Integer))
-> (s -> ([Int], Int)) -> s -> (Integer, Integer)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> s -> ([Int], Int)
forall a. RealFloat a => Integer -> a -> ([Int], Int)
Numeric.floatToDigits Integer
10)
s
s
overPositive :: (Eq a, Num a, Num b) => (a -> b) -> a -> b
overPositive :: (a -> b) -> a -> b
overPositive a -> b
f a
x = if a -> a
forall a. Num a => a -> a
signum a
x a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== -a
1 then -(a -> b
f (-a
x)) else a -> b
f a
x
fromDigits :: [Int] -> Int -> (Integer, Integer)
fromDigits :: [Int] -> Int -> (Integer, Integer)
fromDigits [Int]
ds Int
e =
((Integer, Integer) -> Int -> (Integer, Integer))
-> (Integer, Integer) -> [Int] -> (Integer, Integer)
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
List.foldl' (\(Integer
a, Integer
n) Int
d -> (Integer
a Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* Integer
10 Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Int -> Integer
forall a. Integral a => a -> Integer
toInteger Int
d, Integer
n Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Integer
1)) (Integer
0, Int -> Integer
forall a. Integral a => a -> Integer
toInteger Int
e) [Int]
ds
makeRational :: Integer -> Integer -> Rational
makeRational :: Integer -> Integer -> Rational
makeRational Integer
d Integer
e = Integer -> Rational
forall a. Real a => a -> Rational
toRational Integer
d Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
* Rational
10 Rational -> Integer -> Rational
forall a b. (Fractional a, Integral b) => a -> b -> a
^^ Integer
e
fromNonNegativeIntegral
:: (Integral s, Num t) => s -> Either Exception.ArithException t
fromNonNegativeIntegral :: s -> Either ArithException t
fromNonNegativeIntegral s
x =
if s
x s -> s -> Bool
forall a. Ord a => a -> a -> Bool
< s
0 then ArithException -> Either ArithException t
forall a b. a -> Either a b
Left ArithException
Exception.Underflow else t -> Either ArithException t
forall a b. b -> Either a b
Right (t -> Either ArithException t) -> t -> Either ArithException t
forall a b. (a -> b) -> a -> b
$ s -> t
forall a b. (Integral a, Num b) => a -> b
fromIntegral s
x
maxFloat :: Num a => a
maxFloat :: a
maxFloat = a
16777215
maxDouble :: Num a => a
maxDouble :: a
maxDouble = a
9007199254740991