{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE StandaloneKindSignatures #-}
module OAlg.Structure.Algebraic.Definition
(
Algebraic, Alg, ForgetfulAlg
)
where
import OAlg.Prelude
import OAlg.Structure.Oriented.Definition
import OAlg.Structure.Multiplicative.Definition
import OAlg.Structure.Fibred.Definition
import OAlg.Structure.Additive.Definition
import OAlg.Structure.Distributive.Definition
import OAlg.Structure.Vectorial.Definition
class (Distributive a, Vectorial a) => Algebraic a
instance Algebraic ()
instance Algebraic Int
instance Algebraic Integer
instance Algebraic N
instance Algebraic Z
instance Algebraic Q
instance Entity p => Algebraic (Orientation p)
instance Algebraic a => Algebraic (Op a)
data Alg k
type instance Structure (Alg k) x = (Algebraic x, k ~ Scalar x)
instance Transformable (Alg k) Typ where tau :: forall x. Struct (Alg k) x -> Struct Typ x
tau Struct (Alg k) x
Struct = forall s x. Structure s x => Struct s x
Struct
instance Transformable (Alg k) Ent where tau :: forall x. Struct (Alg k) x -> Struct Ent x
tau Struct (Alg k) x
Struct = forall s x. Structure s x => Struct s x
Struct
instance Transformable (Alg k) Ort where tau :: forall x. Struct (Alg k) x -> Struct Ort x
tau Struct (Alg k) x
Struct = forall s x. Structure s x => Struct s x
Struct
instance Transformable (Alg k) Mlt where tau :: forall x. Struct (Alg k) x -> Struct Mlt x
tau Struct (Alg k) x
Struct = forall s x. Structure s x => Struct s x
Struct
instance Transformable (Alg k) Fbr where tau :: forall x. Struct (Alg k) x -> Struct Fbr x
tau Struct (Alg k) x
Struct = forall s x. Structure s x => Struct s x
Struct
instance Transformable (Alg k) FbrOrt where tau :: forall x. Struct (Alg k) x -> Struct FbrOrt x
tau Struct (Alg k) x
Struct = forall s x. Structure s x => Struct s x
Struct
instance Transformable (Alg k) Add where tau :: forall x. Struct (Alg k) x -> Struct Add x
tau Struct (Alg k) x
Struct = forall s x. Structure s x => Struct s x
Struct
instance Transformable (Alg k) Dst where tau :: forall x. Struct (Alg k) x -> Struct Dst x
tau Struct (Alg k) x
Struct = forall s x. Structure s x => Struct s x
Struct
instance Transformable (Alg k) (Vec k) where tau :: forall x. Struct (Alg k) x -> Struct (Vec k) x
tau Struct (Alg k) x
Struct = forall s x. Structure s x => Struct s x
Struct
instance Transformable1 Op (Alg k) where tau1 :: forall x. Struct (Alg k) x -> Struct (Alg k) (Op x)
tau1 Struct (Alg k) x
Struct = forall s x. Structure s x => Struct s x
Struct
class ( ForgetfulOrt (s k), ForgetfulMlt (s k)
, ForgetfulFbr (s k), ForgetfulFbrOrt (s k)
, ForgetfulAdd (s k), ForgetfulDst (s k)
, ForgetfulVec k s
, Transformable (s k) (Alg k)
) => ForgetfulAlg k s
instance ForgetfulTyp (Alg k)
instance ForgetfulOrt (Alg k)
instance ForgetfulMlt (Alg k)
instance ForgetfulFbr (Alg k)
instance ForgetfulFbrOrt (Alg k)
instance ForgetfulAdd (Alg k)
instance ForgetfulDst (Alg k)
instance ForgetfulVec k Alg
instance ForgetfulAlg k Alg