half-space-0.1.1.0: Additive monoids generalising vector spaces
Copyright(c) Justus Sagemüller 2022
LicenseGPL v3
Maintainer(@) jsag $ hvl.no
Stabilityexperimental
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Monoid.Additive

Description

 

Documentation

class AdditiveMonoid h where Source #

Minimal complete definition

Nothing

Methods

zeroHV :: h Source #

default zeroHV :: (Generic h, AdditiveMonoid (AMRep h)) => h Source #

addHVs :: h -> h -> h Source #

default addHVs :: (Generic h, AdditiveMonoid (AMRep h)) => h -> h -> h Source #

Instances

Instances details
AdditiveMonoid Int16 Source # 
Instance details

Defined in Data.Monoid.Additive

AdditiveMonoid Int32 Source # 
Instance details

Defined in Data.Monoid.Additive

AdditiveMonoid Int64 Source # 
Instance details

Defined in Data.Monoid.Additive

AdditiveMonoid Int8 Source # 
Instance details

Defined in Data.Monoid.Additive

AdditiveMonoid Word16 Source # 
Instance details

Defined in Data.Monoid.Additive

AdditiveMonoid Word32 Source # 
Instance details

Defined in Data.Monoid.Additive

AdditiveMonoid Word64 Source # 
Instance details

Defined in Data.Monoid.Additive

AdditiveMonoid Word8 Source # 
Instance details

Defined in Data.Monoid.Additive

AdditiveMonoid Integer Source # 
Instance details

Defined in Data.Monoid.Additive

AdditiveMonoid Double Source # 
Instance details

Defined in Data.Monoid.Additive

AdditiveMonoid Float Source # 
Instance details

Defined in Data.Monoid.Additive

AdditiveMonoid Int Source # 
Instance details

Defined in Data.Monoid.Additive

Methods

zeroHV :: Int Source #

addHVs :: Int -> Int -> Int Source #

AdditiveMonoid Word Source # 
Instance details

Defined in Data.Monoid.Additive

Num k => AdditiveMonoid (Cℝay (ZeroDim k)) Source # 
Instance details

Defined in Data.Monoid.Additive

AdditiveGroup (Needle (Rep a Void)) => AdditiveMonoid (GenericNeedle a) Source # 
Instance details

Defined in Data.Monoid.Additive

AdditiveMonoid (ZeroDim k) Source # 
Instance details

Defined in Data.Monoid.Additive

(AdditiveMonoid h, AdditiveMonoid i) => AdditiveMonoid (h, i) Source # 
Instance details

Defined in Data.Monoid.Additive

Methods

zeroHV :: (h, i) Source #

addHVs :: (h, i) -> (h, i) -> (h, i) Source #

AdditiveMonoid h => AdditiveMonoid (Rec0 h s) Source # 
Instance details

Defined in Data.Monoid.Additive

Methods

zeroHV :: Rec0 h s Source #

addHVs :: Rec0 h s -> Rec0 h s -> Rec0 h s Source #

(AdditiveMonoid h, AdditiveMonoid i, AdditiveMonoid j) => AdditiveMonoid (h, i, j) Source # 
Instance details

Defined in Data.Monoid.Additive

Methods

zeroHV :: (h, i, j) Source #

addHVs :: (h, i, j) -> (h, i, j) -> (h, i, j) Source #

(AdditiveMonoid (f p), AdditiveMonoid (g p)) => AdditiveMonoid ((f :*: g) p) Source # 
Instance details

Defined in Data.Monoid.Additive

Methods

zeroHV :: (f :*: g) p Source #

addHVs :: (f :*: g) p -> (f :*: g) p -> (f :*: g) p Source #

AdditiveMonoid (f p) => AdditiveMonoid (M1 i c f p) Source # 
Instance details

Defined in Data.Monoid.Additive

Methods

zeroHV :: M1 i c f p Source #

addHVs :: M1 i c f p -> M1 i c f p -> M1 i c f p Source #

class AdditiveMonoid h => HalfSpace h where Source #

Minimal complete definition

Nothing

Associated Types

type FullSubspace h :: Type Source #

type FullSubspace h = GenericFullSubspace h

type Ray h :: Type Source #

type Ray h = Ray (AMRep h)

type MirrorJoin h :: Type Source #

type MirrorJoin h = GenericMirrorJoin h

Methods

scaleNonNeg :: Ray h -> h -> h Source #

default scaleNonNeg :: (Generic h, HalfSpace (AMRep h), FullSubspace h ~ GenericFullSubspace h, Ray h ~ Ray (AMRep h)) => Ray h -> h -> h Source #

fromFullSubspace :: FullSubspace h -> h Source #

default fromFullSubspace :: (Generic h, HalfSpace (AMRep h), FullSubspace h ~ GenericFullSubspace h, Ray h ~ Ray (AMRep h)) => FullSubspace h -> h Source #

projectToFullSubspace :: h -> FullSubspace h Source #

default projectToFullSubspace :: (Generic h, HalfSpace (AMRep h), FullSubspace h ~ GenericFullSubspace h, Ray h ~ Ray (AMRep h)) => h -> FullSubspace h Source #

fullSubspaceIsVectorSpace :: ((VectorSpace (FullSubspace h), ScalarSpace (Scalar (FullSubspace h)), Scalar (FullSubspace h) ~ MirrorJoin (Ray h)) => r) -> r Source #

rayIsHalfSpace :: (HalfSpace (Ray h) => r) -> r Source #

default rayIsHalfSpace :: HalfSpace (Ray h) => (HalfSpace (Ray h) => r) -> r Source #

mirrorJoinIsVectorSpace :: ((VectorSpace (MirrorJoin h), Scalar (MirrorJoin h) ~ MirrorJoin (Ray h)) => r) -> r Source #

fromPositiveHalf :: h -> MirrorJoin h Source #

default fromPositiveHalf :: (Generic h, HalfSpace (AMRep h), MirrorJoin h ~ GenericMirrorJoin h, Ray h ~ Ray (AMRep h)) => h -> MirrorJoin h Source #

fromNegativeHalf :: h -> MirrorJoin h Source #

default fromNegativeHalf :: (Generic h, HalfSpace (AMRep h), MirrorJoin h ~ GenericMirrorJoin h, Ray h ~ Ray (AMRep h)) => h -> MirrorJoin h Source #

Instances

Instances details
(Num k, VectorSpace k, Scalar k ~ k) => HalfSpace (Cℝay (ZeroDim k)) Source # 
Instance details

Defined in Data.Monoid.Additive

Associated Types

type FullSubspace (Cℝay (ZeroDim k)) Source #

type Ray (Cℝay (ZeroDim k)) Source #

type MirrorJoin (Cℝay (ZeroDim k)) Source #

ScalarSpace k => HalfSpace (ZeroDim k) Source # 
Instance details

Defined in Data.Monoid.Additive

Associated Types

type FullSubspace (ZeroDim k) Source #

type Ray (ZeroDim k) Source #

type MirrorJoin (ZeroDim k) Source #

(HalfSpace x, VectorSpace y, AdditiveMonoid y, Ray x ~ Cℝay (ZeroDim (Scalar y))) => HalfSpace (x, y) Source # 
Instance details

Defined in Data.Monoid.Additive

Associated Types

type FullSubspace (x, y) Source #

type Ray (x, y) Source #

type MirrorJoin (x, y) Source #

Methods

scaleNonNeg :: Ray (x, y) -> (x, y) -> (x, y) Source #

fromFullSubspace :: FullSubspace (x, y) -> (x, y) Source #

projectToFullSubspace :: (x, y) -> FullSubspace (x, y) Source #

fullSubspaceIsVectorSpace :: ((VectorSpace (FullSubspace (x, y)), ScalarSpace (Scalar (FullSubspace (x, y))), Scalar (FullSubspace (x, y)) ~ MirrorJoin (Ray (x, y))) => r) -> r Source #

rayIsHalfSpace :: (HalfSpace (Ray (x, y)) => r) -> r Source #

mirrorJoinIsVectorSpace :: ((VectorSpace (MirrorJoin (x, y)), Scalar (MirrorJoin (x, y)) ~ MirrorJoin (Ray (x, y))) => r) -> r Source #

fromPositiveHalf :: (x, y) -> MirrorJoin (x, y) Source #

fromNegativeHalf :: (x, y) -> MirrorJoin (x, y) Source #

HalfSpace h => HalfSpace (Rec0 h s) Source # 
Instance details

Defined in Data.Monoid.Additive

Associated Types

type FullSubspace (Rec0 h s) Source #

type Ray (Rec0 h s) Source #

type MirrorJoin (Rec0 h s) Source #

(HalfSpace (f p), VectorSpace (g p), AdditiveMonoid (g p), Ray (f p) ~ Cℝay (ZeroDim (Scalar (g p)))) => HalfSpace ((f :*: g) p) Source # 
Instance details

Defined in Data.Monoid.Additive

Associated Types

type FullSubspace ((f :*: g) p) Source #

type Ray ((f :*: g) p) Source #

type MirrorJoin ((f :*: g) p) Source #

Methods

scaleNonNeg :: Ray ((f :*: g) p) -> (f :*: g) p -> (f :*: g) p Source #

fromFullSubspace :: FullSubspace ((f :*: g) p) -> (f :*: g) p Source #

projectToFullSubspace :: (f :*: g) p -> FullSubspace ((f :*: g) p) Source #

fullSubspaceIsVectorSpace :: ((VectorSpace (FullSubspace ((f :*: g) p)), ScalarSpace (Scalar (FullSubspace ((f :*: g) p))), Scalar (FullSubspace ((f :*: g) p)) ~ MirrorJoin (Ray ((f :*: g) p))) => r) -> r Source #

rayIsHalfSpace :: (HalfSpace (Ray ((f :*: g) p)) => r) -> r Source #

mirrorJoinIsVectorSpace :: ((VectorSpace (MirrorJoin ((f :*: g) p)), Scalar (MirrorJoin ((f :*: g) p)) ~ MirrorJoin (Ray ((f :*: g) p))) => r) -> r Source #

fromPositiveHalf :: (f :*: g) p -> MirrorJoin ((f :*: g) p) Source #

fromNegativeHalf :: (f :*: g) p -> MirrorJoin ((f :*: g) p) Source #

HalfSpace (f p) => HalfSpace (M1 i c f p) Source # 
Instance details

Defined in Data.Monoid.Additive

Associated Types

type FullSubspace (M1 i c f p) Source #

type Ray (M1 i c f p) Source #

type MirrorJoin (M1 i c f p) Source #

Methods

scaleNonNeg :: Ray (M1 i c f p) -> M1 i c f p -> M1 i c f p Source #

fromFullSubspace :: FullSubspace (M1 i c f p) -> M1 i c f p Source #

projectToFullSubspace :: M1 i c f p -> FullSubspace (M1 i c f p) Source #

fullSubspaceIsVectorSpace :: ((VectorSpace (FullSubspace (M1 i c f p)), ScalarSpace (Scalar (FullSubspace (M1 i c f p))), Scalar (FullSubspace (M1 i c f p)) ~ MirrorJoin (Ray (M1 i c f p))) => r) -> r Source #

rayIsHalfSpace :: (HalfSpace (Ray (M1 i c f p)) => r) -> r Source #

mirrorJoinIsVectorSpace :: ((VectorSpace (MirrorJoin (M1 i c f p)), Scalar (MirrorJoin (M1 i c f p)) ~ MirrorJoin (Ray (M1 i c f p))) => r) -> r Source #

fromPositiveHalf :: M1 i c f p -> MirrorJoin (M1 i c f p) Source #

fromNegativeHalf :: M1 i c f p -> MirrorJoin (M1 i c f p) Source #