{-# OPTIONS -Wall -fno-warn-orphans #-} {-# LANGUAGE StandaloneDeriving, TypeSynonymInstances , GeneralizedNewtypeDeriving #-} ---------------------------------------------------------------------- -- | -- Module : Data.Bot.Misc -- Copyright : (c) Conal Elliott 2008 -- License : BSD3 -- -- Maintainer : conal@conal.net -- Stability : experimental -- -- Misc bot alternatives. See -- . ---------------------------------------------------------------------- module Data.Bot.Misc ( StreamBot, ChoosyBot(..) ) where import Data.Monoid import Control.Applicative import Data.Stream hiding (zip,unzip,map,tail) import Control.Arrow.Transformer.Stream import Data.Bot.Mutant -- | Function from streams to streams. Instance of 'Arrow', 'Functor', -- and 'Applicative' (partially applied for the latter two). type StreamBot = StreamArrow (->) -- | Bots who can choose whether or not to react to an input. The -- 'mappend' operation is left-biased in case of simultaneous reaction. newtype ChoosyBot i o = Choosy (MutantBot i (First o)) instance Monoid (ChoosyBot i o) where mempty = Choosy (pure mempty) Choosy b `mappend` Choosy c = Choosy (liftA2 mappend b c) ---- Move elsewhere -- data Stream a = Cons a (Stream a) deriving (Show, Eq) instance Monoid o => Monoid (Stream o) where mempty = pure mempty mappend = liftA2 mappend