
Example: data SampleType = A | B Int | C String | D -- .... etc. sampleTypes = [A, B 5, C "test"] :: [SampleType] How do I find for example element A in the sampleTypes list? Do I have to create e.g.: isA :: SampleType -> Bool isA A = True isA _ = False for every constructor and use find? It feels like this is not the quicker method. Thanks, Adam

On Tue, Jun 3, 2008 at 5:11 PM, Adam Smyczek
Example:
data SampleType = A | B Int | C String | D -- .... etc.
sampleTypes = [A, B 5, C "test"] :: [SampleType]
How do I find for example element A in the sampleTypes list? Do I have to create e.g.:
isA :: SampleType -> Bool isA A = True isA _ = False
for every constructor and use find?
isA is already defined for every constructor, so all you have to do is "find isA"
It feels like this is not the quicker method.
Thanks, Adam
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Adam Smyczek wrote:
data SampleType = A | B Int | C String | D -- .... etc.
sampleTypes = [A, B 5, C "test"] :: [SampleType]
How do I find for example element A in the sampleTypes list?
Here's one way to do it: filter (\x -> case x of A -> True; otherwise -> False) sampleTypes ==> [A] filter (\x -> case x of B _ -> True; otherwise -> False) sampleTypes ==> [B 5] filter (\x -> case x of C _ -> True; otherwise -> False) sampleTypes ==> [C "test"] Your idea works just as well:
isA :: SampleType -> Bool isA A = True isA _ = False
filter isA sampleTypes ==> [A] There is a third possibility: Have you learned about the maybe function or the either function yet? maybe :: b -> (a -> b) -> Maybe a -> b either :: (a -> c) -> (b -> c) -> Either a b -> c I would call these "mediating morphisms", where "morphism" is techno- babble for "function". You could write your own version of one of these for SampleType. Assuming you have: data SampleType = A | B Int | C String You could write: sampletype :: t -> (Int -> t) -> (String -> t) -> SampleType -> t sampletype a bf cf s = case s of A -> a B n -> bf n C s -> cf s isA = sampletype True (const False) (const False) isB = sampletype False (const True) (const False) isC = sampletype False (const False) (const True) filter isA sampleTypes ==> [A] This (the mediating morphism) is probably overkill for what you want to do, though.

On Tue, Jun 3, 2008 at 6:48 PM, Ronald Guida
filter (\x -> case x of A -> True; otherwise -> False) sampleTypes ==> [A]
filter (\x -> case x of B _ -> True; otherwise -> False) sampleTypes ==> [B 5]
There's a neat little mini-trick for these types of pattern matches: filter (\x -> case x of B {} -> True; otherwise -> False) sampleTypes Does the same thing, but works no matter how many arguments the constructor B takes. Luke

Adam Smyczek
data SampleType = A | B Int | C String | D -- .... etc. deriving (Eq)
sampleTypes = [A, B 5, C "test"] :: [SampleType]
If you derive from Eq, you can do isA = (==) A filter isA sampleTypes or ad-hoc: filter ((==) A) sampleTypes things like filter (\x -> case x of { A -> True ; B b | b > 2 -> True ; C c | c == "foo" -> True ; _ -> False}) sampleTypes work, too. Admittedly, I'm lambda-spoilt. -- (c) this sig last receiving data processing entity. Inspect headers for past copyright information. All rights reserved. Unauthorised copying, hiring, renting, public performance and/or broadcasting of this signature prohibited.

Achim Schneider
filter (\x -> case x of { A -> True ; B b | b > 2 -> True ; C c | c == "foo" -> True ; _ -> False}) sampleTypes
coming to think of it: Why can't I write filter (\A -> True \B b | b > 2 -> True \C c | c == "foo" -> True _ -> False ) sampleTypes ? AFAICT it's syntactically unambiguous. -- (c) this sig last receiving data processing entity. Inspect headers for past copyright information. All rights reserved. Unauthorised copying, hiring, renting, public performance and/or broadcasting of this signature prohibited.

There's always one more way to do things in Haskell! :) Here's yet another way to get at the payloads in a list. You don't have to know how this works to use it: data SampleType = A | B Int | C String unA :: SampleType -> [()] unA A = return () unA _ = fail "Not an A" unB :: SampleType -> [Int] unB (B b) = return b unB _ = fail "Not a B" unC :: SampleType -> [String] unC (C c) = return c unC _ = fail "Not a C" -- I can check for more than one constructor... -- Note that a single type must be returned, -- so for C I return e.g. the length of the string unBorC :: SampleType -> [Int] unBorC (B b) = return b unBorC (C c) = return (length c) unBorC _ = fail "Not a B or C" For lists, the >>= operator knows to ignore failure and collect anything else into a new list. The technobabble for this is that [] is a Monad. *Main> let sampleTypes = [A, B 5, C "test", A, A, B 7, C "go"] *Main> sampleTypes >>= unA [(),(),()] *Main> sampleTypes >>= unB [5,7] *Main> sampleTypes >>= unC ["test","go"] *Main> sampleTypes >>= unBorC [5,4,7,2] Adam Smyczek wrote:
Example:
data SampleType = A | B Int | C String | D -- .... etc.
sampleTypes = [A, B 5, C "test"] :: [SampleType]
How do I find for example element A in the sampleTypes list? Do I have to create e.g.:
isA :: SampleType -> Bool isA A = True isA _ = False
for every constructor and use find? It feels like this is not the quicker method.
Thanks, Adam
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Dan Weston
There's always one more way to do things in Haskell! :)
Here's yet another way to get at the payloads in a list. You don't have to know how this works to use it:
Bastard. He's going to try and find out how it works. To get back to the filters: module Main where import Control.Monad data SampleType = A | B Int | C String deriving Show noA :: SampleType -> [SampleType] noA A = mzero noA e = return e noB :: SampleType -> [SampleType] noB (B _) = mzero noB e = return e noAB :: SampleType -> [SampleType] noAB m = [m] >>= noA >>= noB sampleTypes = [A, B 5, C "test", A, A, B 7, C "go"] *Main> sampleTypes >>= noA [B 5,C "test",B 7,C "go"] *Main> sampleTypes >>= noB [A,C "test",A,A,C "go"] *Main> sampleTypes >>= noAB [C "test",C "go"] -- (c) this sig last receiving data processing entity. Inspect headers for past copyright information. All rights reserved. Unauthorised copying, hiring, renting, public performance and/or broadcasting of this signature prohibited.

adam.smyczek:
Example:
data SampleType = A | B Int | C String | D -- .... etc.
sampleTypes = [A, B 5, C "test"] :: [SampleType]
How do I find for example element A in the sampleTypes list? Do I have to create e.g.:
isA :: SampleType -> Bool isA A = True isA _ = False
for every constructor and use find? It feels like this is not the quicker method.
This is where the implicit filtering in a list comprehension comes in really handy, data T = A | B Int | C String | D deriving Show xs = [A, B 5, C "test", D] main = do print [ A | A <- xs ] -- filter A's print [ x | x@(C _) <- xs ] -- filter C's {- *Main> main [A] [C "test"] -}

Adam Smyczek wrote:
data SampleType = A | B Int | C String | D -- .... etc. sampleTypes = [A, B 5, C "test"] :: [SampleType] How do I find for example element A in the sampleTypes list?
There have been many useful replies. But since Adam originally announced that this is a "beginner question", I think some perspective is in order. In Haskell, there is often no need at all for boolean-valued functions to deconstruct a data structure. Usually pattern matching does the job beautifully, and you structure your program to exploit that. In the case that you do need them, though, the previous responses are excellent suggestions. In my experience, the ways that I get data out of an ADT, from most common to most rare, are: 1. Just use pattern matching 2. Use record syntax to get selector functions 3. Define an Eq instance 4. Define per-constructor modifiers when the ADT is used as state in a state monad (this one is admittedly a pain in the neck) I can't remember the last time I needed to write a function like "isA" - it almost never comes up. My opinion, YMMV. Regards, Yitz
participants (8)
-
Achim Schneider
-
Adam Smyczek
-
Dan Weston
-
Don Stewart
-
Luke Palmer
-
Philip Weaver
-
Ronald Guida
-
Yitzchak Gale