module Data.Distributive.Generic
( GDistributive(..)
, genericDistribute
) where
import GHC.Generics
genericDistribute :: (Functor f, Generic1 g, GDistributive (Rep1 g)) => f (g a) -> g (f a)
genericDistribute = to1 . gdistribute . fmap from1
class GDistributive g where
gdistribute :: Functor f => f (g a) -> g (f a)
instance GDistributive U1 where
gdistribute _ = U1
instance (GDistributive a, GDistributive b) => GDistributive (a :*: b) where
gdistribute f = gdistribute (fmap fstP f) :*: gdistribute (fmap sndP f) where
fstP (l :*: _) = l
sndP (_ :*: r) = r
instance (Functor a, Functor b, GDistributive a, GDistributive b) => GDistributive (a :.: b) where
gdistribute = Comp1 . fmap gdistribute . gdistribute . fmap unComp1
instance GDistributive Par1 where
gdistribute = Par1 . fmap unPar1
instance GDistributive f => GDistributive (Rec1 f) where
gdistribute = Rec1 . gdistribute . fmap unRec1
instance GDistributive f => GDistributive (M1 i c f) where
gdistribute = M1 . gdistribute . fmap unM1