Re: [Haskell-cafe] What's wrong with the classes/insances?

2008-06-20 Thread wren ng thornton

Pieter Laeremans wrote:

HI,

What 's wrong with this:

[...]

class Item a where
getCatalog :: Catalog catalog => a -> catalog


This is a shorthand for

 > class Item a where
 > getCatalog :: forall c. (Catalog c) => a -> c

That is, the class provides the contract that given some value of type a 
it will be able to return *any* type c which adheres to the contract of 
the class Catalog. This function is polymorphic in the return type.




instance Catalog c => Item (Content c) where
   getCatalog (Content  _ _ c) = c


The problem is, here you're returning a *specific* type c which adheres 
to Catalog. What happens if the caller of getCatalog is expecting some 
other type (Catalog c') => c' or (Catalog c'') => c'' etc?



There are a few different solutions you could take. The easiest one is 
to use multi-parameter type classes and functional dependencies to 
define Item like so:


 > class Item a c | a -> c where
 > getCatalog :: (Catalog c) => a -> c

This says that for any given type a there is one particular type c which 
getCatalog returns. Depending on your goals this may be enough, but if 
you really want getCatalog to be polymorphic in c then it won't work. 
(If you only want to be, er, multimorphic in c then you can leave out 
the fundep and define instances for each a*c type pair. This can lead to 
needing to declare excessively many type signatures however.)



If you really want to be able to return any c then there are a couple of 
approaches you could take. First is to add a conversion function to the 
Catalog class:


 > class Catalog c where
 > ...
 > convertCatalog:: forall c'. (Catalog c') => c -> c'

Given the rest of the definition for Catalog, this looks to be eminently 
doable-- at least in as far as people don't try to access any other 
fiddly bits inside the value c'. Of course this gives no way of 
preventing them from trying to do that fiddling, which leads to...



The other common approach is to use existential types to wrap values up 
with their class dictionaries like so:


 > data CatalogWrapper = forall c. (Catalog c) => CatalogWrapper c

In this case you'd have getCatalog return a CatalogWrapper instead of a 
(Catalog c) => c. If you're not familiar with existential types they can 
be harder to think about since they loose information about what type 
you actually have inside; once wrapped they're only ever accessible by 
the methods of type classes restricting what we can wrap. But if you 
want to restrict people to only ever using the Catalog interface to 
manipulate them, then this is exactly what you want.



--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] What's wrong with the classes/insances?

2008-06-20 Thread Pieter Laeremans
Thanks all!

I have to admit, I have an OO mndset :-).

I think I have found a more "functional design" :

import Text.StringTemplate.Classes
import Text.StringTemplate

data (ToSElem a) => Item  a b = Item {cargo::a , catalog :: (Catalog a b)}

instance (ToSElem a) => ToSElem (Item a b) where
toSElem = (toSElem . cargo)

type Id = String

type ItemToSelem a b = Item a b -> SElem b
type ItemParser a b = String -> Item a b

type AllItemReader a b = IO [Item a b]
type SingleItemReader a b = Id -> IO (Item a b)

data Catalog a b = Catalog  {reader:: (AllItemReader a b),
singleReader ::( SingleItemReader a b)}

data Content = Content {authort :: String, text:: String}

type ContentItem = Item Content String






What I want to express is that there exists differnet kinds of catalogs which,
depending on how they are configured can read from a file system or a database.
And each catalog can contain a specific type of Item.

For each Item I have to be able to produce the toSELem representation
that subsequently can be used by HStringTemplate

I thik that means I could declare

On Sat, Jun 21, 2008 at 12:26 AM, Dan Doel <[EMAIL PROTECTED]> wrote:
> On Friday 20 June 2008, Pieter Laeremans wrote:
>> type Id = String
>>
>> class Catalog a where
>> listItems :: a -> IO [String]
>> getItem :: a -> Id -> IO (Maybe String)
>>
>> class Item a where
>> getCatalog :: Catalog catalog => a -> catalog
>>
>> data Catalog c => Content c = Content {auteur :: String, inhoud::
>> String, catalog::c}
>>
>> instance Catalog c => Item (Content c) where
>>getCatalog (Content  _ _ c) = c
>>
>> I get this as error from ghci:
>>
>> Couldn't match expected type `catalog' against inferred type `c'
>>   `catalog' is a rigid type variable bound by
>> the type signature for `getCatalog'
>>   at
>> ../Sites/liberaleswebsite/www.liberales.be/cgi-bin/Test.hs:16:26
>>   `c' is a rigid type variable bound by
>>   the instance declaration
>> at
>> ../Sites/liberaleswebsite/www.liberales.be/cgi-bin/Test.hs:20:17 In the
>> expression: c
>> In the definition of `getCatalog': getCatalog (Content _ _ c) = c
>> In the definition for method `getCatalog'
>> Failed, modules loaded: none.
>
> The problem is in the type of getCatalog:
>
>  (Item a, Catalog catalog) => a -> catalog
>
> That type says that given the a, you can produce a value of any type 'catalog'
> so long as that type is an instance of Catalog.
>
> What you probably meant it to say is that you can produce *some particular*
> type that belongs to catalog. There are a couple ways you could express this.
> For instance, using functional dependencies:
>
>class Catalog cat => HasCatalog a cat | a -> cat where
>  getCatalog :: a -> cat
>
> or the new type families:
>
>class (Catalog (Cat a)) => Item a where
>  type Cat a :: *
>  getCatalog :: a -> Cat a
>
> Or you could wrap catalogues in an existential type:
>
>data SomeCatalog = forall c. Catalog c => Cat c
>
>class Item a where
>  getCatalog :: a -> SomeCatalog
>
> However, as just a word of warning, I'd say that when you run into something
> like this, it's probably an indication that you're structuring your program
> from an object oriented mindset, and that may not be the best fit for
> programming in Haskell (of course, it's possible an existential type or some
> such is the appropriate way to do things).
>
> Cheers,
> -- Dan
>



-- 
Pieter Laeremans <[EMAIL PROTECTED]>

"The future is here. It's just not evenly distributed yet." W. Gibson
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] What's wrong with the classes/insances?

2008-06-20 Thread Derek Elkins
On Sat, 2008-06-21 at 00:04 +0200, Pieter Laeremans wrote:
> HI,
> 
> What 's wrong with this:

It looks like you think Haskell is an OO language or want it to be.  It
is not.

> 
> type Id = String
> 
> class Catalog a where
> listItems :: a -> IO [String]
> getItem :: a -> Id -> IO (Maybe String)
> 
> class Item a where
> getCatalog :: Catalog catalog => a -> catalog

This means 
class Item a where
getCatalog :: forall catalog. Catalog catalog => a -> catalog

That means, given some Item a, I can create a value of -any- type that
is an instance of Catalog.  There is no well-defined function that could
do that.

> 
> data Catalog c => Content c = Content {auteur :: String, inhoud::
> String, catalog::c}
> 
> instance Catalog c => Item (Content c) where
>getCatalog (Content  _ _ c) = c
> 
> I get this as error from ghci:
> 
> Couldn't match expected type `catalog' against inferred type `c'
>   `catalog' is a rigid type variable bound by
> the type signature for `getCatalog'
>   at
> ../Sites/liberaleswebsite/www.liberales.be/cgi-bin/Test.hs:16:26
>   `c' is a rigid type variable bound by
>   the instance declaration
> at 
> ../Sites/liberaleswebsite/www.liberales.be/cgi-bin/Test.hs:20:17
> In the expression: c
> In the definition of `getCatalog': getCatalog (Content _ _ c) = c
> In the definition for method `getCatalog'
> Failed, modules loaded: none.
> 
> thanks in advance,
> 
> P
> 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] What's wrong with the classes/insances?

2008-06-20 Thread Dan Doel
On Friday 20 June 2008, Pieter Laeremans wrote:
> type Id = String
>
> class Catalog a where
> listItems :: a -> IO [String]
> getItem :: a -> Id -> IO (Maybe String)
>
> class Item a where
> getCatalog :: Catalog catalog => a -> catalog
>
> data Catalog c => Content c = Content {auteur :: String, inhoud::
> String, catalog::c}
>
> instance Catalog c => Item (Content c) where
>getCatalog (Content  _ _ c) = c
>
> I get this as error from ghci:
>
> Couldn't match expected type `catalog' against inferred type `c'
>   `catalog' is a rigid type variable bound by
> the type signature for `getCatalog'
>   at
> ../Sites/liberaleswebsite/www.liberales.be/cgi-bin/Test.hs:16:26
>   `c' is a rigid type variable bound by
>   the instance declaration
> at
> ../Sites/liberaleswebsite/www.liberales.be/cgi-bin/Test.hs:20:17 In the
> expression: c
> In the definition of `getCatalog': getCatalog (Content _ _ c) = c
> In the definition for method `getCatalog'
> Failed, modules loaded: none.

The problem is in the type of getCatalog:

  (Item a, Catalog catalog) => a -> catalog

That type says that given the a, you can produce a value of any type 'catalog' 
so long as that type is an instance of Catalog.

What you probably meant it to say is that you can produce *some particular* 
type that belongs to catalog. There are a couple ways you could express this. 
For instance, using functional dependencies:

class Catalog cat => HasCatalog a cat | a -> cat where
  getCatalog :: a -> cat

or the new type families:

class (Catalog (Cat a)) => Item a where
  type Cat a :: *
  getCatalog :: a -> Cat a

Or you could wrap catalogues in an existential type:

data SomeCatalog = forall c. Catalog c => Cat c

class Item a where
  getCatalog :: a -> SomeCatalog

However, as just a word of warning, I'd say that when you run into something 
like this, it's probably an indication that you're structuring your program 
from an object oriented mindset, and that may not be the best fit for 
programming in Haskell (of course, it's possible an existential type or some 
such is the appropriate way to do things).

Cheers,
-- Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] What's wrong with the classes/insances?

2008-06-20 Thread Dan Weston

I think the problem is here:

> getCatalog :: Catalog catalog => a -> catalog

This wants to constrain the result of getCatalog to be an instance of 
Catalog, but this only works for function arguments, not results. The 
following code does typecheck, though I have no idea what is does or if 
it is what you want:



type Id = String

class Catalog a where
listItems :: a -> IO [String]
getItem :: a -> Id -> IO (Maybe String)

class Catalog q => Item q a where
getCatalog :: a -> q

data Content d = MkContent {auteur  :: String,
inhoud  :: String,
catalog :: d}

instance Catalog c => Item c (Content c) where
   getCatalog (MkContent  _ _ e) = e



Pieter Laeremans wrote:

HI,

What 's wrong with this:

type Id = String

class Catalog a where
listItems :: a -> IO [String]
getItem :: a -> Id -> IO (Maybe String)

class Item a where
getCatalog :: Catalog catalog => a -> catalog

data Catalog c => Content c = Content {auteur :: String, inhoud::
String, catalog::c}

instance Catalog c => Item (Content c) where
   getCatalog (Content  _ _ c) = c

I get this as error from ghci:

Couldn't match expected type `catalog' against inferred type `c'
  `catalog' is a rigid type variable bound by
the type signature for `getCatalog'
  at
../Sites/liberaleswebsite/www.liberales.be/cgi-bin/Test.hs:16:26
  `c' is a rigid type variable bound by
  the instance declaration
at ../Sites/liberaleswebsite/www.liberales.be/cgi-bin/Test.hs:20:17
In the expression: c
In the definition of `getCatalog': getCatalog (Content _ _ c) = c
In the definition for method `getCatalog'
Failed, modules loaded: none.

thanks in advance,

P




___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] What's wrong with the classes/insances?

2008-06-20 Thread Bulat Ziganshin
Hello Pieter,

Saturday, June 21, 2008, 2:04:10 AM, you wrote:

for me, it seems just like you directly translated OOP classes into
Haskell that is the wrong way. you may look into
http://haskell.org/haskellwiki/OOP_vs_type_classes and
ghc user manual which discuss functional dependencies on the example
of collection classes


> HI,

> What 's wrong with this:

> type Id = String

> class Catalog a where
> listItems :: a -> IO [String]
> getItem :: a -> Id -> IO (Maybe String)

> class Item a where
> getCatalog :: Catalog catalog => a -> catalog

data Catalog c =>> Content c = Content {auteur :: String, inhoud::
> String, catalog::c}

> instance Catalog c => Item (Content c) where
>getCatalog (Content  _ _ c) = c

> I get this as error from ghci:

> Couldn't match expected type `catalog' against inferred type `c'
>   `catalog' is a rigid type variable bound by
> the type signature for `getCatalog'
>   at
> ../Sites/liberaleswebsite/www.liberales.be/cgi-bin/Test.hs:16:26
>   `c' is a rigid type variable bound by
>   the instance declaration
> at
> ../Sites/liberaleswebsite/www.liberales.be/cgi-bin/Test.hs:20:17
> In the expression: c
> In the definition of `getCatalog': getCatalog (Content _ _ c) = c
> In the definition for method `getCatalog'
> Failed, modules loaded: none.

> thanks in advance,

> P




-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] What's wrong with the classes/insances?

2008-06-20 Thread Pieter Laeremans
HI,

What 's wrong with this:

type Id = String

class Catalog a where
listItems :: a -> IO [String]
getItem :: a -> Id -> IO (Maybe String)

class Item a where
getCatalog :: Catalog catalog => a -> catalog

data Catalog c => Content c = Content {auteur :: String, inhoud::
String, catalog::c}

instance Catalog c => Item (Content c) where
   getCatalog (Content  _ _ c) = c

I get this as error from ghci:

Couldn't match expected type `catalog' against inferred type `c'
  `catalog' is a rigid type variable bound by
the type signature for `getCatalog'
  at
../Sites/liberaleswebsite/www.liberales.be/cgi-bin/Test.hs:16:26
  `c' is a rigid type variable bound by
  the instance declaration
at ../Sites/liberaleswebsite/www.liberales.be/cgi-bin/Test.hs:20:17
In the expression: c
In the definition of `getCatalog': getCatalog (Content _ _ c) = c
In the definition for method `getCatalog'
Failed, modules loaded: none.

thanks in advance,

P

-- 
Pieter Laeremans <[EMAIL PROTECTED]>

"The future is here. It's just not evenly distributed yet." W. Gibson
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe