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

Witch.From

Synopsis
  • class From source target where
    • from :: source -> target

Documentation

class From source target where Source #

This type class is for converting values from some source type into some other target type. The constraint From source target means that you can convert from a value of type source into a value of type target.

This type class is for conversions that always succeed. If your conversion sometimes fails, consider implementing TryFrom instead.

Minimal complete definition

Nothing

Methods

from :: source -> target Source #

This method implements the conversion of a value between types. At call sites you may prefer to use into instead.

-- Avoid this:
from (x :: s)

-- Prefer this:
from @s x

The default implementation of this method simply calls coerce, which works for types that have the same runtime representation. This means that for newtypes you do not need to implement this method at all. For example:

>>> newtype Name = Name String
>>> instance From Name String
>>> instance From String Name

default from :: Coercible source target => source -> target Source #

Instances

Instances details
From Double Float Source #

Uses double2Float. This necessarily loses some precision.

Instance details

Defined in Witch.Instances

Methods

from :: Double -> Float Source #

From Float Double Source #

Uses float2Double.

Instance details

Defined in Witch.Instances

Methods

from :: Float -> Double Source #

From Int Int64 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Int -> Int64 Source #

From Int Integer Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Int -> Integer Source #

From Int8 Double Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Int8 -> Double Source #

From Int8 Float Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Int8 -> Float Source #

From Int8 Int Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Int8 -> Int Source #

From Int8 Int16 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Int8 -> Int16 Source #

From Int8 Int32 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Int8 -> Int32 Source #

From Int8 Int64 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Int8 -> Int64 Source #

From Int8 Integer Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Int8 -> Integer Source #

From Int16 Double Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Int16 -> Double Source #

From Int16 Float Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Int16 -> Float Source #

From Int16 Int Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Int16 -> Int Source #

From Int16 Int32 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Int16 -> Int32 Source #

From Int16 Int64 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Int16 -> Int64 Source #

From Int16 Integer Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Int16 -> Integer Source #

From Int32 Double Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Int32 -> Double Source #

From Int32 Int64 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Int32 -> Int64 Source #

From Int32 Integer Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Int32 -> Integer Source #

From Int64 Integer Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Int64 -> Integer Source #

From Integer Day Source #

Uses ModifiedJulianDay.

Instance details

Defined in Witch.Instances

Methods

from :: Integer -> Day Source #

From Natural Integer Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Natural -> Integer Source #

From Rational Double Source #

Uses fromRational. This necessarily loses some precision.

Instance details

Defined in Witch.Instances

Methods

from :: Rational -> Double Source #

From Rational Float Source #

Uses fromRational. This necessarily loses some precision.

Instance details

Defined in Witch.Instances

Methods

from :: Rational -> Float Source #

From Rational TimeOfDay Source #

Uses dayFractionToTimeOfDay.

Instance details

Defined in Witch.Instances

From Rational UniversalTime Source #

Uses ModJulianDate.

Instance details

Defined in Witch.Instances

From Word Integer Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word -> Integer Source #

From Word Natural Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word -> Natural Source #

From Word Word64 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word -> Word64 Source #

From Word8 Double Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word8 -> Double Source #

From Word8 Float Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word8 -> Float Source #

From Word8 Int Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word8 -> Int Source #

From Word8 Int16 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word8 -> Int16 Source #

From Word8 Int32 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word8 -> Int32 Source #

From Word8 Int64 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word8 -> Int64 Source #

From Word8 Integer Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word8 -> Integer Source #

From Word8 Natural Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word8 -> Natural Source #

From Word8 Word Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word8 -> Word Source #

From Word8 Word16 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word8 -> Word16 Source #

From Word8 Word32 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word8 -> Word32 Source #

From Word8 Word64 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word8 -> Word64 Source #

From Word16 Double Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word16 -> Double Source #

From Word16 Float Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word16 -> Float Source #

From Word16 Int Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word16 -> Int Source #

From Word16 Int32 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word16 -> Int32 Source #

From Word16 Int64 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word16 -> Int64 Source #

From Word16 Integer Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word16 -> Integer Source #

From Word16 Natural Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word16 -> Natural Source #

From Word16 Word Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word16 -> Word Source #

From Word16 Word32 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word16 -> Word32 Source #

From Word16 Word64 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word16 -> Word64 Source #

From Word32 Double Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word32 -> Double Source #

From Word32 Int64 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word32 -> Int64 Source #

From Word32 Integer Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word32 -> Integer Source #

From Word32 Natural Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word32 -> Natural Source #

From Word32 Word64 Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word32 -> Word64 Source #

From Word64 Integer Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word64 -> Integer Source #

From Word64 Natural Source #

Uses fromIntegral.

Instance details

Defined in Witch.Instances

Methods

from :: Word64 -> Natural Source #

From a a Source #

Uses id.

Instance details

Defined in Witch.Instances

Methods

from :: a -> a Source #

From Pico NominalDiffTime Source #

Uses secondsToNominalDiffTime.

Instance details

Defined in Witch.Instances

From Pico DiffTime Source #

Uses realToFrac.

Instance details

Defined in Witch.Instances

Methods

from :: Pico -> DiffTime Source #

From String ByteString Source #

Converts via Text.

Instance details

Defined in Witch.Instances

From String ByteString Source #

Converts via Text.

Instance details

Defined in Witch.Instances

From String Text Source #

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

Instance details

Defined in Witch.Instances

Methods

from :: String -> Text Source #

From String Text Source #

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

Instance details

Defined in Witch.Instances

Methods

from :: String -> Text Source #

From ShortByteString ByteString Source #

Uses fromShort.

Instance details

Defined in Witch.Instances

From ByteString ByteString Source #

Uses toStrict.

Instance details

Defined in Witch.Instances

From ByteString ShortByteString Source #

Uses toShort.

Instance details

Defined in Witch.Instances

From ByteString ByteString Source #

Uses fromStrict.

Instance details

Defined in Witch.Instances

From Text String Source #

Uses unpack.

Instance details

Defined in Witch.Instances

Methods

from :: Text -> String Source #

From Text ByteString Source #

Uses encodeUtf8.

Instance details

Defined in Witch.Instances

Methods

from :: Text -> ByteString Source #

From Text ByteString Source #

Converts via ByteString.

Instance details

Defined in Witch.Instances

Methods

from :: Text -> ByteString Source #

From Text Text Source #

Uses toStrict.

Instance details

Defined in Witch.Instances

Methods

from :: Text0 -> Text Source #

From Text String Source #

Uses unpack.

Instance details

Defined in Witch.Instances

Methods

from :: Text -> String Source #

From Text ByteString Source #

Converts via ByteString.

Instance details

Defined in Witch.Instances

Methods

from :: Text -> ByteString Source #

From Text ByteString Source #

Uses encodeUtf8.

Instance details

Defined in Witch.Instances

Methods

from :: Text -> ByteString Source #

From Text Text Source #

Uses fromStrict.

Instance details

Defined in Witch.Instances

Methods

from :: Text -> Text0 Source #

From ZonedTime UTCTime Source #

Uses zonedTimeToUTC.

Instance details

Defined in Witch.Instances

From TimeOfDay Rational Source #

Uses timeOfDayToDayFraction.

Instance details

Defined in Witch.Instances

From TimeOfDay DiffTime Source #

Uses timeOfDayToTime.

Instance details

Defined in Witch.Instances

From UniversalTime Rational Source #

Uses getModJulianDate.

Instance details

Defined in Witch.Instances

From UTCTime SystemTime Source #

Uses utcToSystemTime.

Instance details

Defined in Witch.Instances

From UTCTime POSIXTime Source #

Uses utcTimeToPOSIXSeconds.

Instance details

Defined in Witch.Instances

From SystemTime UTCTime Source #

Uses systemToUTCTime.

Instance details

Defined in Witch.Instances

From SystemTime POSIXTime Source #

Uses systemToPOSIXTime.

Instance details

Defined in Witch.Instances

From SystemTime AbsoluteTime Source #

Uses systemToTAITime.

Instance details

Defined in Witch.Instances

From POSIXTime UTCTime Source #

Uses posixSecondsToUTCTime.

Instance details

Defined in Witch.Instances

From NominalDiffTime Pico Source #

Uses nominalDiffTimeToSeconds.

Instance details

Defined in Witch.Instances

From NominalDiffTime CalendarDiffTime Source #

Uses calendarTimeTime.

Instance details

Defined in Witch.Instances

From DiffTime Pico Source #

Uses realToFrac.

Instance details

Defined in Witch.Instances

Methods

from :: DiffTime -> Pico Source #

From DiffTime TimeOfDay Source #

Uses timeToTimeOfDay.

Instance details

Defined in Witch.Instances

From Day Integer Source #

Uses toModifiedJulianDay.

Instance details

Defined in Witch.Instances

Methods

from :: Day -> Integer Source #

From Day DayOfWeek Source #

Uses dayOfWeek.

Instance details

Defined in Witch.Instances

Methods

from :: Day -> DayOfWeek Source #

From CalendarDiffDays CalendarDiffTime Source #

Uses calendarTimeDays.

Instance details

Defined in Witch.Instances

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

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

Instance details

Defined in Witch.Instances

Methods

from :: a -> Complex a Source #

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

Uses (%) with a denominator of 1.

Instance details

Defined in Witch.Instances

Methods

from :: a -> Ratio a Source #

From ShortByteString [Word8] Source #

Uses unpack.

Instance details

Defined in Witch.Instances

From ByteString [Word8] Source #

Uses unpack.

Instance details

Defined in Witch.Instances

Methods

from :: ByteString -> [Word8] Source #

From ByteString [Word8] Source #

Uses unpack.

Instance details

Defined in Witch.Instances

Methods

from :: ByteString -> [Word8] Source #

From IntSet [Int] Source #

Uses toAscList.

Instance details

Defined in Witch.Instances

Methods

from :: IntSet -> [Int] Source #

From Integer (Fixed a) Source #

Uses MkFixed. This means from @Integer @Centi 2 is 0.02 rather than 2.00.

Instance details

Defined in Witch.Instances

Methods

from :: Integer -> Fixed a Source #

From [Int] IntSet Source #

Uses fromList.

Instance details

Defined in Witch.Instances

Methods

from :: [Int] -> IntSet Source #

From [Word8] ShortByteString Source #

Uses pack.

Instance details

Defined in Witch.Instances

From [Word8] ByteString Source #

Uses pack.

Instance details

Defined in Witch.Instances

Methods

from :: [Word8] -> ByteString Source #

From [Word8] ByteString Source #

Uses pack.

Instance details

Defined in Witch.Instances

Methods

from :: [Word8] -> ByteString Source #

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

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

Instance details

Defined in Witch.Instances

Methods

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

From [a] (Seq a) Source #

Uses fromList.

Instance details

Defined in Witch.Instances

Methods

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

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

Uses fromList.

Instance details

Defined in Witch.Instances

Methods

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

From (NonEmpty a) [a] Source #

Uses toList.

Instance details

Defined in Witch.Instances

Methods

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

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

Uses toAscList.

Instance details

Defined in Witch.Instances

Methods

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

From (Seq a) [a] Source #

Uses toList.

Instance details

Defined in Witch.Instances

Methods

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

From (Set a) [a] Source #

Uses toAscList.

Instance details

Defined in Witch.Instances

Methods

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

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

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

Instance details

Defined in Witch.Instances

Methods

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

HasResolution a => From (Fixed a) Rational Source #

Uses toRational.

Instance details

Defined in Witch.Instances

Methods

from :: Fixed a -> Rational Source #

From (Fixed a) Integer Source #

Uses MkFixed. This means from @Centi @Integer 3.00 is 300 rather than 3.

Instance details

Defined in Witch.Instances

Methods

from :: Fixed a -> Integer Source #

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

Uses toAscList.

Instance details

Defined in Witch.Instances

Methods

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

From (TryFromException s u) (TryFromException s t) Source #

Uses coerce.

Instance details

Defined in Witch.Instances