[Haskell-cafe] Filter by several predicates at once

2008-01-17 Thread Dougal Stanton
Are the functions

 passall, passany :: [a - Bool] - a - Bool
 passall ps v = and $ map ($v) ps
 passany ps v = or $ map ($v) ps

or something similar defined anywhere? Such that one can write

 filter (passany tests) [0..10]
 filter (passall tests) [0..10]

where

 tests = [5, odd]

Or is there a better way of filtering by several predicates for each
value without using

 filter p3 . filter p2 . filter p1

or

 filter (\v - p1 v  p2 v  p3 v) vs

Cheers,

D

-- 
Dougal Stanton
[EMAIL PROTECTED] // http://www.dougalstanton.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Filter by several predicates at once

2008-01-17 Thread Neil Mitchell
Hi

  passall, passany :: [a - Bool] - a - Bool
  passall ps v = and $ map ($v) ps
  passany ps v = or $ map ($v) ps

 or something similar defined anywhere? Such that one can write

Don't think so.

One thing I have often wanted is something like:

or1 a b x = a x || b x
or2 a b x y = a x y || b x y

Then you can do:

filter ((5) `or1` odd) [0..10]
filter ((5) `and1` odd) [0..10]

You can imagine that or1 could get a symbol such as ||#, and or2 could
perhaps be ||## (if # wasn't already really overloaded)

Thanks

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


Re: [Haskell-cafe] Filter by several predicates at once

2008-01-17 Thread Isaac Dupree

Neil Mitchell wrote:

Hi


passall, passany :: [a - Bool] - a - Bool
passall ps v = and $ map ($v) ps
passany ps v = or $ map ($v) ps

or something similar defined anywhere? Such that one can write


nearly; using Prelude:
passall ps v = all ($v) ps
passany ps v = any ($v) ps


One thing I have often wanted is something like:

or1 a b x = a x || b x
or2 a b x y = a x y || b x y


yep, there's the idea of putting Bools in a typeclass that allows you to 
(||) functions-returning-Bool-class-instance for example, which I 
haven't used much but seems like a good idea (though potentially 
confusing, especially if the Prelude-Bool-specific names are reused)


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


Re: [Haskell-cafe] Filter by several predicates at once

2008-01-17 Thread Dougal Stanton
On 17/01/2008, Stuart Cook [EMAIL PROTECTED] wrote:
 On Jan 18, 2008 1:46 AM, Isaac Dupree [EMAIL PROTECTED] wrote:

  nearly; using Prelude:
  passall ps v = all ($v) ps
  passany ps v = any ($v) ps

Yes, thanks Isaac. That should have been obvious, argh...


   passall = swing all
   passany = swing any

 Whether that's any better than the pointwise version is up to you.

I think in this case I will use the explicit version, because I
wouldn't remember how swing worked. What is the motivation for the
name? ;-) (Do I want to hear the answer...?)

D

-- 
Dougal Stanton
[EMAIL PROTECTED] // http://www.dougalstanton.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Filter by several predicates at once

2008-01-17 Thread Stuart Cook
On Jan 18, 2008 1:46 AM, Isaac Dupree [EMAIL PROTECTED] wrote:
 Neil Mitchell wrote:
  Hi
 
  passall, passany :: [a - Bool] - a - Bool
  passall ps v = and $ map ($v) ps
  passany ps v = or $ map ($v) ps
  or something similar defined anywhere? Such that one can write

 nearly; using Prelude:
 passall ps v = all ($v) ps
 passany ps v = any ($v) ps

See also http://haskell.org/haskellwiki/Pointfree#Swing, which would
let you define

  passall = swing all
  passany = swing any

Whether that's any better than the pointwise version is up to you.


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


Re[2]: [Haskell-cafe] Filter by several predicates at once

2008-01-17 Thread Bulat Ziganshin
Hello Isaac,

Thursday, January 17, 2008, 5:46:20 PM, you wrote:

 yep, there's the idea of putting Bools in a typeclass that allows you to
 (||) functions-returning-Bool-class-instance for example, which I 
 haven't used much but seems like a good idea (though potentially 
 confusing, especially if the Prelude-Bool-specific names are reused)

-- Datatypes having default values
classDefaults 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 Num a = Defaults a   where defaultValue = 0

-- Datatypes that can be checked for default value
classTestDefaultValue awhere isDefaultValue :: a - Bool
instance TestDefaultValue Bool where isDefaultValue = not
instance TestDefaultValue [a]  where isDefaultValue = null
instance Num a = TestDefaultValue a where isDefaultValue = (==0)

infixr 3  
infixr 2  |||

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

a  b | isDefaultValue a = defaultValue
| otherwise= b



my code contains countless examples of using these funcs:

1. here it is used to conditionally include options in cmdline:
  [rar, x, arcname]++
  (isAddDir  [-ad])++
  (arcdir  files  [-ap++arcdir])++...

2. here it is used to get list of files where current directory may be
specified as :
   files - dirList (dirName ||| .)

3. here it is used to show file basename or full path if basename is empty:
putStr (takeBaseName file  |||  file)

4. here it's used for conditional code execution:
   do opt_debug command  testMalloc
  ...

5. here it is used to additionally print amount of bad sectors if it's non-zero:
   putStrLn$ show recoverable_sectors++ recoverable errors ++
(bad_sectors   and ++show bad_sectors++ bad sectors)

6. here it's used to create tempfile in current directory unless
temporary directory was explicitly specified in --tempdir option
   let filename = (opt_tempdir command ||| .) / $$temp$$

7. here it is use to apply additional reorder step to sorted list only
if --reorder option was specified
  sorted_diskfiles - (opt_reorder command  reorder) (sort_files command 
diskfiles)

(reorder has type [String] - IO [String])


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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