typeclass woes...how to constain a typeclass to be "closed" under an operation....

{-# LANGUAGE TypeFamilies, MultiParamTypeClasses, FlexibleContexts, FlexibleInstances, GADTs #-}
lets say I have a data type
data S a = S a deriving Show
and a nice simple typeclass
class Foo a where inc :: a -> S a
make Integer an instance and....
instance Foo Integer where inc x = S x
brilliant... now lets say I want my typeclass to enforce that any result of inc is also of a type that is an instance of the typeclass I'll follow my nose...which causes me a problem that makes me realise I maybe I don't understand whats going on.
class Bar a where inc' :: (Bar (S a)) => a -> S a
follow it to....
instance Bar Integer where inc' x = S x
this WORKS!...even though "S Integer" is not an instance of Bar!...maybe I don't understand.
-- x = inc' (1 :: Integer)
This would go BOOM ...."no instance of (Bar (S Integer))" ...so that makes sense.... How do I force Haskell to check the constraint before I evaluate an expression? follow my nose?
-- class (Baz (S a)) => Baz a where -- inc'' :: a -> S a
BOOM ...."Cycle in class declaration".... booo..but I suppose thats understandable.... so a) is my use of typeclasses correct?...or am I missing something? b) if so, how do I force the compiler to make sure my typeclass operations is nicely closed (under the typeclass)? 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 dont seem to have any replies
Booo
Is my question too stupid? Or boring? Or unintelligable?
Its quite common in maths to have operations in a theory that are (set) closed, i just want to translate that notion to a typeclass
I have a suggestion that does work
Class Foo m where
op :: m a -> m (S a)
That is closed, but now were working on types of kind • -> •, which is another leap of complexity
Is this the idiom/pattern i should follow? Or can the closure contraint be expressed directly?
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 5 Jan 2015, at 10:54, Nicholls, Mark
{-# LANGUAGE TypeFamilies, MultiParamTypeClasses, FlexibleContexts, FlexibleInstances, GADTs #-}
lets say I have a data type
data S a = S a deriving Show
and a nice simple typeclass
class Foo a where inc :: a -> S a
make Integer an instance and....
instance Foo Integer where inc x = S x
brilliant... now lets say I want my typeclass to enforce that any result of inc is also of a type that is an instance of the typeclass I'll follow my nose...which causes me a problem that makes me realise I maybe I don't understand whats going on.
class Bar a where inc' :: (Bar (S a)) => a -> S a
follow it to....
instance Bar Integer where inc' x = S x
this WORKS!...even though "S Integer" is not an instance of Bar!...maybe I don't understand.
-- x = inc' (1 :: Integer)
This would go BOOM ....”no instance of (Bar (S Integer))" ...so that makes sense.... How do I force Haskell to check the constraint before I evaluate an expression? follow my nose?
-- class (Baz (S a)) => Baz a where -- inc'' :: a -> S a
BOOM ...."Cycle in class declaration".... booo..but I suppose thats understandable.... so a) is my use of typeclasses correct?...or am I missing something? b) if so, how do I force the compiler to make sure my typeclass operations is nicely closed (under the typeclass)? 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. _______________________________________________ Beginners mailing list Beginners@haskell.orgmailto:Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners 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 think you've slightly surpassed the skill level of this list. You might
try on haskell-cafe, and I would bet you could get an in depth answer on
stackoverflow.
On Tue, Jan 6, 2015 at 3:46 AM, Nicholls, Mark
I dont seem to have any replies Booo Is my question too stupid? Or boring? Or unintelligable?
Its quite common in maths to have operations in a theory that are (set) closed, i just want to translate that notion to a typeclass
I have a suggestion that does work
Class Foo m where op :: m a -> m (S a)
That is closed, but now were working on types of kind • -> •, which is another leap of complexity
Is this the idiom/pattern i should follow? Or can the closure contraint be expressed directly?
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 5 Jan 2015, at 10:54, Nicholls, Mark
wrote: {-# LANGUAGE TypeFamilies, MultiParamTypeClasses, FlexibleContexts, FlexibleInstances, GADTs #-}
lets say I have a data type
data S a = S a deriving Show
and a nice simple typeclass
class Foo a where
inc :: a -> S a
make Integer an instance and....
instance Foo Integer where
inc x = S x
brilliant...
now lets say I want my typeclass to enforce that any result of inc is also of a type that is an instance of the typeclass
I'll follow my nose...which causes me a problem that makes me realise I maybe I don't understand whats going on.
class Bar a where
inc' :: (Bar (S a)) => a -> S a
follow it to....
instance Bar Integer where
inc' x = S x
this WORKS!...even though "S Integer" is not an instance of Bar!...maybe I don't understand.
-- x = inc' (1 :: Integer)
This would go BOOM ....”no instance of (Bar (S Integer))"
...so that makes sense....
How do I force Haskell to check the constraint before I evaluate an expression?
follow my nose?
-- class (Baz (S a)) => Baz a where
-- inc'' :: a -> S a
BOOM ...."Cycle in class declaration"....
booo..but I suppose thats understandable....
so
a) is my use of typeclasses correct?...or am I missing something?
b) if so, how do I force the compiler to make sure my typeclass operations is nicely closed (under the typeclass)?
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.
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
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.
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

I can do the basic Haskell...I've done a course even, but as I don't use it... I quickly degenerate into a beginner.
I think I've refound my feet....I will post it to the café and see what happens.
From: Beginners [mailto:beginners-bounces@haskell.org] On Behalf Of David McBride
Sent: 06 January 2015 4:41 PM
To: The Haskell-Beginners Mailing List - Discussion of primarily beginner-level topics related to Haskell
Subject: Re: [Haskell-beginners] typeclass woes...how to constain a typeclass to be "closed" under an operation....
I think you've slightly surpassed the skill level of this list. You might try on haskell-cafe, and I would bet you could get an in depth answer on stackoverflow.
On Tue, Jan 6, 2015 at 3:46 AM, Nicholls, Mark
{-# LANGUAGE TypeFamilies, MultiParamTypeClasses, FlexibleContexts, FlexibleInstances, GADTs #-}
lets say I have a data type
data S a = S a deriving Show
and a nice simple typeclass
class Foo a where inc :: a -> S a
make Integer an instance and....
instance Foo Integer where inc x = S x
brilliant... now lets say I want my typeclass to enforce that any result of inc is also of a type that is an instance of the typeclass I'll follow my nose...which causes me a problem that makes me realise I maybe I don't understand whats going on.
class Bar a where inc' :: (Bar (S a)) => a -> S a
follow it to....
instance Bar Integer where inc' x = S x
this WORKS!...even though "S Integer" is not an instance of Bar!...maybe I don't understand.
-- x = inc' (1 :: Integer)
This would go BOOM ...."no instance of (Bar (S Integer))" ...so that makes sense.... How do I force Haskell to check the constraint before I evaluate an expression? follow my nose?
-- class (Baz (S a)) => Baz a where -- inc'' :: a -> S a
BOOM ...."Cycle in class declaration".... booo..but I suppose thats understandable.... so a) is my use of typeclasses correct?...or am I missing something? b) if so, how do I force the compiler to make sure my typeclass operations is nicely closed (under the typeclass)? 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. _______________________________________________ Beginners mailing list Beginners@haskell.orgmailto:Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners 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. _______________________________________________ Beginners mailing list Beginners@haskell.orgmailto:Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners 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.

(S Integer) is not an instance of Bar. I solved this by doing the following
You can get around this using an empty instance declaration for (S Integer)
like so
instance Bar (S Integer)
Now, the compiler will know that (S Integer) is an instance of this. It
doesn't matter if there is no definition of inc' as you won't be using it.
However, I don't understand why a class definition will contain itself as a
constraint on one of its method. By doing so,
That is, whenever you do something like this
class Bar a where
inc' :: Bar (S a) => a -> S a
instance Bar Integer where
inc' x = S x
The resulting expression will also have to be an instance of Bar
(.ie.,instance Bar (S Integer)
) I just don't think this makes any sense. Also, tried searching for any
such type signatures in Hoogle, but didn't come across anything like this.
On Tue, Jan 6, 2015 at 11:09 PM, Nicholls, Mark
I can do the basic Haskell…I’ve done a course even, but as I don’t use it… I quickly degenerate into a beginner.
I think I’ve refound my feet….I will post it to the café and see what happens.
*From:* Beginners [mailto:beginners-bounces@haskell.org] *On Behalf Of *David McBride *Sent:* 06 January 2015 4:41 PM *To:* The Haskell-Beginners Mailing List - Discussion of primarily beginner-level topics related to Haskell *Subject:* Re: [Haskell-beginners] typeclass woes...how to constain a typeclass to be "closed" under an operation....
I think you've slightly surpassed the skill level of this list. You might try on haskell-cafe, and I would bet you could get an in depth answer on stackoverflow.
On Tue, Jan 6, 2015 at 3:46 AM, Nicholls, Mark
wrote: I dont seem to have any replies
Booo
Is my question too stupid? Or boring? Or unintelligable?
Its quite common in maths to have operations in a theory that are (set) closed, i just want to translate that notion to a typeclass
I have a suggestion that does work
Class Foo m where
op :: m a -> m (S a)
That is closed, but now were working on types of kind • -> •, which is another leap of complexity
Is this the idiom/pattern i should follow? Or can the closure contraint be expressed directly?
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 5 Jan 2015, at 10:54, Nicholls, Mark
wrote: {-# LANGUAGE TypeFamilies, MultiParamTypeClasses, FlexibleContexts, FlexibleInstances, GADTs #-}
lets say I have a data type
data S a = S a deriving Show
and a nice simple typeclass
class Foo a where
inc :: a -> S a
make Integer an instance and....
instance Foo Integer where
inc x = S x
brilliant...
now lets say I want my typeclass to enforce that any result of inc is also of a type that is an instance of the typeclass
I'll follow my nose...which causes me a problem that makes me realise I maybe I don't understand whats going on.
class Bar a where
inc' :: (Bar (S a)) => a -> S a
follow it to....
instance Bar Integer where
inc' x = S x
this WORKS!...even though "S Integer" is not an instance of Bar!...maybe I don't understand.
-- x = inc' (1 :: Integer)
This would go BOOM ....”no instance of (Bar (S Integer))"
...so that makes sense....
How do I force Haskell to check the constraint before I evaluate an expression?
follow my nose?
-- class (Baz (S a)) => Baz a where
-- inc'' :: a -> S a
BOOM ...."Cycle in class declaration"....
booo..but I suppose thats understandable....
so
a) is my use of typeclasses correct?...or am I missing something?
b) if so, how do I force the compiler to make sure my typeclass operations is nicely closed (under the typeclass)?
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.
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
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.
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
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.
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Ouch I’m now posting about the same problem in both Haskell mailing lists…. The problem was that if you comment out --instance Bar (S Integer) The code still compiles…the “Bar (S a)” isnt evaluated until someone invokes inc’….I want my operation to be closed by definition….in advance. A solution has been posted in the café, which is basically the same as the one I posted here, but fixes the cyclic typeclass error..
class Foo_ a -- just to prevent a cycle in superclass constraints
instance Foo a => Foo_ a
class Foo_ (S a) => Foo a where type S a op :: a -> (S a)
-- and an example where you get a compile error if "op x" has an instance, -- but "op (op x)" does not have an instance. instance Foo Int where type S Int = Char op = toEnum
instance Foo Char where type S Char = (Char,Char) op x = (x,x)
instance Foo (Char,Char) where type S (Char,Char) = Int op (x,y) = fromEnum x
I’ve now tried to write some code using both “idioms”….i.e. the above…and the
The above idiom forces you to define an associated type that inhabits the typeclass
The *->* (e.g. monad) idiom forces you to define a parameter to infer the return type, that also inhabits the typeclass…(technically I suppose “m b” doesn’t inhabit the typeclass, “m” does….but
So…
(>>=)http://hackage.haskell.org/packages/archive/base/latest/doc/html/Prelude.htm... :: Monad m => m a -> (a -> m b) -> m bhttp://hackage.haskell.org/packages/archive/base/latest/doc/html/Prelude.htm...
Is closed.
(S Integer) is not an instance of Bar. I solved this by doing the following
You can get around this using an empty instance declaration for (S Integer) like so
instance Bar (S Integer)
Now, the compiler will know that (S Integer) is an instance of this. It doesn't matter if there is no definition of inc' as you won't be using it.
However, I don't understand why a class definition will contain itself as a constraint on one of its method. By doing so,
That is, whenever you do something like this
class Bar a where
inc' :: Bar (S a) => a -> S a
instance Bar Integer where
inc' x = S x
The resulting expression will also have to be an instance of Bar (.ie.,instance Bar (S Integer)
) I just don't think this makes any sense. Also, tried searching for any such type signatures in Hoogle, but didn't come across anything like this.
On Tue, Jan 6, 2015 at 11:09 PM, Nicholls, Mark
{-# LANGUAGE TypeFamilies, MultiParamTypeClasses, FlexibleContexts, FlexibleInstances, GADTs #-}
lets say I have a data type
data S a = S a deriving Show
and a nice simple typeclass
class Foo a where inc :: a -> S a
make Integer an instance and....
instance Foo Integer where inc x = S x
brilliant... now lets say I want my typeclass to enforce that any result of inc is also of a type that is an instance of the typeclass I'll follow my nose...which causes me a problem that makes me realise I maybe I don't understand whats going on.
class Bar a where inc' :: (Bar (S a)) => a -> S a
follow it to....
instance Bar Integer where inc' x = S x
this WORKS!...even though "S Integer" is not an instance of Bar!...maybe I don't understand.
-- x = inc' (1 :: Integer)
This would go BOOM ....”no instance of (Bar (S Integer))" ...so that makes sense.... How do I force Haskell to check the constraint before I evaluate an expression? follow my nose?
-- class (Baz (S a)) => Baz a where -- inc'' :: a -> S a
BOOM ...."Cycle in class declaration".... booo..but I suppose thats understandable.... so a) is my use of typeclasses correct?...or am I missing something? b) if so, how do I force the compiler to make sure my typeclass operations is nicely closed (under the typeclass)? 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. _______________________________________________ Beginners mailing list Beginners@haskell.orgmailto:Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners 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. _______________________________________________ Beginners mailing list Beginners@haskell.orgmailto:Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners 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. _______________________________________________ Beginners mailing list Beginners@haskell.orgmailto:Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners 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 (3)
-
akash g
-
David McBride
-
Nicholls, Mark