basement-0.0.4: Foundation scrap box of array & string

LicenseBSD-style
MaintainerHaskell Foundation
Safe HaskellNone
LanguageHaskell2010

Basement.From

Description

Flexible Type convertion

From is multi parameter type class that allow converting from a to b.

Only type that are valid to convert to another type should be From instance; otherwise TryFrom should be used.

Into (resp TryInto) allows the contrary instances to be able to specify the destination type before the source. This is practical with TypeApplication

Synopsis

Documentation

class From a b where Source #

Class of things that can be converted from a to b.

In a valid instance, the source should be always representable by the destination, otherwise the instance should be using TryFrom

Minimal complete definition

from

Methods

from :: a -> b Source #

Instances

From Int Int64 Source # 

Methods

from :: Int -> Int64 Source #

From Int Word Source # 

Methods

from :: Int -> Word Source #

From Int8 Int Source # 

Methods

from :: Int8 -> Int Source #

From Int8 Int16 Source # 

Methods

from :: Int8 -> Int16 Source #

From Int8 Int32 Source # 

Methods

from :: Int8 -> Int32 Source #

From Int8 Int64 Source # 

Methods

from :: Int8 -> Int64 Source #

From Int16 Int Source # 

Methods

from :: Int16 -> Int Source #

From Int16 Int32 Source # 

Methods

from :: Int16 -> Int32 Source #

From Int16 Int64 Source # 

Methods

from :: Int16 -> Int64 Source #

From Int32 Int Source # 

Methods

from :: Int32 -> Int Source #

From Int32 Int64 Source # 

Methods

from :: Int32 -> Int64 Source #

From Word Int Source # 

Methods

from :: Word -> Int Source #

From Word Word64 Source # 

Methods

from :: Word -> Word64 Source #

From Word8 Int Source # 

Methods

from :: Word8 -> Int Source #

From Word8 Int16 Source # 

Methods

from :: Word8 -> Int16 Source #

From Word8 Int32 Source # 

Methods

from :: Word8 -> Int32 Source #

From Word8 Int64 Source # 

Methods

from :: Word8 -> Int64 Source #

From Word8 Word Source # 

Methods

from :: Word8 -> Word Source #

From Word8 Word16 Source # 

Methods

from :: Word8 -> Word16 Source #

From Word8 Word32 Source # 

Methods

from :: Word8 -> Word32 Source #

From Word8 Word64 Source # 

Methods

from :: Word8 -> Word64 Source #

From Word8 Word128 Source # 

Methods

from :: Word8 -> Word128 Source #

From Word8 Word256 Source # 

Methods

from :: Word8 -> Word256 Source #

From Word16 Word Source # 

Methods

from :: Word16 -> Word Source #

From Word16 Word32 Source # 

Methods

from :: Word16 -> Word32 Source #

From Word16 Word64 Source # 

Methods

from :: Word16 -> Word64 Source #

From Word16 Word128 Source # 

Methods

from :: Word16 -> Word128 Source #

From Word16 Word256 Source # 

Methods

from :: Word16 -> Word256 Source #

From Word32 Word Source # 

Methods

from :: Word32 -> Word Source #

From Word32 Word64 Source # 

Methods

from :: Word32 -> Word64 Source #

From Word32 Word128 Source # 

Methods

from :: Word32 -> Word128 Source #

From Word32 Word256 Source # 

Methods

from :: Word32 -> Word256 Source #

From Word64 Word128 Source # 

Methods

from :: Word64 -> Word128 Source #

From Word64 Word256 Source # 

Methods

from :: Word64 -> Word256 Source #

IsIntegral n => From n Integer Source # 

Methods

from :: n -> Integer Source #

IsNatural n => From n Natural Source # 

Methods

from :: n -> Natural Source #

From a a Source # 

Methods

from :: a -> a Source #

From AsciiString String Source # 
From AsciiString (UArray Word8) Source # 
From String (UArray Word8) Source # 
(KnownNat n, NatWithinBound Word256 n) => From (Zn n) Word256 Source # 

Methods

from :: Zn n -> Word256 Source #

(KnownNat n, NatWithinBound Word128 n) => From (Zn n) Word128 Source # 

Methods

from :: Zn n -> Word128 Source #

(KnownNat n, NatWithinBound Word64 n) => From (Zn n) Word64 Source # 

Methods

from :: Zn n -> Word64 Source #

(KnownNat n, NatWithinBound Word32 n) => From (Zn n) Word32 Source # 

Methods

from :: Zn n -> Word32 Source #

(KnownNat n, NatWithinBound Word16 n) => From (Zn n) Word16 Source # 

Methods

from :: Zn n -> Word16 Source #

(KnownNat n, NatWithinBound Word8 n) => From (Zn n) Word8 Source # 

Methods

from :: Zn n -> Word8 Source #

From (Zn64 n) Word256 Source # 

Methods

from :: Zn64 n -> Word256 Source #

From (Zn64 n) Word128 Source # 

Methods

from :: Zn64 n -> Word128 Source #

From (Zn64 n) Word64 Source # 

Methods

from :: Zn64 n -> Word64 Source #

(KnownNat n, NatWithinBound Word32 n) => From (Zn64 n) Word32 Source # 

Methods

from :: Zn64 n -> Word32 Source #

(KnownNat n, NatWithinBound Word16 n) => From (Zn64 n) Word16 Source # 

Methods

from :: Zn64 n -> Word16 Source #

(KnownNat n, NatWithinBound Word8 n) => From (Zn64 n) Word8 Source # 

Methods

from :: Zn64 n -> Word8 Source #

From (CountOf ty) Word Source # 

Methods

from :: CountOf ty -> Word Source #

From (CountOf ty) Int Source # 

Methods

from :: CountOf ty -> Int Source #

(KnownNat n, NatWithinBound Word64 n) => From (Zn n) (Zn64 n) Source # 

Methods

from :: Zn n -> Zn64 n Source #

KnownNat n => From (Zn64 n) (Zn n) Source # 

Methods

from :: Zn64 n -> Zn n Source #

PrimType ty => From (Block ty) (UArray ty) Source # 

Methods

from :: Block ty -> UArray ty Source #

PrimType ty => From (UArray ty) (Array ty) Source # 

Methods

from :: UArray ty -> Array ty Source #

PrimType ty => From (UArray ty) (Block ty) Source # 

Methods

from :: UArray ty -> Block ty Source #

PrimType ty => From (Array ty) (Block ty) Source # 

Methods

from :: Array ty -> Block ty Source #

PrimType ty => From (Array ty) (UArray ty) Source # 

Methods

from :: Array ty -> UArray ty Source #

From (Maybe a) (Either () a) Source # 

Methods

from :: Maybe a -> Either () a Source #

(NatWithinBound Int n, PrimType ty) => From (BlockN n ty) (Array ty) Source # 

Methods

from :: BlockN n ty -> Array ty Source #

(NatWithinBound Int n, PrimType ty) => From (BlockN n ty) (UArray ty) Source # 

Methods

from :: BlockN n ty -> UArray ty Source #

From (BlockN n ty) (Block ty) Source # 

Methods

from :: BlockN n ty -> Block ty Source #

From (Either a b) (These a b) Source # 

Methods

from :: Either a b -> These a b Source #

type Into b a = From a b Source #

class TryFrom a b where Source #

Class of things that can mostly be converted from a to b, but with possible error cases.

Minimal complete definition

tryFrom

Methods

tryFrom :: a -> Maybe b Source #

Instances

TryFrom (UArray Word8) String Source # 
(NatWithinBound (CountOf ty) n, KnownNat n, PrimType ty) => TryFrom (Block ty) (BlockN n ty) Source # 

Methods

tryFrom :: Block ty -> Maybe (BlockN n ty) Source #

(NatWithinBound (CountOf ty) n, KnownNat n, PrimType ty) => TryFrom (UArray ty) (BlockN n ty) Source # 

Methods

tryFrom :: UArray ty -> Maybe (BlockN n ty) Source #

(NatWithinBound (CountOf ty) n, KnownNat n, PrimType ty) => TryFrom (Array ty) (BlockN n ty) Source # 

Methods

tryFrom :: Array ty -> Maybe (BlockN n ty) Source #

type TryInto b a = TryFrom a b Source #

into :: Into b a => a -> b Source #

Same as from but reverse the type variable so that the destination type can be specified first

e.g. converting:

from _ Word (10 :: Int)

into @Word (10 :: Int)

tryInto :: TryInto b a => a -> Maybe b Source #

same as tryFrom but reversed