Copyright | (c) Erich Gut |
---|---|
License | BSD3 |
Maintainer | zerich.gut@gmail.com |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- data SomeMorphism m where
- SomeMorphism :: m x y -> SomeMorphism m
- data SomeObjectClass m where
- SomeObjectClass :: Transformable (ObjectClass m) Typ => Struct (ObjectClass m) x -> SomeObjectClass m
- data SomeMorphismSite s m x where
- SomeMorphismDomain :: m x y -> SomeMorphismSite From m x
- SomeMorphismRange :: m x y -> SomeMorphismSite To m y
- data SomePath m where
- somePath :: SomePathSite s m x -> SomePath m
- data SomePathSite s m x where
- SomePathDomain :: Path m x y -> SomePathSite From m x
- SomePathRange :: Path m x y -> SomePathSite To m y
- data SomeEntity m where
- SomeEntity :: Entity x => Struct (ObjectClass m) x -> x -> SomeEntity m
- data SomeApplication h where
- SomeApplication :: h x y -> x -> SomeApplication h
Morphism
data SomeMorphism m where Source #
some morphism.
SomeMorphism :: m x y -> SomeMorphism m |
Instances
data SomeObjectClass m where Source #
some object class.
SomeObjectClass :: Transformable (ObjectClass m) Typ => Struct (ObjectClass m) x -> SomeObjectClass m |
Instances
Show (SomeObjectClass m) Source # | |
Defined in OAlg.Category.Unify showsPrec :: Int -> SomeObjectClass m -> ShowS # show :: SomeObjectClass m -> String # showList :: [SomeObjectClass m] -> ShowS # | |
Eq (SomeObjectClass m) Source # | |
Defined in OAlg.Category.Unify (==) :: SomeObjectClass m -> SomeObjectClass m -> Bool # (/=) :: SomeObjectClass m -> SomeObjectClass m -> Bool # | |
Dualisable (SomeObjectClass m) Source # | |
Defined in OAlg.Category.Unify toDual :: SomeObjectClass m -> Dual (SomeObjectClass m) Source # fromDual :: Dual (SomeObjectClass m) -> SomeObjectClass m Source # | |
Validable (SomeObjectClass m) Source # | |
Defined in OAlg.Category.Unify valid :: SomeObjectClass m -> Statement Source # | |
Typeable m => Entity (SomeObjectClass m) Source # | |
Defined in OAlg.Category.Unify | |
type Dual (SomeObjectClass m :: Type) Source # | |
Defined in OAlg.Category.Unify |
data SomeMorphismSite s m x where Source #
some morphism given by a Site
.
SomeMorphismDomain :: m x y -> SomeMorphismSite From m x | |
SomeMorphismRange :: m x y -> SomeMorphismSite To m y |
Instances
Dualisable (SomeMorphismSite 'To m y) Source # | |
Defined in OAlg.Category.Unify toDual :: SomeMorphismSite 'To m y -> Dual (SomeMorphismSite 'To m y) Source # fromDual :: Dual (SomeMorphismSite 'To m y) -> SomeMorphismSite 'To m y Source # | |
type Dual (SomeMorphismSite s m y :: Type) Source # | |
Defined in OAlg.Category.Unify |
Path
data SomePath m where Source #
some path
somePath :: SomePathSite s m x -> SomePath m Source #
embedding.
data SomePathSite s m x where Source #
SomePathDomain :: Path m x y -> SomePathSite From m x | |
SomePathRange :: Path m x y -> SomePathSite To m y |
Instances
Morphism m => Dualisable (SomePathSite 'To m y) Source # | |
Defined in OAlg.Category.Unify toDual :: SomePathSite 'To m y -> Dual (SomePathSite 'To m y) Source # fromDual :: Dual (SomePathSite 'To m y) -> SomePathSite 'To m y Source # | |
type Dual (SomePathSite s m y :: Type) Source # | |
Defined in OAlg.Category.Unify |
Entity
data SomeEntity m where Source #
some entity x
in x
having the given
as structure.ObjectClass
m
SomeEntity :: Entity x => Struct (ObjectClass m) x -> x -> SomeEntity m |
Application
data SomeApplication h where Source #
some application.
SomeApplication :: h x y -> x -> SomeApplication h |