[Haskell-cafe] Matching constructors

2006-02-10 Thread Creighton Hogg
Hi,
If I have something like
data Patootie = Pa Int | Tootie Int
and I want to pull out the indices of all elements of a list 
that have type constructor Tootie, how would I do that?

I thought I might be able to use findIndices, but I don't 
know how to express the predicate.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Matching constructors

2006-02-10 Thread J. Garrett Morris
tootieIndices = findIndices isTootie
where isTootie (Pa _) = False
  isTootie (Tootie _) = True

would be my first approach.

 /g

On 2/10/06, Creighton Hogg [EMAIL PROTECTED] wrote:
 Hi,
 If I have something like
 data Patootie = Pa Int | Tootie Int
 and I want to pull out the indices of all elements of a list
 that have type constructor Tootie, how would I do that?

 I thought I might be able to use findIndices, but I don't
 know how to express the predicate.
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe



--
We have lingered in the chambers of the sea 
By sea-girls wreathed with seaweed red and brown
Till human voices wake us, and we drown.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Matching constructors

2006-02-10 Thread Henning Thielemann

On Fri, 10 Feb 2006, Creighton Hogg wrote:

 Hi,
 If I have something like
 data Patootie = Pa Int | Tootie Int
 and I want to pull out the indices of all elements of a list
 that have type constructor Tootie, how would I do that?

 I thought I might be able to use findIndices, but I don't
 know how to express the predicate.

(\p - case p of {Pa _ - False; Tootie _ - True})

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


Re: [Haskell-cafe] Matching constructors

2006-02-10 Thread Jared Updike
Or inline as

 findIndices (\x - case x of Tootie _ - True; _ - False) listOfPasAndTooties

There was a recent thread about wanting a more succint way to write
this (unary pattern matching):
http://thread.gmane.org/gmane.comp.lang.haskell.cafe/11109

If John got his wish, then you could write something like
 findIndices (@ Tootie _) listOfPasAndTooties

Maybe this feature will appear in a future Haskell standard? though I
don't see anything on the Haskell' wiki about this...

Cheers
  Jared.
--
http://www.updike.org/~jared/
reverse )-:
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Matching constructors

2006-02-10 Thread Mark T.B. Carroll
Creighton Hogg [EMAIL PROTECTED] writes:

 data Patootie = Pa Int | Tootie Int
 and I want to pull out the indices of all elements of a list 
 that have type constructor Tootie, how would I do that?

x = [Pa 3, Tootie 5, Pa 7, Tootie 9, Pa 11]
y = [ i |Tootie i  - x ]
z = [ i | i@(Tootie _) - x ]

y or z might be helpful.

-- Mark

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


Re: [Haskell-cafe] Matching constructors

2006-02-10 Thread Cale Gibbard
On 10/02/06, Creighton Hogg [EMAIL PROTECTED] wrote:
 Hi,
 If I have something like
 data Patootie = Pa Int | Tootie Int
 and I want to pull out the indices of all elements of a list
 that have type constructor Tootie, how would I do that?

 I thought I might be able to use findIndices, but I don't
 know how to express the predicate.

Just to clear up a small point, Tootie isn't a type constructor, but a
data constructor. ('Maybe' is a type constructor, 'Just' is a data
constructor.)

You can use list comprehensions with pattern matching to write this
fairly succinctly:

tootieIndices xs = [i | (Tootie {}, i) - zip xs [0..]]

The {} matches whatever parameters Tootie might have, so this will
continue to work even if you later extend the Tootie data constructor
with more fields. If you want to match more carefully, you can of
course put a variable there.

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


Re: [Haskell-cafe] matching constructors

2004-03-08 Thread Vadim Zaliva
On Mar 5, 2004, at 15:48, Vadim Zaliva wrote:

OK, I figured it out. For sake of other novices like me here is what 
you need
to do to make it work.

0. Need to import Data.Generics
1. Compile with '-fglasgow-exts' flag
2. When deriving from Data you also need to derive from Typeable.
It slightly bothers me that this solution seems to be using 
non-standard GHC extensions.

Vadim

On Mar 5, 2004, at 12:41, Brandon Michael Moore wrote:

At the lower level of remimplementing your functions I can suggest a 
few
things.
Brandon,

Thanks for great suggestions! Following them, here is how I redone the 
code:

...

import Data.Maybe
import Data.Either
import Data.Typeable
...

data Flag = Verbose |
Input String  |
Output String |
Filter String
deriving Show Data
instance Eq Flag where
x == y = toConstr x == toConstr y
findFlag :: Flag - [Flag] - Flag
findFlag f fs = fromMaybe f (find (==f) fs)
The only problem is my GHC does not seems to find 'Data' class and I 
am getting following errors:

Type constructor or class not in scope: `Data'
Variable not in scope: `toConstr'
Variable not in scope: `toConstr'
Also I have style question: What is the best way to define equality 
test in this example:

1. Via instantiating EQ class
2. via standalone function (I can define sameConstr Flag - Flag - 
Bool)
3. inline lambda expression passed to find

I am leaning towards #2 or #3.

Vadim

--
La perfection est atteinte non quand il ne reste rien a ajouter, mais
quand il ne reste rien a enlever.  (Antoine de Saint-Exupery)
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe
--
La perfection est atteinte non quand il ne reste rien a ajouter, mais
quand il ne reste rien a enlever.  (Antoine de Saint-Exupery)


smime.p7s
Description: S/MIME cryptographic signature
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] matching constructors

2004-03-08 Thread Sven Panne
Vadim Zaliva wrote:
[...] It slightly bothers me that this solution seems to be using non-standard 
GHC extensions.
Hmmm, using generics seems like massive overkill for option handling. Could you
describe what you are exactly trying to achieve?
Cheers,
   S.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] matching constructors

2004-03-08 Thread Vadim Zaliva
On Mar 8, 2004, at 11:17, Sven Panne wrote:

Hmmm, using generics seems like massive overkill for option handling. 
Could you
describe what you are exactly trying to achieve?
I am doing command line options parsing. I've defined Flag type with 
constructor
for each possible option:

data Flag = Verbose |
Input String  |
Output String |
Filter String
deriving (Show, Typeable, Data)
getOpt returns me a list of such objects. Now I need to
look things up there by constructor. For example:

doSomething fltflag
where
(Filter fltflag) = findFlag (Filter none) opts
To achieve this I've defined:

instance Eq Flag where
x == y = toConstr x == toConstr y
findFlag :: Flag - [Flag] - Flag
findFlag f fs = fromMaybe f (find (==f) fs)
Sincerely,
Vadim
--
La perfection est atteinte non quand il ne reste rien a ajouter, mais
quand il ne reste rien a enlever.  (Antoine de Saint-Exupery)


smime.p7s
Description: S/MIME cryptographic signature
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] matching constructors

2004-03-08 Thread Ben Rudiak-Gould
On Mon, 8 Mar 2004, Vadim Zaliva wrote:

 I am doing command line options parsing. I've defined Flag type with 
 constructor
 for each possible option:
 
 data Flag = Verbose |
  Input String  |
  Output String |
  Filter String
  deriving (Show, Typeable, Data)
 
 getOpt returns me a list of such objects. Now I need to
 look things up there by constructor. For example:
 
   
   doSomething fltflag
   where
  (Filter fltflag) = findFlag (Filter none) opts

Try this instead:

doSomething $ option none [fltflag | Filter fltflag - opts]

...

option :: a - [a] - a
option def []  = def
option def [x] = x
option def _   = error Only one of each option allowed


-- Ben

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


Re: [Haskell-cafe] matching constructors

2004-03-08 Thread Vadim Zaliva
On Mar 8, 2004, at 12:55, Ben Rudiak-Gould wrote:

This would work, but I will have to write [] part for each option.
Generics approach is overkill but looks much neater when used.
But thanks for suggestion anyway, it is always good to learn yet
another way of doing things.
Sincerely,
Vadim
Try this instead:
doSomething $ option none [fltflag | Filter fltflag - opts]
option :: a - [a] - a
option def []  = def
option def [x] = x
option def _   = error Only one of each option allowed
--
La perfection est atteinte non quand il ne reste rien a ajouter, mais
quand il ne reste rien a enlever.  (Antoine de Saint-Exupery)


smime.p7s
Description: S/MIME cryptographic signature
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] matching constructors

2004-03-05 Thread Vadim Zaliva
Hi!

I am new to Haskell, but I have background in various programming 
languages (including Lisp)

I have very basic question, if there is a way to match algebraic types 
constructors besides
use of pattern matching. I wrote today code like this:

data Flag = Verbose |
Input String  |
Output String |
Filter String
deriving Show
instance Eq Flag where
Verbose  == Verbose  = True
Input  _ == Input  _ = True
Output _ == Output _ = True
Filter _ == Filter _ = True
_ == _ = False
findFlag :: Flag - [Flag] - Flag
findFlag f [] = f
findFlag y (x:xs) = if x == y then x else findFlag y xs
If there is a cleaner way to implement findFlag and Eq Flag?

Vadim

--
La perfection est atteinte non quand il ne reste rien a ajouter, mais
quand il ne reste rien a enlever.  (Antoine de Saint-Exupery)
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] matching constructors

2004-03-05 Thread Brandon Michael Moore


On Fri, 5 Mar 2004, Vadim Zaliva wrote:

 Hi!

 I am new to Haskell, but I have background in various programming
 languages (including Lisp)

 I have very basic question, if there is a way to match algebraic types
 constructors besides
 use of pattern matching. I wrote today code like this:

 data Flag = Verbose |
  Input String  |
  Output String |
  Filter String
  deriving Show

 instance Eq Flag where
  Verbose  == Verbose  = True
  Input  _ == Input  _ = True
  Output _ == Output _ = True
  Filter _ == Filter _ = True
  _ == _ = False

 findFlag :: Flag - [Flag] - Flag
 findFlag f [] = f
 findFlag y (x:xs) = if x == y then x else findFlag y xs

 If there is a cleaner way to implement findFlag and Eq Flag?

 Vadim

It looks like you are doing some sort of option processing. There have
been some suggestions recently for better approaches on the haskell list.
See the thread High-level technique for program options handling from
January.

The basic idea there is to define a record type holding your options in
the most useful form for your program, and turn your arguments into
functions that transfrom such a record, rather than values you need to
analyze. The example in Tomasz Zeilonka's post has exactly the option
structure of your code.



At the lower level of remimplementing your functions I can suggest a few
things.

It's probably overkill, but the Data typeclass provides an operation that
takes a value and returns the constructor used. Add Data to the list of
typeclasses you want to derive, and you can write your equality function
as (GHC only)

 x == y = toConstr x == toConstr y

For your findFlag function, the library function find is nearly what
you want, except it returns a value in Maybe rather than taking a default:

findFlag :: Flag - [Flag] - Maybe Flag
findFlag f fs = find (==f) fs

You could use the maybe function (Maybe a - b - (a-b) - b) to supply
the default.


Brandon

 --
 La perfection est atteinte non quand il ne reste rien a ajouter, mais
 quand il ne reste rien a enlever.  (Antoine de Saint-Exupery)

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



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