witch-1.2.3.2: Convert values from one type into another.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Witch.Generic

Synopsis

Documentation

class GFrom s t where Source #

This type class is used to implement generic conversions using the Generically helper. This is an advanced use case. Most users will not need to know about this type class. And even for those that want to derive Generically, this type class should be an implementation detail.

This type class can convert between any two types as long as they have Generic instances and they are structurally similar. For example, if you define your own empty type you could convert it to the typical Void type:

data Empty deriving Generic
deriving via Generically Void instance From Empty Void

Or your own unit type:

data Unit = MkUnit deriving Generic
deriving via Generically () instance From Unit ()

Note that this looks superficially similar to newtype Unit = MkUnit () together with instance From Unit (), but that goes through Coercible and requires the types to be representationally equal. This approach (with Generically) only requires the types to be structurally equal. In this case, Unit is structurally equal to () since they both have a single constructor with no arguments.

This also works with arbitrary product types, like a custom pair type:

data Pair a b = MkPair a b deriving Generic
deriving via Generically (Pair c d)
  instance (From a c, From b d) => From (a, b) (Pair c d)

Note that this can also convert the type variables as long as they have From instances as well. This allows converting from (Int, Int) to Pair Integer Integer in one step, for example.

And this works with arbitrary sum types as well:

data Result a b = Failure a | Success b deriving Generic
deriving via Generically (Result c d)
  instance (From a c, From b d) => From (Either a b) (Result c d)

Note that these conversions are all structural not semantic. That means if you had defined Result as Success b | Failure a, then converting from Either would be "wrong". Left would convert into Success and Right would convert into Failure.

Methods

gFrom :: s x -> t x Source #

Instances

Instances details
GFrom (U1 :: Type -> Type) (U1 :: Type -> Type) Source # 
Instance details

Defined in Witch.Generic

Methods

gFrom :: U1 x -> U1 x Source #

GFrom (V1 :: Type -> Type) (V1 :: Type -> Type) Source # 
Instance details

Defined in Witch.Generic

Methods

gFrom :: V1 x -> V1 x Source #

(GFrom s1 t1, GFrom s2 t2) => GFrom (s1 :*: s2) (t1 :*: t2) Source # 
Instance details

Defined in Witch.Generic

Methods

gFrom :: (s1 :*: s2) x -> (t1 :*: t2) x Source #

(GFrom s1 t1, GFrom s2 t2) => GFrom (s1 :+: s2) (t1 :+: t2) Source # 
Instance details

Defined in Witch.Generic

Methods

gFrom :: (s1 :+: s2) x -> (t1 :+: t2) x Source #

From s t => GFrom (K1 a s :: Type -> Type) (K1 b t :: Type -> Type) Source # 
Instance details

Defined in Witch.Generic

Methods

gFrom :: K1 a s x -> K1 b t x Source #

GFrom s t => GFrom (M1 a b s) (M1 c d t) Source # 
Instance details

Defined in Witch.Generic

Methods

gFrom :: M1 a b s x -> M1 c d t x Source #

Orphan instances

(Generic s, Generic t, GFrom (Rep s) (Rep t)) => From s (Generically t) Source #

See the GFrom type class for an explanation of this instance.

Instance details

Methods

from :: s -> Generically t Source #