gasp-1.4.0.0: A framework of algebraic classes
Safe HaskellSafe-Inferred
LanguageHaskell2010

Algebra.Morphism.LinComb

Synopsis

Documentation

newtype LinComb x c Source #

Normalised linear combinations as maps from variables to coefficients (zero coefficient never present in the map)

Constructors

LinComb (Map x c) 

Instances

Instances details
Scalable s a => Scalable s (LinComb k a) Source # 
Instance details

Defined in Algebra.Morphism.LinComb

Methods

(*^) :: s -> LinComb k a -> LinComb k a Source #

Foldable (LinComb x) Source # 
Instance details

Defined in Algebra.Morphism.LinComb

Methods

fold :: Monoid m => LinComb x m -> m #

foldMap :: Monoid m => (a -> m) -> LinComb x a -> m #

foldMap' :: Monoid m => (a -> m) -> LinComb x a -> m #

foldr :: (a -> b -> b) -> b -> LinComb x a -> b #

foldr' :: (a -> b -> b) -> b -> LinComb x a -> b #

foldl :: (b -> a -> b) -> b -> LinComb x a -> b #

foldl' :: (b -> a -> b) -> b -> LinComb x a -> b #

foldr1 :: (a -> a -> a) -> LinComb x a -> a #

foldl1 :: (a -> a -> a) -> LinComb x a -> a #

toList :: LinComb x a -> [a] #

null :: LinComb x a -> Bool #

length :: LinComb x a -> Int #

elem :: Eq a => a -> LinComb x a -> Bool #

maximum :: Ord a => LinComb x a -> a #

minimum :: Ord a => LinComb x a -> a #

sum :: Num a => LinComb x a -> a #

product :: Num a => LinComb x a -> a #

Traversable (LinComb x) Source # 
Instance details

Defined in Algebra.Morphism.LinComb

Methods

traverse :: Applicative f => (a -> f b) -> LinComb x a -> f (LinComb x b) #

sequenceA :: Applicative f => LinComb x (f a) -> f (LinComb x a) #

mapM :: Monad m => (a -> m b) -> LinComb x a -> m (LinComb x b) #

sequence :: Monad m => LinComb x (m a) -> m (LinComb x a) #

Functor (LinComb x) Source # 
Instance details

Defined in Algebra.Morphism.LinComb

Methods

fmap :: (a -> b) -> LinComb x a -> LinComb x b #

(<$) :: a -> LinComb x b -> LinComb x a #

(Show x, Show c) => Show (LinComb x c) Source # 
Instance details

Defined in Algebra.Morphism.LinComb

Methods

showsPrec :: Int -> LinComb x c -> ShowS #

show :: LinComb x c -> String #

showList :: [LinComb x c] -> ShowS #

(AbelianAdditive c, DecidableZero c, Ord x) => AbelianAdditive (LinComb x c) Source # 
Instance details

Defined in Algebra.Morphism.LinComb

(AbelianAdditive c, DecidableZero c, Ord e) => Additive (LinComb e c) Source # 
Instance details

Defined in Algebra.Morphism.LinComb

Methods

(+) :: LinComb e c -> LinComb e c -> LinComb e c Source #

zero :: LinComb e c Source #

times :: Natural -> LinComb e c -> LinComb e c Source #

(AbelianAdditive c, Eq c, DecidableZero c, Ord e) => DecidableZero (LinComb e c) Source # 
Instance details

Defined in Algebra.Morphism.LinComb

Methods

isZero :: LinComb e c -> Bool Source #

(AbelianAdditive c, Group c, DecidableZero c, Ord e) => Group (LinComb e c) Source # 
Instance details

Defined in Algebra.Morphism.LinComb

Methods

(-) :: LinComb e c -> LinComb e c -> LinComb e c Source #

subtract :: LinComb e c -> LinComb e c -> LinComb e c Source #

negate :: LinComb e c -> LinComb e c Source #

mult :: Integer -> LinComb e c -> LinComb e c Source #

(Eq x, Eq c) => Eq (LinComb x c) Source # 
Instance details

Defined in Algebra.Morphism.LinComb

Methods

(==) :: LinComb x c -> LinComb x c -> Bool #

(/=) :: LinComb x c -> LinComb x c -> Bool #

(Ord x, Ord c) => Ord (LinComb x c) Source # 
Instance details

Defined in Algebra.Morphism.LinComb

Methods

compare :: LinComb x c -> LinComb x c -> Ordering #

(<) :: LinComb x c -> LinComb x c -> Bool #

(<=) :: LinComb x c -> LinComb x c -> Bool #

(>) :: LinComb x c -> LinComb x c -> Bool #

(>=) :: LinComb x c -> LinComb x c -> Bool #

max :: LinComb x c -> LinComb x c -> LinComb x c #

min :: LinComb x c -> LinComb x c -> LinComb x c #

eval :: forall d x c v. Scalable d x => Additive x => (c -> d) -> (v -> x) -> LinComb v c -> x Source #

toList :: LinComb k a -> [(k, a)] Source #

var :: Multiplicative c => x -> LinComb x c Source #

unsafeFromList :: Ord v => [(v, c)] -> LinComb v c Source #

Convert from list without testing coefficients

fromList :: DecidableZero c => Additive c => Ord v => [(v, c)] -> LinComb v c Source #

subst :: DecidableZero c => AbelianAdditive c => Scalable c c => Ord v => (x -> LinComb v c) -> LinComb x c -> LinComb v c Source #

Substitution by evaluation

mapVars :: Ord x => (t -> x) -> LinComb t c -> LinComb x c Source #

transform variables. coefficients are not touched

mulVarsMonotonic :: Multiplicative x => x -> LinComb x c -> LinComb x c Source #

Multiplies elements, assuming multiplication is monotonous.

traverseVars :: Applicative f => Ord x => (v -> f x) -> LinComb v c -> f (LinComb x c) Source #

transform variables with effect. coefficients are not touched

bitraverse :: Applicative f => Ord x => (v -> f x) -> (c -> f d) -> LinComb v c -> f (LinComb x d) Source #

transform variables and coefficients with effect.