{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE ConstraintKinds #-}
module OAlg.Hom.Multiplicative.Definition
(
HomMultiplicative, IsoMultiplicative
, isoFromOpOpMlt
, isoOppositeMlt
)
where
import Data.Typeable
import OAlg.Prelude
import OAlg.Category.Path
import OAlg.Data.Constructable
import OAlg.Structure.Oriented hiding (Path(..))
import OAlg.Structure.Multiplicative
import OAlg.Hom.Definition
import OAlg.Hom.Oriented.Definition
class (EmbeddableMorphism h Mlt, HomOriented h) => HomMultiplicative h
instance HomMultiplicative h => HomMultiplicative (Path h)
instance ( HomMultiplicative h, Transformable1 Op t
, ForgetfulMlt t, ForgetfulTyp t, Typeable t
)
=> HomMultiplicative (Forget t h)
type instance Hom Mlt h = HomMultiplicative h
type IsoMultiplicative h = ( FunctorialHomOriented h, Cayleyan2 h
, HomMultiplicative h
)
instance (TransformableOp s, ForgetfulMlt s, ForgetfulTyp s, Typeable s)
=> HomMultiplicative (IdHom s)
instance (TransformableOp s, ForgetfulMlt s, ForgetfulTyp s, Typeable s)
=> HomMultiplicative (HomOp s)
instance (TransformableOp s, ForgetfulMlt s, ForgetfulTyp s, Typeable s)
=> HomMultiplicative (IsoOp s)
isoFromOpOpMlt :: Multiplicative a => IsoOp Mlt (Op (Op a)) a
isoFromOpOpMlt :: forall a. Multiplicative a => IsoOp Mlt (Op (Op a)) a
isoFromOpOpMlt = forall x. Constructable x => Form x -> x
make (forall s a.
(Structure s (Op (Op a)), Structure s a) =>
HomOp s (Op (Op a)) a
FromOpOp forall (m :: * -> * -> *) p z x. m p z -> Path m x p -> Path m x z
:. forall (m :: * -> * -> *) x. Struct (ObjectClass m) x -> Path m x x
IdPath forall s x. Structure s x => Struct s x
Struct)
isoOppositeMlt :: Entity p => IsoOp Mlt (Op (Orientation p)) (Orientation p)
isoOppositeMlt :: forall p.
Entity p =>
IsoOp Mlt (Op (Orientation p)) (Orientation p)
isoOppositeMlt = forall x. Constructable x => Form x -> x
make (forall s p.
(Structure s (Op (Orientation p)), Structure s (Orientation p)) =>
HomOp s (Op (Orientation p)) (Orientation p)
Opposite forall (m :: * -> * -> *) p z x. m p z -> Path m x p -> Path m x z
:. forall (m :: * -> * -> *) x. Struct (ObjectClass m) x -> Path m x x
IdPath forall s x. Structure s x => Struct s x
Struct)
instance HomMultiplicative h => HomMultiplicative (OpHom h)