{- | We often need to iterate some update equation until convergence is detected. This module uses the State monad to provide a very general way of expressing computations of this kind. Copyright (C) Sean Holden 2011. sbh11\@cl.cam.ac.uk -} {- This file is part of HasGP. HasGP is free software: you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation, either version 3 of the License, or (at your option) any later version. HasGP is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with HasGP. If not, see . -} module HasGP.Support.Iterate where import Control.Monad.State {- | iterateOnce takes a function to update a state and another to compute a value associated with a given state. It returns a state transformer performing the corresponding update - that is, one iteration. -} iterateOnce::(s -> s) -> (s -> a) -> State s a iterateOnce updateState stateValue = do currentState <- get let newState = updateState currentState put newState return $ stateValue newState {- | iterateToConvergence takes a state transformer typically generated using iterateOnce, a convergence test that compares two values associated with the current and next states returning True if we've converged, and an initial value. It returns a state transformer that performs iteration until convergence. When run from an initial state it returns the state at convergence and the corresponding value. -} iterateToConvergence::State s a -> (a -> a -> Bool) -> a -> State s a iterateToConvergence doOnce converged currentValue = do newValue <- doOnce if (converged currentValue newValue) then return newValue else iterateToConvergence doOnce converged newValue {- | The same as iterateToConvergence, but takes the state update and state value functions directly, so the resulting state transformer only requires a start state to be run. -} iterateToConvergence'::(s -> s) -> (s -> a) -> (a -> a -> Bool) -> State s a iterateToConvergence' updateState stateValue converged = do startState <- get let initialValue = stateValue startState let itOnce = iterateOnce updateState stateValue iterateToConvergence itOnce converged initialValue {- | The same as iterateToConvergence, but does one update to obtain an initial value and continues from there. Consequently, no initial value is required, but you do one extra update. -} iterateToConvergence''::State s a -> (a -> a -> Bool) -> State s a iterateToConvergence'' doOnce converged = do newValue <- doOnce iterateToConvergence doOnce converged newValue