functional dependency problem

2002-07-09 Thread Till Mossakowski

I wish to add to Christian's question:

why is it not possible to annotate v with its full type:

info :: (Collects e ce, Show e) => ce -> String
info (v::(Collects e ce, Show e) => ce) = show ((one v)::e) 

I then get the error message

All of the type variables in the constraint `Collects e
  ce' are already in scope
(at least one must be universally quantified here)
In the type: (Collects e ce) => ce
While checking a pattern type signature
When checking the pattern: v :: forall. (Collects e ce) => ce
In the definition of `info':
info (v :: forall. (Collects e ce) => ce) = show ((one v) :: e)

(and a similar message for the constraint Show e),
which I do not understand - why should e and ce be already in scope?

(I think that this question is actually independent of functional
dependencies - it is about type class constraints).

Till
-- 
Till MossakowskiPhone +49-421-218-4683
Dept. of Computer Science   Fax +49-421-218-3054
University of Bremen[EMAIL PROTECTED]   
P.O.Box 330440, D-28334 Bremen  http://www.tzi.de/~till
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: functional dependency problem

2002-07-09 Thread Christian Maeder

Simon Peyton-Jones wrote:
> 
> | info :: (Collects e ce, Show e) => ce -> String
> | info v = show ((one v) ::e)
> 
> As the error message says, and as the Haskell report says,
> this means
> 
>   info v = show ((one v) :: (forall e.e))
> 
> which is not what you meant.  

Ok, I did not know that I have to mention a type variable in the pattern
on the lhs in order to use it monomorphically on the rhs, like in:

info (v :: ce) = show (one (v :: ce))

Still, I would like to get "e" as a monomorphic type from the functional
dependency "ce -> e" in class Collects, maybe as a language extension in
the form of:
   
info (v :: ce | ce -> e) = show ((one v) :: e)

Cheers Christian
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



RE: unsafePerformIO around FFI calls

2002-07-09 Thread Simon Marlow


> > That's a nice succinct way to describe it.  Another way, which boils
> > down to the same thing but which is a little more concrete, is to
> > ask:
> 
> >   - Does the function's result depend only on the values of its
> > arguments?
> 
> I have two problems with this alternative test:
> 
> 1) It is sometimes slightly stricter test than necessary.
> 
>Consider a hypothetical pair of C functions
>
>  Foo toFoo(int);
>  int fromFoo(Foo);
>
>which satisfy the property
>
>  fromFoo(toFoo(x)) == x
>
>but such that the result of toFoo does not depend on its argument.
>(Perhaps toFoo allocates some memory in which to stores its result
>and returns a pointer to that memory.)
>
>The function's result does vary independently of its values so it
>fails your test.
>
>But if toFoo/fromFoo are the only functions on Foo, then we could
>obviously have implemented the same API in Haskell with the aid of
>newtype so it passes my test.

Ok, if we're going to nit pick :)  When talking about equality you have
to restrict that to "observable equivalence" in the context of whatever
abstract types you're dealing with.  If a function always returns
observably equivalent results when given observably equivalent
arguments, then it is "safe".

For example, toFoo would not be safe if you can test for equality
between pointers.  But if all you can do is convert it back using
fromFoo, then you're ok.

> 2) It fails to recognise the fact that IO actions have side effects.

Well, side effects are usually only visible in the IO monad so that's
ok.  In your free() example, the result is either () or _|_, so the
function does depend on more than just the value of the argument.  I
think the definition holds (but only just).

For example, we normally consider a function which uses some temporary
allocation on the C heap as "safe" to use from unsafePerformIO.  But its
side effect is visible from the IO monad by inspecting the C heap
pointer.

Cheers,
Simon
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



RE: ghc and -fno-implicit-prelude

2002-07-09 Thread Simon Peyton-Jones

In the upcoming 5.04 release you'll be able to do exactly
that.  GHC will use whatever >>= is in scope if you say
-fno-implicit-prelude.

Simon

| -Original Message-
| From: MR K P SCHUPKE [mailto:[EMAIL PROTECTED]] 
| Sent: 09 July 2002 15:03
| To: [EMAIL PROTECTED]
| Subject: ghc and -fno-implicit-prelude 
| 
| 
| Can I get ghc to use a local definition of `>>=` and 
| return... currently 
| I have:
| 
| {-# OPTIONS -fglasgow-exts -fno-implicit-prelude #-}
| module Main(main) where
| import qualified Prelude (Monad(..))
| import Prelude hiding (Monad(..))
| 
| ... Then a definition of Monad using a Premonad for return, 
| however when 
| compiling
| do notation it produces an error saying it cannot deduce 
| (PrelBase.Monad p)
| 
| Can I force ghc to use the definition of the Monad class I 
| have provided 
| for do notation
| (IE Monad derived from Premonad derived from Prelude.Functor)
| 
| Regards,
| Keean.
| 
| 
| ___
| Glasgow-haskell-users mailing list 
| [EMAIL PROTECTED] 
| http://www.haskell.org/mailman/listinfo/glasgow-| haskell-users
| 
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



ghc and -fno-implicit-prelude

2002-07-09 Thread MR K P SCHUPKE

Can I get ghc to use a local definition of `>>=` and return... currently 
I have:

{-# OPTIONS -fglasgow-exts -fno-implicit-prelude #-}
module Main(main) where
import qualified Prelude (Monad(..))
import Prelude hiding (Monad(..))

... Then a definition of Monad using a Premonad for return, however when 
compiling
do notation it produces an error saying it cannot deduce (PrelBase.Monad p)

Can I force ghc to use the definition of the Monad class I have provided 
for do notation
(IE Monad derived from Premonad derived from Prelude.Functor)

Regards,
Keean.


___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: unsafePerformIO around FFI calls

2002-07-09 Thread Alastair Reid


> That's a nice succinct way to describe it.  Another way, which boils
> down to the same thing but which is a little more concrete, is to
> ask:

>   - Does the function's result depend only on the values of its
> arguments?

I have two problems with this alternative test:

1) It is sometimes slightly stricter test than necessary.

   Consider a hypothetical pair of C functions
   
 Foo toFoo(int);
 int fromFoo(Foo);
   
   which satisfy the property
   
 fromFoo(toFoo(x)) == x
   
   but such that the result of toFoo does not depend on its argument.
   (Perhaps toFoo allocates some memory in which to stores its result
   and returns a pointer to that memory.)
   
   The function's result does vary independently of its values so it
   fails your test.
   
   But if toFoo/fromFoo are the only functions on Foo, then we could
   obviously have implemented the same API in Haskell with the aid of
   newtype so it passes my test.


2) It fails to recognise the fact that IO actions have side effects.

   For example, the C library function 'free' always returns the same
   result (i.e., '()') but it's a bad idea to call free twice on the
   same argument.

   One could argue that the side effect is part of the result because
   IO actions return a modified world but only a long term functional
   programmer would think like that so it doesn't help the man in the
   street.  (In fact, IIRC, the Concurrent Haskell semantics doesn't
   use the state-passing explanation so you don't even see side effects
   reflected as changes in the returned world state.)


-- 
Alastair Reid [EMAIL PROTECTED]  
Reid Consulting (UK) Limited  http://www.reid-consulting-uk.ltd.uk/alastair/

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



RE: unsafePerformIO around FFI calls

2002-07-09 Thread Simon Marlow

> Hal Daume <[EMAIL PROTECTED]> writes:
> > I'm curious exactly what is "safe" and what is "unsafe" to wrap
> > unsafePerformIO around when it comes to FFI calls. 
> 
> Here's a simple test:
> 
>  Could you imagine an alternative implementation of the same API in
>  pure Haskell?  (Don't consider efficiency or effort required to write
>  the implementation, just whether it can be done.)
> 
>  If so, then it is ok to use unsafePerformIO and the ffi to implement
>  the API instead.
> 
> If it fails that test, it is incredibly unlikely that it is ok and a
> proof that it is ok is likely to be pretty complex - maybe worth a
> PLDI paper or some such.

That's a nice succinct way to describe it.  Another way, which boils
down to the same thing but which is a little more concrete, is to ask:

  - Does the function's result depend only on the values of its
arguments?

(obviously only makes sense for a top-level IO function which you want
to wrap in unsafePerformIO - for a non-top-level function or expression
just replace 'arguments' with 'arguments and free variables').

Cheers,
Simon
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



RE: functional dependency problem

2002-07-09 Thread Simon Peyton-Jones

| info :: (Collects e ce, Show e) => ce -> String
| info v = show ((one v) ::e)

As the error message says, and as the Haskell report says,
this means

  info v = show ((one v) :: (forall e.e))

which is not what you meant.  Haskell does not have scoped
type variables, so any type variables in signatures are 
quantified at the signature (hence the forall).  

GHC does have scoped type variables, but in this case
since 'e' is not mentioned in the argument or result type
they are no help either. 

So apart from the double 'the' (thank you) GHC is behaving
correctly here.

Simon

| -Original Message-
| From: Christian Maeder [mailto:[EMAIL PROTECTED]] 
| Sent: 08 July 2002 17:54
| To: [EMAIL PROTECTED]
| Subject: functional dependency problem
| 
| 
| Hi,
| 
| please consider the following example (from Mark P. Jones: 
| "Type Classes with Functional Dependencies" LNCS 1782, ESOP 
| 2000), that I've extended with a function "one":
| 
| class Collects e ce | ce -> e where
| empty  :: ce
| insert :: e -> ce -> ce
| member :: e -> ce -> Bool
| one:: ce -> e   -- added just for the sake of
| demonstration
| 
| The following function was ok for GHC version 5.02.3:
| 
| info :: (Collects e ce, Show e) => ce -> String
| info v = show (one v) 
| 
| However, when I tried to mention the element type "e", that 
| does not occurr in the result type, I got the following error 
| for "show ((one
| v)::e)":
| 
| Could not deduce (Collects e ce) from the context ()
| Probable fix:
| Add (Collects e ce) to the the type signature of an expression
| arising from use of `one' at Collects.hs:11
| In an expression with a type signature: (one v) :: forall e. e
| In the first argument of `show', namely `((one v) :: forall e. e)'
| 
| (It did also not help to write "show ((one v)::Collects e ce => e)"
| 
| Because "ce" determines the type "e" via the functional 
| dependency in "Collects", I think "e" should not be 
| changed/generalized to "forall e. e". (You may think, that 
| "e" should not be mentioned at all, if it is not part of the 
| functionality.)
| 
| At least the behaviour of GHC seems to be inkonsistent, as it 
| should be possible to supply type signatures to (sub-)expressions.
| 
| Regards Christian
| 
| P.S. 
| duplicate "the"-typo in:
| Add (Collects e ce) to the the type signature of an expression
|^^^ 
| ___
| Glasgow-haskell-users mailing list 
| [EMAIL PROTECTED] 
| http://www.haskell.org/mailman/listinfo/glasgow-| haskell-users
| 
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users