RE: [Haskell-cafe] how would this be done? type classes? existentialtypes?

Try using a GADT: data Rs where Rs :: Resource a => a -> Rs class Resource a where resourceName :: a -> String instance Resource String where resourceName x = "String" instance Resource Int where resourceName x = "Int" resName (Rs x) = resourceName x resNames = map resName test = resNames [Rs "Hi", Rs (1::Int) ] The most important observations is that when pattern matching on (Rs x) we cannot make any assumptions about x, except using the class members of Resource. We hope this will help you, Gerrit (and the rest of the ST-lab) -----Original Message----- From: haskell-cafe-bounces@haskell.org on behalf of Matthias Fischmann Sent: Thu 3/16/2006 12:57 PM To: haskell-cafe@haskell.org Subject: [Haskell-cafe] how would this be done? type classes? existentialtypes? hi, this is one of those situations that always make scheme and perl hackers laugh at me: i have written a piece of code that is intuitively clear, and now i am trying to turn it into something that compiles. and here it goes. i have a type class that looks something like this: class Resource a where resourceName :: a -> String resourceAdvance :: a -> a resourceStarved :: a -> Bool resourceSpend :: a -> Int -> a resourceEarn :: a -> Int -> a resource types are rice, crude oil, pizza, software code, and so on. they all have a different internal structure and the same abstract interface, that's why i have defined this type class. now i want to create a list of a type similar to [r1, r2, r3] :: (Resource a) => [a] but with r1 being pizza, r2 being crude oil, and so on. my first idea was this: data Rs = forall a . (Resource a) => Rs a unRs (Rs a) = a rsName :: Rs -> String rsName = resourceName . unRs ... and then export Rs as an abstract data type. this would allow for lists of type [Rs], which is exactly what i want. but what is the type of unRs? or better: can i make it type at all? and isn't this solution a little redundant and verbose? should i do it like in the example for existentially quantified types in the ghc manual? http://www.haskell.org/ghc/docs/latest/html/users_guide/type-extensions.html but wouldnt't the code become really messy? or should i do the type class and instances, and then do Rs the existentially quantified way, with all class methods arguments to the Rs constructor? or is there a completely different way to do this (besides using scheme or perl :-)? thanks, matthias -----Original Message----- From: haskell-cafe-bounces@haskell.org on behalf of Matthias Fischmann Sent: Thu 3/16/2006 12:57 PM To: haskell-cafe@haskell.org Subject: [Haskell-cafe] how would this be done? type classes? existentialtypes? hi, this is one of those situations that always make scheme and perl hackers laugh at me: i have written a piece of code that is intuitively clear, and now i am trying to turn it into something that compiles. and here it goes. i have a type class that looks something like this: class Resource a where resourceName :: a -> String resourceAdvance :: a -> a resourceStarved :: a -> Bool resourceSpend :: a -> Int -> a resourceEarn :: a -> Int -> a resource types are rice, crude oil, pizza, software code, and so on. they all have a different internal structure and the same abstract interface, that's why i have defined this type class. now i want to create a list of a type similar to [r1, r2, r3] :: (Resource a) => [a] but with r1 being pizza, r2 being crude oil, and so on. my first idea was this: data Rs = forall a . (Resource a) => Rs a unRs (Rs a) = a rsName :: Rs -> String rsName = resourceName . unRs ... and then export Rs as an abstract data type. this would allow for lists of type [Rs], which is exactly what i want. but what is the type of unRs? or better: can i make it type at all? and isn't this solution a little redundant and verbose? should i do it like in the example for existentially quantified types in the ghc manual? http://www.haskell.org/ghc/docs/latest/html/users_guide/type-extensions.html but wouldnt't the code become really messy? or should i do the type class and instances, and then do Rs the existentially quantified way, with all class methods arguments to the Rs constructor? or is there a completely different way to do this (besides using scheme or perl :-)? thanks, matthias

yes, that helps. also thanks to lennart and chris, i think i got it working. ... and have more questions: is there any difference between these two? if they are equivalent, why the two different ways to say it? data X where X :: (Resource a) => a -> X data Y = forall a . (Resource a) => Y a and now it gets interesting: i need instances for Rs on Show, Read, Eq, Ord. Show is very simple, but Read? if i look at a string, it's already to late to decide which type is has, right? same problem with Eq: i could first check whether the rsNames match and if so, go ahead and compare the two resource class instances inside Rs. but the type system would never know whether this is safe or not. solution: add methods rsEq, rsOrd to the Resource class and use them to instantiate Eq, and Ord respectively. this is not pretty, but not particularly ugly either, and it works. but this still doesn't work for Read, right? m. On Thu, Mar 16, 2006 at 01:37:36PM +0100, Geest, G. van den wrote:
To: Matthias Fischmann
, haskell-cafe@haskell.org From: "Geest, G. van den" Date: Thu, 16 Mar 2006 13:37:36 +0100 Subject: RE: [Haskell-cafe] how would this be done? type classes? existentialtypes? Try using a GADT:
data Rs where Rs :: Resource a => a -> Rs
class Resource a where resourceName :: a -> String
instance Resource String where resourceName x = "String"
instance Resource Int where resourceName x = "Int"
resName (Rs x) = resourceName x
resNames = map resName
test = resNames [Rs "Hi", Rs (1::Int) ]
The most important observations is that when pattern matching on (Rs x) we cannot make any assumptions about x, except using the class members of Resource.
We hope this will help you,
Gerrit (and the rest of the ST-lab)
-----Original Message----- From: haskell-cafe-bounces@haskell.org on behalf of Matthias Fischmann Sent: Thu 3/16/2006 12:57 PM To: haskell-cafe@haskell.org Subject: [Haskell-cafe] how would this be done? type classes? existentialtypes?
hi,
this is one of those situations that always make scheme and perl hackers laugh at me: i have written a piece of code that is intuitively clear, and now i am trying to turn it into something that compiles. and here it goes.
i have a type class that looks something like this:
class Resource a where resourceName :: a -> String resourceAdvance :: a -> a resourceStarved :: a -> Bool resourceSpend :: a -> Int -> a resourceEarn :: a -> Int -> a
resource types are rice, crude oil, pizza, software code, and so on. they all have a different internal structure and the same abstract interface, that's why i have defined this type class.
now i want to create a list of a type similar to
[r1, r2, r3] :: (Resource a) => [a]
but with r1 being pizza, r2 being crude oil, and so on. my first idea was this:
data Rs = forall a . (Resource a) => Rs a unRs (Rs a) = a rsName :: Rs -> String rsName = resourceName . unRs ...
and then export Rs as an abstract data type. this would allow for lists of type [Rs], which is exactly what i want.
but what is the type of unRs? or better: can i make it type at all? and isn't this solution a little redundant and verbose? should i do it like in the example for existentially quantified types in the ghc manual?
http://www.haskell.org/ghc/docs/latest/html/users_guide/type-extensions.html
but wouldnt't the code become really messy? or should i do the type class and instances, and then do Rs the existentially quantified way, with all class methods arguments to the Rs constructor? or is there a completely different way to do this (besides using scheme or perl :-)?
thanks, matthias
-----Original Message----- From: haskell-cafe-bounces@haskell.org on behalf of Matthias Fischmann Sent: Thu 3/16/2006 12:57 PM To: haskell-cafe@haskell.org Subject: [Haskell-cafe] how would this be done? type classes? existentialtypes?
hi,
this is one of those situations that always make scheme and perl hackers laugh at me: i have written a piece of code that is intuitively clear, and now i am trying to turn it into something that compiles. and here it goes.
i have a type class that looks something like this:
class Resource a where resourceName :: a -> String resourceAdvance :: a -> a resourceStarved :: a -> Bool resourceSpend :: a -> Int -> a resourceEarn :: a -> Int -> a
resource types are rice, crude oil, pizza, software code, and so on. they all have a different internal structure and the same abstract interface, that's why i have defined this type class.
now i want to create a list of a type similar to
[r1, r2, r3] :: (Resource a) => [a]
but with r1 being pizza, r2 being crude oil, and so on. my first idea was this:
data Rs = forall a . (Resource a) => Rs a unRs (Rs a) = a rsName :: Rs -> String rsName = resourceName . unRs ...
and then export Rs as an abstract data type. this would allow for lists of type [Rs], which is exactly what i want.
but what is the type of unRs? or better: can i make it type at all? and isn't this solution a little redundant and verbose? should i do it like in the example for existentially quantified types in the ghc manual?
http://www.haskell.org/ghc/docs/latest/html/users_guide/type-extensions.html
but wouldnt't the code become really messy? or should i do the type class and instances, and then do Rs the existentially quantified way, with all class methods arguments to the Rs constructor? or is there a completely different way to do this (besides using scheme or perl :-)?
thanks, matthias
-- Institute of Information Systems, Humboldt-Universitaet zu Berlin web: http://www.wiwi.hu-berlin.de/~fis/ e-mail: fis@wiwi.hu-berlin.de tel: +49 30 2093-5742 fax: +49 30 2093-5741 office: Spandauer Strasse 1, R.324, 10178 Berlin, Germany pgp: AD67 CF64 7BB4 3B9A 6F25 0996 4D73 F1FD 8D32 9BAA

Matthias Fischmann wrote:
is there any difference between these two? if they are equivalent, why the two different ways to say it?
data X where X :: (Resource a) => a -> X data Y = forall a . (Resource a) => Y a
There's no difference. There are two ways to say it for historical reasons. The second notation dates back many years, while the first notation is new and experimental. Only the first notation supports GADTs, and only the second supports deriving declarations and strict fields and record syntax (though I think this is going to change). Also the second notation is more convenient when you're declaring an ordinary datatype---compare data List a = Nil | Cons a (List a) data List a where { Nil :: List a ; Cons :: a -> List a -> List a }
and now it gets interesting: i need instances for Rs on Show, Read, Eq, Ord. Show is very simple, but Read?
I think you're right: it's impossible to implement Read for Rs in an extensible way, because there's no way to obtain the necessary Resource dictionary at runtime. I've wished in the past for a family of functions, one for each single-parameter typeclass, with types something like Dynamic -> (forall a. C a => a -> b) -> Maybe b and you'd need something similar here. Assuming this is indeed impossible and you have to close the world of Resources, you may as well do it by writing data Rs = RsRice Rice | RsCrudeOil CrudeOil | ... deriving (Show,Read,Eq,Ord) -- Ben

On Fri, Mar 17, 2006 at 04:53:42PM +0000, Ben Rudiak-Gould wrote:
Matthias Fischmann wrote:
and now it gets interesting: i need instances for Rs on Show, Read, Eq, Ord. Show is very simple, but Read?
I think you're right: it's impossible to implement Read for Rs in an extensible way, because there's no way to obtain the necessary Resource dictionary at runtime. I've wished in the past for a family of functions,
With all the suggestions on this list I figured something out that compiles, though. It requires extension of the Read instance of Rx, but that's ok because it is an issue local to the module. Here is the code: class (Show a, Read a) => Resource a where rsName :: a -> String rsAdvance :: a -> a rsStarved :: a -> Bool data Rs = forall a . (Resource a) => Rs a instance Resource Rs where rsName (Rs a) = rsName a rsAdvance (Rs a) = Rs (rsAdvance a) rsStarved (Rs a) = rsStarved a instance Show Rs where show (Rs r) = "Rs " ++ rsName r ++ " (" ++ show r ++ ")" instance Read Rs where readsPrec pred = readConstructor where readConstructor ('R':'s':' ':'"':s) = readResourceType "" s readConstructor s = [] readResourceType acc ('"':' ':'(':s) = readResource (reverse acc) s readResourceType acc (x:s) | isAlpha x = readResourceType (x:acc) s readResourceType _ s = [] readResource "Rice" s = case readsPrec 0 s of [(r :: RsRice, s')] -> readClosingParen (Rs r) s'; _ -> [] readResource "CrudeOil" s = case readsPrec 0 s of [(r :: RsCrudeOil, s')] -> readClosingParen (Rs r) s'; _ -> [] readResource _ s = assert False (error "no instance.") readClosingParen r (')':s) = case readsPrec pred s of rs -> (r, s) : rs readClosingParen _ _ = [] (Is there a better way to match list prefixes? If I had read a paper on monadic parsing or two, this might look more elegant, but it seems to me to be sufficient for this simple application. Feel free to post the true thing. :-) I am more convinced yet that Eq and Ord are impossible: Which specific resource type is hidden in the Rs constructor is, well: hidden. But there is a dirty trick if you have enough time and memory to waste, and it doesn't even require extention for each new instance: instance Eq Rs where r == r' = show r == show r' instance Ord Rs where compare r r' = compare (show r) (show r') And here are the resource instances: data RsRice = RsRice { rsRiceName :: String, -- an intuitive and descriptive name of the resource rsRiceProduction :: Int, rsRiceConsumption :: Int, rsRiceReserve :: Int -- available for consumption or trading } deriving (Show, Read, Eq, Ord) instance Resource RsRice where rsName _ = "Rice" rsAdvance r = r { rsRiceReserve = rsRiceReserve r + rsRiceProduction r - rsRiceConsumption r } rsStarved = (== 0) . rsRiceReserve rsReserve (RsRice _ _ _ res) = res rsSpend = rsRiceTrade (-) rsEarn = rsRiceTrade (+) rsRiceTrade :: (Int -> Int -> Int) -> RsRice -> Int -> RsRice rsRiceTrade (+) r amount = r { rsRiceReserve = rsRiceReserve r + amount } data RsCrudeOil = RsCrudeOil { rsCrudeOilName :: String, rsCrudeOilProduction :: Int, rsCrudeOilConsumption :: Int, rsCrudeOilReserve :: Int, rsCrudeOilReserveSize :: Int -- any water unit above this number is discarded immediately. } deriving (Show, Read, Eq, Ord) instance Resource RsCrudeOil where -- ... Btw, I am tempted to implemente crude oil as an incremental extension to rice, by adding a record field 'rice'. Would this increase the number of indirections for basic operations on resources, or would ghc be capable of optimizing that away entirely? Thanks again to all, I am following the thread, even if I won't answer any more. m.
participants (3)
-
Ben Rudiak-Gould
-
Geest, G. van den
-
Matthias Fischmann