
My initial guess would be no...its built into the language But.... I find myself tempted to use it (in order to match on a type that's the instance of a typeclass)...which makes me think I've missed something. So...
data Foo = Foo data Bar = Bar
Ooo...this looks like an OO design pattern...surely wrong?
class Wibble a where visit :: (Foo -> b) -> (Bar -> b) -> a -> b
instance Wibble Foo where visit f _ x = f x instance Wibble Bar where visit _ f x = f x
I want a list of Wibbles.... hmmm... (Wibble a) => [a] is clearly wrong... I want [(Wibble a) =>a] so I package it up?
data WibblePackage where WibblePackage :: (Wibble a) => a -> WibblePackage
lets try this now...so pointless function across Wibbles in a list.
fizzBuzz :: [WibblePackage] -> Integer fizzBuzz [] = 0 fizzBuzz ((WibblePackage x) : xs) = (visit (\_ -> 1) (\_ -> 2) x) + (fizzBuzz xs)
help :: Integer help = fizzBuzz [WibblePackage Foo,WibblePackage Bar]
That works! OO nerds will get uptight about "closing" the Wibble typeclass....but I've managed to create a list of different types and have a mechanism for recovering the type. How would a Haskell nerd do this? (I have looked, but they look more complicated....maybe to my OO eye). CONFIDENTIALITY NOTICE This e-mail (and any attached files) is confidential and protected by copyright (and other intellectual property rights). If you are not the intended recipient please e-mail the sender and then delete the email and any attached files immediately. Any further use or dissemination is prohibited. While MTV Networks Europe has taken steps to ensure that this email and any attachments are virus free, it is your responsibility to ensure that this message and any attachments are virus free and do not affect your systems / data. Communicating by email is not 100% secure and carries risks such as delay, data corruption, non-delivery, wrongful interception and unauthorised amendment. If you communicate with us by e-mail, you acknowledge and assume these risks, and you agree to take appropriate measures to minimise these risks when e-mailing us. MTV Networks International, MTV Networks UK & Ireland, Greenhouse, Nickelodeon Viacom Consumer Products, VBSi, Viacom Brand Solutions International, Be Viacom, Viacom International Media Networks and VIMN and Comedy Central are all trading names of MTV Networks Europe. MTV Networks Europe is a partnership between MTV Networks Europe Inc. and Viacom Networks Europe Inc. Address for service in Great Britain is 17-29 Hawley Crescent, London, NW1 8TT.

I discovered the same general pattern foroop
On Friday, June 19, 2015, Nicholls, Mark
My initial guess would be no…its built into the language
But….
I find myself tempted to use it (in order to match on a type that’s the instance of a typeclass)…which makes me think I’ve missed something.
So…
data Foo = Foo
data Bar = Bar
Ooo…this looks like an OO design pattern…surely wrong?
class Wibble a where
visit :: (Foo -> b) -> (Bar -> b) -> a -> b
instance Wibble Foo where
visit f _ x = f x
instance Wibble Bar where
visit _ f x = f x
I want a list of Wibbles....
hmmm...
(Wibble a) => [a] is clearly wrong...
I want [(Wibble a) =>a]
so I package it up?
data WibblePackage where
WibblePackage :: (Wibble a) => a -> WibblePackage
lets try this now…so pointless function across Wibbles in a list.
fizzBuzz :: [WibblePackage] -> Integer
fizzBuzz [] = 0
fizzBuzz ((WibblePackage x) : xs) = (visit (\_ -> 1) (\_ -> 2) x) + (fizzBuzz xs)
help :: Integer
help = fizzBuzz [WibblePackage Foo,WibblePackage Bar]
That works!
OO nerds will get uptight about “closing” the Wibble typeclass….but I’ve managed to create a list of different types and have a mechanism for recovering the type.
How would a Haskell nerd do this? (I have looked, but they look more complicated….maybe to my OO eye).
CONFIDENTIALITY NOTICE
This e-mail (and any attached files) is confidential and protected by copyright (and other intellectual property rights). If you are not the intended recipient please e-mail the sender and then delete the email and any attached files immediately. Any further use or dissemination is prohibited.
While MTV Networks Europe has taken steps to ensure that this email and any attachments are virus free, it is your responsibility to ensure that this message and any attachments are virus free and do not affect your systems / data.
Communicating by email is not 100% secure and carries risks such as delay, data corruption, non-delivery, wrongful interception and unauthorised amendment. If you communicate with us by e-mail, you acknowledge and assume these risks, and you agree to take appropriate measures to minimise these risks when e-mailing us.
MTV Networks International, MTV Networks UK & Ireland, Greenhouse, Nickelodeon Viacom Consumer Products, VBSi, Viacom Brand Solutions International, Be Viacom, Viacom International Media Networks and VIMN and Comedy Central are all trading names of MTV Networks Europe. MTV Networks Europe is a partnership between MTV Networks Europe Inc. and Viacom Networks Europe Inc. Address for service in Great Britain is 17-29 Hawley Crescent, London, NW1 8TT.
-- Sent from my hyper-communicator

Doh fat fingers!
I discovered the same general pattern for oops programming in Haskell. An
example -
https://github.com/ajnsit/oop-inheritence-in-haskell/blob/master/Main.hs
On Friday, June 19, 2015, Anupam Jain
I discovered the same general pattern foroop
On Friday, June 19, 2015, Nicholls, Mark
javascript:_e(%7B%7D,'cvml','nicholls.mark@vimn.com');> wrote: My initial guess would be no…its built into the language
But….
I find myself tempted to use it (in order to match on a type that’s the instance of a typeclass)…which makes me think I’ve missed something.
So…
data Foo = Foo
data Bar = Bar
Ooo…this looks like an OO design pattern…surely wrong?
class Wibble a where
visit :: (Foo -> b) -> (Bar -> b) -> a -> b
instance Wibble Foo where
visit f _ x = f x
instance Wibble Bar where
visit _ f x = f x
I want a list of Wibbles....
hmmm...
(Wibble a) => [a] is clearly wrong...
I want [(Wibble a) =>a]
so I package it up?
data WibblePackage where
WibblePackage :: (Wibble a) => a -> WibblePackage
lets try this now…so pointless function across Wibbles in a list.
fizzBuzz :: [WibblePackage] -> Integer
fizzBuzz [] = 0
fizzBuzz ((WibblePackage x) : xs) = (visit (\_ -> 1) (\_ -> 2) x) + (fizzBuzz xs)
help :: Integer
help = fizzBuzz [WibblePackage Foo,WibblePackage Bar]
That works!
OO nerds will get uptight about “closing” the Wibble typeclass….but I’ve managed to create a list of different types and have a mechanism for recovering the type.
How would a Haskell nerd do this? (I have looked, but they look more complicated….maybe to my OO eye).
CONFIDENTIALITY NOTICE
This e-mail (and any attached files) is confidential and protected by copyright (and other intellectual property rights). If you are not the intended recipient please e-mail the sender and then delete the email and any attached files immediately. Any further use or dissemination is prohibited.
While MTV Networks Europe has taken steps to ensure that this email and any attachments are virus free, it is your responsibility to ensure that this message and any attachments are virus free and do not affect your systems / data.
Communicating by email is not 100% secure and carries risks such as delay, data corruption, non-delivery, wrongful interception and unauthorised amendment. If you communicate with us by e-mail, you acknowledge and assume these risks, and you agree to take appropriate measures to minimise these risks when e-mailing us.
MTV Networks International, MTV Networks UK & Ireland, Greenhouse, Nickelodeon Viacom Consumer Products, VBSi, Viacom Brand Solutions International, Be Viacom, Viacom International Media Networks and VIMN and Comedy Central are all trading names of MTV Networks Europe. MTV Networks Europe is a partnership between MTV Networks Europe Inc. and Viacom Networks Europe Inc. Address for service in Great Britain is 17-29 Hawley Crescent, London, NW1 8TT.
-- Sent from my hyper-communicator
-- Sent from my hyper-communicator

The design pattern is very well known in the OO community…most of the use cases evaporate in Haskell….in some sense its part of the language…
Haskell is my 9th or 10th language, I can barely write “hello world” without the manual, so I’m still at times I’m still trying to discover the basic idioms…
How to put heterogenuos things in a list…and yet not loose all type information (I know about HList…but I think that’s for special occasions)
From: Haskell-Cafe [mailto:haskell-cafe-bounces@haskell.org] On Behalf Of Anupam Jain
Sent: 19 June 2015 5:04 PM
To: haskell-cafe Cafe
Subject: Re: [Haskell-cafe] Do people use visitor pattern in Haskell...
I discovered the same general pattern foroop
On Friday, June 19, 2015, Nicholls, Mark
data Foo = Foo data Bar = Bar
Ooo…this looks like an OO design pattern…surely wrong?
class Wibble a where visit :: (Foo -> b) -> (Bar -> b) -> a -> b
instance Wibble Foo where visit f _ x = f x instance Wibble Bar where visit _ f x = f x
I want a list of Wibbles.... hmmm... (Wibble a) => [a] is clearly wrong... I want [(Wibble a) =>a] so I package it up?
data WibblePackage where WibblePackage :: (Wibble a) => a -> WibblePackage
lets try this now…so pointless function across Wibbles in a list.
fizzBuzz :: [WibblePackage] -> Integer fizzBuzz [] = 0 fizzBuzz ((WibblePackage x) : xs) = (visit (\_ -> 1) (\_ -> 2) x) + (fizzBuzz xs)
help :: Integer help = fizzBuzz [WibblePackage Foo,WibblePackage Bar]
That works! OO nerds will get uptight about “closing” the Wibble typeclass….but I’ve managed to create a list of different types and have a mechanism for recovering the type. How would a Haskell nerd do this? (I have looked, but they look more complicated….maybe to my OO eye). CONFIDENTIALITY NOTICE This e-mail (and any attached files) is confidential and protected by copyright (and other intellectual property rights). If you are not the intended recipient please e-mail the sender and then delete the email and any attached files immediately. Any further use or dissemination is prohibited. While MTV Networks Europe has taken steps to ensure that this email and any attachments are virus free, it is your responsibility to ensure that this message and any attachments are virus free and do not affect your systems / data. Communicating by email is not 100% secure and carries risks such as delay, data corruption, non-delivery, wrongful interception and unauthorised amendment. If you communicate with us by e-mail, you acknowledge and assume these risks, and you agree to take appropriate measures to minimise these risks when e-mailing us. MTV Networks International, MTV Networks UK & Ireland, Greenhouse, Nickelodeon Viacom Consumer Products, VBSi, Viacom Brand Solutions International, Be Viacom, Viacom International Media Networks and VIMN and Comedy Central are all trading names of MTV Networks Europe. MTV Networks Europe is a partnership between MTV Networks Europe Inc. and Viacom Networks Europe Inc. Address for service in Great Britain is 17-29 Hawley Crescent, London, NW1 8TT. -- Sent from my hyper-communicator CONFIDENTIALITY NOTICE This e-mail (and any attached files) is confidential and protected by copyright (and other intellectual property rights). If you are not the intended recipient please e-mail the sender and then delete the email and any attached files immediately. Any further use or dissemination is prohibited. While MTV Networks Europe has taken steps to ensure that this email and any attachments are virus free, it is your responsibility to ensure that this message and any attachments are virus free and do not affect your systems / data. Communicating by email is not 100% secure and carries risks such as delay, data corruption, non-delivery, wrongful interception and unauthorised amendment. If you communicate with us by e-mail, you acknowledge and assume these risks, and you agree to take appropriate measures to minimise these risks when e-mailing us. MTV Networks International, MTV Networks UK & Ireland, Greenhouse, Nickelodeon Viacom Consumer Products, VBSi, Viacom Brand Solutions International, Be Viacom, Viacom International Media Networks and VIMN and Comedy Central are all trading names of MTV Networks Europe. MTV Networks Europe is a partnership between MTV Networks Europe Inc. and Viacom Networks Europe Inc. Address for service in Great Britain is 17-29 Hawley Crescent, London, NW1 8TT.

This is a frequent antipattern:
https://lukepalmer.wordpress.com/2010/01/24/haskell-antipattern-existential-...
If all you can do with WibblePackage is recover either a Foo or a Bar, why
not just use Either Foo Bar?
On Fri, Jun 19, 2015 at 5:09 PM, Nicholls, Mark
The design pattern is very well known in the OO community…most of the use cases evaporate in Haskell….in some sense its part of the language…
Haskell is my 9th or 10th language, I can barely write “hello world” without the manual, so I’m still at times I’m still trying to discover the basic idioms…
How to put heterogenuos things in a list…and yet not loose all type information (I know about HList…but I think that’s for special occasions)
*From:* Haskell-Cafe [mailto:haskell-cafe-bounces@haskell.org] *On Behalf Of *Anupam Jain *Sent:* 19 June 2015 5:04 PM *To:* haskell-cafe Cafe *Subject:* Re: [Haskell-cafe] Do people use visitor pattern in Haskell...
I discovered the same general pattern foroop
On Friday, June 19, 2015, Nicholls, Mark
wrote: My initial guess would be no…its built into the language
But….
I find myself tempted to use it (in order to match on a type that’s the instance of a typeclass)…which makes me think I’ve missed something.
So…
data Foo = Foo
data Bar = Bar
Ooo…this looks like an OO design pattern…surely wrong?
class Wibble a where
visit :: (Foo -> b) -> (Bar -> b) -> a -> b
instance Wibble Foo where
visit f _ x = f x
instance Wibble Bar where
visit _ f x = f x
I want a list of Wibbles....
hmmm...
(Wibble a) => [a] is clearly wrong...
I want [(Wibble a) =>a]
so I package it up?
data WibblePackage where
WibblePackage :: (Wibble a) => a -> WibblePackage
lets try this now…so pointless function across Wibbles in a list.
fizzBuzz :: [WibblePackage] -> Integer
fizzBuzz [] = 0
fizzBuzz ((WibblePackage x) : xs) = (visit (\_ -> 1) (\_ -> 2) x) + (fizzBuzz xs)
help :: Integer
help = fizzBuzz [WibblePackage Foo,WibblePackage Bar]
That works!
OO nerds will get uptight about “closing” the Wibble typeclass….but I’ve managed to create a list of different types and have a mechanism for recovering the type.
How would a Haskell nerd do this? (I have looked, but they look more complicated….maybe to my OO eye).
CONFIDENTIALITY NOTICE
This e-mail (and any attached files) is confidential and protected by copyright (and other intellectual property rights). If you are not the intended recipient please e-mail the sender and then delete the email and any attached files immediately. Any further use or dissemination is prohibited.
While MTV Networks Europe has taken steps to ensure that this email and any attachments are virus free, it is your responsibility to ensure that this message and any attachments are virus free and do not affect your systems / data.
Communicating by email is not 100% secure and carries risks such as delay, data corruption, non-delivery, wrongful interception and unauthorised amendment. If you communicate with us by e-mail, you acknowledge and assume these risks, and you agree to take appropriate measures to minimise these risks when e-mailing us.
MTV Networks International, MTV Networks UK & Ireland, Greenhouse, Nickelodeon Viacom Consumer Products, VBSi, Viacom Brand Solutions International, Be Viacom, Viacom International Media Networks and VIMN and Comedy Central are all trading names of MTV Networks Europe. MTV Networks Europe is a partnership between MTV Networks Europe Inc. and Viacom Networks Europe Inc. Address for service in Great Britain is 17-29 Hawley Crescent, London, NW1 8TT.
-- Sent from my hyper-communicator
CONFIDENTIALITY NOTICE
This e-mail (and any attached files) is confidential and protected by copyright (and other intellectual property rights). If you are not the intended recipient please e-mail the sender and then delete the email and any attached files immediately. Any further use or dissemination is prohibited.
While MTV Networks Europe has taken steps to ensure that this email and any attachments are virus free, it is your responsibility to ensure that this message and any attachments are virus free and do not affect your systems / data.
Communicating by email is not 100% secure and carries risks such as delay, data corruption, non-delivery, wrongful interception and unauthorised amendment. If you communicate with us by e-mail, you acknowledge and assume these risks, and you agree to take appropriate measures to minimise these risks when e-mailing us.
MTV Networks International, MTV Networks UK & Ireland, Greenhouse, Nickelodeon Viacom Consumer Products, VBSi, Viacom Brand Solutions International, Be Viacom, Viacom International Media Networks and VIMN and Comedy Central are all trading names of MTV Networks Europe. MTV Networks Europe is a partnership between MTV Networks Europe Inc. and Viacom Networks Europe Inc. Address for service in Great Britain is 17-29 Hawley Crescent, London, NW1 8TT.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

If all you can do with WibblePackage is recover either a Foo or a Bar, why not just use Either Foo Bar?
Typically, I just go straight for "data types a la carte" when I need any
kind of type-level disjunction. Define the type synonym:
type (:+:) a b = Either a b
and define a type class
class (:<:) a b where
inj :: a -> b
with some appropriate instances (as specified in the paper)[1], and you can
chain disjunctions almost automatically:
data Commercial = Commercial
data Retail = Retail
data Investment = Investment
type Bank = Retail :+: Commercial :+: Investment
bac :: Bank
bac = inj $ Retail
[1]: http://www.cs.ru.nl/~W.Swierstra/Publications/DataTypesALaCarte.pdf
On Fri, Jun 19, 2015 at 9:10 AM, Patrick Chilton
This is a frequent antipattern: https://lukepalmer.wordpress.com/2010/01/24/haskell-antipattern-existential-...
If all you can do with WibblePackage is recover either a Foo or a Bar, why not just use Either Foo Bar?
On Fri, Jun 19, 2015 at 5:09 PM, Nicholls, Mark
wrote: The design pattern is very well known in the OO community…most of the use cases evaporate in Haskell….in some sense its part of the language…
Haskell is my 9th or 10th language, I can barely write “hello world” without the manual, so I’m still at times I’m still trying to discover the basic idioms…
How to put heterogenuos things in a list…and yet not loose all type information (I know about HList…but I think that’s for special occasions)
*From:* Haskell-Cafe [mailto:haskell-cafe-bounces@haskell.org] *On Behalf Of *Anupam Jain *Sent:* 19 June 2015 5:04 PM *To:* haskell-cafe Cafe *Subject:* Re: [Haskell-cafe] Do people use visitor pattern in Haskell...
I discovered the same general pattern foroop
On Friday, June 19, 2015, Nicholls, Mark
wrote: My initial guess would be no…its built into the language
But….
I find myself tempted to use it (in order to match on a type that’s the instance of a typeclass)…which makes me think I’ve missed something.
So…
data Foo = Foo
data Bar = Bar
Ooo…this looks like an OO design pattern…surely wrong?
class Wibble a where
visit :: (Foo -> b) -> (Bar -> b) -> a -> b
instance Wibble Foo where
visit f _ x = f x
instance Wibble Bar where
visit _ f x = f x
I want a list of Wibbles....
hmmm...
(Wibble a) => [a] is clearly wrong...
I want [(Wibble a) =>a]
so I package it up?
data WibblePackage where
WibblePackage :: (Wibble a) => a -> WibblePackage
lets try this now…so pointless function across Wibbles in a list.
fizzBuzz :: [WibblePackage] -> Integer
fizzBuzz [] = 0
fizzBuzz ((WibblePackage x) : xs) = (visit (\_ -> 1) (\_ -> 2) x) + (fizzBuzz xs)
help :: Integer
help = fizzBuzz [WibblePackage Foo,WibblePackage Bar]
That works!
OO nerds will get uptight about “closing” the Wibble typeclass….but I’ve managed to create a list of different types and have a mechanism for recovering the type.
How would a Haskell nerd do this? (I have looked, but they look more complicated….maybe to my OO eye).
CONFIDENTIALITY NOTICE
This e-mail (and any attached files) is confidential and protected by copyright (and other intellectual property rights). If you are not the intended recipient please e-mail the sender and then delete the email and any attached files immediately. Any further use or dissemination is prohibited.
While MTV Networks Europe has taken steps to ensure that this email and any attachments are virus free, it is your responsibility to ensure that this message and any attachments are virus free and do not affect your systems / data.
Communicating by email is not 100% secure and carries risks such as delay, data corruption, non-delivery, wrongful interception and unauthorised amendment. If you communicate with us by e-mail, you acknowledge and assume these risks, and you agree to take appropriate measures to minimise these risks when e-mailing us.
MTV Networks International, MTV Networks UK & Ireland, Greenhouse, Nickelodeon Viacom Consumer Products, VBSi, Viacom Brand Solutions International, Be Viacom, Viacom International Media Networks and VIMN and Comedy Central are all trading names of MTV Networks Europe. MTV Networks Europe is a partnership between MTV Networks Europe Inc. and Viacom Networks Europe Inc. Address for service in Great Britain is 17-29 Hawley Crescent, London, NW1 8TT.
-- Sent from my hyper-communicator
CONFIDENTIALITY NOTICE
This e-mail (and any attached files) is confidential and protected by copyright (and other intellectual property rights). If you are not the intended recipient please e-mail the sender and then delete the email and any attached files immediately. Any further use or dissemination is prohibited.
While MTV Networks Europe has taken steps to ensure that this email and any attachments are virus free, it is your responsibility to ensure that this message and any attachments are virus free and do not affect your systems / data.
Communicating by email is not 100% secure and carries risks such as delay, data corruption, non-delivery, wrongful interception and unauthorised amendment. If you communicate with us by e-mail, you acknowledge and assume these risks, and you agree to take appropriate measures to minimise these risks when e-mailing us.
MTV Networks International, MTV Networks UK & Ireland, Greenhouse, Nickelodeon Viacom Consumer Products, VBSi, Viacom Brand Solutions International, Be Viacom, Viacom International Media Networks and VIMN and Comedy Central are all trading names of MTV Networks Europe. MTV Networks Europe is a partnership between MTV Networks Europe Inc. and Viacom Networks Europe Inc. Address for service in Great Britain is 17-29 Hawley Crescent, London, NW1 8TT.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

data WibblePackage = WPFoo Foo | WPBar Bar Отправлено с iPhone
19 июня 2015 г., в 17:48, Nicholls, Mark
написал(а): My initial guess would be no…its built into the language
But….
I find myself tempted to use it (in order to match on a type that’s the instance of a typeclass)…which makes me think I’ve missed something.
So…
data Foo = Foo data Bar = Bar
Ooo…this looks like an OO design pattern…surely wrong?
class Wibble a where visit :: (Foo -> b) -> (Bar -> b) -> a -> b
instance Wibble Foo where visit f _ x = f x instance Wibble Bar where visit _ f x = f x
I want a list of Wibbles.... hmmm... (Wibble a) => [a] is clearly wrong... I want [(Wibble a) =>a]
so I package it up?
data WibblePackage where WibblePackage :: (Wibble a) => a -> WibblePackage
lets try this now…so pointless function across Wibbles in a list.
fizzBuzz :: [WibblePackage] -> Integer fizzBuzz [] = 0 fizzBuzz ((WibblePackage x) : xs) = (visit (\_ -> 1) (\_ -> 2) x) + (fizzBuzz xs)
help :: Integer help = fizzBuzz [WibblePackage Foo,WibblePackage Bar]
That works!
OO nerds will get uptight about “closing” the Wibble typeclass….but I’ve managed to create a list of different types and have a mechanism for recovering the type.
How would a Haskell nerd do this? (I have looked, but they look more complicated….maybe to my OO eye).
CONFIDENTIALITY NOTICE
This e-mail (and any attached files) is confidential and protected by copyright (and other intellectual property rights). If you are not the intended recipient please e-mail the sender and then delete the email and any attached files immediately. Any further use or dissemination is prohibited.
While MTV Networks Europe has taken steps to ensure that this email and any attachments are virus free, it is your responsibility to ensure that this message and any attachments are virus free and do not affect your systems / data.
Communicating by email is not 100% secure and carries risks such as delay, data corruption, non-delivery, wrongful interception and unauthorised amendment. If you communicate with us by e-mail, you acknowledge and assume these risks, and you agree to take appropriate measures to minimise these risks when e-mailing us.
MTV Networks International, MTV Networks UK & Ireland, Greenhouse, Nickelodeon Viacom Consumer Products, VBSi, Viacom Brand Solutions International, Be Viacom, Viacom International Media Networks and VIMN and Comedy Central are all trading names of MTV Networks Europe. MTV Networks Europe is a partnership between MTV Networks Europe Inc. and Viacom Networks Europe Inc. Address for service in Great Britain is 17-29 Hawley Crescent, London, NW1 8TT.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

The shortest answers are the best.
Of course.
Thanks.
From: MigMit [mailto:miguelimo38@yandex.ru]
Sent: 19 June 2015 5:09 PM
To: Nicholls, Mark
Cc: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Do people use visitor pattern in Haskell...
data WibblePackage = WPFoo Foo | WPBar Bar
Отправлено с iPhone
19 июня 2015 г., в 17:48, Nicholls, Mark
data Foo = Foo data Bar = Bar
Ooo…this looks like an OO design pattern…surely wrong?
class Wibble a where visit :: (Foo -> b) -> (Bar -> b) -> a -> b
instance Wibble Foo where visit f _ x = f x instance Wibble Bar where visit _ f x = f x
I want a list of Wibbles.... hmmm... (Wibble a) => [a] is clearly wrong... I want [(Wibble a) =>a] so I package it up?
data WibblePackage where WibblePackage :: (Wibble a) => a -> WibblePackage
lets try this now…so pointless function across Wibbles in a list.
fizzBuzz :: [WibblePackage] -> Integer fizzBuzz [] = 0 fizzBuzz ((WibblePackage x) : xs) = (visit (\_ -> 1) (\_ -> 2) x) + (fizzBuzz xs)
help :: Integer help = fizzBuzz [WibblePackage Foo,WibblePackage Bar]
That works! OO nerds will get uptight about “closing” the Wibble typeclass….but I’ve managed to create a list of different types and have a mechanism for recovering the type. How would a Haskell nerd do this? (I have looked, but they look more complicated….maybe to my OO eye). CONFIDENTIALITY NOTICE This e-mail (and any attached files) is confidential and protected by copyright (and other intellectual property rights). If you are not the intended recipient please e-mail the sender and then delete the email and any attached files immediately. Any further use or dissemination is prohibited. While MTV Networks Europe has taken steps to ensure that this email and any attachments are virus free, it is your responsibility to ensure that this message and any attachments are virus free and do not affect your systems / data. Communicating by email is not 100% secure and carries risks such as delay, data corruption, non-delivery, wrongful interception and unauthorised amendment. If you communicate with us by e-mail, you acknowledge and assume these risks, and you agree to take appropriate measures to minimise these risks when e-mailing us. MTV Networks International, MTV Networks UK & Ireland, Greenhouse, Nickelodeon Viacom Consumer Products, VBSi, Viacom Brand Solutions International, Be Viacom, Viacom International Media Networks and VIMN and Comedy Central are all trading names of MTV Networks Europe. MTV Networks Europe is a partnership between MTV Networks Europe Inc. and Viacom Networks Europe Inc. Address for service in Great Britain is 17-29 Hawley Crescent, London, NW1 8TT. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.orgmailto:Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe CONFIDENTIALITY NOTICE This e-mail (and any attached files) is confidential and protected by copyright (and other intellectual property rights). If you are not the intended recipient please e-mail the sender and then delete the email and any attached files immediately. Any further use or dissemination is prohibited. While MTV Networks Europe has taken steps to ensure that this email and any attachments are virus free, it is your responsibility to ensure that this message and any attachments are virus free and do not affect your systems / data. Communicating by email is not 100% secure and carries risks such as delay, data corruption, non-delivery, wrongful interception and unauthorised amendment. If you communicate with us by e-mail, you acknowledge and assume these risks, and you agree to take appropriate measures to minimise these risks when e-mailing us. MTV Networks International, MTV Networks UK & Ireland, Greenhouse, Nickelodeon Viacom Consumer Products, VBSi, Viacom Brand Solutions International, Be Viacom, Viacom International Media Networks and VIMN and Comedy Central are all trading names of MTV Networks Europe. MTV Networks Europe is a partnership between MTV Networks Europe Inc. and Viacom Networks Europe Inc. Address for service in Great Britain is 17-29 Hawley Crescent, London, NW1 8TT.

This is a pattern people usually refer to as the "existential typeclass
antipattern".
An article goes into more depth here:
https://lukepalmer.wordpress.com/2010/01/24/haskell-antipattern-existential-...
Sometimes you need a GADT with an existential type and a typeclass, but it
doesn't occur as often as the equivalent does in OO.
On Fri, Jun 19, 2015 at 10:48 AM, Nicholls, Mark
My initial guess would be no…its built into the language
But….
I find myself tempted to use it (in order to match on a type that’s the instance of a typeclass)…which makes me think I’ve missed something.
So…
data Foo = Foo
data Bar = Bar
Ooo…this looks like an OO design pattern…surely wrong?
class Wibble a where
visit :: (Foo -> b) -> (Bar -> b) -> a -> b
instance Wibble Foo where
visit f _ x = f x
instance Wibble Bar where
visit _ f x = f x
I want a list of Wibbles....
hmmm...
(Wibble a) => [a] is clearly wrong...
I want [(Wibble a) =>a]
so I package it up?
data WibblePackage where
WibblePackage :: (Wibble a) => a -> WibblePackage
lets try this now…so pointless function across Wibbles in a list.
fizzBuzz :: [WibblePackage] -> Integer
fizzBuzz [] = 0
fizzBuzz ((WibblePackage x) : xs) = (visit (\_ -> 1) (\_ -> 2) x) + (fizzBuzz xs)
help :: Integer
help = fizzBuzz [WibblePackage Foo,WibblePackage Bar]
That works!
OO nerds will get uptight about “closing” the Wibble typeclass….but I’ve managed to create a list of different types and have a mechanism for recovering the type.
How would a Haskell nerd do this? (I have looked, but they look more complicated….maybe to my OO eye).
CONFIDENTIALITY NOTICE
This e-mail (and any attached files) is confidential and protected by copyright (and other intellectual property rights). If you are not the intended recipient please e-mail the sender and then delete the email and any attached files immediately. Any further use or dissemination is prohibited.
While MTV Networks Europe has taken steps to ensure that this email and any attachments are virus free, it is your responsibility to ensure that this message and any attachments are virus free and do not affect your systems / data.
Communicating by email is not 100% secure and carries risks such as delay, data corruption, non-delivery, wrongful interception and unauthorised amendment. If you communicate with us by e-mail, you acknowledge and assume these risks, and you agree to take appropriate measures to minimise these risks when e-mailing us.
MTV Networks International, MTV Networks UK & Ireland, Greenhouse, Nickelodeon Viacom Consumer Products, VBSi, Viacom Brand Solutions International, Be Viacom, Viacom International Media Networks and VIMN and Comedy Central are all trading names of MTV Networks Europe. MTV Networks Europe is a partnership between MTV Networks Europe Inc. and Viacom Networks Europe Inc. Address for service in Great Britain is 17-29 Hawley Crescent, London, NW1 8TT.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
-- Chris Allen Currently working on http://haskellbook.com

Sorry for adding to the dogpile, should've guessed others would point to
the same resource :)
On Fri, Jun 19, 2015 at 11:11 AM, Christopher Allen
This is a pattern people usually refer to as the "existential typeclass antipattern".
An article goes into more depth here: https://lukepalmer.wordpress.com/2010/01/24/haskell-antipattern-existential-...
Sometimes you need a GADT with an existential type and a typeclass, but it doesn't occur as often as the equivalent does in OO.
On Fri, Jun 19, 2015 at 10:48 AM, Nicholls, Mark
wrote: My initial guess would be no…its built into the language
But….
I find myself tempted to use it (in order to match on a type that’s the instance of a typeclass)…which makes me think I’ve missed something.
So…
data Foo = Foo
data Bar = Bar
Ooo…this looks like an OO design pattern…surely wrong?
class Wibble a where
visit :: (Foo -> b) -> (Bar -> b) -> a -> b
instance Wibble Foo where
visit f _ x = f x
instance Wibble Bar where
visit _ f x = f x
I want a list of Wibbles....
hmmm...
(Wibble a) => [a] is clearly wrong...
I want [(Wibble a) =>a]
so I package it up?
data WibblePackage where
WibblePackage :: (Wibble a) => a -> WibblePackage
lets try this now…so pointless function across Wibbles in a list.
fizzBuzz :: [WibblePackage] -> Integer
fizzBuzz [] = 0
fizzBuzz ((WibblePackage x) : xs) = (visit (\_ -> 1) (\_ -> 2) x) + (fizzBuzz xs)
help :: Integer
help = fizzBuzz [WibblePackage Foo,WibblePackage Bar]
That works!
OO nerds will get uptight about “closing” the Wibble typeclass….but I’ve managed to create a list of different types and have a mechanism for recovering the type.
How would a Haskell nerd do this? (I have looked, but they look more complicated….maybe to my OO eye).
CONFIDENTIALITY NOTICE
This e-mail (and any attached files) is confidential and protected by copyright (and other intellectual property rights). If you are not the intended recipient please e-mail the sender and then delete the email and any attached files immediately. Any further use or dissemination is prohibited.
While MTV Networks Europe has taken steps to ensure that this email and any attachments are virus free, it is your responsibility to ensure that this message and any attachments are virus free and do not affect your systems / data.
Communicating by email is not 100% secure and carries risks such as delay, data corruption, non-delivery, wrongful interception and unauthorised amendment. If you communicate with us by e-mail, you acknowledge and assume these risks, and you agree to take appropriate measures to minimise these risks when e-mailing us.
MTV Networks International, MTV Networks UK & Ireland, Greenhouse, Nickelodeon Viacom Consumer Products, VBSi, Viacom Brand Solutions International, Be Viacom, Viacom International Media Networks and VIMN and Comedy Central are all trading names of MTV Networks Europe. MTV Networks Europe is a partnership between MTV Networks Europe Inc. and Viacom Networks Europe Inc. Address for service in Great Britain is 17-29 Hawley Crescent, London, NW1 8TT.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
-- Chris Allen Currently working on http://haskellbook.com
-- Chris Allen Currently working on http://haskellbook.com

class Wibble a where
visit :: (Foo -> b) -> (Bar -> b) -> a -> b
The type `forall b. (X -> b) -> (Y -> b) -> b` is isomorphic to `Either X Y`. If you rearrange the signature of `visit` a little bit, visit_ :: a -> forall b . (Foo -> b) -> (Bar -> b) -> b you can see that you're really just defining a function `a -> Either Foo Bar`. So the class can be simplified to: class Wibble' a where visit' :: a -> Either Foo Bar It follows that `WibblePackage'` is equivalent to type WibblePackage' = forall a . (WibbleInstance a, a) where type WibbleInstance a = a -> Either Foo Bar Because of the `forall`, there's nothing you can do with the second component of the tuple (`a`) except to apply it to the first (`a -> Either Foo Bar`), so it's just a long-winded way of saying type WibblePackage'' = Either Foo Bar In a non-strict language like Haskell, there's no reason to use such a complicated type signature to delay the application of `a -> Either Foo Bar` to `a`.

Brilliant, v interesring
Excuse the spelling, sent from a phone with itty bitty keys, it like trying to sow a button on a shirt with a sausage.
On 19 Jun 2015, at 19:37, Phil Ruffwind
class Wibble a where
visit :: (Foo -> b) -> (Bar -> b) -> a -> b
The type `forall b. (X -> b) -> (Y -> b) -> b` is isomorphic to `Either X Y`. If you rearrange the signature of `visit` a little bit,
visit_ :: a -> forall b . (Foo -> b) -> (Bar -> b) -> b
you can see that you're really just defining a function `a -> Either Foo Bar`. So the class can be simplified to:
class Wibble' a where visit' :: a -> Either Foo Bar
It follows that `WibblePackage'` is equivalent to
type WibblePackage' = forall a . (WibbleInstance a, a)
where
type WibbleInstance a = a -> Either Foo Bar
Because of the `forall`, there's nothing you can do with the second component of the tuple (`a`) except to apply it to the first (`a -> Either Foo Bar`), so it's just a long-winded way of saying
type WibblePackage'' = Either Foo Bar
In a non-strict language like Haskell, there's no reason to use such a complicated type signature to delay the application of `a -> Either Foo Bar` to `a`. CONFIDENTIALITY NOTICE
This e-mail (and any attached files) is confidential and protected by copyright (and other intellectual property rights). If you are not the intended recipient please e-mail the sender and then delete the email and any attached files immediately. Any further use or dissemination is prohibited. While MTV Networks Europe has taken steps to ensure that this email and any attachments are virus free, it is your responsibility to ensure that this message and any attachments are virus free and do not affect your systems / data. Communicating by email is not 100% secure and carries risks such as delay, data corruption, non-delivery, wrongful interception and unauthorised amendment. If you communicate with us by e-mail, you acknowledge and assume these risks, and you agree to take appropriate measures to minimise these risks when e-mailing us. MTV Networks International, MTV Networks UK & Ireland, Greenhouse, Nickelodeon Viacom Consumer Products, VBSi, Viacom Brand Solutions International, Be Viacom, Viacom International Media Networks and VIMN and Comedy Central are all trading names of MTV Networks Europe. MTV Networks Europe is a partnership between MTV Networks Europe Inc. and Viacom Networks Europe Inc. Address for service in Great Britain is 17-29 Hawley Crescent, London, NW1 8TT.
participants (7)
-
Alexander Solla
-
Anupam Jain
-
Christopher Allen
-
MigMit
-
Nicholls, Mark
-
Patrick Chilton
-
Phil Ruffwind