[Haskell-cafe] typeclasses comprehension problems: situation classes?

2009-05-16 Thread Belka

Hello, cafe visitors!

I'm trying to learn Haskell typeclasses, - about how to use them, - but
can't handle some conceptiual problems, which confuses me a lot. I took one
real problem (ErrorInfo gragual gathering), to tackle it in my studies: I
have a class of situations: there is an object, and it gets cumulatively
filled (or updated) with content. The code is in the end - it consists of 3
versions:
1. My first try. Fast written, based on intuitive understanding. Failed.
2. The second try - exploring an open world assumption. I hoped this would
set me on the right path. Failure.
3. Surrendered to compiler - statisfied all it's requirements. This code
looks absurd to me: parameter-never-to-be-used, unwanted-defaults. Compiler
accepted this one though.

Problems: 
1. How to define *fillerRole* correctly, so that it depends on the
type-value of src_t?
2. How to define *initFillable* correctly, so that it depends only on the
type-value filled_t, which is specified by the context of evaluation?
3. What are my misconcepts in the use of Haskell typeclasses here? 
4. Maybe I should distinguish *situation class* (as this one), as something
unavailable in Haskell? This assumption is the last one to make... I'd
rather belive, that there is something I'm not aware of (for a considerably
long time already) in Haskell. A lack of some programming technique

Please, Help!

Regards, 
Belka

==TRY=1===DOESN'T=COMPILE==

{-# LANGUAGE MultiParamTypeClasses  #-}

class FillsConsideringRoles src_t filled_t role_t where
 initFillable :: filled_t
 fillerRole   :: role_t
 fill :: src_t - filled_t - filled_t



data Role = Role1 | Role2 deriving (Show)
data FillableObject = FillableObject 
{ foData1 :: Maybe (Int, Role)
, foData2 :: Maybe (Int, Role)
} deriving (Show)

newEmptyFillableObject :: FillableObject
newEmptyFillableObject = FillableObject Nothing Nothing

data Constructor1 = Constructor1 Int
data Constructor2 = Constructor2 Int

instance FillsConsideringRoles Constructor1 FillableObject Role where
 initFillable = newEmptyFillableObject
 fillerRole = Role1
 fill c fo = let (Constructor1 i) = c in fo { foData1 = Just (i,
fillerRole) }

instance FillsConsideringRoles Constructor2 FillableObject Role where
 initFillable = newEmptyFillableObject
 fillerRole = Role2
 fill c fo = let (Constructor2 i) = c in fo { foData2 = Just (i,
fillerRole) }

main = putStrLn $ show $ fill c2 $ fill c1 initFillable
   where
  c1 = Constructor1 76
  c2 = Constructor2 43

==TRY=1==[END]===

==TRY=2===DOESN'T=COMPILE
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverlappingInstances #-}

class FillsConsideringRoles src_t filled_t role_t where
 initFillable :: filled_t
 fillerRole   :: role_t
 fill :: src_t - filled_t - filled_t

--

data Role = DefaultRole | Role1 | Role2 deriving (Show)
data FillableObject = FillableObject 
{ foData1 :: Maybe (Int, Role)
, foData2 :: Maybe (Int, Role)
} deriving (Show)

newEmptyFillableObject :: FillableObject
newEmptyFillableObject = FillableObject Nothing Nothing

data Constructor1 = Constructor1 Int
data Constructor2 = Constructor2 Int

instance FillsConsideringRoles filler_t filled_t Role where
 fillerRole = DefaultRole
instance FillsConsideringRoles Constructor2 filled_t Role where
 fillerRole = Role2
instance FillsConsideringRoles Constructor1 filled_t Role where
 fillerRole = Role1

instance FillsConsideringRoles filler_t FillableObject role_t where
 initFillable = newEmptyFillableObject

instance FillsConsideringRoles Constructor1 FillableObject Role where
 fill c fo = let (Constructor1 i) = c in fo { foData1 = Just (i,
fillerRole) }

instance FillsConsideringRoles Constructor2 FillableObject Role where
 fill c fo = let (Constructor2 i) = c in fo { foData2 = Just (i,
fillerRole) }

main = putStrLn $ show $ fill c2 $ fill c1 initFillable
   where
  c1 = Constructor1 76
  c2 = Constructor2 43
==TRY=2==[END]===

==TRY=3===WORKS=
{-# LANGUAGE MultiParamTypeClasses  #-}

class FillsConsideringRoles src_t filled_t role_t where
 initFillable :: ((),src_t, role_t) - filled_t
 fillerRole   :: ((),src_t, filled_t) - role_t
 fill :: ((),role_t) - src_t - filled_t - filled_t



data Role = DefaultRole | Role1 | Role2 deriving (Show)
data FillableObject = FillableObject 
 

Re: [Haskell-cafe] typeclasses comprehension problems: situation classes?

2009-05-16 Thread Bulat Ziganshin
Hello Belka,

Saturday, May 16, 2009, 9:22:54 PM, you wrote:

 I'm trying to learn Haskell typeclasses, - about how to use them, - but

am i correctly understood that you've started learning type classes
with multi-parameter ones? this may be a bit too brave, especially for
a woman :D

i suggest you to read first http://haskell.org/haskellwiki/OOP_vs_type_classes

about MPTC - you may find great intro in ghc manual, but anyway i
suggest to start with single-parameter ones


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] typeclasses comprehension problems: situation classes?

2009-05-16 Thread Magnus Therning

Bulat Ziganshin wrote:

Hello Belka,

Saturday, May 16, 2009, 9:22:54 PM, you wrote:


I'm trying to learn Haskell typeclasses, - about how to use them, - but


am i correctly understood that you've started learning type classes
with multi-parameter ones? this may be a bit too brave, especially for
a woman :D


Oh, I'd say that holds for men even more :-)  It surely did hold for the man 
writing this.


(Oh, and may I suggest that we all are careful with the gender jokes on the 
list, no matter how well-intended and even if we know the woman in question. 
It's simply too easy to mis-interpret on a medium with a bandwidth like email.)


/M

--
Magnus Therning(OpenPGP: 0xAB4DFBA4)
magnus@therning.org  Jabber: magnus@therning.org
http://therning.org/magnus identi.ca|twitter: magthe



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe