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

module Control.Wire.Prefab.Simple
    ( -- * Simple predefined wires.
      constant,
      identity,

      -- * Forced reduction
      force,
      forceNF,

      -- * Inject signals
      inject,
      injectEvent
    )
    where

import Control.DeepSeq (NFData, deepseq)
import Control.Wire.Types
import Data.Monoid


-- | The constant wire.  Outputs the given value all the time.

constant :: WirePure (>~) => b -> Wire e (>~) a b
constant x = mkPureFix (Right . const x)


-- | Force the input signal to weak head normal form, before outputting
-- it.  Applies 'seq' to the input signal.
--
-- * Depends: Current instant.

force :: WirePure (>~) => Wire e (>~) b b
force = mkPureFix (Right $!)


-- | Force the input signal to normal form, before outputting it.
-- Applies 'deepseq' to the input signal.
--
-- * Depends: Current instant.

forceNF :: (NFData b, WirePure (>~)) => Wire e (>~) b b
forceNF = mkPureFix (\x -> x `deepseq` Right x)


-- | The identity wire.  Outputs its input signal unchanged.
--
-- * Depends: Current instant.

identity :: WirePure (>~) => Wire e (>~) a a
identity = mkPureFix (Right $)


-- | Inject the given 'Either' value as a signal.  'Left' means
-- inhibition.
--
-- * Depends: Current instant.
--
-- * Inhibits: When input is 'Left'.

inject :: WirePure (>~) => Wire e (>~) (Either e b) b
inject = mkPureFix id


-- | Inject the given 'Maybe' value as a signal.  'Nothing' means
-- inhibition.
--
-- * Depends: Current instant.
--
-- * Inhibits: When input is 'Nothing'.

injectEvent :: (Monoid e, WirePure (>~)) => Wire e (>~) (Maybe b) b
injectEvent = mkPureFix (maybe (Left mempty) Right)