cmaes-0.2.1.1: CMA-ES wrapper in Haskell

Safe HaskellNone

Numeric.Optimization.Algorithms.CMAES

Description

Usage:

  1. create an optimization problem of type Config by one of minimize, minimizeIO etc.
  2. run it.

Let's optimize the following function f(xs). xs is a list of Double and f has its minimum at xs !! i = sqrt(i).

>>> import Test.DocTest.Prop
>>> let f = sum . zipWith (\i x -> (x*abs x - i)**2) [0..] :: [Double] -> Double
>>> let initXs = replicate 10 0                            :: [Double]
>>> bestXs <- run $ minimize f initXs
>>> assert $ f bestXs < 1e-10

If your optimization is not working well, try:

  • Set scaling in the Config to the appropriate search range of each parameter.
  • Set tolFun in the Config to the appropriate scale of the function values.

An example for scaling the function value:

>>> let f2 xs = (/1e100) $ sum $ zipWith (\i x -> (x*abs x - i)**2) [0..] xs
>>> bestXs <- run $ (minimize f2 $ replicate 10 0) {tolFun = Just 1e-111}
>>> assert $ f2 bestXs < 1e-110

An example for scaling the input values:

>>> let f3 xs = sum $ zipWith (\i x -> (x*abs x - i)**2) [0,1e100..] xs
>>> let xs30 = replicate 10 0 :: [Double]
>>> let m3 = (minimize f3 xs30) {scaling = Just (repeat 1e50)}
>>> xs31 <- run $ m3
>>> assert $ f3 xs31 / f3 xs30 < 1e-10

Use minimizeT to optimize functions on traversable structures.

>>> import qualified Data.Vector as V
>>> let f4 = V.sum . V.imap (\i x -> (x*abs x - fromIntegral i)**2)
>>> :t f4
f4 :: V.Vector Double -> Double
>>> bestVx <- run $ minimizeT f4 $ V.replicate 10 0
>>> assert $ f4 bestVx < 1e-10

Or use minimizeG to optimize functions of any type that is Data and that contains Doubles. Here is an example that deal with Triangles.

>>> :set -XDeriveDataTypeable
>>> import Data.Data
>>> data Pt = Pt Double Double deriving (Typeable,Data)
>>> let dist (Pt ax ay) (Pt bx by) = ((ax-bx)**2 + (ay-by)**2)**0.5
>>> data Triangle = Triangle Pt Pt Pt deriving (Typeable,Data)

Let us create a triangle ABC so that AB = 3, AC = 4, BC = 5.

>>> let f5 (Triangle a b c) = (dist a b - 3.0)**2 + (dist a c - 4.0)**2 + (dist b c - 5.0)**2
>>> let triangle0 = Triangle o o o where o = Pt 0 0
>>> :t f5
f5 :: Triangle -> Double
>>> bestTriangle <- run $ (minimizeG f5 triangle0){tolFun = Just 1e-20}
>>> assert $ f5 bestTriangle < 1e-10

Then the angle BAC should be orthogonal.

>>> let (Triangle (Pt ax ay) (Pt bx by) (Pt cx cy)) = bestTriangle
>>> assert $ abs ((bx-ax)*(cx-ax) + (by-ay)*(cy-ay)) < 1e-10

When optimizing noisy functions, set noiseHandling = True (and increase noiseReEvals) for better results.

>>> import System.Random
>>> let noise = randomRIO (0,1e-2)
>>> let f6Pure = sum . zipWith (\i x -> (x*abs x - i)**2) [0..]
>>> let f6 xs = fmap (f6Pure xs +) noise
>>> :t f6
f6 :: [Double] -> IO Double
>>> xs60 <- run $ (minimizeIO f6 $ replicate 10 0) {noiseHandling = False}
>>> xs61 <- run $ (minimizeIO f6 $ replicate 10 0) {noiseHandling = True,noiseReEvals=Just 10}
>>> -- assert $ f6Pure xs61 < f6Pure xs60

(note : the above assertion holds with probability of about 70%.)

Synopsis

Documentation

run :: forall tgt. Config tgt -> IO tgtSource

Execute the optimizer and get the solution.

data Config tgt Source

Optimizer configuration. tgt is the type of the value to be optimized.

Constructors

Config 

Fields

funcIO :: tgt -> IO Double

The Function to be optimized.

projection :: tgt -> [Double]

Extract the parameters to be tuned from tgt.

embedding :: [Double] -> tgt

Create a value of type tgt from the parameters.

initXs :: [Double]

An initial guess of the parameters.

sigma0 :: Double

The global scaling factor.

scaling :: Maybe [Double]

Typical deviation of each input parameters. The length of the list is adjusted to be the same as initXs, e.g. you can lazily use an infinite list here.

typicalXs :: Maybe [Double]

Typical mean of each input parameters. The length of this list too, is adjusted to be the same as initXs.

noiseHandling :: Bool

Assume the function to be rugged and/or noisy

noiseReEvals :: Maybe Int

How many re-evaluation to make to estimate the noise.

noiseEps :: Maybe Double

Perturb the parameters by this amount (relative to sigma) to estimate the noise

tolFacUpX :: Maybe Double

Terminate when one of the scaling grew too big (initial scaling was too small.)

tolUpSigma :: Maybe Double

Terminate when the global scaling grew too big.

tolFun :: Maybe Double

Terminate when the function value diversity in the current and last few generations is smaller than this value

tolStagnation :: Maybe Int

Terminate when the improvement is not seen for this number of iterations.

tolX :: Maybe Double

Terminate when the deviations in the solutions are smaller than this value.

verbose :: Bool

Repeat the CMA-ES output into stderr.

otherArgs :: [(String, String)]

Interfaces for passing other configuration arguments directly to cma.py

defaultConfig :: Config aSource

The default Config values. Also consult the original document http://www.lri.fr/~hansen/pythoncma.html#-fmin for default values of the parameters not listed here.

minimize :: ([Double] -> Double) -> [Double] -> Config [Double]Source

Create a minimizing problem, given a pure function and an initial guess.

minimizeIO :: ([Double] -> IO Double) -> [Double] -> Config [Double]Source

Create a minimizing problem, given an IO function and an initial guess.

minimizeT :: Traversable t => (t Double -> Double) -> t Double -> Config (t Double)Source

Create a minimizing problem for a function on traversable structure t.

minimizeTIO :: Traversable t => (t Double -> IO Double) -> t Double -> Config (t Double)Source

Create a minimizing problem for an effectful function on a traversable structure t.

minimizeG :: Data a => (a -> Double) -> a -> Config aSource

Create a minimizing problem for a function on almost any type a which contain Doubles.

minimizeGIO :: Data a => (a -> IO Double) -> a -> Config aSource

Create a minimizing problem for an effectful function of almost any type.

getDoubles :: Data a => a -> [Double]Source

getDoubles and putDoubles are generic functions used to put [Double] in and out of generic data types. Let's test them.

>>> let d3 = (1,2,3) :: (Double,Int,Double)
>>> getDoubles d3
[1.0,3.0]
>>> putDoubles [4,5] d3
(4.0,2,5.0)
>>> let complicated = ([0,1],(2,[3,4])) :: ([Double],(Double,[Double]))
>>> getDoubles complicated
[0.0,1.0,2.0,3.0,4.0]
>>> putDoubles [5,6,7,8,9] complicated
([5.0,6.0],(7.0,[8.0,9.0]))

Putting back the obtained values should not change the data.

>>> import Test.DocTest.Prop
>>> type Complicated = ([[Double]],(),(([(Double,String)]),[Double]))
>>> prop ((\x -> putDoubles (getDoubles x) x == x) :: Complicated -> Bool)

You can get the original list back after putting it.

>>> let make3 xs = take 3 $ xs ++ [0..]
>>> prop ((\xs' y -> let xs = make3 xs' in getDoubles (putDoubles xs y)==xs) :: [Double] -> (Double,Double,Double) -> Bool)

putDoubles :: Data a => [Double] -> a -> aSource