{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# OPTIONS_GHC -Wno-orphans #-}

module Witch.Instances where

import qualified Control.Exception as Exception
import qualified Control.Monad as Monad
import qualified Data.Bits as Bits
import qualified Data.ByteString as ByteString
import qualified Data.ByteString.Char8 as Char8
import qualified Data.ByteString.Lazy as LazyByteString
import qualified Data.ByteString.Lazy.Char8 as LazyChar8
import qualified Data.ByteString.Short as ShortByteString
import qualified Data.Char as Char
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.Tagged as Tagged
import qualified Data.Text as Text
import qualified Data.Text.Encoding as Text
import qualified Data.Text.Encoding.Error 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 System.IO.Unsafe as Unsafe
import qualified Witch.Encoding as Encoding
import qualified Witch.From as From
import qualified Witch.TryFrom as TryFrom
import qualified Witch.TryFromException as TryFromException
import qualified Witch.Utility as Utility

-- | Uses 'id'.
instance From.From a a where
  from :: a -> a
from = forall a. a -> a
id

-- Int8

-- | Uses 'fromIntegral'.
instance From.From Int.Int8 Int.Int16 where
  from :: Int8 -> Int16
from = forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Uses 'fromIntegral'.
instance From.From Int.Int8 Int.Int32 where
  from :: Int8 -> Int32
from = forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Uses 'fromIntegral'.
instance From.From Int.Int8 Int.Int64 where
  from :: Int8 -> Int64
from = forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Uses 'fromIntegral'.
instance From.From Int.Int8 Int where
  from :: Int8 -> Int
from = forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Uses 'fromIntegral'.
instance From.From Int.Int8 Integer where
  from :: Int8 -> Integer
from = forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Int.Int8 Word.Word8 where
  tryFrom :: Int8 -> Either (TryFromException Int8 Word8) Word8
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Int.Int8 Word.Word16 where
  tryFrom :: Int8 -> Either (TryFromException Int8 Word16) Word16
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Int.Int8 Word.Word32 where
  tryFrom :: Int8 -> Either (TryFromException Int8 Word32) Word32
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Int.Int8 Word.Word64 where
  tryFrom :: Int8 -> Either (TryFromException Int8 Word64) Word64
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Int.Int8 Word where
  tryFrom :: Int8 -> Either (TryFromException Int8 Word) Word
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'fromIntegral' when the input is not negative.
instance TryFrom.TryFrom Int.Int8 Natural.Natural where
  tryFrom :: Int8 -> Either (TryFromException Int8 Natural) Natural
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall s t. (Integral s, Num t) => s -> Either ArithException t
fromNonNegativeIntegral

-- | Uses 'fromIntegral'.
instance From.From Int.Int8 Float where
  from :: Int8 -> Float
from = forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Uses 'fromIntegral'.
instance From.From Int.Int8 Double where
  from :: Int8 -> Double
from = forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- Int16

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Int.Int16 Int.Int8 where
  tryFrom :: Int16 -> Either (TryFromException Int16 Int8) Int8
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'fromIntegral'.
instance From.From Int.Int16 Int.Int32 where
  from :: Int16 -> Int32
from = forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Uses 'fromIntegral'.
instance From.From Int.Int16 Int.Int64 where
  from :: Int16 -> Int64
from = forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Uses 'fromIntegral'.
instance From.From Int.Int16 Int where
  from :: Int16 -> Int
from = forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Uses 'fromIntegral'.
instance From.From Int.Int16 Integer where
  from :: Int16 -> Integer
from = forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Int.Int16 Word.Word8 where
  tryFrom :: Int16 -> Either (TryFromException Int16 Word8) Word8
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Int.Int16 Word.Word16 where
  tryFrom :: Int16 -> Either (TryFromException Int16 Word16) Word16
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Int.Int16 Word.Word32 where
  tryFrom :: Int16 -> Either (TryFromException Int16 Word32) Word32
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Int.Int16 Word.Word64 where
  tryFrom :: Int16 -> Either (TryFromException Int16 Word64) Word64
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Int.Int16 Word where
  tryFrom :: Int16 -> Either (TryFromException Int16 Word) Word
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'fromIntegral' when the input is not negative.
instance TryFrom.TryFrom Int.Int16 Natural.Natural where
  tryFrom :: Int16 -> Either (TryFromException Int16 Natural) Natural
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall s t. (Integral s, Num t) => s -> Either ArithException t
fromNonNegativeIntegral

-- | Uses 'fromIntegral'.
instance From.From Int.Int16 Float where
  from :: Int16 -> Float
from = forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Uses 'fromIntegral'.
instance From.From Int.Int16 Double where
  from :: Int16 -> Double
from = forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- Int32

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Int.Int32 Int.Int8 where
  tryFrom :: Int32 -> Either (TryFromException Int32 Int8) Int8
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Int.Int32 Int.Int16 where
  tryFrom :: Int32 -> Either (TryFromException Int32 Int16) Int16
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'fromIntegral'.
instance From.From Int.Int32 Int.Int64 where
  from :: Int32 -> Int64
from = forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Int.Int32 Int where
  tryFrom :: Int32 -> Either (TryFromException Int32 Int) Int
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'fromIntegral'.
instance From.From Int.Int32 Integer where
  from :: Int32 -> Integer
from = forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Int.Int32 Word.Word8 where
  tryFrom :: Int32 -> Either (TryFromException Int32 Word8) Word8
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Int.Int32 Word.Word16 where
  tryFrom :: Int32 -> Either (TryFromException Int32 Word16) Word16
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Int.Int32 Word.Word32 where
  tryFrom :: Int32 -> Either (TryFromException Int32 Word32) Word32
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Int.Int32 Word.Word64 where
  tryFrom :: Int32 -> Either (TryFromException Int32 Word64) Word64
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Int.Int32 Word where
  tryFrom :: Int32 -> Either (TryFromException Int32 Word) Word
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'fromIntegral' when the input is not negative.
instance TryFrom.TryFrom Int.Int32 Natural.Natural where
  tryFrom :: Int32 -> Either (TryFromException Int32 Natural) Natural
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall s t. (Integral s, Num t) => s -> Either ArithException t
fromNonNegativeIntegral

-- | Uses 'fromIntegral' when the input is between -16,777,215 and 16,777,215
-- inclusive.
instance TryFrom.TryFrom Int.Int32 Float where
  tryFrom :: Int32 -> Either (TryFromException Int32 Float) Float
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ \Int32
s ->
    if Int32
s forall a. Ord a => a -> a -> Bool
< -forall a. Num a => a
maxFloat
      then forall a b. a -> Either a b
Left ArithException
Exception.Underflow
      else
        if Int32
s forall a. Ord a => a -> a -> Bool
> forall a. Num a => a
maxFloat
          then forall a b. a -> Either a b
Left ArithException
Exception.Overflow
          else forall a b. b -> Either a b
Right forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral Int32
s

-- | Uses 'fromIntegral'.
instance From.From Int.Int32 Double where
  from :: Int32 -> Double
from = forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- Int64

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Int.Int64 Int.Int8 where
  tryFrom :: Int64 -> Either (TryFromException Int64 Int8) Int8
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Int.Int64 Int.Int16 where
  tryFrom :: Int64 -> Either (TryFromException Int64 Int16) Int16
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Int.Int64 Int.Int32 where
  tryFrom :: Int64 -> Either (TryFromException Int64 Int32) Int32
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Int.Int64 Int where
  tryFrom :: Int64 -> Either (TryFromException Int64 Int) Int
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'fromIntegral'.
instance From.From Int.Int64 Integer where
  from :: Int64 -> Integer
from = forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Int.Int64 Word.Word8 where
  tryFrom :: Int64 -> Either (TryFromException Int64 Word8) Word8
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Int.Int64 Word.Word16 where
  tryFrom :: Int64 -> Either (TryFromException Int64 Word16) Word16
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Int.Int64 Word.Word32 where
  tryFrom :: Int64 -> Either (TryFromException Int64 Word32) Word32
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Int.Int64 Word.Word64 where
  tryFrom :: Int64 -> Either (TryFromException Int64 Word64) Word64
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Int.Int64 Word where
  tryFrom :: Int64 -> Either (TryFromException Int64 Word) Word
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'fromIntegral' when the input is not negative.
instance TryFrom.TryFrom Int.Int64 Natural.Natural where
  -- This should use @eitherTryFrom fromNonNegativeIntegral@, but that causes
  -- a bug in GHC 9.0.1.
  -- https://mail.haskell.org/pipermail/haskell-cafe/2021-March/133540.html
  tryFrom :: Int64 -> Either (TryFromException Int64 Natural) Natural
tryFrom =
    forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ \Int64
s -> forall source target.
TryFrom source target =>
source -> Either (TryFromException source target) target
TryFrom.tryFrom (forall source target. From source target => source -> target
From.from Int64
s :: Integer)

-- | Uses 'fromIntegral' when the input is between -16,777,215 and 16,777,215
-- inclusive.
instance TryFrom.TryFrom Int.Int64 Float where
  tryFrom :: Int64 -> Either (TryFromException Int64 Float) Float
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ \Int64
s ->
    if Int64
s forall a. Ord a => a -> a -> Bool
< -forall a. Num a => a
maxFloat
      then forall a b. a -> Either a b
Left ArithException
Exception.Underflow
      else
        if Int64
s forall a. Ord a => a -> a -> Bool
> forall a. Num a => a
maxFloat
          then forall a b. a -> Either a b
Left ArithException
Exception.Overflow
          else forall a b. b -> Either a b
Right forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
s

-- | Uses 'fromIntegral' when the input is between -9,007,199,254,740,991 and
-- 9,007,199,254,740,991 inclusive.
instance TryFrom.TryFrom Int.Int64 Double where
  tryFrom :: Int64 -> Either (TryFromException Int64 Double) Double
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ \Int64
s ->
    if Int64
s forall a. Ord a => a -> a -> Bool
< -forall a. Num a => a
maxDouble
      then forall a b. a -> Either a b
Left ArithException
Exception.Underflow
      else
        if Int64
s forall a. Ord a => a -> a -> Bool
> forall a. Num a => a
maxDouble
          then forall a b. a -> Either a b
Left ArithException
Exception.Overflow
          else forall a b. b -> Either a b
Right forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
s

-- Int

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Int Int.Int8 where
  tryFrom :: Int -> Either (TryFromException Int Int8) Int8
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Int Int.Int16 where
  tryFrom :: Int -> Either (TryFromException Int Int16) Int16
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Int Int.Int32 where
  tryFrom :: Int -> Either (TryFromException Int Int32) Int32
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'fromIntegral'.
instance From.From Int Int.Int64 where
  from :: Int -> Int64
from = forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Uses 'fromIntegral'.
instance From.From Int Integer where
  from :: Int -> Integer
from = forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Int Word.Word8 where
  tryFrom :: Int -> Either (TryFromException Int Word8) Word8
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Int Word.Word16 where
  tryFrom :: Int -> Either (TryFromException Int Word16) Word16
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Int Word.Word32 where
  tryFrom :: Int -> Either (TryFromException Int Word32) Word32
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Int Word.Word64 where
  tryFrom :: Int -> Either (TryFromException Int Word64) Word64
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Int Word where
  tryFrom :: Int -> Either (TryFromException Int Word) Word
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'fromIntegral' when the input is not negative.
instance TryFrom.TryFrom Int Natural.Natural where
  tryFrom :: Int -> Either (TryFromException Int Natural) Natural
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall s t. (Integral s, Num t) => s -> Either ArithException t
fromNonNegativeIntegral

-- | Uses 'fromIntegral' when the input is between -16,777,215 and 16,777,215
-- inclusive.
instance TryFrom.TryFrom Int Float where
  tryFrom :: Int -> Either (TryFromException Int Float) Float
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ \Int
s ->
    if Int
s forall a. Ord a => a -> a -> Bool
< -forall a. Num a => a
maxFloat
      then forall a b. a -> Either a b
Left ArithException
Exception.Underflow
      else
        if Int
s forall a. Ord a => a -> a -> Bool
> forall a. Num a => a
maxFloat
          then forall a b. a -> Either a b
Left ArithException
Exception.Overflow
          else forall a b. b -> Either a b
Right forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
s

-- | Uses 'fromIntegral' when the input is between -9,007,199,254,740,991 and
-- 9,007,199,254,740,991 inclusive.
instance TryFrom.TryFrom Int Double where
  tryFrom :: Int -> Either (TryFromException Int Double) Double
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ \Int
s ->
    if forall a. Integral a => a -> Integer
toInteger (forall a. Bounded a => a
maxBound :: Int) forall a. Ord a => a -> a -> Bool
<= forall a. Num a => a
maxDouble
      then forall a b. b -> Either a b
Right forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
s
      else
        if Int
s forall a. Ord a => a -> a -> Bool
< -forall a. Num a => a
maxDouble
          then forall a b. a -> Either a b
Left ArithException
Exception.Underflow
          else
            if Int
s forall a. Ord a => a -> a -> Bool
> forall a. Num a => a
maxDouble
              then forall a b. a -> Either a b
Left ArithException
Exception.Overflow
              else forall a b. b -> Either a b
Right forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
s

-- Integer

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Integer Int.Int8 where
  tryFrom :: Integer -> Either (TryFromException Integer Int8) Int8
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Integer Int.Int16 where
  tryFrom :: Integer -> Either (TryFromException Integer Int16) Int16
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Integer Int.Int32 where
  tryFrom :: Integer -> Either (TryFromException Integer Int32) Int32
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Integer Int.Int64 where
  tryFrom :: Integer -> Either (TryFromException Integer Int64) Int64
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Integer Int where
  tryFrom :: Integer -> Either (TryFromException Integer Int) Int
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Integer Word.Word8 where
  tryFrom :: Integer -> Either (TryFromException Integer Word8) Word8
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Integer Word.Word16 where
  tryFrom :: Integer -> Either (TryFromException Integer Word16) Word16
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Integer Word.Word32 where
  tryFrom :: Integer -> Either (TryFromException Integer Word32) Word32
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Integer Word.Word64 where
  tryFrom :: Integer -> Either (TryFromException Integer Word64) Word64
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Integer Word where
  tryFrom :: Integer -> Either (TryFromException Integer Word) Word
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'fromInteger' when the input is not negative.
instance TryFrom.TryFrom Integer Natural.Natural where
  -- This should use @eitherTryFrom fromNonNegativeIntegral@, but that causes
  -- a bug in GHC 9.0.1. By inlining @fromNonNegativeIntegral@ and replacing
  -- @fromIntegral@ with @fromInteger@, we can work around the bug.
  -- https://mail.haskell.org/pipermail/haskell-cafe/2021-March/133540.html
  tryFrom :: Integer -> Either (TryFromException Integer Natural) Natural
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$
    \Integer
s -> if Integer
s forall a. Ord a => a -> a -> Bool
< Integer
0 then forall a b. a -> Either a b
Left ArithException
Exception.Underflow else forall a b. b -> Either a b
Right forall a b. (a -> b) -> a -> b
$ forall a. Num a => Integer -> a
fromInteger Integer
s

-- | Uses 'fromIntegral' when the input is between -16,777,215 and 16,777,215
-- inclusive.
instance TryFrom.TryFrom Integer Float where
  tryFrom :: Integer -> Either (TryFromException Integer Float) Float
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ \Integer
s ->
    if Integer
s forall a. Ord a => a -> a -> Bool
< -forall a. Num a => a
maxFloat
      then forall a b. a -> Either a b
Left ArithException
Exception.Underflow
      else
        if Integer
s forall a. Ord a => a -> a -> Bool
> forall a. Num a => a
maxFloat
          then forall a b. a -> Either a b
Left ArithException
Exception.Overflow
          else forall a b. b -> Either a b
Right forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
s

-- | Uses 'fromIntegral' when the input is between -9,007,199,254,740,991 and
-- 9,007,199,254,740,991 inclusive.
instance TryFrom.TryFrom Integer Double where
  tryFrom :: Integer -> Either (TryFromException Integer Double) Double
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ \Integer
s ->
    if Integer
s forall a. Ord a => a -> a -> Bool
< -forall a. Num a => a
maxDouble
      then forall a b. a -> Either a b
Left ArithException
Exception.Underflow
      else
        if Integer
s forall a. Ord a => a -> a -> Bool
> forall a. Num a => a
maxDouble
          then forall a b. a -> Either a b
Left ArithException
Exception.Overflow
          else forall a b. b -> Either a b
Right forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
s

-- Word8

-- | Uses 'fromIntegral'.
instance From.From Word.Word8 Word.Word16 where
  from :: Word8 -> Word16
from = forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Uses 'fromIntegral'.
instance From.From Word.Word8 Word.Word32 where
  from :: Word8 -> Word32
from = forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Uses 'fromIntegral'.
instance From.From Word.Word8 Word.Word64 where
  from :: Word8 -> Word64
from = forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Uses 'fromIntegral'.
instance From.From Word.Word8 Word where
  from :: Word8 -> Word
from = forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Uses 'fromIntegral'.
instance From.From Word.Word8 Natural.Natural where
  from :: Word8 -> Natural
from = forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Word.Word8 Int.Int8 where
  tryFrom :: Word8 -> Either (TryFromException Word8 Int8) Int8
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'fromIntegral'.
instance From.From Word.Word8 Int.Int16 where
  from :: Word8 -> Int16
from = forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Uses 'fromIntegral'.
instance From.From Word.Word8 Int.Int32 where
  from :: Word8 -> Int32
from = forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Uses 'fromIntegral'.
instance From.From Word.Word8 Int.Int64 where
  from :: Word8 -> Int64
from = forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Uses 'fromIntegral'.
instance From.From Word.Word8 Int where
  from :: Word8 -> Int
from = forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Uses 'fromIntegral'.
instance From.From Word.Word8 Integer where
  from :: Word8 -> Integer
from = forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Uses 'fromIntegral'.
instance From.From Word.Word8 Float where
  from :: Word8 -> Float
from = forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Uses 'fromIntegral'.
instance From.From Word.Word8 Double where
  from :: Word8 -> Double
from = forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- Word16

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Word.Word16 Word.Word8 where
  tryFrom :: Word16 -> Either (TryFromException Word16 Word8) Word8
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'fromIntegral'.
instance From.From Word.Word16 Word.Word32 where
  from :: Word16 -> Word32
from = forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Uses 'fromIntegral'.
instance From.From Word.Word16 Word.Word64 where
  from :: Word16 -> Word64
from = forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Uses 'fromIntegral'.
instance From.From Word.Word16 Word where
  from :: Word16 -> Word
from = forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Uses 'fromIntegral'.
instance From.From Word.Word16 Natural.Natural where
  from :: Word16 -> Natural
from = forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Word.Word16 Int.Int8 where
  tryFrom :: Word16 -> Either (TryFromException Word16 Int8) Int8
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Word.Word16 Int.Int16 where
  tryFrom :: Word16 -> Either (TryFromException Word16 Int16) Int16
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'fromIntegral'.
instance From.From Word.Word16 Int.Int32 where
  from :: Word16 -> Int32
from = forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Uses 'fromIntegral'.
instance From.From Word.Word16 Int.Int64 where
  from :: Word16 -> Int64
from = forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Uses 'fromIntegral'.
instance From.From Word.Word16 Int where
  from :: Word16 -> Int
from = forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Uses 'fromIntegral'.
instance From.From Word.Word16 Integer where
  from :: Word16 -> Integer
from = forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Uses 'fromIntegral'.
instance From.From Word.Word16 Float where
  from :: Word16 -> Float
from = forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Uses 'fromIntegral'.
instance From.From Word.Word16 Double where
  from :: Word16 -> Double
from = forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- Word32

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Word.Word32 Word.Word8 where
  tryFrom :: Word32 -> Either (TryFromException Word32 Word8) Word8
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Word.Word32 Word.Word16 where
  tryFrom :: Word32 -> Either (TryFromException Word32 Word16) Word16
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'fromIntegral'.
instance From.From Word.Word32 Word.Word64 where
  from :: Word32 -> Word64
from = forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Word.Word32 Word where
  tryFrom :: Word32 -> Either (TryFromException Word32 Word) Word
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'fromIntegral'.
instance From.From Word.Word32 Natural.Natural where
  from :: Word32 -> Natural
from = forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Word.Word32 Int.Int8 where
  tryFrom :: Word32 -> Either (TryFromException Word32 Int8) Int8
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Word.Word32 Int.Int16 where
  tryFrom :: Word32 -> Either (TryFromException Word32 Int16) Int16
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Word.Word32 Int.Int32 where
  tryFrom :: Word32 -> Either (TryFromException Word32 Int32) Int32
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'fromIntegral'.
instance From.From Word.Word32 Int.Int64 where
  from :: Word32 -> Int64
from = forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Word.Word32 Int where
  tryFrom :: Word32 -> Either (TryFromException Word32 Int) Int
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'fromIntegral'.
instance From.From Word.Word32 Integer where
  from :: Word32 -> Integer
from = forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Uses 'fromIntegral' when the input is less than or equal to 16,777,215.
instance TryFrom.TryFrom Word.Word32 Float where
  tryFrom :: Word32 -> Either (TryFromException Word32 Float) Float
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ \Word32
s ->
    if Word32
s forall a. Ord a => a -> a -> Bool
<= forall a. Num a => a
maxFloat then forall a b. b -> Either a b
Right forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
s else forall a b. a -> Either a b
Left ArithException
Exception.Overflow

-- | Uses 'fromIntegral'.
instance From.From Word.Word32 Double where
  from :: Word32 -> Double
from = forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- Word64

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Word.Word64 Word.Word8 where
  tryFrom :: Word64 -> Either (TryFromException Word64 Word8) Word8
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Word.Word64 Word.Word16 where
  tryFrom :: Word64 -> Either (TryFromException Word64 Word16) Word16
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Word.Word64 Word.Word32 where
  tryFrom :: Word64 -> Either (TryFromException Word64 Word32) Word32
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Word.Word64 Word where
  tryFrom :: Word64 -> Either (TryFromException Word64 Word) Word
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'fromIntegral'.
instance From.From Word.Word64 Natural.Natural where
  -- This should use @fromIntegral@, but that causes a bug in GHC 9.0.1.
  -- https://mail.haskell.org/pipermail/haskell-cafe/2021-March/133540.html
  from :: Word64 -> Natural
from Word64
s = forall source target.
(HasCallStack, TryFrom source target, Show source, Typeable source,
 Typeable target) =>
source -> target
Utility.unsafeFrom (forall source target. From source target => source -> target
From.from Word64
s :: Integer)

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Word.Word64 Int.Int8 where
  tryFrom :: Word64 -> Either (TryFromException Word64 Int8) Int8
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Word.Word64 Int.Int16 where
  tryFrom :: Word64 -> Either (TryFromException Word64 Int16) Int16
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Word.Word64 Int.Int32 where
  tryFrom :: Word64 -> Either (TryFromException Word64 Int32) Int32
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Word.Word64 Int.Int64 where
  tryFrom :: Word64 -> Either (TryFromException Word64 Int64) Int64
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Word.Word64 Int where
  tryFrom :: Word64 -> Either (TryFromException Word64 Int) Int
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'fromIntegral'.
instance From.From Word.Word64 Integer where
  from :: Word64 -> Integer
from = forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Uses 'fromIntegral' when the input is less than or equal to 16,777,215.
instance TryFrom.TryFrom Word.Word64 Float where
  tryFrom :: Word64 -> Either (TryFromException Word64 Float) Float
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ \Word64
s ->
    if Word64
s forall a. Ord a => a -> a -> Bool
<= forall a. Num a => a
maxFloat then forall a b. b -> Either a b
Right forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
s else forall a b. a -> Either a b
Left ArithException
Exception.Overflow

-- | Uses 'fromIntegral' when the input is less than or equal to
-- 9,007,199,254,740,991.
instance TryFrom.TryFrom Word.Word64 Double where
  tryFrom :: Word64 -> Either (TryFromException Word64 Double) Double
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ \Word64
s ->
    if Word64
s forall a. Ord a => a -> a -> Bool
<= forall a. Num a => a
maxDouble
      then forall a b. b -> Either a b
Right forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
s
      else forall a b. a -> Either a b
Left ArithException
Exception.Overflow

-- Word

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Word Word.Word8 where
  tryFrom :: Word -> Either (TryFromException Word Word8) Word8
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Word Word.Word16 where
  tryFrom :: Word -> Either (TryFromException Word Word16) Word16
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Word Word.Word32 where
  tryFrom :: Word -> Either (TryFromException Word Word32) Word32
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'fromIntegral'.
instance From.From Word Word.Word64 where
  from :: Word -> Word64
from = forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Uses 'fromIntegral'.
instance From.From Word Natural.Natural where
  from :: Word -> Natural
from = forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Word Int.Int8 where
  tryFrom :: Word -> Either (TryFromException Word Int8) Int8
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Word Int.Int16 where
  tryFrom :: Word -> Either (TryFromException Word Int16) Int16
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Word Int.Int32 where
  tryFrom :: Word -> Either (TryFromException Word Int32) Int32
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Word Int.Int64 where
  tryFrom :: Word -> Either (TryFromException Word Int64) Int64
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Word Int where
  tryFrom :: Word -> Either (TryFromException Word Int) Int
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'fromIntegral'.
instance From.From Word Integer where
  from :: Word -> Integer
from = forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Uses 'fromIntegral' when the input is less than or equal to 16,777,215.
instance TryFrom.TryFrom Word Float where
  tryFrom :: Word -> Either (TryFromException Word Float) Float
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ \Word
s ->
    if Word
s forall a. Ord a => a -> a -> Bool
<= forall a. Num a => a
maxFloat then forall a b. b -> Either a b
Right forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral Word
s else forall a b. a -> Either a b
Left ArithException
Exception.Overflow

-- | Uses 'fromIntegral' when the input is less than or equal to
-- 9,007,199,254,740,991.
instance TryFrom.TryFrom Word Double where
  tryFrom :: Word -> Either (TryFromException Word Double) Double
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ \Word
s ->
    if (forall a. Integral a => a -> Integer
toInteger (forall a. Bounded a => a
maxBound :: Word) forall a. Ord a => a -> a -> Bool
<= forall a. Num a => a
maxDouble) Bool -> Bool -> Bool
|| (Word
s forall a. Ord a => a -> a -> Bool
<= forall a. Num a => a
maxDouble)
      then forall a b. b -> Either a b
Right forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral Word
s
      else forall a b. a -> Either a b
Left ArithException
Exception.Overflow

-- Natural

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Natural.Natural Word.Word8 where
  tryFrom :: Natural -> Either (TryFromException Natural Word8) Word8
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Natural.Natural Word.Word16 where
  tryFrom :: Natural -> Either (TryFromException Natural Word16) Word16
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Natural.Natural Word.Word32 where
  tryFrom :: Natural -> Either (TryFromException Natural Word32) Word32
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Natural.Natural Word.Word64 where
  tryFrom :: Natural -> Either (TryFromException Natural Word64) Word64
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Natural.Natural Word where
  tryFrom :: Natural -> Either (TryFromException Natural Word) Word
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Natural.Natural Int.Int8 where
  tryFrom :: Natural -> Either (TryFromException Natural Int8) Int8
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Natural.Natural Int.Int16 where
  tryFrom :: Natural -> Either (TryFromException Natural Int16) Int16
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Natural.Natural Int.Int32 where
  tryFrom :: Natural -> Either (TryFromException Natural Int32) Int32
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Natural.Natural Int.Int64 where
  tryFrom :: Natural -> Either (TryFromException Natural Int64) Int64
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'Bits.toIntegralSized'.
instance TryFrom.TryFrom Natural.Natural Int where
  tryFrom :: Natural -> Either (TryFromException Natural Int) Int
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b.
(Integral a, Integral b, Bits a, Bits b) =>
a -> Maybe b
Bits.toIntegralSized

-- | Uses 'fromIntegral'.
instance From.From Natural.Natural Integer where
  from :: Natural -> Integer
from = forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Uses 'fromIntegral' when the input is less than or equal to 16,777,215.
instance TryFrom.TryFrom Natural.Natural Float where
  tryFrom :: Natural -> Either (TryFromException Natural Float) Float
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ \Natural
s ->
    if Natural
s forall a. Ord a => a -> a -> Bool
<= forall a. Num a => a
maxFloat then forall a b. b -> Either a b
Right forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral Natural
s else forall a b. a -> Either a b
Left ArithException
Exception.Overflow

-- | Uses 'fromIntegral' when the input is less than or equal to
-- 9,007,199,254,740,991.
instance TryFrom.TryFrom Natural.Natural Double where
  tryFrom :: Natural -> Either (TryFromException Natural Double) Double
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ \Natural
s ->
    if Natural
s forall a. Ord a => a -> a -> Bool
<= forall a. Num a => a
maxDouble
      then forall a b. b -> Either a b
Right forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral Natural
s
      else forall a b. a -> Either a b
Left ArithException
Exception.Overflow

-- Float

-- | Converts via 'Integer'.
instance TryFrom.TryFrom Float Int.Int8 where
  tryFrom :: Float -> Either (TryFromException Float Int8) Int8
tryFrom = forall through source target.
(TryFrom source through, TryFrom through target) =>
source -> Either (TryFromException source target) target
Utility.tryVia @Integer

-- | Converts via 'Integer'.
instance TryFrom.TryFrom Float Int.Int16 where
  tryFrom :: Float -> Either (TryFromException Float Int16) Int16
tryFrom = forall through source target.
(TryFrom source through, TryFrom through target) =>
source -> Either (TryFromException source target) target
Utility.tryVia @Integer

-- | Converts via 'Integer'.
instance TryFrom.TryFrom Float Int.Int32 where
  tryFrom :: Float -> Either (TryFromException Float Int32) Int32
tryFrom = forall through source target.
(TryFrom source through, TryFrom through target) =>
source -> Either (TryFromException source target) target
Utility.tryVia @Integer

-- | Converts via 'Integer'.
instance TryFrom.TryFrom Float Int.Int64 where
  tryFrom :: Float -> Either (TryFromException Float Int64) Int64
tryFrom = forall through source target.
(TryFrom source through, TryFrom through target) =>
source -> Either (TryFromException source target) target
Utility.tryVia @Integer

-- | Converts via 'Integer'.
instance TryFrom.TryFrom Float Int where
  tryFrom :: Float -> Either (TryFromException Float Int) Int
tryFrom = forall through source target.
(TryFrom source through, TryFrom through target) =>
source -> Either (TryFromException source target) target
Utility.tryVia @Integer

-- | Converts via 'Rational' when the input is between -16,777,215 and
-- 16,777,215 inclusive.
instance TryFrom.TryFrom Float Integer where
  tryFrom :: Float -> Either (TryFromException Float Integer) Integer
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ \Float
s -> case 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 -> forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ forall e. Exception e => e -> SomeException
Exception.toException TryFromException Float Integer
e
    Right Integer
t
      | Integer
t forall a. Ord a => a -> a -> Bool
< -forall a. Num a => a
maxFloat -> forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ forall e. Exception e => e -> SomeException
Exception.toException ArithException
Exception.Underflow
      | Integer
t forall a. Ord a => a -> a -> Bool
> forall a. Num a => a
maxFloat -> forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ forall e. Exception e => e -> SomeException
Exception.toException ArithException
Exception.Overflow
      | Bool
otherwise -> forall a b. b -> Either a b
Right Integer
t

-- | Converts via 'Integer'.
instance TryFrom.TryFrom Float Word.Word8 where
  tryFrom :: Float -> Either (TryFromException Float Word8) Word8
tryFrom = forall through source target.
(TryFrom source through, TryFrom through target) =>
source -> Either (TryFromException source target) target
Utility.tryVia @Integer

-- | Converts via 'Integer'.
instance TryFrom.TryFrom Float Word.Word16 where
  tryFrom :: Float -> Either (TryFromException Float Word16) Word16
tryFrom = forall through source target.
(TryFrom source through, TryFrom through target) =>
source -> Either (TryFromException source target) target
Utility.tryVia @Integer

-- | Converts via 'Integer'.
instance TryFrom.TryFrom Float Word.Word32 where
  tryFrom :: Float -> Either (TryFromException Float Word32) Word32
tryFrom = forall through source target.
(TryFrom source through, TryFrom through target) =>
source -> Either (TryFromException source target) target
Utility.tryVia @Integer

-- | Converts via 'Integer'.
instance TryFrom.TryFrom Float Word.Word64 where
  tryFrom :: Float -> Either (TryFromException Float Word64) Word64
tryFrom = forall through source target.
(TryFrom source through, TryFrom through target) =>
source -> Either (TryFromException source target) target
Utility.tryVia @Integer

-- | Converts via 'Integer'.
instance TryFrom.TryFrom Float Word where
  tryFrom :: Float -> Either (TryFromException Float Word) Word
tryFrom = forall through source target.
(TryFrom source through, TryFrom through target) =>
source -> Either (TryFromException source target) target
Utility.tryVia @Integer

-- | Converts via 'Integer'.
instance TryFrom.TryFrom Float Natural.Natural where
  tryFrom :: Float -> Either (TryFromException Float Natural) Natural
tryFrom = forall through source target.
(TryFrom source through, TryFrom through target) =>
source -> Either (TryFromException source target) target
Utility.tryVia @Integer

-- | Uses 'Numeric.floatToDigits' when the input is not NaN or infinity.
instance TryFrom.TryFrom Float Rational where
  tryFrom :: Float -> Either (TryFromException Float Rational) Rational
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall s. RealFloat s => s -> Either ArithException Rational
realFloatToRational

-- | Uses 'Float.float2Double'.
instance From.From Float Double where
  from :: Float -> Double
from = Float -> Double
Float.float2Double

-- Double

-- | Converts via 'Integer'.
instance TryFrom.TryFrom Double Int.Int8 where
  tryFrom :: Double -> Either (TryFromException Double Int8) Int8
tryFrom = forall through source target.
(TryFrom source through, TryFrom through target) =>
source -> Either (TryFromException source target) target
Utility.tryVia @Integer

-- | Converts via 'Integer'.
instance TryFrom.TryFrom Double Int.Int16 where
  tryFrom :: Double -> Either (TryFromException Double Int16) Int16
tryFrom = forall through source target.
(TryFrom source through, TryFrom through target) =>
source -> Either (TryFromException source target) target
Utility.tryVia @Integer

-- | Converts via 'Integer'.
instance TryFrom.TryFrom Double Int.Int32 where
  tryFrom :: Double -> Either (TryFromException Double Int32) Int32
tryFrom = forall through source target.
(TryFrom source through, TryFrom through target) =>
source -> Either (TryFromException source target) target
Utility.tryVia @Integer

-- | Converts via 'Integer'.
instance TryFrom.TryFrom Double Int.Int64 where
  tryFrom :: Double -> Either (TryFromException Double Int64) Int64
tryFrom = forall through source target.
(TryFrom source through, TryFrom through target) =>
source -> Either (TryFromException source target) target
Utility.tryVia @Integer

-- | Converts via 'Integer'.
instance TryFrom.TryFrom Double Int where
  tryFrom :: Double -> Either (TryFromException Double Int) Int
tryFrom = forall through source target.
(TryFrom source through, TryFrom through target) =>
source -> Either (TryFromException source target) target
Utility.tryVia @Integer

-- | Converts via 'Rational' when the input is between -9,007,199,254,740,991
-- and 9,007,199,254,740,991 inclusive.
instance TryFrom.TryFrom Double Integer where
  tryFrom :: Double -> Either (TryFromException Double Integer) Integer
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ \Double
s -> case 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 -> forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ forall e. Exception e => e -> SomeException
Exception.toException TryFromException Double Integer
e
    Right Integer
t
      | Integer
t forall a. Ord a => a -> a -> Bool
< -forall a. Num a => a
maxDouble -> forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ forall e. Exception e => e -> SomeException
Exception.toException ArithException
Exception.Underflow
      | Integer
t forall a. Ord a => a -> a -> Bool
> forall a. Num a => a
maxDouble -> forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ forall e. Exception e => e -> SomeException
Exception.toException ArithException
Exception.Overflow
      | Bool
otherwise -> forall a b. b -> Either a b
Right Integer
t

-- | Converts via 'Integer'.
instance TryFrom.TryFrom Double Word.Word8 where
  tryFrom :: Double -> Either (TryFromException Double Word8) Word8
tryFrom = forall through source target.
(TryFrom source through, TryFrom through target) =>
source -> Either (TryFromException source target) target
Utility.tryVia @Integer

-- | Converts via 'Integer'.
instance TryFrom.TryFrom Double Word.Word16 where
  tryFrom :: Double -> Either (TryFromException Double Word16) Word16
tryFrom = forall through source target.
(TryFrom source through, TryFrom through target) =>
source -> Either (TryFromException source target) target
Utility.tryVia @Integer

-- | Converts via 'Integer'.
instance TryFrom.TryFrom Double Word.Word32 where
  tryFrom :: Double -> Either (TryFromException Double Word32) Word32
tryFrom = forall through source target.
(TryFrom source through, TryFrom through target) =>
source -> Either (TryFromException source target) target
Utility.tryVia @Integer

-- | Converts via 'Integer'.
instance TryFrom.TryFrom Double Word.Word64 where
  tryFrom :: Double -> Either (TryFromException Double Word64) Word64
tryFrom = forall through source target.
(TryFrom source through, TryFrom through target) =>
source -> Either (TryFromException source target) target
Utility.tryVia @Integer

-- | Converts via 'Integer'.
instance TryFrom.TryFrom Double Word where
  tryFrom :: Double -> Either (TryFromException Double Word) Word
tryFrom = forall through source target.
(TryFrom source through, TryFrom through target) =>
source -> Either (TryFromException source target) target
Utility.tryVia @Integer

-- | Converts via 'Integer'.
instance TryFrom.TryFrom Double Natural.Natural where
  tryFrom :: Double -> Either (TryFromException Double Natural) Natural
tryFrom = forall through source target.
(TryFrom source through, TryFrom through target) =>
source -> Either (TryFromException source target) target
Utility.tryVia @Integer

-- | Uses 'Numeric.floatToDigits' when the input is not NaN or infinity.
instance TryFrom.TryFrom Double Rational where
  tryFrom :: Double -> Either (TryFromException Double Rational) Rational
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall s. RealFloat s => s -> Either ArithException Rational
realFloatToRational

-- | Uses 'Float.double2Float'. This necessarily loses some precision.
instance From.From Double Float where
  from :: Double -> Float
from = Double -> Float
Float.double2Float

-- Ratio

-- | Uses '(Ratio.%)' with a denominator of 1.
instance (Integral a) => From.From a (Ratio.Ratio a) where
  from :: a -> Ratio a
from = (forall a. Integral a => a -> a -> Ratio a
Ratio.% a
1)

-- | Uses 'Ratio.numerator' when the denominator is 1.
instance (Eq a, Num a) => TryFrom.TryFrom (Ratio.Ratio a) a where
  tryFrom :: Ratio a -> Either (TryFromException (Ratio a) a) a
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ \Ratio a
s ->
    if forall a. Ratio a -> a
Ratio.denominator Ratio a
s forall a. Eq a => a -> a -> Bool
== a
1
      then forall a b. b -> Either a b
Right forall a b. (a -> b) -> a -> b
$ forall a. Ratio a -> a
Ratio.numerator Ratio a
s
      else forall a b. a -> Either a b
Left ArithException
Exception.LossOfPrecision

-- | Uses 'fromRational'. This necessarily loses some precision.
instance From.From Rational Float where
  from :: Rational -> Float
from = forall a. Fractional a => Rational -> a
fromRational

-- | Uses 'fromRational'. This necessarily loses some precision.
instance From.From Rational Double where
  from :: Rational -> Double
from = forall a. Fractional a => Rational -> a
fromRational

-- | Uses `fromRational` as long as there isn't a loss of precision.
instance (Fixed.HasResolution a) => TryFrom.TryFrom Rational (Fixed.Fixed a) where
  tryFrom :: Rational -> Either (TryFromException Rational (Fixed a)) (Fixed a)
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ \Rational
s ->
    let t :: Fixed.Fixed a
        t :: Fixed a
t = forall a. Fractional a => Rational -> a
fromRational Rational
s
     in if forall a. Real a => a -> Rational
toRational Fixed a
t forall a. Eq a => a -> a -> Bool
== Rational
s then forall a b. b -> Either a b
Right Fixed a
t else forall a b. a -> Either a b
Left ArithException
Exception.LossOfPrecision

-- Fixed

-- | Uses 'Fixed.MkFixed'. This means @from \@Integer \@Centi 2@ is @0.02@
-- rather than @2.00@.
instance From.From Integer (Fixed.Fixed a) where
  from :: Integer -> Fixed a
from = forall k (a :: k). Integer -> Fixed a
Fixed.MkFixed

-- | Uses 'Fixed.MkFixed'. This means @from \@Centi \@Integer 3.00@ is @300@
-- rather than @3@.
instance From.From (Fixed.Fixed a) Integer where
  from :: Fixed a -> Integer
from (Fixed.MkFixed Integer
t) = Integer
t

-- | Uses 'toRational'.
instance (Fixed.HasResolution a) => From.From (Fixed.Fixed a) Rational where
  from :: Fixed a -> Rational
from = forall a. Real a => a -> Rational
toRational

-- Complex

-- | Uses '(Complex.:+)' with an imaginary part of 0.
instance (Num a) => From.From a (Complex.Complex a) where
  from :: a -> Complex a
from = (forall a. a -> a -> Complex a
Complex.:+ a
0)

-- | Uses 'Complex.realPart' when the imaginary part is 0.
instance (Eq a, Num a) => TryFrom.TryFrom (Complex.Complex a) a where
  tryFrom :: Complex a -> Either (TryFromException (Complex a) a) a
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ \Complex a
s ->
    if forall a. Complex a -> a
Complex.imagPart Complex a
s forall a. Eq a => a -> a -> Bool
== a
0
      then forall a b. b -> Either a b
Right forall a b. (a -> b) -> a -> b
$ forall a. Complex a -> a
Complex.realPart Complex a
s
      else forall a b. a -> Either a b
Left ArithException
Exception.LossOfPrecision

-- NonEmpty

-- | Uses 'NonEmpty.nonEmpty'.
instance TryFrom.TryFrom [a] (NonEmpty.NonEmpty a) where
  tryFrom :: [a] -> Either (TryFromException [a] (NonEmpty a)) (NonEmpty a)
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a. [a] -> Maybe (NonEmpty a)
NonEmpty.nonEmpty

-- | Uses 'NonEmpty.toList'.
instance From.From (NonEmpty.NonEmpty a) [a] where
  from :: NonEmpty a -> [a]
from = forall a. NonEmpty a -> [a]
NonEmpty.toList

-- Set

-- | Uses 'Set.fromList'.
instance (Ord a) => From.From [a] (Set.Set a) where
  from :: [a] -> Set a
from = forall a. Ord a => [a] -> Set a
Set.fromList

-- | Uses 'Set.toAscList'.
instance From.From (Set.Set a) [a] where
  from :: Set a -> [a]
from = forall a. Set a -> [a]
Set.toAscList

-- IntSet

-- | Uses 'IntSet.fromList'.
instance From.From [Int] IntSet.IntSet where
  from :: [Int] -> IntSet
from = [Int] -> IntSet
IntSet.fromList

-- | Uses 'IntSet.toAscList'.
instance From.From IntSet.IntSet [Int] where
  from :: IntSet -> [Int]
from = IntSet -> [Int]
IntSet.toAscList

-- Map

-- | Uses 'Map.fromList'. If there are duplicate keys, later values will
-- overwrite earlier ones.
instance (Ord k) => From.From [(k, v)] (Map.Map k v) where
  from :: [(k, v)] -> Map k v
from = forall k v. Ord k => [(k, v)] -> Map k v
Map.fromList

-- | Uses 'Map.toAscList'.
instance From.From (Map.Map k v) [(k, v)] where
  from :: Map k v -> [(k, v)]
from = forall k v. Map k v -> [(k, v)]
Map.toAscList

-- IntMap

-- | Uses 'IntMap.fromList'. If there are duplicate keys, later values will
-- overwrite earlier ones.
instance From.From [(Int, v)] (IntMap.IntMap v) where
  from :: [(Int, v)] -> IntMap v
from = forall v. [(Int, v)] -> IntMap v
IntMap.fromList

-- | Uses 'IntMap.toAscList'.
instance From.From (IntMap.IntMap v) [(Int, v)] where
  from :: IntMap v -> [(Int, v)]
from = forall v. IntMap v -> [(Int, v)]
IntMap.toAscList

-- Seq

-- | Uses 'Seq.fromList'.
instance From.From [a] (Seq.Seq a) where
  from :: [a] -> Seq a
from = forall a. [a] -> Seq a
Seq.fromList

-- | Uses 'Foldable.toList'.
instance From.From (Seq.Seq a) [a] where
  from :: Seq a -> [a]
from = forall (t :: * -> *) a. Foldable t => t a -> [a]
Foldable.toList

-- ByteString

-- | Uses 'ByteString.pack'.
instance From.From [Word.Word8] ByteString.ByteString where
  from :: [Word8] -> ByteString
from = [Word8] -> ByteString
ByteString.pack

-- | Uses 'ByteString.unpack'.
instance From.From ByteString.ByteString [Word.Word8] where
  from :: ByteString -> [Word8]
from = ByteString -> [Word8]
ByteString.unpack

-- | Uses 'LazyByteString.fromStrict'.
instance From.From ByteString.ByteString LazyByteString.ByteString where
  from :: ByteString -> ByteString
from = ByteString -> ByteString
LazyByteString.fromStrict

-- | Uses 'ShortByteString.toShort'.
instance From.From ByteString.ByteString ShortByteString.ShortByteString where
  from :: ByteString -> ShortByteString
from = ByteString -> ShortByteString
ShortByteString.toShort

-- LazyByteString

-- | Uses 'LazyByteString.pack'.
instance From.From [Word.Word8] LazyByteString.ByteString where
  from :: [Word8] -> ByteString
from = [Word8] -> ByteString
LazyByteString.pack

-- | Uses 'LazyByteString.unpack'.
instance From.From LazyByteString.ByteString [Word.Word8] where
  from :: ByteString -> [Word8]
from = ByteString -> [Word8]
LazyByteString.unpack

-- | Uses 'LazyByteString.toStrict'.
instance From.From LazyByteString.ByteString ByteString.ByteString where
  from :: ByteString -> ByteString
from = ByteString -> ByteString
LazyByteString.toStrict

-- ShortByteString

-- | Uses 'ShortByteString.pack'.
instance From.From [Word.Word8] ShortByteString.ShortByteString where
  from :: [Word8] -> ShortByteString
from = [Word8] -> ShortByteString
ShortByteString.pack

-- | Uses 'ShortByteString.unpack'.
instance From.From ShortByteString.ShortByteString [Word.Word8] where
  from :: ShortByteString -> [Word8]
from = ShortByteString -> [Word8]
ShortByteString.unpack

-- | Uses 'ShortByteString.fromShort'.
instance From.From ShortByteString.ShortByteString ByteString.ByteString where
  from :: ShortByteString -> ByteString
from = ShortByteString -> ByteString
ShortByteString.fromShort

-- Text

-- | Uses 'LazyText.fromStrict'.
instance From.From Text.Text LazyText.Text where
  from :: Text -> Text
from = Text -> Text
LazyText.fromStrict

-- LazyText

-- | Uses 'LazyText.toStrict'.
instance From.From LazyText.Text Text.Text where
  from :: Text -> Text
from = Text -> Text
LazyText.toStrict

-- String

-- | Uses 'Text.pack'. Some 'Char' values cannot be represented in 'Text.Text'
-- and will be replaced with @'\\xFFFD'@.
instance From.From String Text.Text where
  from :: String -> Text
from = String -> Text
Text.pack

-- | Uses 'Text.unpack'.
instance From.From Text.Text String where
  from :: Text -> String
from = Text -> String
Text.unpack

-- | Uses 'LazyText.pack'. Some 'Char' values cannot be represented in
-- 'LazyText.Text' and will be replaced with @'\\xFFFD'@.
instance From.From String LazyText.Text where
  from :: String -> Text
from = String -> Text
LazyText.pack

-- | Uses 'LazyText.unpack'.
instance From.From LazyText.Text String where
  from :: Text -> String
from = Text -> String
LazyText.unpack

-- TryFromException

-- | Uses @coerce@.
instance
  From.From
    (TryFromException.TryFromException source oldTarget)
    (TryFromException.TryFromException source newTarget)

-- Day

-- | Uses 'Time.ModifiedJulianDay'.
instance From.From Integer Time.Day where
  from :: Integer -> Day
from = Integer -> Day
Time.ModifiedJulianDay

-- | Uses 'Time.toModifiedJulianDay'.
instance From.From Time.Day Integer where
  from :: Day -> Integer
from = Day -> Integer
Time.toModifiedJulianDay

-- DayOfWeek

-- | Uses 'Time.dayOfWeek'.
instance From.From Time.Day Time.DayOfWeek where
  from :: Day -> DayOfWeek
from = Day -> DayOfWeek
Time.dayOfWeek

-- UniversalTime

-- | Uses 'Time.ModJulianDate'.
instance From.From Rational Time.UniversalTime where
  from :: Rational -> UniversalTime
from = Rational -> UniversalTime
Time.ModJulianDate

-- | Uses 'Time.getModJulianDate'.
instance From.From Time.UniversalTime Rational where
  from :: UniversalTime -> Rational
from = UniversalTime -> Rational
Time.getModJulianDate

-- DiffTime

-- | Uses 'realToFrac'.
instance From.From Fixed.Pico Time.DiffTime where
  from :: Pico -> DiffTime
from = forall a b. (Real a, Fractional b) => a -> b
realToFrac

-- | Uses 'realToFrac'.
instance From.From Time.DiffTime Fixed.Pico where
  from :: DiffTime -> Pico
from = forall a b. (Real a, Fractional b) => a -> b
realToFrac

-- NominalDiffTime

-- | Uses 'Time.secondsToNominalDiffTime'.
instance From.From Fixed.Pico Time.NominalDiffTime where
  from :: Pico -> NominalDiffTime
from = Pico -> NominalDiffTime
Time.secondsToNominalDiffTime

-- | Uses 'Time.nominalDiffTimeToSeconds'.
instance From.From Time.NominalDiffTime Fixed.Pico where
  from :: NominalDiffTime -> Pico
from = NominalDiffTime -> Pico
Time.nominalDiffTimeToSeconds

-- POSIXTime

-- | Uses 'Time.systemToPOSIXTime'.
instance From.From Time.SystemTime Time.POSIXTime where
  from :: SystemTime -> NominalDiffTime
from = SystemTime -> NominalDiffTime
Time.systemToPOSIXTime

-- | Uses 'Time.utcTimeToPOSIXSeconds'.
instance From.From Time.UTCTime Time.POSIXTime where
  from :: UTCTime -> NominalDiffTime
from = UTCTime -> NominalDiffTime
Time.utcTimeToPOSIXSeconds

-- | Uses 'Time.posixSecondsToUTCTime'.
instance From.From Time.POSIXTime Time.UTCTime where
  from :: NominalDiffTime -> UTCTime
from = NominalDiffTime -> UTCTime
Time.posixSecondsToUTCTime

-- SystemTime

-- | Uses 'Time.utcToSystemTime'.
instance From.From Time.UTCTime Time.SystemTime where
  from :: UTCTime -> SystemTime
from = UTCTime -> SystemTime
Time.utcToSystemTime

-- | Uses 'Time.systemToTAITime'.
instance From.From Time.SystemTime Time.AbsoluteTime where
  from :: SystemTime -> AbsoluteTime
from = SystemTime -> AbsoluteTime
Time.systemToTAITime

-- | Uses 'Time.systemToUTCTime'.
instance From.From Time.SystemTime Time.UTCTime where
  from :: SystemTime -> UTCTime
from = SystemTime -> UTCTime
Time.systemToUTCTime

-- TimeOfDay

-- | Uses 'Time.timeToTimeOfDay'.
instance From.From Time.DiffTime Time.TimeOfDay where
  from :: DiffTime -> TimeOfDay
from = DiffTime -> TimeOfDay
Time.timeToTimeOfDay

-- | Uses 'Time.dayFractionToTimeOfDay'.
instance From.From Rational Time.TimeOfDay where
  from :: Rational -> TimeOfDay
from = Rational -> TimeOfDay
Time.dayFractionToTimeOfDay

-- | Uses 'Time.timeOfDayToTime'.
instance From.From Time.TimeOfDay Time.DiffTime where
  from :: TimeOfDay -> DiffTime
from = TimeOfDay -> DiffTime
Time.timeOfDayToTime

-- | Uses 'Time.timeOfDayToDayFraction'.
instance From.From Time.TimeOfDay Rational where
  from :: TimeOfDay -> Rational
from = TimeOfDay -> Rational
Time.timeOfDayToDayFraction

-- CalendarDiffTime

-- | Uses 'Time.calendarTimeDays'.
instance From.From Time.CalendarDiffDays Time.CalendarDiffTime where
  from :: CalendarDiffDays -> CalendarDiffTime
from = CalendarDiffDays -> CalendarDiffTime
Time.calendarTimeDays

-- | Uses 'Time.calendarTimeTime'.
instance From.From Time.NominalDiffTime Time.CalendarDiffTime where
  from :: NominalDiffTime -> CalendarDiffTime
from = NominalDiffTime -> CalendarDiffTime
Time.calendarTimeTime

-- ZonedTime

-- | Uses 'Time.zonedTimeToUTC'.
instance From.From Time.ZonedTime Time.UTCTime where
  from :: ZonedTime -> UTCTime
from = ZonedTime -> UTCTime
Time.zonedTimeToUTC

-- Tagged

-- | Uses @coerce@. Essentially the same as 'Tagged.Tagged'.
instance From.From a (Tagged.Tagged t a)

-- | Uses @coerce@. Essentially the same as 'Tagged.unTagged'.
instance From.From (Tagged.Tagged t a) a

-- | Uses @coerce@. Essentially the same as 'Tagged.retag'.
instance From.From (Tagged.Tagged t a) (Tagged.Tagged u a)

-- ISO-8859-1

-- | Uses 'Text.decodeLatin1'.
instance From.From (Encoding.ISO_8859_1 ByteString.ByteString) Text.Text where
  from :: ISO_8859_1 ByteString -> Text
from = ByteString -> Text
Text.decodeLatin1 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall source target. From source target => source -> target
From.from

-- | Converts via 'Text.Text'.
instance From.From (Encoding.ISO_8859_1 ByteString.ByteString) LazyText.Text where
  from :: ISO_8859_1 ByteString -> Text
from = forall through source target.
(From source through, From through target) =>
source -> target
Utility.via @Text.Text

-- | Converts via 'Text.Text'.
instance From.From (Encoding.ISO_8859_1 ByteString.ByteString) String where
  from :: ISO_8859_1 ByteString -> String
from = forall through source target.
(From source through, From through target) =>
source -> target
Utility.via @Text.Text

-- | Uses 'LazyText.decodeLatin1'.
instance From.From (Encoding.ISO_8859_1 LazyByteString.ByteString) LazyText.Text where
  from :: ISO_8859_1 ByteString -> Text
from = ByteString -> Text
LazyText.decodeLatin1 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall source target. From source target => source -> target
From.from

-- | Converts via 'LazyText.Text'.
instance From.From (Encoding.ISO_8859_1 LazyByteString.ByteString) Text.Text where
  from :: ISO_8859_1 ByteString -> Text
from = forall through source target.
(From source through, From through target) =>
source -> target
Utility.via @LazyText.Text

-- | Converts via 'LazyText.Text'.
instance From.From (Encoding.ISO_8859_1 LazyByteString.ByteString) String where
  from :: ISO_8859_1 ByteString -> String
from = forall through source target.
(From source through, From through target) =>
source -> target
Utility.via @LazyText.Text

-- | Converts via 'String'.
instance TryFrom.TryFrom Text.Text (Encoding.ISO_8859_1 ByteString.ByteString) where
  tryFrom :: Text
-> Either
     (TryFromException Text (ISO_8859_1 ByteString))
     (ISO_8859_1 ByteString)
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ forall source target.
TryFrom source target =>
source -> Either (TryFromException source target) target
TryFrom.tryFrom forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall target source. From source target => source -> target
Utility.into @String

-- | Converts via 'String'.
instance TryFrom.TryFrom Text.Text (Encoding.ISO_8859_1 LazyByteString.ByteString) where
  tryFrom :: Text
-> Either
     (TryFromException Text (ISO_8859_1 ByteString))
     (ISO_8859_1 ByteString)
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ forall source target.
TryFrom source target =>
source -> Either (TryFromException source target) target
TryFrom.tryFrom forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall target source. From source target => source -> target
Utility.into @String

-- | Converts via 'String'.
instance TryFrom.TryFrom LazyText.Text (Encoding.ISO_8859_1 LazyByteString.ByteString) where
  tryFrom :: Text
-> Either
     (TryFromException Text (ISO_8859_1 ByteString))
     (ISO_8859_1 ByteString)
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ forall source target.
TryFrom source target =>
source -> Either (TryFromException source target) target
TryFrom.tryFrom forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall target source. From source target => source -> target
Utility.into @String

-- | Converts via 'String'.
instance TryFrom.TryFrom LazyText.Text (Encoding.ISO_8859_1 ByteString.ByteString) where
  tryFrom :: Text
-> Either
     (TryFromException Text (ISO_8859_1 ByteString))
     (ISO_8859_1 ByteString)
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ forall source target.
TryFrom source target =>
source -> Either (TryFromException source target) target
TryFrom.tryFrom forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall target source. From source target => source -> target
Utility.into @String

-- | Uses 'Char8.pack' when each character 'Char.isLatin1'.
instance TryFrom.TryFrom String (Encoding.ISO_8859_1 ByteString.ByteString) where
  tryFrom :: String
-> Either
     (TryFromException String (ISO_8859_1 ByteString))
     (ISO_8859_1 ByteString)
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b. (a -> b) -> a -> b
$ \String
string -> do
    forall (f :: * -> *). Alternative f => Bool -> f ()
Monad.guard forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Char -> Bool
Char.isLatin1 String
string
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall source target. From source target => source -> target
From.from forall a b. (a -> b) -> a -> b
$ String -> ByteString
Char8.pack String
string

-- | Uses 'LazyChar8.pack' when each character 'Char.isLatin1'.
instance TryFrom.TryFrom String (Encoding.ISO_8859_1 LazyByteString.ByteString) where
  tryFrom :: String
-> Either
     (TryFromException String (ISO_8859_1 ByteString))
     (ISO_8859_1 ByteString)
tryFrom = forall source target.
(source -> Maybe target)
-> source -> Either (TryFromException source target) target
Utility.maybeTryFrom forall a b. (a -> b) -> a -> b
$ \String
string -> do
    forall (f :: * -> *). Alternative f => Bool -> f ()
Monad.guard forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Char -> Bool
Char.isLatin1 String
string
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall source target. From source target => source -> target
From.from forall a b. (a -> b) -> a -> b
$ String -> ByteString
LazyChar8.pack String
string

-- UTF-8

-- | Uses 'Text.decodeUtf8''.
instance TryFrom.TryFrom (Encoding.UTF_8 ByteString.ByteString) Text.Text where
  tryFrom :: UTF_8 ByteString
-> Either (TryFromException (UTF_8 ByteString) Text) Text
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ ByteString -> Either UnicodeException Text
Text.decodeUtf8' forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall source target. From source target => source -> target
From.from

-- | Converts via 'Text.Text'.
instance TryFrom.TryFrom (Encoding.UTF_8 ByteString.ByteString) LazyText.Text where
  tryFrom :: UTF_8 ByteString
-> Either (TryFromException (UTF_8 ByteString) Text) Text
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall target source. From source target => source -> target
Utility.into @LazyText.Text) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall target source.
TryFrom source target =>
source -> Either (TryFromException source target) target
Utility.tryInto @Text.Text

-- | Converts via 'Text.Text'.
instance TryFrom.TryFrom (Encoding.UTF_8 ByteString.ByteString) String where
  tryFrom :: UTF_8 ByteString
-> Either (TryFromException (UTF_8 ByteString) String) String
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall target source. From source target => source -> target
Utility.into @String) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall target source.
TryFrom source target =>
source -> Either (TryFromException source target) target
Utility.tryInto @Text.Text

-- | Uses 'LazyText.decodeUtf8''.
instance TryFrom.TryFrom (Encoding.UTF_8 LazyByteString.ByteString) LazyText.Text where
  tryFrom :: UTF_8 ByteString
-> Either (TryFromException (UTF_8 ByteString) Text) Text
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ ByteString -> Either UnicodeException Text
LazyText.decodeUtf8' forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall source target. From source target => source -> target
From.from

-- | Converts via 'LazyText.Text'.
instance TryFrom.TryFrom (Encoding.UTF_8 LazyByteString.ByteString) Text.Text where
  tryFrom :: UTF_8 ByteString
-> Either (TryFromException (UTF_8 ByteString) Text) Text
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall target source. From source target => source -> target
Utility.into @Text.Text) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall target source.
TryFrom source target =>
source -> Either (TryFromException source target) target
Utility.tryInto @LazyText.Text

-- | Converts via 'LazyText.Text'.
instance TryFrom.TryFrom (Encoding.UTF_8 LazyByteString.ByteString) String where
  tryFrom :: UTF_8 ByteString
-> Either (TryFromException (UTF_8 ByteString) String) String
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall target source. From source target => source -> target
Utility.into @String) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall target source.
TryFrom source target =>
source -> Either (TryFromException source target) target
Utility.tryInto @LazyText.Text

-- | Uses 'Text.encodeUtf8'.
instance From.From Text.Text (Encoding.UTF_8 ByteString.ByteString) where
  from :: Text -> UTF_8 ByteString
from = forall source target. From source target => source -> target
From.from forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
Text.encodeUtf8

-- | Converts via 'ByteString.ByteString'.
instance From.From Text.Text (Encoding.UTF_8 LazyByteString.ByteString) where
  from :: Text -> UTF_8 ByteString
from = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall source target. From source target => source -> target
From.from forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall target source. From source target => source -> target
Utility.into @(Encoding.UTF_8 ByteString.ByteString)

-- | Uses 'LazyText.encodeUtf8'.
instance From.From LazyText.Text (Encoding.UTF_8 LazyByteString.ByteString) where
  from :: Text -> UTF_8 ByteString
from = forall source target. From source target => source -> target
From.from forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
LazyText.encodeUtf8

-- | Converts via 'LazyByteString.ByteString'.
instance From.From LazyText.Text (Encoding.UTF_8 ByteString.ByteString) where
  from :: Text -> UTF_8 ByteString
from = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall source target. From source target => source -> target
From.from forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall target source. From source target => source -> target
Utility.into @(Encoding.UTF_8 LazyByteString.ByteString)

-- | Converts via 'Text.Text'.
instance From.From String (Encoding.UTF_8 ByteString.ByteString) where
  from :: String -> UTF_8 ByteString
from = forall through source target.
(From source through, From through target) =>
source -> target
Utility.via @Text.Text

-- | Converts via 'LazyText.Text'.
instance From.From String (Encoding.UTF_8 LazyByteString.ByteString) where
  from :: String -> UTF_8 ByteString
from = forall through source target.
(From source through, From through target) =>
source -> target
Utility.via @LazyText.Text

-- UTF-16LE

-- | Uses 'Text.decodeUtf16LE'.
instance TryFrom.TryFrom (Encoding.UTF_16LE ByteString.ByteString) Text.Text where
  tryFrom :: UTF_16LE ByteString
-> Either (TryFromException (UTF_16LE ByteString) Text) Text
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ forall e a. Exception e => a -> Either e a
tryEvaluate @Text.UnicodeException forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
Text.decodeUtf16LE forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall source target. From source target => source -> target
From.from

-- | Converts via 'Text.Text'.
instance TryFrom.TryFrom (Encoding.UTF_16LE ByteString.ByteString) LazyText.Text where
  tryFrom :: UTF_16LE ByteString
-> Either (TryFromException (UTF_16LE ByteString) Text) Text
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall target source. From source target => source -> target
Utility.into @LazyText.Text) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall target source.
TryFrom source target =>
source -> Either (TryFromException source target) target
Utility.tryInto @Text.Text

-- | Converts via 'Text.Text'.
instance TryFrom.TryFrom (Encoding.UTF_16LE ByteString.ByteString) String where
  tryFrom :: UTF_16LE ByteString
-> Either (TryFromException (UTF_16LE ByteString) String) String
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall target source. From source target => source -> target
Utility.into @String) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall target source.
TryFrom source target =>
source -> Either (TryFromException source target) target
Utility.tryInto @Text.Text

-- | Uses 'LazyText.decodeUtf16LE'.
instance TryFrom.TryFrom (Encoding.UTF_16LE LazyByteString.ByteString) LazyText.Text where
  tryFrom :: UTF_16LE ByteString
-> Either (TryFromException (UTF_16LE ByteString) Text) Text
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ forall e a. Exception e => a -> Either e a
tryEvaluate @Text.UnicodeException forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
LazyText.decodeUtf16LE forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall source target. From source target => source -> target
From.from

-- | Converts via 'LazyText.Text'.
instance TryFrom.TryFrom (Encoding.UTF_16LE LazyByteString.ByteString) Text.Text where
  tryFrom :: UTF_16LE ByteString
-> Either (TryFromException (UTF_16LE ByteString) Text) Text
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall target source. From source target => source -> target
Utility.into @Text.Text) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall target source.
TryFrom source target =>
source -> Either (TryFromException source target) target
Utility.tryInto @LazyText.Text

-- | Converts via 'LazyText.Text'.
instance TryFrom.TryFrom (Encoding.UTF_16LE LazyByteString.ByteString) String where
  tryFrom :: UTF_16LE ByteString
-> Either (TryFromException (UTF_16LE ByteString) String) String
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall target source. From source target => source -> target
Utility.into @String) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall target source.
TryFrom source target =>
source -> Either (TryFromException source target) target
Utility.tryInto @LazyText.Text

-- | Uses 'Text.encodeUtf16LE'.
instance From.From Text.Text (Encoding.UTF_16LE ByteString.ByteString) where
  from :: Text -> UTF_16LE ByteString
from = forall source target. From source target => source -> target
From.from forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
Text.encodeUtf16LE

-- | Converts via 'ByteString.ByteString'.
instance From.From Text.Text (Encoding.UTF_16LE LazyByteString.ByteString) where
  from :: Text -> UTF_16LE ByteString
from = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall source target. From source target => source -> target
From.from forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall target source. From source target => source -> target
Utility.into @(Encoding.UTF_16LE ByteString.ByteString)

-- | Uses 'LazyText.encodeUtf16LE'.
instance From.From LazyText.Text (Encoding.UTF_16LE LazyByteString.ByteString) where
  from :: Text -> UTF_16LE ByteString
from = forall source target. From source target => source -> target
From.from forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
LazyText.encodeUtf16LE

-- | Converts via 'LazyByteString.ByteString'.
instance From.From LazyText.Text (Encoding.UTF_16LE ByteString.ByteString) where
  from :: Text -> UTF_16LE ByteString
from = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall source target. From source target => source -> target
From.from forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall target source. From source target => source -> target
Utility.into @(Encoding.UTF_16LE LazyByteString.ByteString)

-- | Converts via 'Text.Text'.
instance From.From String (Encoding.UTF_16LE ByteString.ByteString) where
  from :: String -> UTF_16LE ByteString
from = forall through source target.
(From source through, From through target) =>
source -> target
Utility.via @Text.Text

-- | Converts via 'LazyText.Text'.
instance From.From String (Encoding.UTF_16LE LazyByteString.ByteString) where
  from :: String -> UTF_16LE ByteString
from = forall through source target.
(From source through, From through target) =>
source -> target
Utility.via @LazyText.Text

-- UTF-16BE

-- | Uses 'Text.decodeUtf16BE'.
instance TryFrom.TryFrom (Encoding.UTF_16BE ByteString.ByteString) Text.Text where
  tryFrom :: UTF_16BE ByteString
-> Either (TryFromException (UTF_16BE ByteString) Text) Text
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ forall e a. Exception e => a -> Either e a
tryEvaluate @Text.UnicodeException forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
Text.decodeUtf16BE forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall source target. From source target => source -> target
From.from

-- | Converts via 'Text.Text'.
instance TryFrom.TryFrom (Encoding.UTF_16BE ByteString.ByteString) LazyText.Text where
  tryFrom :: UTF_16BE ByteString
-> Either (TryFromException (UTF_16BE ByteString) Text) Text
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall target source. From source target => source -> target
Utility.into @LazyText.Text) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall target source.
TryFrom source target =>
source -> Either (TryFromException source target) target
Utility.tryInto @Text.Text

-- | Converts via 'Text.Text'.
instance TryFrom.TryFrom (Encoding.UTF_16BE ByteString.ByteString) String where
  tryFrom :: UTF_16BE ByteString
-> Either (TryFromException (UTF_16BE ByteString) String) String
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall target source. From source target => source -> target
Utility.into @String) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall target source.
TryFrom source target =>
source -> Either (TryFromException source target) target
Utility.tryInto @Text.Text

-- | Uses 'LazyText.decodeUtf16BE'.
instance TryFrom.TryFrom (Encoding.UTF_16BE LazyByteString.ByteString) LazyText.Text where
  tryFrom :: UTF_16BE ByteString
-> Either (TryFromException (UTF_16BE ByteString) Text) Text
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ forall e a. Exception e => a -> Either e a
tryEvaluate @Text.UnicodeException forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
LazyText.decodeUtf16BE forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall source target. From source target => source -> target
From.from

-- | Converts via 'LazyText.Text'.
instance TryFrom.TryFrom (Encoding.UTF_16BE LazyByteString.ByteString) Text.Text where
  tryFrom :: UTF_16BE ByteString
-> Either (TryFromException (UTF_16BE ByteString) Text) Text
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall target source. From source target => source -> target
Utility.into @Text.Text) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall target source.
TryFrom source target =>
source -> Either (TryFromException source target) target
Utility.tryInto @LazyText.Text

-- | Converts via 'LazyText.Text'.
instance TryFrom.TryFrom (Encoding.UTF_16BE LazyByteString.ByteString) String where
  tryFrom :: UTF_16BE ByteString
-> Either (TryFromException (UTF_16BE ByteString) String) String
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall target source. From source target => source -> target
Utility.into @String) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall target source.
TryFrom source target =>
source -> Either (TryFromException source target) target
Utility.tryInto @LazyText.Text

-- | Uses 'Text.encodeUtf16BE'.
instance From.From Text.Text (Encoding.UTF_16BE ByteString.ByteString) where
  from :: Text -> UTF_16BE ByteString
from = forall source target. From source target => source -> target
From.from forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
Text.encodeUtf16BE

-- | Converts via 'ByteString.ByteString'.
instance From.From Text.Text (Encoding.UTF_16BE LazyByteString.ByteString) where
  from :: Text -> UTF_16BE ByteString
from = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall source target. From source target => source -> target
From.from forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall target source. From source target => source -> target
Utility.into @(Encoding.UTF_16BE ByteString.ByteString)

-- | Uses 'LazyText.encodeUtf16BE'.
instance From.From LazyText.Text (Encoding.UTF_16BE LazyByteString.ByteString) where
  from :: Text -> UTF_16BE ByteString
from = forall source target. From source target => source -> target
From.from forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
LazyText.encodeUtf16BE

-- | Converts via 'LazyByteString.ByteString'.
instance From.From LazyText.Text (Encoding.UTF_16BE ByteString.ByteString) where
  from :: Text -> UTF_16BE ByteString
from = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall source target. From source target => source -> target
From.from forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall target source. From source target => source -> target
Utility.into @(Encoding.UTF_16BE LazyByteString.ByteString)

-- | Converts via 'Text.Text'.
instance From.From String (Encoding.UTF_16BE ByteString.ByteString) where
  from :: String -> UTF_16BE ByteString
from = forall through source target.
(From source through, From through target) =>
source -> target
Utility.via @Text.Text

-- | Converts via 'LazyText.Text'.
instance From.From String (Encoding.UTF_16BE LazyByteString.ByteString) where
  from :: String -> UTF_16BE ByteString
from = forall through source target.
(From source through, From through target) =>
source -> target
Utility.via @LazyText.Text

-- UTF-32LE

-- | Uses 'Text.decodeUtf32LE'.
instance TryFrom.TryFrom (Encoding.UTF_32LE ByteString.ByteString) Text.Text where
  tryFrom :: UTF_32LE ByteString
-> Either (TryFromException (UTF_32LE ByteString) Text) Text
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ forall e a. Exception e => a -> Either e a
tryEvaluate @Text.UnicodeException forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
Text.decodeUtf32LE forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall source target. From source target => source -> target
From.from

-- | Converts via 'Text.Text'.
instance TryFrom.TryFrom (Encoding.UTF_32LE ByteString.ByteString) LazyText.Text where
  tryFrom :: UTF_32LE ByteString
-> Either (TryFromException (UTF_32LE ByteString) Text) Text
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall target source. From source target => source -> target
Utility.into @LazyText.Text) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall target source.
TryFrom source target =>
source -> Either (TryFromException source target) target
Utility.tryInto @Text.Text

-- | Converts via 'Text.Text'.
instance TryFrom.TryFrom (Encoding.UTF_32LE ByteString.ByteString) String where
  tryFrom :: UTF_32LE ByteString
-> Either (TryFromException (UTF_32LE ByteString) String) String
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall target source. From source target => source -> target
Utility.into @String) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall target source.
TryFrom source target =>
source -> Either (TryFromException source target) target
Utility.tryInto @Text.Text

-- | Uses 'LazyText.decodeUtf32LE'.
instance TryFrom.TryFrom (Encoding.UTF_32LE LazyByteString.ByteString) LazyText.Text where
  tryFrom :: UTF_32LE ByteString
-> Either (TryFromException (UTF_32LE ByteString) Text) Text
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ forall e a. Exception e => a -> Either e a
tryEvaluate @Text.UnicodeException forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
LazyText.decodeUtf32LE forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall source target. From source target => source -> target
From.from

-- | Converts via 'LazyText.Text'.
instance TryFrom.TryFrom (Encoding.UTF_32LE LazyByteString.ByteString) Text.Text where
  tryFrom :: UTF_32LE ByteString
-> Either (TryFromException (UTF_32LE ByteString) Text) Text
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall target source. From source target => source -> target
Utility.into @Text.Text) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall target source.
TryFrom source target =>
source -> Either (TryFromException source target) target
Utility.tryInto @LazyText.Text

-- | Converts via 'LazyText.Text'.
instance TryFrom.TryFrom (Encoding.UTF_32LE LazyByteString.ByteString) String where
  tryFrom :: UTF_32LE ByteString
-> Either (TryFromException (UTF_32LE ByteString) String) String
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall target source. From source target => source -> target
Utility.into @String) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall target source.
TryFrom source target =>
source -> Either (TryFromException source target) target
Utility.tryInto @LazyText.Text

-- | Uses 'Text.encodeUtf32LE'.
instance From.From Text.Text (Encoding.UTF_32LE ByteString.ByteString) where
  from :: Text -> UTF_32LE ByteString
from = forall source target. From source target => source -> target
From.from forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
Text.encodeUtf32LE

-- | Converts via 'ByteString.ByteString'.
instance From.From Text.Text (Encoding.UTF_32LE LazyByteString.ByteString) where
  from :: Text -> UTF_32LE ByteString
from = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall source target. From source target => source -> target
From.from forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall target source. From source target => source -> target
Utility.into @(Encoding.UTF_32LE ByteString.ByteString)

-- | Uses 'LazyText.encodeUtf32LE'.
instance From.From LazyText.Text (Encoding.UTF_32LE LazyByteString.ByteString) where
  from :: Text -> UTF_32LE ByteString
from = forall source target. From source target => source -> target
From.from forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
LazyText.encodeUtf32LE

-- | Converts via 'LazyByteString.ByteString'.
instance From.From LazyText.Text (Encoding.UTF_32LE ByteString.ByteString) where
  from :: Text -> UTF_32LE ByteString
from = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall source target. From source target => source -> target
From.from forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall target source. From source target => source -> target
Utility.into @(Encoding.UTF_32LE LazyByteString.ByteString)

-- | Converts via 'Text.Text'.
instance From.From String (Encoding.UTF_32LE ByteString.ByteString) where
  from :: String -> UTF_32LE ByteString
from = forall through source target.
(From source through, From through target) =>
source -> target
Utility.via @Text.Text

-- | Converts via 'LazyText.Text'.
instance From.From String (Encoding.UTF_32LE LazyByteString.ByteString) where
  from :: String -> UTF_32LE ByteString
from = forall through source target.
(From source through, From through target) =>
source -> target
Utility.via @LazyText.Text

-- UTF-32BE

-- | Uses 'Text.decodeUtf32BE'.
instance TryFrom.TryFrom (Encoding.UTF_32BE ByteString.ByteString) Text.Text where
  tryFrom :: UTF_32BE ByteString
-> Either (TryFromException (UTF_32BE ByteString) Text) Text
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ forall e a. Exception e => a -> Either e a
tryEvaluate @Text.UnicodeException forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
Text.decodeUtf32BE forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall source target. From source target => source -> target
From.from

-- | Converts via 'Text.Text'.
instance TryFrom.TryFrom (Encoding.UTF_32BE ByteString.ByteString) LazyText.Text where
  tryFrom :: UTF_32BE ByteString
-> Either (TryFromException (UTF_32BE ByteString) Text) Text
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall target source. From source target => source -> target
Utility.into @LazyText.Text) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall target source.
TryFrom source target =>
source -> Either (TryFromException source target) target
Utility.tryInto @Text.Text

-- | Converts via 'Text.Text'.
instance TryFrom.TryFrom (Encoding.UTF_32BE ByteString.ByteString) String where
  tryFrom :: UTF_32BE ByteString
-> Either (TryFromException (UTF_32BE ByteString) String) String
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall target source. From source target => source -> target
Utility.into @String) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall target source.
TryFrom source target =>
source -> Either (TryFromException source target) target
Utility.tryInto @Text.Text

-- | Uses 'LazyText.decodeUtf32BE'.
instance TryFrom.TryFrom (Encoding.UTF_32BE LazyByteString.ByteString) LazyText.Text where
  tryFrom :: UTF_32BE ByteString
-> Either (TryFromException (UTF_32BE ByteString) Text) Text
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ forall e a. Exception e => a -> Either e a
tryEvaluate @Text.UnicodeException forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
LazyText.decodeUtf32BE forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall source target. From source target => source -> target
From.from

-- | Converts via 'LazyText.Text'.
instance TryFrom.TryFrom (Encoding.UTF_32BE LazyByteString.ByteString) Text.Text where
  tryFrom :: UTF_32BE ByteString
-> Either (TryFromException (UTF_32BE ByteString) Text) Text
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall target source. From source target => source -> target
Utility.into @Text.Text) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall target source.
TryFrom source target =>
source -> Either (TryFromException source target) target
Utility.tryInto @LazyText.Text

-- | Converts via 'LazyText.Text'.
instance TryFrom.TryFrom (Encoding.UTF_32BE LazyByteString.ByteString) String where
  tryFrom :: UTF_32BE ByteString
-> Either (TryFromException (UTF_32BE ByteString) String) String
tryFrom = forall exception source target.
Exception exception =>
(source -> Either exception target)
-> source -> Either (TryFromException source target) target
Utility.eitherTryFrom forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall target source. From source target => source -> target
Utility.into @String) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall target source.
TryFrom source target =>
source -> Either (TryFromException source target) target
Utility.tryInto @LazyText.Text

-- | Uses 'Text.encodeUtf32BE'.
instance From.From Text.Text (Encoding.UTF_32BE ByteString.ByteString) where
  from :: Text -> UTF_32BE ByteString
from = forall source target. From source target => source -> target
From.from forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
Text.encodeUtf32BE

-- | Converts via 'ByteString.ByteString'.
instance From.From Text.Text (Encoding.UTF_32BE LazyByteString.ByteString) where
  from :: Text -> UTF_32BE ByteString
from = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall source target. From source target => source -> target
From.from forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall target source. From source target => source -> target
Utility.into @(Encoding.UTF_32BE ByteString.ByteString)

-- | Uses 'LazyText.encodeUtf32BE'.
instance From.From LazyText.Text (Encoding.UTF_32BE LazyByteString.ByteString) where
  from :: Text -> UTF_32BE ByteString
from = forall source target. From source target => source -> target
From.from forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
LazyText.encodeUtf32BE

-- | Converts via 'LazyByteString.ByteString'.
instance From.From LazyText.Text (Encoding.UTF_32BE ByteString.ByteString) where
  from :: Text -> UTF_32BE ByteString
from = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall source target. From source target => source -> target
From.from forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall target source. From source target => source -> target
Utility.into @(Encoding.UTF_32BE LazyByteString.ByteString)

-- | Converts via 'Text.Text'.
instance From.From String (Encoding.UTF_32BE ByteString.ByteString) where
  from :: String -> UTF_32BE ByteString
from = forall through source target.
(From source through, From through target) =>
source -> target
Utility.via @Text.Text

-- | Converts via 'LazyText.Text'.
instance From.From String (Encoding.UTF_32BE LazyByteString.ByteString) where
  from :: String -> UTF_32BE ByteString
from = forall through source target.
(From source through, From through target) =>
source -> target
Utility.via @LazyText.Text

--

realFloatToRational ::
  (RealFloat s) => s -> Either Exception.ArithException Rational
realFloatToRational :: forall s. RealFloat s => s -> Either ArithException Rational
realFloatToRational s
s
  | forall a. RealFloat a => a -> Bool
isNaN s
s = forall a b. a -> Either a b
Left ArithException
Exception.LossOfPrecision
  | forall a. RealFloat a => a -> Bool
isInfinite s
s =
      if s
s forall a. Ord a => a -> a -> Bool
> s
0
        then forall a b. a -> Either a b
Left ArithException
Exception.Overflow
        else forall a b. a -> Either a b
Left ArithException
Exception.Underflow
  | Bool
otherwise =
      forall a b. b -> Either a b
Right forall a b. (a -> b) -> a -> b
$
        forall a b. (Eq a, Num a, Num b) => (a -> b) -> a -> b
overPositive
          (forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Integer -> Integer -> Rational
makeRational forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry [Int] -> Int -> (Integer, Integer)
fromDigits forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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 :: forall a b. (Eq a, Num a, Num b) => (a -> b) -> a -> b
overPositive a -> b
f a
x = if forall a. Num a => a -> a
signum a
x 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 =
  forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
List.foldl' (\(Integer
a, Integer
n) Int
d -> (Integer
a forall a. Num a => a -> a -> a
* Integer
10 forall a. Num a => a -> a -> a
+ forall a. Integral a => a -> Integer
toInteger Int
d, Integer
n forall a. Num a => a -> a -> a
- Integer
1)) (Integer
0, forall a. Integral a => a -> Integer
toInteger Int
e) [Int]
ds

makeRational :: Integer -> Integer -> Rational
makeRational :: Integer -> Integer -> Rational
makeRational Integer
d Integer
e = forall a. Real a => a -> Rational
toRational Integer
d forall a. Num a => a -> a -> a
* Rational
10 forall a b. (Fractional a, Integral b) => a -> b -> a
^^ Integer
e

fromNonNegativeIntegral ::
  (Integral s, Num t) => s -> Either Exception.ArithException t
fromNonNegativeIntegral :: forall s t. (Integral s, Num t) => s -> Either ArithException t
fromNonNegativeIntegral s
x =
  if s
x forall a. Ord a => a -> a -> Bool
< s
0 then forall a b. a -> Either a b
Left ArithException
Exception.Underflow else forall a b. b -> Either a b
Right forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral s
x

-- | The maximum integral value that can be unambiguously represented as a
-- 'Float'. Equal to 16,777,215.
maxFloat :: (Num a) => a
maxFloat :: forall a. Num a => a
maxFloat = a
16777215

-- | The maximum integral value that can be unambiguously represented as a
-- 'Double'. Equal to 9,007,199,254,740,991.
maxDouble :: (Num a) => a
maxDouble :: forall a. Num a => a
maxDouble = a
9007199254740991

tryEvaluate :: (Exception.Exception e) => a -> Either e a
tryEvaluate :: forall e a. Exception e => a -> Either e a
tryEvaluate = forall a. IO a -> a
Unsafe.unsafePerformIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e a. Exception e => IO a -> IO (Either e a)
Exception.try forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> IO a
Exception.evaluate