-- |
-- Module:     Control.Wire.Prefab.Split
-- Copyright:  (c) 2011 Ertugrul Soeylemez
-- License:    BSD3
-- Maintainer: Ertugrul Soeylemez <es@ertes.de>
--
-- Nondeterministic wires.

module Control.Wire.Prefab.Split
    ( -- * Nondeterministic wires
      WSplit(..)
    )
    where

import qualified Data.Foldable as F
import Control.Arrow
import Control.Monad
import Control.Wire.Types
import Data.Foldable (Foldable)


-- | Split the wires in the sense of the underlying arrow.  A /thread/
-- in this sense is called a branch.  This makes most sense with some
-- logic monad (like a list monad transformer) wrapped in a 'Kleisli'
-- arrow.
--
-- Warning: Incorrect usage will cause space leaks.  Use with care!

class Arrow (>~) => WSplit (>~) where
    -- | Splits the wire into a branch for each given input value.
    -- Additionally adds a single inhibiting branch.
    --
    -- Note: This wire splits at every instant.  In many cases you
    -- probably want to apply 'swallow' to it to split only in the first
    -- instant.
    --
    -- * Branches: As many as there are input values + 1.
    --
    -- * Depends: Current instant.
    --
    -- * Inhibits: Always in one branch, never in all others.
    branch :: Foldable f => Wire e (>~) (f b) b

    -- | Quits the current branch.
    --
    -- * Branches: Zero.
    quit :: Wire e (>~) a b

    -- | Acts like the identity wire in the first instant and terminates
    -- the branch in the next.
    --
    -- * Branches: One, then zero.
    --
    -- * Depends: Current instant.
    quitWith :: Wire e (>~) b b


instance MonadPlus m => WSplit (Kleisli m) where
    branch =
        WmGen $ \xs' -> do
            x <- F.foldl' (\xs x -> xs `mplus` return x) mzero xs'
            return (Right x, branch)

    quit     = WmGen (const mzero)
    quitWith = WmPure (\x -> (Right x, quit))