| Safe Haskell | None |
|---|
Numeric.Optimization.Algorithms.CMAES
Description
Usage:
- create an optimization problem of type
Configby one ofminimize,minimizeIOetc. -
runit.
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
scalingin theConfigto the appropriate search range of each parameter. - Set
tolFunin theConfigto 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) :: V.Vector Double -> Double>>>bestVx <- run $ minimizeT f4 $ V.replicate 10 0>>>assert $ f4 bestVx < 1e-10
Or use minimizeG to optimize functions of almost any type. Let's create a triangle ABC
so that AB = 3, AC = 4, BC = 5.
>>>let dist (ax,ay) (bx,by) = ((ax-bx)**2 + (ay-by)**2)**0.5>>>let f5 [a,b,c] = (dist a b - 3.0)**2 + (dist a c - 4.0)**2 + (dist b c - 5.0)**2>>>bestTriangle <- run $ (minimizeG f5 [(0,0),(0,0),(0,0)]){tolFun = Just 1e-20}>>>assert $ f5 bestTriangle < 1e-10
Then the angle BAC should be orthogonal.
>>>let [(ax,ay),(bx,by),(cx,cy)] = bestTriangle>>>assert $ abs ((bx-ax)*(cx-ax) + (by-ay)*(cy-ay)) < 1e-10
When optimizing noisy functions, set noiseHandling = True 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>>>xs60 <- run $ (minimizeIO f6 $ replicate 10 0) {noiseHandling = False}>>>xs61 <- run $ (minimizeIO f6 $ replicate 10 0) {noiseHandling = True}>>>assert $ f6Pure xs61 < f6Pure xs60
- run :: forall tgt. Config tgt -> IO tgt
- data Config tgt = Config {
- funcIO :: tgt -> IO Double
- projection :: tgt -> [Double]
- embedding :: [Double] -> tgt
- initXs :: [Double]
- sigma0 :: Double
- scaling :: Maybe [Double]
- typicalXs :: Maybe [Double]
- noiseHandling :: Bool
- noiseReEvals :: Maybe Int
- noiseEps :: Maybe Double
- tolFacUpX :: Maybe Double
- tolUpSigma :: Maybe Double
- tolFun :: Maybe Double
- tolStagnation :: Maybe Int
- tolX :: Maybe Double
- verbose :: Bool
- defaultConfig :: Config a
- minimize :: ([Double] -> Double) -> [Double] -> Config [Double]
- minimizeIO :: ([Double] -> IO Double) -> [Double] -> Config [Double]
- minimizeT :: Traversable t => (t Double -> Double) -> t Double -> Config (t Double)
- minimizeTIO :: Traversable t => (t Double -> IO Double) -> t Double -> Config (t Double)
- minimizeG :: Data a => (a -> Double) -> a -> Config a
- minimizeGIO :: Data a => (a -> IO Double) -> a -> Config a
Documentation
Optimizer configuration. tgt is the type of the value to be
optimized.
Constructors
| Config | |
Fields
| |
defaultConfig :: Config aSource
The default Config values.
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.