{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleContexts #-}
module OAlg.Structure.Distributive.Definition
(
Distributive, Dst, ForgetfulDst
, TransposableDistributive
)
where
import OAlg.Prelude
import OAlg.Structure.Oriented.Definition
import OAlg.Structure.Multiplicative.Definition
import OAlg.Structure.Fibred.Definition
import OAlg.Structure.Additive.Definition
class (FibredOriented d, Additive d, Multiplicative d) => Distributive d
instance Distributive ()
instance Distributive Int
instance Distributive Integer
instance Distributive N
instance Distributive Z
instance Distributive Q
instance Entity p => Distributive (Orientation p)
instance Distributive d => Distributive (Op d)
class (TransposableMultiplicative d, Distributive d) => TransposableDistributive d
instance Entity p => TransposableDistributive (Orientation p)
instance TransposableDistributive N
instance TransposableDistributive Z
instance TransposableDistributive Q
data Dst
type instance Structure Dst x = Distributive x
instance Transformable Dst Typ where tau :: forall x. Struct Dst x -> Struct Typ x
tau Struct Dst x
Struct = forall s x. Structure s x => Struct s x
Struct
instance Transformable Dst Ent where tau :: forall x. Struct Dst x -> Struct Ent x
tau Struct Dst x
Struct = forall s x. Structure s x => Struct s x
Struct
instance Transformable Dst Ort where tau :: forall x. Struct Dst x -> Struct Ort x
tau Struct Dst x
Struct = forall s x. Structure s x => Struct s x
Struct
instance Transformable Dst Mlt where tau :: forall x. Struct Dst x -> Struct Mlt x
tau Struct Dst x
Struct = forall s x. Structure s x => Struct s x
Struct
instance Transformable Dst Fbr where tau :: forall x. Struct Dst x -> Struct Fbr x
tau Struct Dst x
Struct = forall s x. Structure s x => Struct s x
Struct
instance Transformable Dst FbrOrt where tau :: forall x. Struct Dst x -> Struct FbrOrt x
tau Struct Dst x
Struct = forall s x. Structure s x => Struct s x
Struct
instance Transformable Dst Add where tau :: forall x. Struct Dst x -> Struct Add x
tau Struct Dst x
Struct = forall s x. Structure s x => Struct s x
Struct
instance Transformable1 Op Dst where tau1 :: forall x. Struct Dst x -> Struct Dst (Op x)
tau1 Struct Dst x
Struct = forall s x. Structure s x => Struct s x
Struct
instance TransformableOp Dst
class ( ForgetfulOrt s, ForgetfulMlt s
, ForgetfulFbr s, ForgetfulAdd s
, ForgetfulFbrOrt s
, Transformable s Dst
) => ForgetfulDst s
instance ForgetfulTyp Dst
instance ForgetfulOrt Dst
instance ForgetfulMlt Dst
instance ForgetfulFbr Dst
instance ForgetfulFbrOrt Dst
instance ForgetfulAdd Dst
instance ForgetfulDst Dst