-- |
-- Module:     Control.Wire.Trans.Simple
-- Copyright:  (c) 2011 Ertugrul Soeylemez
-- License:    BSD3
-- Maintainer: Ertugrul Soeylemez <es@ertes.de>
--
-- Simple wire transformers.

module Control.Wire.Trans.Simple
    ( -- * Override input
      (--<),
      (>--)
    )
    where

import Control.Arrow
import Control.Wire.Types


-- | Apply the given function to the input, until the argument wire
-- starts producing.
--
-- * Depends: Like argument wire.
-- * Inhibits: Like argument wire.

(--<) :: Arrow (>~) => Wire e (>~) a b -> (a -> a) -> Wire e (>~) a b
WPure f --< g =
    mkPure $ \x' ->
        let (mx, w) = f (g x') in
        (mx, either (const $ w --< g) (const w) mx)
WGen c --< g =
    mkGen $ proc x' -> do
        (mx, w) <- c -< g x'
        returnA -< (mx, either (const $ w --< g) (const w) mx)

infixr 5 --<


-- | Apply the given function to the input, until the argument wire
-- starts producing.
--
-- * Depends: Like argument wire.
-- * Inhibits: Like argument wire.

(>--) :: Arrow (>~) => (a -> a) -> Wire e (>~) a b -> Wire e (>~) a b
(>--) = flip (--<)

infixl 5 >--