exp-pairs-0.1.5.2: Linear programming over exponent pairs

Copyright(c) Andrew Lelechenko, 2014-2015
LicenseGPL-3
Maintainerandrew.lelechenko@gmail.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Math.ExpPairs

Description

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 # 

Methods

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

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

Foldable LinearForm Source # 

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 #

Eq t => Eq (LinearForm t) Source # 

Methods

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

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

Num t => Num (LinearForm t) Source # 
Show t => Show (LinearForm t) Source # 
Generic (LinearForm t) Source # 

Associated Types

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

Methods

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

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

Num t => Monoid (LinearForm t) Source # 
NFData t => NFData (LinearForm t) Source # 

Methods

rnf :: LinearForm t -> () #

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

Methods

pretty :: LinearForm t -> Doc #

prettyList :: [LinearForm t] -> Doc #

type Rep (LinearForm t) Source # 

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 # 

Methods

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

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

Foldable RationalForm Source # 

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 #

Eq t => Eq (RationalForm t) Source # 
Num t => Fractional (RationalForm t) Source # 
Num t => Num (RationalForm t) Source # 
Show t => Show (RationalForm t) Source # 
Generic (RationalForm t) Source # 

Associated Types

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

Methods

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

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

NFData t => NFData (RationalForm t) Source # 

Methods

rnf :: RationalForm t -> () #

(Num t, Eq t, Pretty t) => Pretty (RationalForm t) Source # 
type Rep (RationalForm t) Source # 
type Rep (RationalForm t) = D1 (MetaData "RationalForm" "Math.ExpPairs.LinearForm" "exp-pairs-0.1.5.2-50yifXeMqwmGLdyksjZUeY" False) (C1 (MetaCons ":/:" (InfixI NotAssociative 5) False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (LinearForm t))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (LinearForm t)))))

data IneqType Source #

Constants to specify the strictness of Constraint.

data Constraint t Source #

A linear constraint of two variables.

Instances

Functor Constraint Source # 

Methods

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

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

Foldable Constraint Source # 

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 #

Eq t => Eq (Constraint t) Source # 

Methods

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

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

Show t => Show (Constraint t) Source # 
Generic (Constraint t) Source # 

Associated Types

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

Methods

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

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

NFData t => NFData (Constraint t) Source # 

Methods

rnf :: Constraint t -> () #

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

Methods

pretty :: Constraint t -> Doc #

prettyList :: [Constraint t] -> Doc #

type Rep (Constraint t) Source # 
type Rep (Constraint t) = D1 (MetaData "Constraint" "Math.ExpPairs.LinearForm" "exp-pairs-0.1.5.2-50yifXeMqwmGLdyksjZUeY" False) (C1 (MetaCons "Constraint" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (LinearForm t))) (S1 (MetaSel (Nothing 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 # 

Methods

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

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

Ord Path Source # 

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 # 
Show Path Source # 

Methods

showsPrec :: Int -> Path -> ShowS #

show :: Path -> String #

showList :: [Path] -> ShowS #

Generic Path Source # 

Associated Types

type Rep Path :: * -> * #

Methods

from :: Path -> Rep Path x #

to :: Rep Path x -> Path #

Monoid Path Source # 

Methods

mempty :: Path #

mappend :: Path -> Path -> Path #

mconcat :: [Path] -> Path #

Pretty Path Source # 

Methods

pretty :: Path -> Doc #

prettyList :: [Path] -> Doc #

type Rep Path Source # 
type Rep Path = D1 (MetaData "Path" "Math.ExpPairs.Process" "exp-pairs-0.1.5.2-50yifXeMqwmGLdyksjZUeY" False) (C1 (MetaCons "Path" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ProcessMatrix)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Process]))))

data RatioInf t Source #

Extends a rational type with positive and negative infinities.

Constructors

InfMinus

Negative infinity

Finite !(Ratio t)

Finite value

InfPlus

Positive infinity

Instances

Eq t => Eq (RatioInf t) Source # 

Methods

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

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

Integral t => Fractional (RatioInf t) Source # 
Integral t => Num (RatioInf t) Source # 
Integral t => Ord (RatioInf t) Source # 

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 # 

Methods

toRational :: RatioInf t -> Rational #

Show t => Show (RatioInf t) Source # 

Methods

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

show :: RatioInf t -> String #

showList :: [RatioInf t] -> ShowS #

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

Methods

pretty :: RatioInf t -> Doc #

prettyList :: [RatioInf t] -> Doc #

type RationalInf = RatioInf Integer Source #

Arbitrary-precision rational numbers with positive and negative infinities.

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

For a given c returns linear form c * k

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

For a given c returns linear form c * l

pattern M :: forall a. (Num a, Eq 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.