witch-0.1.1.0: Convert values from one type into another.
Safe HaskellNone
LanguageHaskell2010

Witch.Instances

Synopsis

Documentation

maybeTryCast :: (s -> Maybe t) -> s -> Either (TryCastException s t) t Source #

maxFloat :: Num a => a Source #

The maximum integral value that can be unambiguously represented as a Float. Equal to 16,777,215.

maxDouble :: Num a => a Source #

The maximum integral value that can be unambiguously represented as a Double. Equal to 9,007,199,254,740,991.

Orphan instances

Cast Double Float Source #

Uses realToFrac. This necessarily loses some precision.

Instance details

Methods

cast :: Double -> Float Source #

Cast Float Double Source #

Uses realToFrac.

Instance details

Methods

cast :: Float -> Double Source #

Cast Int Int64 Source #

Uses fromIntegral.

Instance details

Methods

cast :: Int -> Int64 Source #

Cast Int Integer Source #

Uses fromIntegral.

Instance details

Methods

cast :: Int -> Integer Source #

Cast Int8 Double Source #

Uses fromIntegral.

Instance details

Methods

cast :: Int8 -> Double Source #

Cast Int8 Float Source #

Uses fromIntegral.

Instance details

Methods

cast :: Int8 -> Float Source #

Cast Int8 Int Source #

Uses fromIntegral.

Instance details

Methods

cast :: Int8 -> Int Source #

Cast Int8 Int16 Source #

Uses fromIntegral.

Instance details

Methods

cast :: Int8 -> Int16 Source #

Cast Int8 Int32 Source #

Uses fromIntegral.

Instance details

Methods

cast :: Int8 -> Int32 Source #

Cast Int8 Int64 Source #

Uses fromIntegral.

Instance details

Methods

cast :: Int8 -> Int64 Source #

Cast Int8 Integer Source #

Uses fromIntegral.

Instance details

Methods

cast :: Int8 -> Integer Source #

Cast Int16 Double Source #

Uses fromIntegral.

Instance details

Methods

cast :: Int16 -> Double Source #

Cast Int16 Float Source #

Uses fromIntegral.

Instance details

Methods

cast :: Int16 -> Float Source #

Cast Int16 Int Source #

Uses fromIntegral.

Instance details

Methods

cast :: Int16 -> Int Source #

Cast Int16 Int32 Source #

Uses fromIntegral.

Instance details

Methods

cast :: Int16 -> Int32 Source #

Cast Int16 Int64 Source #

Uses fromIntegral.

Instance details

Methods

cast :: Int16 -> Int64 Source #

Cast Int16 Integer Source #

Uses fromIntegral.

Instance details

Methods

cast :: Int16 -> Integer Source #

Cast Int32 Double Source #

Uses fromIntegral.

Instance details

Methods

cast :: Int32 -> Double Source #

Cast Int32 Int64 Source #

Uses fromIntegral.

Instance details

Methods

cast :: Int32 -> Int64 Source #

Cast Int32 Integer Source #

Uses fromIntegral.

Instance details

Methods

cast :: Int32 -> Integer Source #

Cast Int64 Integer Source #

Uses fromIntegral.

Instance details

Methods

cast :: Int64 -> Integer Source #

Cast Natural Integer Source #

Uses fromIntegral.

Instance details

Methods

cast :: Natural -> Integer Source #

Cast Rational Double Source #

Uses fromRational. This necessarily loses some precision.

Instance details

Methods

cast :: Rational -> Double Source #

Cast Rational Float Source #

Uses fromRational. This necessarily loses some precision.

Instance details

Methods

cast :: Rational -> Float Source #

Cast Word Integer Source #

Uses fromIntegral.

Instance details

Methods

cast :: Word -> Integer Source #

Cast Word Natural Source #

Uses fromIntegral.

Instance details

Methods

cast :: Word -> Natural Source #

Cast Word Word64 Source #

Uses fromIntegral.

Instance details

Methods

cast :: Word -> Word64 Source #

Cast Word8 Double Source #

Uses fromIntegral.

Instance details

Methods

cast :: Word8 -> Double Source #

Cast Word8 Float Source #

Uses fromIntegral.

Instance details

Methods

cast :: Word8 -> Float Source #

Cast Word8 Int Source #

Uses fromIntegral.

Instance details

Methods

cast :: Word8 -> Int Source #

Cast Word8 Int16 Source #

Uses fromIntegral.

Instance details

Methods

cast :: Word8 -> Int16 Source #

Cast Word8 Int32 Source #

Uses fromIntegral.

Instance details

Methods

cast :: Word8 -> Int32 Source #

Cast Word8 Int64 Source #

Uses fromIntegral.

Instance details

Methods

cast :: Word8 -> Int64 Source #

Cast Word8 Integer Source #

Uses fromIntegral.

Instance details

Methods

cast :: Word8 -> Integer Source #

Cast Word8 Natural Source #

Uses fromIntegral.

Instance details

Methods

cast :: Word8 -> Natural Source #

Cast Word8 Word Source #

Uses fromIntegral.

Instance details

Methods

cast :: Word8 -> Word Source #

Cast Word8 Word16 Source #

Uses fromIntegral.

Instance details

Methods

cast :: Word8 -> Word16 Source #

Cast Word8 Word32 Source #

Uses fromIntegral.

Instance details

Methods

cast :: Word8 -> Word32 Source #

Cast Word8 Word64 Source #

Uses fromIntegral.

Instance details

Methods

cast :: Word8 -> Word64 Source #

Cast Word16 Double Source #

Uses fromIntegral.

Instance details

Methods

cast :: Word16 -> Double Source #

Cast Word16 Float Source #

Uses fromIntegral.

Instance details

Methods

cast :: Word16 -> Float Source #

Cast Word16 Int Source #

Uses fromIntegral.

Instance details

Methods

cast :: Word16 -> Int Source #

Cast Word16 Int32 Source #

Uses fromIntegral.

Instance details

Methods

cast :: Word16 -> Int32 Source #

Cast Word16 Int64 Source #

Uses fromIntegral.

Instance details

Methods

cast :: Word16 -> Int64 Source #

Cast Word16 Integer Source #

Uses fromIntegral.

Instance details

Methods

cast :: Word16 -> Integer Source #

Cast Word16 Natural Source #

Uses fromIntegral.

Instance details

Methods

cast :: Word16 -> Natural Source #

Cast Word16 Word Source #

Uses fromIntegral.

Instance details

Methods

cast :: Word16 -> Word Source #

Cast Word16 Word32 Source #

Uses fromIntegral.

Instance details

Methods

cast :: Word16 -> Word32 Source #

Cast Word16 Word64 Source #

Uses fromIntegral.

Instance details

Methods

cast :: Word16 -> Word64 Source #

Cast Word32 Double Source #

Uses fromIntegral.

Instance details

Methods

cast :: Word32 -> Double Source #

Cast Word32 Int64 Source #

Uses fromIntegral.

Instance details

Methods

cast :: Word32 -> Int64 Source #

Cast Word32 Integer Source #

Uses fromIntegral.

Instance details

Methods

cast :: Word32 -> Integer Source #

Cast Word32 Natural Source #

Uses fromIntegral.

Instance details

Methods

cast :: Word32 -> Natural Source #

Cast Word32 Word64 Source #

Uses fromIntegral.

Instance details

Methods

cast :: Word32 -> Word64 Source #

Cast Word64 Integer Source #

Uses fromIntegral.

Instance details

Methods

cast :: Word64 -> Integer Source #

Cast Word64 Natural Source #

Uses fromIntegral.

Instance details

Methods

cast :: Word64 -> Natural Source #

Cast String Text Source #

Uses pack. Some Char values cannot be represented in Text and will be replaced with '\xFFFD'.

Instance details

Methods

cast :: String -> Text Source #

Cast String Text Source #

Uses pack. Some Char values cannot be represented in Text and will be replaced with '\xFFFD'.

Instance details

Methods

cast :: String -> Text Source #

Cast ShortByteString ByteString Source #

Uses fromShort.

Instance details

Cast ByteString ByteString Source #

Uses toStrict.

Instance details

Cast ByteString ShortByteString Source #

Uses toShort.

Instance details

Cast ByteString ByteString Source #

Uses fromStrict.

Instance details

Cast Text String Source #

Uses unpack.

Instance details

Methods

cast :: Text -> String Source #

Cast Text ByteString Source #

Uses encodeUtf8.

Instance details

Methods

cast :: Text -> ByteString Source #

Cast Text Text Source #

Uses toStrict.

Instance details

Methods

cast :: Text0 -> Text Source #

Cast Text String Source #

Uses unpack.

Instance details

Methods

cast :: Text -> String Source #

Cast Text ByteString Source #

Uses encodeUtf8.

Instance details

Methods

cast :: Text -> ByteString Source #

Cast Text Text Source #

Uses fromStrict.

Instance details

Methods

cast :: Text -> Text0 Source #

TryCast Double Int Source #

Converts via Integer.

Instance details

TryCast Double Int8 Source #

Converts via Integer.

Instance details

TryCast Double Int16 Source #

Converts via Integer.

Instance details

TryCast Double Int32 Source #

Converts via Integer.

Instance details

TryCast Double Int64 Source #

Converts via Integer.

Instance details

TryCast Double Integer Source #

Converts via Rational when the input is between -9,007,199,254,740,991 and 9,007,199,254,740,991 inclusive.

Instance details

TryCast Double Natural Source #

Converts via Integer.

Instance details

TryCast Double Rational Source #

Uses toRational when the input is not NaN or infinity.

Instance details

TryCast Double Word Source #

Converts via Integer.

Instance details

TryCast Double Word8 Source #

Converts via Integer.

Instance details

TryCast Double Word16 Source #

Converts via Integer.

Instance details

TryCast Double Word32 Source #

Converts via Integer.

Instance details

TryCast Double Word64 Source #

Converts via Integer.

Instance details

TryCast Float Int Source #

Converts via Integer.

Instance details

TryCast Float Int8 Source #

Converts via Integer.

Instance details

TryCast Float Int16 Source #

Converts via Integer.

Instance details

TryCast Float Int32 Source #

Converts via Integer.

Instance details

TryCast Float Int64 Source #

Converts via Integer.

Instance details

TryCast Float Integer Source #

Converts via Rational when the input is between -16,777,215 and 16,777,215 inclusive.

Instance details

TryCast Float Natural Source #

Converts via Integer.

Instance details

TryCast Float Rational Source #

Uses toRational when the input is not NaN or infinity.

Instance details

TryCast Float Word Source #

Converts via Integer.

Instance details

TryCast Float Word8 Source #

Converts via Integer.

Instance details

TryCast Float Word16 Source #

Converts via Integer.

Instance details

TryCast Float Word32 Source #

Converts via Integer.

Instance details

TryCast Float Word64 Source #

Converts via Integer.

Instance details

TryCast Int Double Source #

Uses fromIntegral when the input is between -9,007,199,254,740,991 and 9,007,199,254,740,991 inclusive.

Instance details

TryCast Int Float Source #

Uses fromIntegral when the input is between -16,777,215 and 16,777,215 inclusive.

Instance details

TryCast Int Int8 Source #

Uses toIntegralSized.

Instance details

TryCast Int Int16 Source #

Uses toIntegralSized.

Instance details

TryCast Int Int32 Source #

Uses toIntegralSized.

Instance details

TryCast Int Natural Source #

Uses fromIntegral when the input is non-negative.

Instance details

TryCast Int Word Source #

Uses toIntegralSized.

Instance details

TryCast Int Word8 Source #

Uses toIntegralSized.

Instance details

TryCast Int Word16 Source #

Uses toIntegralSized.

Instance details

TryCast Int Word32 Source #

Uses toIntegralSized.

Instance details

TryCast Int Word64 Source #

Uses toIntegralSized.

Instance details

TryCast Int8 Natural Source #

Uses fromIntegral when the input is non-negative.

Instance details

TryCast Int8 Word Source #

Uses toIntegralSized.

Instance details

TryCast Int8 Word8 Source #

Uses toIntegralSized.

Instance details

TryCast Int8 Word16 Source #

Uses toIntegralSized.

Instance details

TryCast Int8 Word32 Source #

Uses toIntegralSized.

Instance details

TryCast Int8 Word64 Source #

Uses toIntegralSized.

Instance details

TryCast Int16 Int8 Source #

Uses toIntegralSized.

Instance details

TryCast Int16 Natural Source #

Uses fromIntegral when the input is non-negative.

Instance details

TryCast Int16 Word Source #

Uses toIntegralSized.

Instance details

TryCast Int16 Word8 Source #

Uses toIntegralSized.

Instance details

TryCast Int16 Word16 Source #

Uses toIntegralSized.

Instance details

TryCast Int16 Word32 Source #

Uses toIntegralSized.

Instance details

TryCast Int16 Word64 Source #

Uses toIntegralSized.

Instance details

TryCast Int32 Float Source #

Uses fromIntegral when the input is between -16,777,215 and 16,777,215 inclusive.

Instance details

TryCast Int32 Int Source #

Uses toIntegralSized.

Instance details

TryCast Int32 Int8 Source #

Uses toIntegralSized.

Instance details

TryCast Int32 Int16 Source #

Uses toIntegralSized.

Instance details

TryCast Int32 Natural Source #

Uses fromIntegral when the input is non-negative.

Instance details

TryCast Int32 Word Source #

Uses toIntegralSized.

Instance details

TryCast Int32 Word8 Source #

Uses toIntegralSized.

Instance details

TryCast Int32 Word16 Source #

Uses toIntegralSized.

Instance details

TryCast Int32 Word32 Source #

Uses toIntegralSized.

Instance details

TryCast Int32 Word64 Source #

Uses toIntegralSized.

Instance details

TryCast Int64 Double Source #

Uses fromIntegral when the input is between -9,007,199,254,740,991 and 9,007,199,254,740,991 inclusive.

Instance details

TryCast Int64 Float Source #

Uses fromIntegral when the input is between -16,777,215 and 16,777,215 inclusive.

Instance details

TryCast Int64 Int Source #

Uses toIntegralSized.

Instance details

TryCast Int64 Int8 Source #

Uses toIntegralSized.

Instance details

TryCast Int64 Int16 Source #

Uses toIntegralSized.

Instance details

TryCast Int64 Int32 Source #

Uses toIntegralSized.

Instance details

TryCast Int64 Natural Source #

Uses fromIntegral when the input is non-negative.

Instance details

TryCast Int64 Word Source #

Uses toIntegralSized.

Instance details

TryCast Int64 Word8 Source #

Uses toIntegralSized.

Instance details

TryCast Int64 Word16 Source #

Uses toIntegralSized.

Instance details

TryCast Int64 Word32 Source #

Uses toIntegralSized.

Instance details

TryCast Int64 Word64 Source #

Uses toIntegralSized.

Instance details

TryCast Integer Double Source #

Uses fromIntegral when the input is between -9,007,199,254,740,991 and 9,007,199,254,740,991 inclusive.

Instance details

TryCast Integer Float Source #

Uses fromIntegral when the input is between -16,777,215 and 16,777,215 inclusive.

Instance details

TryCast Integer Int Source #

Uses toIntegralSized.

Instance details

TryCast Integer Int8 Source #

Uses toIntegralSized.

Instance details

TryCast Integer Int16 Source #

Uses toIntegralSized.

Instance details

TryCast Integer Int32 Source #

Uses toIntegralSized.

Instance details

TryCast Integer Int64 Source #

Uses toIntegralSized.

Instance details

TryCast Integer Natural Source #

Uses fromInteger when the input is non-negative.

Instance details

TryCast Integer Word Source #

Uses toIntegralSized.

Instance details

TryCast Integer Word8 Source #

Uses toIntegralSized.

Instance details

TryCast Integer Word16 Source #

Uses toIntegralSized.

Instance details

TryCast Integer Word32 Source #

Uses toIntegralSized.

Instance details

TryCast Integer Word64 Source #

Uses toIntegralSized.

Instance details

TryCast Natural Double Source #

Uses fromIntegral when the input is between -9,007,199,254,740,991 and 9,007,199,254,740,991 inclusive.

Instance details

TryCast Natural Float Source #

Uses fromIntegral when the input is between -16,777,215 and 16,777,215 inclusive.

Instance details

TryCast Natural Int Source #

Uses toIntegralSized.

Instance details

TryCast Natural Int8 Source #

Uses toIntegralSized.

Instance details

TryCast Natural Int16 Source #

Uses toIntegralSized.

Instance details

TryCast Natural Int32 Source #

Uses toIntegralSized.

Instance details

TryCast Natural Int64 Source #

Uses toIntegralSized.

Instance details

TryCast Natural Word Source #

Uses toIntegralSized.

Instance details

TryCast Natural Word8 Source #

Uses toIntegralSized.

Instance details

TryCast Natural Word16 Source #

Uses toIntegralSized.

Instance details

TryCast Natural Word32 Source #

Uses toIntegralSized.

Instance details

TryCast Natural Word64 Source #

Uses toIntegralSized.

Instance details

TryCast Word Double Source #

Uses fromIntegral when the input is between -9,007,199,254,740,991 and 9,007,199,254,740,991 inclusive.

Instance details

TryCast Word Float Source #

Uses fromIntegral when the input is between -16,777,215 and 16,777,215 inclusive.

Instance details

TryCast Word Int Source #

Uses toIntegralSized.

Instance details

TryCast Word Int8 Source #

Uses toIntegralSized.

Instance details

TryCast Word Int16 Source #

Uses toIntegralSized.

Instance details

TryCast Word Int32 Source #

Uses toIntegralSized.

Instance details

TryCast Word Int64 Source #

Uses toIntegralSized.

Instance details

TryCast Word Word8 Source #

Uses toIntegralSized.

Instance details

TryCast Word Word16 Source #

Uses toIntegralSized.

Instance details

TryCast Word Word32 Source #

Uses toIntegralSized.

Instance details

TryCast Word8 Int8 Source #

Uses toIntegralSized.

Instance details

TryCast Word16 Int8 Source #

Uses toIntegralSized.

Instance details

TryCast Word16 Int16 Source #

Uses toIntegralSized.

Instance details

TryCast Word16 Word8 Source #

Uses toIntegralSized.

Instance details

TryCast Word32 Float Source #

Uses fromIntegral when the input is between -16,777,215 and 16,777,215 inclusive.

Instance details

TryCast Word32 Int Source #

Uses toIntegralSized.

Instance details

TryCast Word32 Int8 Source #

Uses toIntegralSized.

Instance details

TryCast Word32 Int16 Source #

Uses toIntegralSized.

Instance details

TryCast Word32 Int32 Source #

Uses toIntegralSized.

Instance details

TryCast Word32 Word Source #

Uses toIntegralSized.

Instance details

TryCast Word32 Word8 Source #

Uses toIntegralSized.

Instance details

TryCast Word32 Word16 Source #

Uses toIntegralSized.

Instance details

TryCast Word64 Double Source #

Uses fromIntegral when the input is between -9,007,199,254,740,991 and 9,007,199,254,740,991 inclusive.

Instance details

TryCast Word64 Float Source #

Uses fromIntegral when the input is between -16,777,215 and 16,777,215 inclusive.

Instance details

TryCast Word64 Int Source #

Uses toIntegralSized.

Instance details

TryCast Word64 Int8 Source #

Uses toIntegralSized.

Instance details

TryCast Word64 Int16 Source #

Uses toIntegralSized.

Instance details

TryCast Word64 Int32 Source #

Uses toIntegralSized.

Instance details

TryCast Word64 Int64 Source #

Uses toIntegralSized.

Instance details

TryCast Word64 Word Source #

Uses toIntegralSized.

Instance details

TryCast Word64 Word8 Source #

Uses toIntegralSized.

Instance details

TryCast Word64 Word16 Source #

Uses toIntegralSized.

Instance details

TryCast Word64 Word32 Source #

Uses toIntegralSized.

Instance details

TryCast ByteString Text Source #

Uses decodeUtf8'.

Instance details

TryCast ByteString Text Source #

Uses decodeUtf8'.

Instance details

Num a => Cast a (Complex a) Source #

Uses (:+) with an imaginary part of 0.

Instance details

Methods

cast :: a -> Complex a Source #

Integral a => Cast a (Ratio a) Source #

Uses (%) with a denominator of 1.

Instance details

Methods

cast :: a -> Ratio a Source #

Cast ShortByteString [Word8] Source #

Uses unpack.

Instance details

Cast ByteString [Word8] Source #

Uses unpack.

Instance details

Methods

cast :: ByteString -> [Word8] Source #

Cast ByteString [Word8] Source #

Uses unpack.

Instance details

Methods

cast :: ByteString -> [Word8] Source #

Cast IntSet [Int] Source #

Uses toAscList.

Instance details

Methods

cast :: IntSet -> [Int] Source #

Cast Integer (Fixed a) Source #

Uses MkFixed. This means cast 2 :: Centi is 0.02 rather than 2.00.

Instance details

Methods

cast :: Integer -> Fixed a Source #

Cast [Int] IntSet Source #

Uses fromList.

Instance details

Methods

cast :: [Int] -> IntSet Source #

Cast [Word8] ShortByteString Source #

Uses pack.

Instance details

Cast [Word8] ByteString Source #

Uses pack.

Instance details

Methods

cast :: [Word8] -> ByteString Source #

Cast [Word8] ByteString Source #

Uses pack.

Instance details

Methods

cast :: [Word8] -> ByteString Source #

(Eq a, Num a) => TryCast (Ratio a) a Source #

Uses numerator when the denominator is 1.

Instance details

Methods

tryCast :: Ratio a -> Either (TryCastException (Ratio a) a) a Source #

(Eq a, Num a) => TryCast (Complex a) a Source #

Uses realPart when the imaginary part is 0.

Instance details

Cast [(Int, v)] (IntMap v) Source #

Uses fromList. If there are duplicate keys, later values will overwrite earlier ones.

Instance details

Methods

cast :: [(Int, v)] -> IntMap v Source #

Cast [a] (Seq a) Source #

Uses fromList.

Instance details

Methods

cast :: [a] -> Seq a Source #

Ord a => Cast [a] (Set a) Source #

Uses fromList.

Instance details

Methods

cast :: [a] -> Set a Source #

Cast (NonEmpty a) [a] Source #

Uses toList.

Instance details

Methods

cast :: NonEmpty a -> [a] Source #

Cast (IntMap v) [(Int, v)] Source #

Uses toAscList.

Instance details

Methods

cast :: IntMap v -> [(Int, v)] Source #

Cast (Seq a) [a] Source #

Uses toList.

Instance details

Methods

cast :: Seq a -> [a] Source #

Cast (Set a) [a] Source #

Uses toAscList.

Instance details

Methods

cast :: Set a -> [a] Source #

TryCast [a] (NonEmpty a) Source #

Uses nonEmpty.

Instance details

Methods

tryCast :: [a] -> Either (TryCastException [a] (NonEmpty a)) (NonEmpty a) Source #

Ord k => Cast [(k, v)] (Map k v) Source #

Uses fromList. If there are duplicate keys, later values will overwrite earlier ones.

Instance details

Methods

cast :: [(k, v)] -> Map k v Source #

Cast (Fixed a) Integer Source #

Uses MkFixed. This means cast (3.00 :: Centi) is 300 rather than 3.

Instance details

Methods

cast :: Fixed a -> Integer Source #

Cast (Map k v) [(k, v)] Source #

Uses toAscList.

Instance details

Methods

cast :: Map k v -> [(k, v)] Source #

Cast (TryCastException s t0) (TryCastException s t1) Source # 
Instance details