{-# LANGUAGE CPP #-}
-----------------------------------------------------------------------------
-- |
-- Module      :  Control.Parallel.Eden.Iteration
-- Copyright   :  (c) Philipps Universitaet Marburg 2009-2014
-- License     :  BSD-style (see the file LICENSE)
-- 
-- Maintainer  :  eden@mathematik.uni-marburg.de
-- Stability   :  beta
-- Portability :  not portable
--
-- This Haskell module defines iteration skeletons for Eden.
--
-- Depends on the Eden Compiler.
--
-- Eden Project
--
module Control.Parallel.Eden.Iteration ( 
  -- * Iteration Skeletons  
  iterUntilAt, iterUntil
  ) where
import Control.Parallel.Eden.Auxiliary
import Control.Parallel.Eden.Map
#if defined( __PARALLEL_HASKELL__ ) || defined (NOT_PARALLEL)
import Control.Parallel.Eden
#else
import Control.Parallel.Eden.EdenConcHs
#endif

-- \cite{SkeletonBookChapter02}, code (c) Fernando Rubio
-- | The iterUntil skeleton is an iterated map skeleton. Each worker
-- function transforms one local worker state and one task per iteration.
-- The result is the next local state and the iterations
-- result, which is send back to the master. The master transforms the
-- output of all tasks of one iteration and a local master state into
-- the worker inputs of the next iteration and a new master state
-- using the combine function (output: Right tasks masterState) or
-- decides to terminate the iteration (output: Left result). The input
-- transformation function generates all initial worker states and
-- initial worker tasks and the initial master state from the skeleton.
iterUntil :: (Trans wl,Trans t, Trans sr) => 
	     (inp -> ([wl],[t],ml))            -- ^input transformation function
	     -> (wl -> t -> (sr,wl))           -- ^worker function
	     -> (ml -> [sr] -> Either r ([t],ml)) -- ^combine function
             -> inp                            -- ^input
             -> r                              -- ^result
iterUntil = iterUntilAt [0]

-- | This is the basic implementation, using places for explicit process
-- | placement of the worker processes.
iterUntilAt :: (Trans wl,Trans t, Trans sr) => 
               Places                            -- ^where to instatiate
               -> (inp -> ([wl],[t],ml))         -- ^input transformation function
               -> (wl -> t -> (sr,wl))           -- ^worker function
               -> (ml -> [sr] -> Either r ([t],ml)) -- ^combine function
               -> inp                            -- ^input
               -> r                              -- ^result
iterUntilAt pids split wf comb x = result where 
  (result, moretaskss) = manager comb ml (lazyTranspose srss)
  srss                 = parMapAt pids (worker wf) (zip wlocals taskss)
  taskss               = lazyTranspose (initials: moretaskss)
  (wlocals,initials,ml)= split x

-- master/manager functionality of the iterUntil skeleton
manager :: (ml -> [sr] -> Either r ([t],ml)) -> 
	   ml -> [[sr]] -> (r,[[t]])
manager comb ml (srs:srss) = case comb ml srs of
       Left res       -> (res,[]) -- Left: stop iteration
       Right (ts,ml') -> -- Right: proceed with new tasks (ts) and new state ml'
                         let (res',tss) = manager comb ml' srss
			 in (res', ts:tss)

--worker functionality of the iterUntil skeleton
worker :: (wl -> t -> (sr,wl)) -> (wl,[t]) -> [sr]
worker wf (local,[])    = []
worker wf (local, t:ts) = sr: worker wf (local',ts) where 
  (sr,local') = wf local t