exp-pairs-0.2.1.0: Linear programming over exponent pairs

Copyright(c) Andrew Lelechenko 2014-2020
LicenseGPL-3
Maintainerandrew.lelechenko@gmail.com
Safe HaskellNone
LanguageHaskell2010

Math.ExpPairs

Description

Linear programming over exponent pairs

Package implements an algorithm to minimize the maximum of a list of rational objective functions over the set of exponent pairs. See full description in A. V. Lelechenko, Linear programming over exponent pairs. Acta Univ. Sapientiae, Inform. 5, No. 2, 271-287 (2013). http://www.acta.sapientia.ro/acta-info/C5-2/info52-7.pdf

A set of useful applications can be found in Math.ExpPairs.Ivic, Math.ExpPairs.Kratzel and Math.ExpPairs.MenzerNowak.

Synopsis

Documentation

optimize :: [RationalForm Rational] -> [Constraint Rational] -> OptimizeResult Source #

This function takes a list of rational forms and a list of constraints and returns an exponent pair, which satisfies all constraints and minimizes the maximum of all rational forms.

optimalValue :: OptimizeResult -> RationalInf Source #

The minimal value of objective function.

optimalPair :: OptimizeResult -> InitPair Source #

The initial exponent pair, on which minimal value was achieved.

optimalPath :: OptimizeResult -> Path Source #

The sequence of processes, after which minimal value was achieved.

data LinearForm t Source #

Define an affine linear form of three variables: a*k + b*l + c*m. First argument of LinearForm stands for a, second for b and third for c. Linear forms form a monoid by addition.

Instances
Functor LinearForm Source # 
Instance details

Defined in Math.ExpPairs.LinearForm

Methods

fmap :: (a -> b) -> LinearForm a -> LinearForm b #

(<$) :: a -> LinearForm b -> LinearForm a #

Foldable LinearForm Source # 
Instance details

Defined in Math.ExpPairs.LinearForm

Methods

fold :: Monoid m => LinearForm m -> m #

foldMap :: Monoid m => (a -> m) -> LinearForm a -> m #

foldr :: (a -> b -> b) -> b -> LinearForm a -> b #

foldr' :: (a -> b -> b) -> b -> LinearForm a -> b #

foldl :: (b -> a -> b) -> b -> LinearForm a -> b #

foldl' :: (b -> a -> b) -> b -> LinearForm a -> b #

foldr1 :: (a -> a -> a) -> LinearForm a -> a #

foldl1 :: (a -> a -> a) -> LinearForm a -> a #

toList :: LinearForm a -> [a] #

null :: LinearForm a -> Bool #

length :: LinearForm a -> Int #

elem :: Eq a => a -> LinearForm a -> Bool #

maximum :: Ord a => LinearForm a -> a #

minimum :: Ord a => LinearForm a -> a #

sum :: Num a => LinearForm a -> a #

product :: Num a => LinearForm a -> a #

Traversable LinearForm Source # 
Instance details

Defined in Math.ExpPairs.LinearForm

Methods

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

sequenceA :: Applicative f => LinearForm (f a) -> f (LinearForm a) #

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

sequence :: Monad m => LinearForm (m a) -> m (LinearForm a) #

Eq t => Eq (LinearForm t) Source # 
Instance details

Defined in Math.ExpPairs.LinearForm

Methods

(==) :: LinearForm t -> LinearForm t -> Bool #

(/=) :: LinearForm t -> LinearForm t -> Bool #

Num t => Num (LinearForm t) Source # 
Instance details

Defined in Math.ExpPairs.LinearForm

Show t => Show (LinearForm t) Source # 
Instance details

Defined in Math.ExpPairs.LinearForm

Generic (LinearForm t) Source # 
Instance details

Defined in Math.ExpPairs.LinearForm

Associated Types

type Rep (LinearForm t) :: Type -> Type #

Methods

from :: LinearForm t -> Rep (LinearForm t) x #

to :: Rep (LinearForm t) x -> LinearForm t #

Num t => Semigroup (LinearForm t) Source # 
Instance details

Defined in Math.ExpPairs.LinearForm

Num t => Monoid (LinearForm t) Source # 
Instance details

Defined in Math.ExpPairs.LinearForm

NFData t => NFData (LinearForm t) Source # 
Instance details

Defined in Math.ExpPairs.LinearForm

Methods

rnf :: LinearForm t -> () #

(Num t, Eq t, Pretty t) => Pretty (LinearForm t) Source # 
Instance details

Defined in Math.ExpPairs.LinearForm

Methods

pretty :: LinearForm t -> Doc ann #

prettyList :: [LinearForm t] -> Doc ann #

type Rep (LinearForm t) Source # 
Instance details

Defined in Math.ExpPairs.LinearForm

data RationalForm t Source #

Define a rational form of two variables, equal to the ratio of two LinearForm.

Constructors

(LinearForm t) :/: (LinearForm t) infix 5 
Instances
Functor RationalForm Source # 
Instance details

Defined in Math.ExpPairs.LinearForm

Methods

fmap :: (a -> b) -> RationalForm a -> RationalForm b #

(<$) :: a -> RationalForm b -> RationalForm a #

Foldable RationalForm Source # 
Instance details

Defined in Math.ExpPairs.LinearForm

Methods

fold :: Monoid m => RationalForm m -> m #

foldMap :: Monoid m => (a -> m) -> RationalForm a -> m #

foldr :: (a -> b -> b) -> b -> RationalForm a -> b #

foldr' :: (a -> b -> b) -> b -> RationalForm a -> b #

foldl :: (b -> a -> b) -> b -> RationalForm a -> b #

foldl' :: (b -> a -> b) -> b -> RationalForm a -> b #

foldr1 :: (a -> a -> a) -> RationalForm a -> a #

foldl1 :: (a -> a -> a) -> RationalForm a -> a #

toList :: RationalForm a -> [a] #

null :: RationalForm a -> Bool #

length :: RationalForm a -> Int #

elem :: Eq a => a -> RationalForm a -> Bool #

maximum :: Ord a => RationalForm a -> a #

minimum :: Ord a => RationalForm a -> a #

sum :: Num a => RationalForm a -> a #

product :: Num a => RationalForm a -> a #

Traversable RationalForm Source # 
Instance details

Defined in Math.ExpPairs.LinearForm

Methods

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

sequenceA :: Applicative f => RationalForm (f a) -> f (RationalForm a) #

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

sequence :: Monad m => RationalForm (m a) -> m (RationalForm a) #

Eq t => Eq (RationalForm t) Source # 
Instance details

Defined in Math.ExpPairs.LinearForm

Num t => Fractional (RationalForm t) Source # 
Instance details

Defined in Math.ExpPairs.LinearForm

Num t => Num (RationalForm t) Source # 
Instance details

Defined in Math.ExpPairs.LinearForm

Show t => Show (RationalForm t) Source # 
Instance details

Defined in Math.ExpPairs.LinearForm

Generic (RationalForm t) Source # 
Instance details

Defined in Math.ExpPairs.LinearForm

Associated Types

type Rep (RationalForm t) :: Type -> Type #

Methods

from :: RationalForm t -> Rep (RationalForm t) x #

to :: Rep (RationalForm t) x -> RationalForm t #

NFData t => NFData (RationalForm t) Source # 
Instance details

Defined in Math.ExpPairs.LinearForm

Methods

rnf :: RationalForm t -> () #

(Num t, Eq t, Pretty t) => Pretty (RationalForm t) Source # 
Instance details

Defined in Math.ExpPairs.LinearForm

Methods

pretty :: RationalForm t -> Doc ann #

prettyList :: [RationalForm t] -> Doc ann #

type Rep (RationalForm t) Source # 
Instance details

Defined in Math.ExpPairs.LinearForm

type Rep (RationalForm t) = D1 (MetaData "RationalForm" "Math.ExpPairs.LinearForm" "exp-pairs-0.2.1.0-J4IGbuSTVwXCgBqjoU0P5n" False) (C1 (MetaCons ":/:" (InfixI NotAssociative 5) False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (LinearForm t)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (LinearForm t))))

data IneqType Source #

Constants to specify the strictness of Constraint.

Instances
Bounded IneqType Source # 
Instance details

Defined in Math.ExpPairs.LinearForm

Enum IneqType Source # 
Instance details

Defined in Math.ExpPairs.LinearForm

Eq IneqType Source # 
Instance details

Defined in Math.ExpPairs.LinearForm

Ord IneqType Source # 
Instance details

Defined in Math.ExpPairs.LinearForm

Show IneqType Source # 
Instance details

Defined in Math.ExpPairs.LinearForm

Generic IneqType Source # 
Instance details

Defined in Math.ExpPairs.LinearForm

Associated Types

type Rep IneqType :: Type -> Type #

Methods

from :: IneqType -> Rep IneqType x #

to :: Rep IneqType x -> IneqType #

Pretty IneqType Source # 
Instance details

Defined in Math.ExpPairs.LinearForm

Methods

pretty :: IneqType -> Doc ann #

prettyList :: [IneqType] -> Doc ann #

type Rep IneqType Source # 
Instance details

Defined in Math.ExpPairs.LinearForm

type Rep IneqType = D1 (MetaData "IneqType" "Math.ExpPairs.LinearForm" "exp-pairs-0.2.1.0-J4IGbuSTVwXCgBqjoU0P5n" False) (C1 (MetaCons "Strict" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "NonStrict" PrefixI False) (U1 :: Type -> Type))

data Constraint t Source #

A linear constraint of two variables.

Instances
Functor Constraint Source # 
Instance details

Defined in Math.ExpPairs.LinearForm

Methods

fmap :: (a -> b) -> Constraint a -> Constraint b #

(<$) :: a -> Constraint b -> Constraint a #

Foldable Constraint Source # 
Instance details

Defined in Math.ExpPairs.LinearForm

Methods

fold :: Monoid m => Constraint m -> m #

foldMap :: Monoid m => (a -> m) -> Constraint a -> m #

foldr :: (a -> b -> b) -> b -> Constraint a -> b #

foldr' :: (a -> b -> b) -> b -> Constraint a -> b #

foldl :: (b -> a -> b) -> b -> Constraint a -> b #

foldl' :: (b -> a -> b) -> b -> Constraint a -> b #

foldr1 :: (a -> a -> a) -> Constraint a -> a #

foldl1 :: (a -> a -> a) -> Constraint a -> a #

toList :: Constraint a -> [a] #

null :: Constraint a -> Bool #

length :: Constraint a -> Int #

elem :: Eq a => a -> Constraint a -> Bool #

maximum :: Ord a => Constraint a -> a #

minimum :: Ord a => Constraint a -> a #

sum :: Num a => Constraint a -> a #

product :: Num a => Constraint a -> a #

Traversable Constraint Source # 
Instance details

Defined in Math.ExpPairs.LinearForm

Methods

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

sequenceA :: Applicative f => Constraint (f a) -> f (Constraint a) #

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

sequence :: Monad m => Constraint (m a) -> m (Constraint a) #

Eq t => Eq (Constraint t) Source # 
Instance details

Defined in Math.ExpPairs.LinearForm

Methods

(==) :: Constraint t -> Constraint t -> Bool #

(/=) :: Constraint t -> Constraint t -> Bool #

Show t => Show (Constraint t) Source # 
Instance details

Defined in Math.ExpPairs.LinearForm

Generic (Constraint t) Source # 
Instance details

Defined in Math.ExpPairs.LinearForm

Associated Types

type Rep (Constraint t) :: Type -> Type #

Methods

from :: Constraint t -> Rep (Constraint t) x #

to :: Rep (Constraint t) x -> Constraint t #

NFData t => NFData (Constraint t) Source # 
Instance details

Defined in Math.ExpPairs.LinearForm

Methods

rnf :: Constraint t -> () #

(Num t, Eq t, Pretty t) => Pretty (Constraint t) Source # 
Instance details

Defined in Math.ExpPairs.LinearForm

Methods

pretty :: Constraint t -> Doc ann #

prettyList :: [Constraint t] -> Doc ann #

type Rep (Constraint t) Source # 
Instance details

Defined in Math.ExpPairs.LinearForm

type Rep (Constraint t) = D1 (MetaData "Constraint" "Math.ExpPairs.LinearForm" "exp-pairs-0.2.1.0-J4IGbuSTVwXCgBqjoU0P5n" False) (C1 (MetaCons "Constraint" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (LinearForm t)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 IneqType)))

type InitPair = InitPair' Rational Source #

Exponent pair built from rational fractions of Corput16, HuxW87b1 and Hux05

data Path Source #

Holds a list of Process and a matrix of projective transformation, which they define.

Instances
Eq Path Source # 
Instance details

Defined in Math.ExpPairs.Process

Methods

(==) :: Path -> Path -> Bool #

(/=) :: Path -> Path -> Bool #

Ord Path Source # 
Instance details

Defined in Math.ExpPairs.Process

Methods

compare :: Path -> Path -> Ordering #

(<) :: Path -> Path -> Bool #

(<=) :: Path -> Path -> Bool #

(>) :: Path -> Path -> Bool #

(>=) :: Path -> Path -> Bool #

max :: Path -> Path -> Path #

min :: Path -> Path -> Path #

Read Path Source # 
Instance details

Defined in Math.ExpPairs.Process

Show Path Source # 
Instance details

Defined in Math.ExpPairs.Process

Methods

showsPrec :: Int -> Path -> ShowS #

show :: Path -> String #

showList :: [Path] -> ShowS #

Generic Path Source # 
Instance details

Defined in Math.ExpPairs.Process

Associated Types

type Rep Path :: Type -> Type #

Methods

from :: Path -> Rep Path x #

to :: Rep Path x -> Path #

Semigroup Path Source # 
Instance details

Defined in Math.ExpPairs.Process

Methods

(<>) :: Path -> Path -> Path #

sconcat :: NonEmpty Path -> Path #

stimes :: Integral b => b -> Path -> Path #

Monoid Path Source # 
Instance details

Defined in Math.ExpPairs.Process

Methods

mempty :: Path #

mappend :: Path -> Path -> Path #

mconcat :: [Path] -> Path #

Pretty Path Source # 
Instance details

Defined in Math.ExpPairs.Process

Methods

pretty :: Path -> Doc ann #

prettyList :: [Path] -> Doc ann #

type Rep Path Source # 
Instance details

Defined in Math.ExpPairs.Process

data RatioInf t Source #

Extend Ratio t with \( \pm \infty \) positive and negative infinities.

Constructors

InfMinus

\( - \infty \)

Finite !(Ratio t)

Finite value

InfPlus

\( + \infty \)

Instances
Eq t => Eq (RatioInf t) Source # 
Instance details

Defined in Math.ExpPairs.RatioInf

Methods

(==) :: RatioInf t -> RatioInf t -> Bool #

(/=) :: RatioInf t -> RatioInf t -> Bool #

Integral t => Fractional (RatioInf t) Source # 
Instance details

Defined in Math.ExpPairs.RatioInf

Integral t => Num (RatioInf t) Source # 
Instance details

Defined in Math.ExpPairs.RatioInf

Integral t => Ord (RatioInf t) Source # 
Instance details

Defined in Math.ExpPairs.RatioInf

Methods

compare :: RatioInf t -> RatioInf t -> Ordering #

(<) :: RatioInf t -> RatioInf t -> Bool #

(<=) :: RatioInf t -> RatioInf t -> Bool #

(>) :: RatioInf t -> RatioInf t -> Bool #

(>=) :: RatioInf t -> RatioInf t -> Bool #

max :: RatioInf t -> RatioInf t -> RatioInf t #

min :: RatioInf t -> RatioInf t -> RatioInf t #

Integral t => Real (RatioInf t) Source # 
Instance details

Defined in Math.ExpPairs.RatioInf

Methods

toRational :: RatioInf t -> Rational #

Show t => Show (RatioInf t) Source # 
Instance details

Defined in Math.ExpPairs.RatioInf

Methods

showsPrec :: Int -> RatioInf t -> ShowS #

show :: RatioInf t -> String #

showList :: [RatioInf t] -> ShowS #

(Integral t, Pretty t) => Pretty (RatioInf t) Source # 
Instance details

Defined in Math.ExpPairs.RatioInf

Methods

pretty :: RatioInf t -> Doc ann #

prettyList :: [RatioInf t] -> Doc ann #

type RationalInf = RatioInf Integer Source #

Arbitrary-precision rational numbers with positive and negative infinities.

pattern K :: (Eq a, Num a) => a -> LinearForm a Source #

For a given c returns linear form c * k

pattern L :: (Eq a, Num a) => a -> LinearForm a Source #

For a given c returns linear form c * l

pattern M :: (Eq a, Num a) => a -> LinearForm a Source #

For a given c returns linear form c * m

(>.) :: Num t => LinearForm t -> LinearForm t -> Constraint t infix 5 Source #

Build a constraint, which states that the value of the first linear form is greater than the value of the second one.

(>=.) :: Num t => LinearForm t -> LinearForm t -> Constraint t infix 5 Source #

Build a constraint, which states that the value of the first linear form is greater or equal to the value of the second one.

(<.) :: Num t => LinearForm t -> LinearForm t -> Constraint t infix 5 Source #

Build a constraint, which states that the value of the first linear form is less than the value of the second one.

(<=.) :: Num t => LinearForm t -> LinearForm t -> Constraint t infix 5 Source #

Build a constraint, which states that the value of the first linear form is less or equal to the value of the second one.

scaleLF :: (Num t, Eq t) => t -> LinearForm t -> LinearForm t Source #

Multiply a linear form by a given coefficient.