-- |
-- Module:     Control.Wire.Prefab.Split
-- Copyright:  (c) 2011 Ertugrul Soeylemez
-- License:    BSD3
-- Maintainer: Ertugrul Soeylemez <es@ertes.de>
--
-- Wires for splitting and terminating computations.

module Control.Wire.Prefab.Split
    ( -- * Simple splitters
      fork,

      -- * Simple terminators
      quit,
      quitWith
    )
    where

import Control.Arrow
import Control.Wire.Types
import Data.Monoid


-- | Takes the input list and forks the wire for each value.  Also forks
-- a single inhibiting wire.  Warning:  Incorrect usage will cause space
-- leaks!  Use with care!
--
-- * Depends: Current instant
--
-- * Inhibits: Always in one thread, never in all others.
--
-- * Threads: Length of input list + 1.

fork :: (ArrowChoice (>~), ArrowPlus (>~), Monoid e) => Wire e (>~) [b] b
fork = mkFix fork'
    where
    fork' = proc xs' ->
        case xs' of
          []     -> returnA -< Left mempty
          (x:xs) -> arr (Right . fst) <+> (fork' <<^ snd) -< (x, xs)


-- | Terminates the current wire with no output.
--
-- * Threads: None.

quit :: ArrowZero (>~) => Wire e (>~) a b
quit = mkGen zeroArrow


-- | Terminates the current wire thread with the given input value as
-- the last output.
--
-- * Depends: Current instant.
--
-- * Threads: 1, then none.

quitWith :: ArrowZero (>~) => Wire e (>~) b b
quitWith = mkGen $ arr (\x -> (Right x, quit))