[Haskell-cafe] Inferred type is not general enough

2004-07-08 Thread Ivan Tihonov
I start some ip networks related work in haskell and wrote two basic 
classes Location and Packet. Before writing IpLocation and IpPacket 
instances i have written simple TestLocation and TestPacket instances 
just to compile this and check for errors in class definitions. But 
looks like i misunderstand some haskell principles...

==
class Location a where
point :: a - String
class Packet a where
source, destination :: Location b = a - b
size :: Num b = a - b
--
data TestLocation = TestSource | TestDestination
data TestPacket = TestPacket
--
instance Location TestLocation where
point a = location
instance Packet TestPacket where
source p = TestSource
destination p = TestDestination
size p = 99
$ hugs Test.hs
ERROR Test.hs:20 - Inferred type is not general enough
*** Expression: source
*** Expected type : (Packet TestPacket, Location a) = TestPacket - a
*** Inferred type : (Packet TestPacket, Location TestLocation) = 
TestPacket - TestLocation

==
But if i remove source and destination from class and instance 
definitions alone size compiles well.

How write this in a haskell way?
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Inferred type is not general enough

2004-07-08 Thread Stefan Holdermans
Ivan,

It's the type of source and destination that is playing you parts. Let's
write them explicitly quantified,

  source  :: forall a b . (Packet a, Location b) = a - b
  destination :: forall a b . (Packet a, Location b) = a - b

and reflect on this for a while. This basicly says that whenever I have a
value of a type a that is known to be an instance of Packet, then for each
type b that is known to be an instance of Location, source will give me an
instance of that type b. (The same holds for destination, of course.)

So now, I can define a new data type

  data Foo = Foo ,

declare it an instance of Location

  instance Location Foo where
point foo = foo ,

and write the following function, knowing that TestPacket is an instance of
Packet,

  getFoo:: Packet - Foo
  getFoo packet =  source packet .

But, clearly, your implementation of source for TestPacket is not prepared
to produce a value of Foo. Instead, it always produce a value of
TestLocation. To be well-typed, however, it shoud be capable of producing a
value of any type that is declared an instance of Location.

A possible solution would be to fix the type of the returned location for
each instance of Packet,

  class (Location b) = Packet a b where
source, destination :: a - b

but this requires multi-parameter type classes, which are not part of
Haskell 98. Another approach would be to enrich the interface of the
Location class, so that it provides support for the construction of
locations.

HTH,

Stefan


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Inferred type is not general enough

2004-07-08 Thread Ben Lippmeier
Ivan,
I don't yet know how to explain this formally, but I know how to fix 
your problem..

You need to add a parameter to the Packet class so the compiler knows 
what type to use for the Location.

.. The following code works for me.. You'll need to use a 
compiler/interpreter which supports multi-parameter type classes.. like 
ghci with the glasgow extensions turned on

-
class Location a where
   point :: a - String
class Packet a loc where
   source   :: Location loc =  a - loc
   destination  :: Location loc =  a - loc
   size :: Num b = a - b
--
data TestLocation
   = TestSource
   | TestDestination
data TestPacket = TestPacket
--
instance Location TestLocation where
   point a = location
instance Packet TestPacket TestLocation
where
   source p= TestSource
   destination p   = TestDestination
   size p  = 99

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Inferred type is not general enough

2004-07-08 Thread Stefan Holdermans
Ivan,

Oops ...

  SH and write the following function, knowing that
  SH TestPacket is an instance of Packet,
  SH 
  SH   getFoo:: Packet - Foo
  SH   getFoo packet =  source packet .

Clearly, I meant to write

  getFoo :: TestPacket - Foo

here.

Regards,

Stefan


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Inferred type is not general enough

2004-07-08 Thread Ivan Tihonov
Stefan Holdermans wrote:
Huh. I'm really get stuck. Can someone write me working implementation 
of my crap?

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Inferred type is not general enough

2004-07-08 Thread Ben Lippmeier
Ivan..
Uh.. by 'works' I meant 'compiles' :)
Here is a fixed version..
As I understand it, the 2 parameter class (Location loc = Packet p loc) 
means
 loc is a Location, and types p and loc are related by class Packet

with just that information, if you try (as you did) something like
$ source TestPacket
Then you've given the compiler the type for 'p' (TestPacket), but it 
won't go the distance and decide that type for 'loc' is TestLocation.. 
even though that's the only instance you've given it.

You can tell the compiler that The type of 'p' sets the type of 'loc' 
with a functional dependency.. which is the | p - loc annotation at 
the end of the class definition in the new version below.

There is a paper which covers exactly this problem, in detail. I suggest 
you read it (I did).

Type classes with functional dependencies, Mark P. Jones, 2000
You can get it from his homepage at, http://www.cse.ogi.edu/~mpj/
Ben.

Ivan Tihonov wrote:
It compiles well, but doesn't work for me :(
BTW: (email answers are not always real-time :) )
new version:
--
class Location a where
   point:: a - String
class Location loc = Packet p loc | p - loc where
   source   :: p - loc
   destination  :: p - loc
   size :: Num b = p - b
--
data TestLocation
   = TestSource
   | TestDestination
   deriving (Show)
data TestPacket = TestPacket
--
instance Location TestLocation where
   point a= location
instance Packet TestPacket TestLocation
where
   source p   = TestSource
   destination p  = TestDestination
   size p = 99

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Inferred type is not general enough

2004-07-08 Thread Stefan Holdermans
Ivan,

  IT Stefan Holdermans wrote:
  IT 
  IT Huh. I'm really get stuck. Can someone write me working 
  IT implementation of my crap?

Huh? Did *I* wrote that ... ? ;)

\begin{code}
{-# -OPTIONS -fglasgow-exts #-}

class Location a where
  point :: a - String
  
class (Location b) = Packet a b where
  source  :: a - b
  destination :: a - b
  size:: forall c . (Num c) = a - c
  
data TestLocation = TestSource | TestDestination
  deriving (Show)

instance Location TestLocation where
  point = show
  
data TestPacket = TestPacket

instance Packet TestPacket TestLocation where
  source  = const TestSource
  destination = const TestDestination
  size= const 99
  
main :: IO ()
main =  print $ (source TestPacket :: TestLocation)  
\end{code}

As I mentioned, depending on your needs, there are other options: enriching
the Location class, parameterizing the packet types, ...

HTH,

Stefan


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Inferred type is not general enough

2004-07-08 Thread Glynn Clements

Ivan Tihonov wrote:

 I start some ip networks related work in haskell and wrote two basic 
 classes Location and Packet. Before writing IpLocation and IpPacket 
 instances i have written simple TestLocation and TestPacket instances 
 just to compile this and check for errors in class definitions. But 
 looks like i misunderstand some haskell principles...
 
 ==
 class Location a where
  point :: a - String
 
 class Packet a where
  source, destination :: Location b = a - b

This says that source can return any type which is an instance of
Location. IOW, any instance of Packet can have any instance of
Location as its source and destination (and can even use different
instances of Location for the two functions).

 data TestLocation = TestSource | TestDestination
 data TestPacket = TestPacket

 instance Packet TestPacket where
  source p = TestSource

However, this definition of source has type:

TestPacket - TestLocation

when, according to the class definition, it should have type:

(Location b) = TestPacket - b

 ERROR Test.hs:20 - Inferred type is not general enough
 *** Expression: source
 *** Expected type : (Packet TestPacket, Location a) = TestPacket - a
 *** Inferred type : (Packet TestPacket, Location TestLocation) = TestPacket - 
 TestLocation

Hence this error message; the function returns a specific instance of
Location, when it should return an arbitry instance.

You can use functional dependencies, which aren't in the Haskell98
standard, but are supported by Hugs (use the -98 switch to enable
extensions) and GHC (use the -fglasgow-exts switch). I.e.:

class (Location b)  = Packet a b | a - b where
 source, destination :: a - b
 size :: Num c = a - c

...

instance Packet TestPacket TestLocation where

The class definition says that each instance of Packet uses a specific
instance of Location. The instance declaration says that, for
TestPacket, source and destination will always have type TestLocation.

-- 
Glynn Clements [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Inferred type is not general enough

2004-07-08 Thread Ivan Tihonov
thanks a lot, functional dependencies is my choice.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe