| Copyright | (c) Erich Gut |
|---|---|
| License | BSD3 |
| Maintainer | zerich.gut@gmail.com |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
OAlg.Data.Generator
Description
Generator for finitely generated Points within a Distributive structure.
Synopsis
- data Generator s a where
- newtype XSomeFreeSliceFromLiftable a = XSomeFreeSliceFromLiftable (Point a -> X (SomeFreeSlice From a))
- xsfsfl :: XSomeFreeSliceFromLiftable a -> Point a -> X (SomeFreeSlice From a)
- class XStandardSomeFreeSliceFromLiftable a where
Generator
data Generator s a where Source #
generator for finitely generated Points within a Distributive structure.
Property Let be in Generator d k' k'' coker ker lftGenerator and let
DiagramChainTo g (p:|p':|Nil) = d
p p' g <<------- g' <------< g''
then holds:
cokeris the cokernel ofp'withpas the shell of its universal cone.keris the kernel ofpwithp'as the shell of its universal cone.'KenrelSliceFromSomeFreeTip k'' k' kerisvalid.For all
h =inSliceFrom_ h'withSliceFrom(Freek) aholds:endh'==g
g'
^ |
/ |
lft h / | p
/ |
/ v
* ---> g
h'
Constructors
| GeneratorTo :: (Attestable k', Sliced (Free k') a, Attestable k'', Sliced (Free k'') a) => Diagram (Chain To) N3 N2 a -> Free k' a -> Free k'' a -> Cokernel N1 a -> Kernel N1 a -> (forall (k :: N'). Slice From (Free k) a -> a) -> Generator To a |
Instances
| (Distributive a, XStandardOrtSiteFrom a, XStandardOrtSiteTo a, XStandardSomeFreeSliceFromLiftable a) => Validable (Generator 'To a) Source # | |
X
newtype XSomeFreeSliceFromLiftable a Source #
Constructors
| XSomeFreeSliceFromLiftable (Point a -> X (SomeFreeSlice From a)) |
Instances
| (Oriented a, XStandardPoint a) => Validable (XSomeFreeSliceFromLiftable a) Source # | |
Defined in OAlg.Data.Generator Methods valid :: XSomeFreeSliceFromLiftable a -> Statement Source # | |
xsfsfl :: XSomeFreeSliceFromLiftable a -> Point a -> X (SomeFreeSlice From a) Source #
the underlying random variable for some free slice.
class XStandardSomeFreeSliceFromLiftable a where Source #
random variable of lift-able free slice froms.
Property Let a be in instance of XStandardSomeFreeSliceFromLiftable then holds:
For all p in and Point a in the range of
SomeFreeSlice (SliceFrom _ h) holds: xStandardSomeFreeSliceFromLiftable p.end h == p