Hello Lennart,

Thursday, May 28, 2009, 11:57:09 AM, you wrote:

> -- | Generalization of the 'Bool' type.  Used by the generalized 'Eq' and 
> 'Ord'.
> class Boolean bool where
>     (&&)  :: bool -> bool -> bool   -- ^Logical conjunction.
>     (||)  :: bool -> bool -> bool   -- ^Logical disjunction.

i use another approach which imho is somewhat closer to interpretation
of logical operations in dynamic languages (lua, ruby, perl):

a ||| b | isDefaultValue a = b
        | otherwise        = a

a &&& b | isDefaultValue a = defaultValue
        | otherwise        = b

-- Class of types having default value:
class    Defaults a      where defaultValue :: a
instance Defaults ()     where defaultValue = ()
instance Defaults Bool   where defaultValue = False
instance Defaults [a]    where defaultValue = []
instance Defaults (a->a)               where defaultValue = id
instance Defaults (Maybe a)            where defaultValue = Nothing
instance Defaults (a->IO a)            where defaultValue = return
instance Defaults a => Defaults (IO a) where defaultValue = return defaultValue
instance Defaults Int                  where defaultValue = 0
instance Defaults Integer              where defaultValue = 0
instance Defaults Double               where defaultValue = 0

-- Class of types that can be tested for default value:
class    TestDefaultValue a       where isDefaultValue :: a -> Bool
instance TestDefaultValue Bool    where isDefaultValue = not
instance TestDefaultValue [a]     where isDefaultValue = null
instance TestDefaultValue Int     where isDefaultValue = (==0)
instance TestDefaultValue Integer where isDefaultValue = (==0)
instance TestDefaultValue Double  where isDefaultValue = (==0)


usage examples:

return$ (isDir &&& addTrailingPathSeparator) filespec
openWebsite$ (isWindows &&& windosifyPath) file
let options =
      (compressionEnabled &&&  cvt "-m"   compressionMethod')++
      (encryptionEnabled  &&&  cvt "-ae=" 
encryptionMethod')++encryptionOptions++
      (protectionEnabled  &&&  cvt "-rr"  protectionMethod')
let another_msg = ciphers ||| "not encrypted"
let msg = ftLocked footer &&& "yes" ||| "no"


-- 
Best regards,
 Bulat                            mailto:bulat.zigans...@gmail.com

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to