Passing Constructors as arguments

I am learning Haskell and have set a small exercise for myself on a frames and slots program. Would appreciate some help on how to pass constructors of data structures as arguments to a function. Thanks, -- Ralph __________ A Frames test
module Frames where
Define frame slots:
type FirstName = String -- first name type LastName = String -- last name type Organization = String type Email = String type WorkPhone = String type CellPhone = String type TelephoneNumber = String
Define slots for a contact
data ContactProperty = FN FirstName | LN LastName | OR Organization | EM Email | WP TelephoneNumber | MP TelephoneNumber deriving (Show, Eq)
data Contact = Contact [ContactProperty] deriving (Show, Eq)
type Contacts = [ Contact]
Now I need a way to extract properties from the frame. Start by testing pattern matching without using parameters. Then I need to find out how to pass a constructor as a parameter.
getProperty:: [ContactProperty] -> FirstName getProperty ((FN fn):_) = fn getProperty (_:xs) = getProperty xs getProperty [] = "unknown"
firstName:: Contact -> FirstName firstName (Contact cpl) = getProperty cpl
Define Contacts
c1::Contacts c1 = [ ( Contact [(FN "Ralph"),(LN "Hodgson"),(OR "TopQuadrant"),(EM "rhodgson@topquadrant.com")]), ( Contact [(FN "Mills"),(LN "Davis"),(EM "mdavis@project10x.com")])]
Tests
t1=firstName $ head c1 -- should be "Ralph" t2=firstName $ last c1 -- should be "Mills"

Am Mittwoch, 13. April 2005 15:43 schrieb Ralph Hodgson:
I am learning Haskell and have set a small exercise for myself on a frames and slots program. Would appreciate some help on how to pass constructors of data structures as arguments to a function.
Thanks,
-- Ralph <snip> Now I need a way to extract properties from the frame. Start by testing pattern matching without using parameters. Then I need to find out how to pass a constructor as a parameter.
Your code works fine. I'm not sure, what your problem is. Given type-correctness, data constructors can be passed as arguments to functions like any other function. Probably that's not your question, however. As a wild guess, maybe you should use labelled records, data Contact = Contact { firstName :: FirstName , lastName :: LastName , ... } and you have your selector-functions. And it's possible to define partial contacts as me = Contact{firstName="Daniel", lastName="Fischer"} -- just don't ask for my phone-number or anything else which is undefined. If I'm far off, state your problem more precisely.
getProperty:: [ContactProperty] -> FirstName getProperty ((FN fn):_) = fn getProperty (_:xs) = getProperty xs getProperty [] = "unknown"
firstName:: Contact -> FirstName firstName (Contact cpl) = getProperty cpl
Cheers, Daniel

Thanks for your help Daniel - I am clarifying my message Daniel Fischer wrote:
Am Mittwoch, 13. April 2005 15:43 schrieb Ralph Hodgson:
I am learning Haskell and have set a small exercise for myself on a frames and slots program. Would appreciate some help on how to pass constructors of data structures as arguments to a function.
Thanks,
-- Ralph
<snip>
Now I need a way to extract properties from the frame. Start by testing pattern matching without using parameters. Then I need to find out how to pass a constructor as a parameter.
Your code works fine. I'm not sure, what your problem is. Given type-correctness, data constructors can be passed as arguments to functions like any other function. Probably that's not your question, however.
I would like to see an example of passing constructors as arguments. I am still getting familiar with constructs like:
getProperty ( a -> b) -> [ContactProperty] -> b
I am not sure how to test the Constructor passed as the argument. Do I say the following:
getProperty c ((c v:_) = v getProperty c ((_:xs) = getProperty c xs ..
I have tried doing this but GHC gives me parse errors. There is Haskell syntax that I don't know yet that I need to learn.
As a wild guess, maybe you should use labelled records,
data Contact = Contact { firstName :: FirstName , lastName :: LastName , ... }
and you have your selector-functions.
thanks - very useful
And it's possible to define partial contacts as
me = Contact{firstName="Daniel", lastName="Fischer"}
-- just don't ask for my phone-number or anything else which is undefined.
If I'm far off, state your problem more precisely.
getProperty:: [ContactProperty] -> FirstName getProperty ((FN fn):_) = fn getProperty (_:xs) = getProperty xs getProperty [] = "unknown"
firstName:: Contact -> FirstName firstName (Contact cpl) = getProperty cpl
Cheers, Daniel

Am Mittwoch, 13. April 2005 17:14 schrieben Sie:
Thanks for your help Daniel - I am clarifying my message
I would like to see an example of passing constructors as arguments. I
am still getting familiar with constructs like:
getProperty ( a -> b) -> [ContactProperty] -> b
I am not sure how to test the Constructor passed as the argument. Do I
This isn't an argument, by the way, it's a parameter.
say the following:
getProperty c ((c v:_) = v getProperty c ((_:xs) = getProperty c xs
You can't do it thus, a variable-pattern like c may only appear once in a function definition and "c v" isn't a legal pattern, so may not appear on the lhs of the definition. Neither may an incompletely applied constructor: Hugs mode: Restart with command line option +98 for Haskell 98 mode ERROR "./Ini.hs":29 - Constructor "Left" must have exactly 1 argument in pattern The offending line is humm Left = LT You can achieve your goal with dummy values: getProperty c@(FN d) (x:xs) = case x of FN fn -> fn _ -> getProperty c xs getProperty c@(LN d) (x:xs) = case x of LN ln -> ln _ -> getProperty c xs ... and then call getProperty (FN undefined) list. This isn't very nice, though. I'd rather do it (if labelled records aren't the thing to do) using Maybe types: firstName :: ContactProperty -> Maybe FirstName firstName (FN fn) = Just fn firstName _ = Nothing and so on, then (this depends on all properties being represented by a String, if different types were involved, it'd be more complicated) getProperty :: (ContactProperty -> Maybe String) -> [ContactProperty] -> String getProperty f xs = case catMaybes $ map f xs of [] -> "unknown" (p:ps) -> p However, this isn't nice either.
..
I have tried doing this but GHC gives me parse errors. There is Haskell syntax that I don't know yet that I need to learn.
Quite natural, I strongly recommend reading the 'Gentle Introduction to Haskell' and every now and then looking whether you already know enough Haskell to profit by reading the report. The sections on pattern matching have valuable information on the problem at hand.
As a wild guess, maybe you should use labelled records,
data Contact = Contact { firstName :: FirstName , lastName :: LastName , ... }
and you have your selector-functions.
thanks - very useful
Nice to read that :-) Cheers, Daniel

I don't really understand what you want to achieve : constructors are functions, thus first class objects ... I suppose you want a destructor, ie a function extracting the first name from a property for example. You may want to have a look there : http://haskell.org/hawiki/DecoratingStructures Pierre Ralph Hodgson a écrit :
I am learning Haskell and have set a small exercise for myself on a frames and slots program. Would appreciate some help on how to pass constructors of data structures as arguments to a function.
Thanks,
-- Ralph __________
A Frames test
module Frames where Define frame slots:
type FirstName = String -- first name type LastName = String -- last name type Organization = String type Email = String type WorkPhone = String type CellPhone = String type TelephoneNumber = String
Define slots for a contact
data ContactProperty = FN FirstName | LN LastName | OR Organization | EM Email | WP TelephoneNumber | MP TelephoneNumber deriving (Show, Eq)
data Contact = Contact [ContactProperty] deriving (Show, Eq)
type Contacts = [ Contact]
Now I need a way to extract properties from the frame. Start by testing pattern matching without using parameters. Then I need to find out how to pass a constructor as a parameter.
getProperty:: [ContactProperty] -> FirstName getProperty ((FN fn):_) = fn getProperty (_:xs) = getProperty xs getProperty [] = "unknown"
firstName:: Contact -> FirstNamen firstName (Contact cpl) = getProperty cpl
Define Contacts
c1::Contacts c1 = [ ( Contact [(FN "Ralph"),(LN "Hodgson"),(OR "TopQuadrant"),(EM "rhodgson@topquadrant.com")]), ( Contact [(FN "Mills"),(LN "Davis"),(EM "mdavis@project10x.com")])]
Tests
t1=firstName $ head c1 -- should be "Ralph" t2=firstName $ last c1 -- should be "Mills"
------------------------------------------------------------------------
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Pierre Barbier de Reuille INRA - UMR Cirad/Inra/Cnrs/Univ.MontpellierII AMAP Botanique et Bio-informatique de l'Architecture des Plantes TA40/PSII, Boulevard de la Lironde 34398 MONTPELLIER CEDEX 5, France tel : (33) 4 67 61 65 77 fax : (33) 4 67 61 56 68
participants (3)
-
Daniel Fischer
-
Pierre Barbier de Reuille
-
Ralph Hodgson