Safe Haskell | None |
---|
This library has embedded within it two example TSP files drawn from the TSPLIB; burma14 and fl417. This module provides a loading routine for these two files only. General loading routines for the TSPLIB format are provided by the Combinatorial Problems library.
This module also provides a collection of simple TSP perturbation and recombination methods for use in the following examples. Much of the code for these examples, in terms of the TSP implementation, recombination and perturbation methods is not particularly efficient and only intended for example purposes.
To run these examples first use the following imports;
import Control.Search.Local import Control.Search.Local.Example import Control.Search.Local.Strategy import Control.Search.Local.Eager
- A simple maximal iterative improver. This will print out all the solutions encountered.
loadExampleFile BURMA14 >>= return . loopP (maximalii (map adjacentExchangeN))
- A stochastic choice from the improvement neighbourhood
iiExample = do prob<-loadExampleFile FL417 strat<-newStdGen >>= return . stochasticii rChoice . randoms return . loopP (strat (map adjacentExchangeN)) $ prob where rChoice xs p = xs !! (floor ((p::Float) * fromIntegral (length xs)))
- The standard TABU search, with a TABU list size of 5
loadExampleFile BURMA14 >>= return . bestSoFar . loopP (standardTabu 5 (map adjacentExchangeN) (map head))
- A more complex TABU search, with a varying neighbourhood and varying TABU list size
tabuExample = do prob<-loadExampleFile FL417 nF <- newStdGen >>= return . stochasticNeighbourhood 417 vWin <- newStdGen >>= return . varyWindow . randomRs (5,10) return . bestSoFar . loopP (tabu (vWin . window 15) nF (map head)) $ prob
- A simulated annealing search, using an adjacent exchange perturbation and a common geometric cooling strategy. The values of the cooling strategy have been selected through rather rough and ready quick testing.
saExample = do prob<-loadExampleFile FL417 (fIs,sIs) <- newStdGen >>= return . (\a->(map head a,map last a)) . chunk 2 . randomRs (0,numCities prob-1) let perturb = zipWith3 swapPositions fIs sIs choiceRs <-newStdGen >>= return . randoms return . bestSoFar . loopP (sa getTSPVal perturb (geoCooling 80000 (0.99 :: Float)) choiceRs) $ prob
- A genetic algorithm which only makes use of recombination.
gaNoMutate = do prob<-loadExampleFile FL417 recomb<-newStdGen >>= return . stochasticRecombine startSols <- newStdGen >>= return . randomStarts 20 prob let dist = (++[1]) . takeWhile (<1) $ iterate (*1.0884) (0.2::Float) rs <- newStdGen >>= return . randoms return . bestSoFar . loopS (ga (makePop 20) (recomb . gaSelect 2 dist rs) id) $ startSols
- A complete genetic algorithm that mutates in a random pattern (at a rate of 1/20th)
gaWithMutate = do prob<-loadExampleFile FL417 recomb<-newStdGen >>= return . stochasticRecombine startSols <- newStdGen >>= return . randomStarts 20 prob pattern <- newStdGen >>= return . map (<(0.05::Float)) . randoms -- boolean pattern (fIs,sIs) <- newStdGen >>= return . (\a->(map head a,map last a)) . chunk 2 . randomRs (0,numCities prob-1) let dist = (++[1]) . takeWhile (<1) $ iterate (*1.0884) (0.2::Float) let mut = nest pattern (zipWith3 swapPositions fIs sIs) rs <- newStdGen >>= return . randoms return . bestSoFar . loopS (ga (makePop 20) (recomb . gaSelect 2 dist rs) mut) $ startSols
All these examples are best demonstrated by composition with the following limiting function, parametrised as seen fit by the user;
strategy >>= return . limiterTSP 0 10
- data ExampleFiles
- loadExampleFile :: ExampleFiles -> IO TSPProblem
- swapPositions :: Int -> Int -> TSPProblem -> TSPProblem
- adjacentExchange :: Int -> TSPProblem -> TSPProblem
- adjacentExchangeN :: TSPProblem -> [TSPProblem]
- stochasticNeighbourhood :: RandomGen g => Int -> g -> StreamT TSPProblem (List TSPProblem)
- stochasticRecombine :: RandomGen g => g -> StreamT (List TSPProblem) TSPProblem
- randomStarts :: RandomGen g => Int -> TSPProblem -> g -> [TSPProblem]
- getTSPVal :: Floating f => TSPProblem -> f
- limiter :: (Floating f, Ord f) => (s -> f) -> f -> Int -> StreamT s s
- limiterTSP :: Double -> Int -> StreamT TSPProblem TSPProblem
Loading routines
loadExampleFile :: ExampleFiles -> IO TSPProblemSource
Demonstration loading routine for only two files stored within this library. After loading this routine also randomises the initial solution route.
For more general TSP loading routines see TSPLIB
.
Perturbation functions
swapPositions :: Int -> Int -> TSPProblem -> TSPProblemSource
A synonym for the function swapCitiesOnIndex
found in the TSP
library.
This will form the foundation of our perturbation and neighbourhood functions.
adjacentExchange :: Int -> TSPProblem -> TSPProblemSource
Swap a city, indicated by index, with the city after it, indicated by index.
Neighbourhood functions
adjacentExchangeN :: TSPProblem -> [TSPProblem]Source
For a particular path, generate every path that can exist from swapping adjacent cities.
stochasticNeighbourhood :: RandomGen g => Int -> g -> StreamT TSPProblem (List TSPProblem)Source
Many strategies benefit from a small manageable neighbourhood, but with the opportunity to access wider options. This stream transformer provides this, at each step providing a neighbourhood of size N, drawn randomly from the set of all possible city swaps, adjacent or otherwise.
This does not need to be defined as a stream transformer, but the alternative still requires parametrisation with values that will be drawn from a source of random numbers. This version would then require lifting to become a stream transformer, and this introduces more complications in the meta-heuristic code.
Recombination function
stochasticRecombine :: RandomGen g => g -> StreamT (List TSPProblem) TSPProblemSource
A recombination process, for use in the genetic algorithm examples. This is presented as a contraction, however it does assume that each population has already been constrained to elements that will form the parents of the new solution. This process also assumes that there will be exactly 2 parents to each new solution, so it is an example of a recombination method only.
Other TSP interaction functions
randomStarts :: RandomGen g => Int -> TSPProblem -> g -> [TSPProblem]Source
Genetic algorithms require a number of (usually) stochastically generated solutions to begin the process, not 1. This function is provided for these cases, taking the parameters;
- the number of solutions to produce
- a sample solution (for edgeweights and problem size)
- a random number generator
getTSPVal :: Floating f => TSPProblem -> fSource
Not a loading routine, but a synonym for a function within the TSP
library.
Functions for terminating the search, not yet folded into the main library
limiter :: (Floating f, Ord f) => (s -> f) -> f -> Int -> StreamT s sSource
A stream transformation that converts a local search process into a finite list. The function takes a quality function parameter, that can yield a floating point quality of a solution. The remaining functions control the limiting process;
- When the difference in quality between two solutions is below the second parameter, terminate (2) The two solutions that we are comparing are divided by the integer parameter
limiterTSP :: Double -> Int -> StreamT TSPProblem TSPProblemSource
Specialisation of limiter, fixing the quality function and the problem data type.