{- 
    Copyright 2011 Mario Blazevic

    This file is part of the Streaming Component Combinators (SCC) project.

    The SCC project is free software: you can redistribute it and/or modify it under the terms of the GNU General Public
    License as published by the Free Software Foundation, either version 3 of the License, or (at your option) any later
    version.

    SCC is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty
    of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License for more details.

    You should have received a copy of the GNU General Public License along with SCC.  If not, see
    <http://www.gnu.org/licenses/>.
-}

-- | This module defines the MonoidNull class.
-- 

module Data.Monoid.Null (
   -- * Classes
   MonoidNull(..)
   )
where
   
import Data.Monoid (Monoid(mempty), First(..), Last(..))
import qualified Data.List as List
import qualified Data.ByteString as ByteString
import qualified Data.Text as Text
import Data.ByteString (ByteString)
import Data.Text (Text)
   
-- | Extension of 'Monoid' that allows testing a value for equality with 'mempty'. The following law must hold:
-- 
-- > mnull == (== mempty)
class Monoid m => MonoidNull m where
   mnull :: m -> Bool

instance MonoidNull [x] where
   mnull = List.null

instance MonoidNull ByteString where
   mnull = ByteString.null

instance MonoidNull Text where
   mnull = Text.null

instance (MonoidNull a, MonoidNull b) => MonoidNull (a, b) where
   mnull (a, b) = mnull a && mnull b
   
instance Monoid a => MonoidNull (Maybe a) where
   mnull Nothing = True
   mnull _ = False

instance MonoidNull (First a) where
   mnull (First Nothing) = True
   mnull _ = False

instance MonoidNull (Last a) where
   mnull (Last Nothing) = True
   mnull _ = False