-- |
-- Module:     Control.Wire.Instances
-- Copyright:  (c) 2011 Ertugrul Soeylemez
-- License:    BSD3
-- Maintainer: Ertugrul Soeylemez <es@ertes.de>
--
-- This module defines 'Functor', 'Applicative', 'Alternative', 'Monad'
-- and 'MonadPlus' instances for 'First' and 'Last' monoids.

module Control.Wire.Instances () where

import Control.Applicative
import Control.Monad
import Data.Monoid


instance Functor First where
    fmap f (First c) = First (fmap f c)

instance Applicative First where
    pure = First . pure
    First cf <*> First cx = First (cf <*> cx)

instance Alternative First where
    empty = First Nothing
    First cx <|> First cy = First (cx <|> cy)

instance Monad First where
    return = pure
    First cx >>= f = First (cx >>= getFirst . f)

instance MonadPlus First where
    mzero = empty
    mplus = (<|>)


instance Functor Last where
    fmap f (Last c) = Last (fmap f c)

instance Applicative Last where
    pure = Last . pure
    Last cf <*> Last cx = Last (cf <*> cx)

instance Alternative Last where
    empty = Last Nothing
    Last cx <|> Last cy = Last (cy <|> cx)

instance Monad Last where
    return = pure
    Last cx >>= f = Last (cx >>= getLast . f)

instance MonadPlus Last where
    mzero = empty
    mplus = (<|>)