Re: Question about use of | in a class declaration

2002-08-21 Thread Andrew J Bromage

G'day all.

On Wed, Aug 21, 2002 at 02:31:05PM +0100, Guest, Simon wrote:

> Please could someone explain the meaning of | in this class
> declaration (from Andrew's example):
> 
>   class (Ord k) => Map m k v | m -> k v where
> lookupM :: m -> k -> Maybe v

Others have answered the question about what it means.  However, this
doesn't explain why I used a fundep when Haskell has perfectly good
constructor classes.  I could have written:

class (Ord k) => Map m k v where
  lookupM :: m k v -> k -> Maybe v

instance (Ord k) => Map FiniteMap k v where
  lookupM = lookupFM

However, this would not work for the other two cases (the assoc list
and the function).  For that, I'd have to introduce a new type, such
as:

newtype MapFunc k v = MapFunc (k -> Maybe v)

instance (Ord k) => Map MapFunc k v where
  lookupM (MapFunc f) = f

A good Haskell compiler would optimise the representation of the type,
so it wouldn't cost much (or possibly _anything_) at run time, but it's
still a pain to program with.  You need to pack and unpack the MapFunc
type at awkward places, when all you really want to do is rearrange
type variables for one declaration.  Fundeps let you avoid many of these
"artificial" constructors.

Unfortunately, I don't think that fundeps will help you to get rid
of all of them.  For example, the standard state transformer monad:

newtype State s a = State { runState :: s -> (a, s) }

I don't think you can get rid of the constructor here.

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



Re: Question about use of | in a class declaration

2002-08-21 Thread Andrew J Bromage

G'day all.

On Wed, Aug 21, 2002 at 02:46:16PM -0400, Mark Carroll wrote:

> One issue we have here is that any Haskell we write is stuff we'll
> probably want to keep using for a while so, although we've only just got
> most of the bugs out of the H98 report, I'll certainly watch with interest
> as people come to a consensus about multi-parameter typeclasses,
> concurrency libraries, etc. and such things start to look very much like
> they'll be fixed in the next round of standardisation. It's hard to know
> which are experiments that ultimately will be shunned in favour of
> something else, and which are just all-round good ideas. (-:

Apart from the mailing lists, there are two forums which are sort
of used for this.

One is the wiki:

http://haskell.org/wiki/wiki?HaskellTwo

...which, as those of us who use it regularly know, is down at
the moment.  The other is the Haskell Wish List:

http://www.pms.informatik.uni-muenchen.de/forschung/haskell-wish-list/

...which has also been down for some time.

Clearly whichever malevolent forces are responsible for downtime
don't want Haskell to evolve. :-)

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



Re: monads, modules, sandboxes

2002-08-21 Thread Richard Uhtenwoldt

this will be my last message on this topic as I need to stop
reading this list for a few months.

Alastair Reid writes:

>A potential difference (which Richard Uhtenwoldt hints at) is that it
>can be hard to control the flow of OS capabilities as the capability
>is passed from one process to another to another.  This gets
>especially tricky when you want policies like 'X can either read files
>or use the network but not both' (so X cannot leak secrets learnt from
>the filesystem).  I think this is why capability OSs have fallen out
>of favour in the OS community.  I suspect that typesystems are better
>able to express and enforce these policies.

seems to me capabilities can do that:

you just pass to X a capability (pointer) to an object that will
return either a read-only capability to the filesystem or a capability
to the network inferface but not both.

either that or use the revocable-capability pattern twice in such a
way that before the first network access happens, the
filesystem capability is revoked and before the first filesystem read
happens the network access capability is revoked.

to flesh out that first alternative a little, the object passed to X
could probably be coded up by modifying the following E language
function (found at http://www.erights.org/elang/concurrency/race.html)
for making "use-once" capabilities.  and yes I realize this code is
not exactly the essence of conciseness and brevity.

>   A "once" of a function is a use-once version of that function. Ie,
>   "once(func)" returns a object that will forward no more than one "run"
>   message to "func". The two argument form "once(verb, target)" is a
>   generalization which will forward no more than one "verb" message to
>   the target.
>
>   For the Miranda Methods, the result of the once (the forwarder
>   below) must make good decisions about whether to override them and
>   possibly forward them, or not override them and let them default to
>   methods on the forwarder. For non-Miranda methods other than the
>   suppressed method, they are simply forwarded.
>
> def once {
> to (verb, target) :any {
> var used := false
> def forwarder {
> # use the Miranda order/3, though it shouldn't matter
>
> # use the Miranda optSealedDispatch/1 to protect the target
>
> # forward getAllegedType/0, though one could argue that, once
> # used up, the type shouldn't include the supressed verb
> to getAllegedType() :any {
> target getAllegedType()
> }
>
> # forward respondsTo, but supress verb.  One could argue that res
pondsTo
> # and getAllegedType() should be consistent with each other.
> to respondsTo(verb2, arity) :boolean {
> verb != verb2 && target respondsTo(verb2, arity)
> }
>
> # forward printOn/1
> to printOn(out) { target printOn(out) }
>
> # forward reactToLostClient
> to reactToLostClient(problem) {
> target reactToLostClient(problem)
> }
>
> # use the Miranda whenMoreResolved/1 to protect the target
>
> # use the Miranda whenBroken/1 to protect the target
>
> # use the Miranda yourself/0 to protect the target
>
> # handle all other messages
> match [verb2, args] {
> if (verb == verb2) {
> if (used) {
> throw("used up")
> }
> used := true
> }
> E call(target, verb2, args)
> }
> }
> }
>
> # default to suppressing "run"
> to (target) :any { once("run", target) }
> }

what follows is not so much an explanation as a series of disconnected
points that a bright and motivated reader might infer real knowledge
from.

point 1.  I observe that type-systems work is very abstract and
formal and if I were doing a type system for secure programming I
would definitely look to the capability literature for conceptual
guidance.  too easy when doing formal work to lose sight of where the
juicy "wins" (opportunities) lie and more generally to lose sight of
the economic and social implications of the technical work and to
start playing a sterile "glass bead game".

insight and vision is where the capability literature is very fertile.
here I'm speaking of the capability PL literature (much of which is
ultimately based on Hewitt) not the older capability OS literature (eg
Butler Lampson's paper from the early 1970s) which is all intertwined
with hairy OS implementation issues and takes forever to learn, it
seems to this languages geek.

point 2.  Alastair Reid writes:

>>  I now think the
>> body of ideas around capability PLs (again mostly dynamically-typed
>> OOPLs these days) is likely to be richer and more scientifically
>> fertile for the long term than FP even.
>
>Can you say mo

Re: Question about use of | in a class declaration

2002-08-21 Thread Mark Carroll

On Wed, 21 Aug 2002, Christian Sievers wrote:
(snip)
> It might not have become clear from the previous answers:
> this construction is not Haskell 98, but an extension.
> That's why it's not in the report.
(snip)

One issue we have here is that any Haskell we write is stuff we'll
probably want to keep using for a while so, although we've only just got
most of the bugs out of the H98 report, I'll certainly watch with interest
as people come to a consensus about multi-parameter typeclasses,
concurrency libraries, etc. and such things start to look very much like
they'll be fixed in the next round of standardisation. It's hard to know
which are experiments that ultimately will be shunned in favour of
something else, and which are just all-round good ideas. (-:

-- Mark

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



Re: Question about use of | in a class declaration

2002-08-21 Thread Christian Sievers

Simon Guest asked:

> Please could someone explain the meaning of | in this class declaration (from 
>Andrew's example):
> 
>   class (Ord k) => Map m k v | m -> k v where
> lookupM :: m -> k -> Maybe v
> 
> I couldn't find reference to this in any of my standard Haskell tutorials, nor the 
>Haskell 98 report.  Any references?

It might not have become clear from the previous answers:
this construction is not Haskell 98, but an extension.
That's why it's not in the report.

BTW: Already multi parameter type classes 
(such as  "class (Ord k) => Map m k v where ...")
^ ^ ^ only one type variable allowed here
aren't Haskell 98.


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



RE: Question about use of | in a class declaration

2002-08-21 Thread Simon Marlow


> Here what the User's Guide says:
> 
> > Functional dependencies are implemented as described by 
> Mark Jones in 
> > "Type Classes with Functional Dependencies", Mark P. Jones, 
> In Proceedings 
> > of the 9th European Symposium on Programming, ESOP 2000, 
> Berlin, Germany, 
> > March 2000, Springer-Verlag LNCS 1782.
> > 
> > There should be more documentation, but there isn't (yet). 
> Yell if you need it.
> 
> Folks, let's yell together!
> This is a nice feature. It SHOULD be better known.
> If Simon's team has no time to write it, perhaps it would be 
> nice to put the reference to Mark's paper on line?
> http://www.cse.ogi.edu/~mpj/pubs/fundeps.html

I've put the above link in the docs.

Cheers,
Simon

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



Re: Question about use of | in a class declaration

2002-08-21 Thread Jerzy Karczmarczuk

Hal Daume III wrote:
> 
> This is a functional dependency.  You can probably find informationin the
> GHC docs.  It's a way of telling the compiler how to derive type
> information on multiparameter classes.

Oh, can you?

Here what the User's Guide says:

> Functional dependencies are implemented as described by Mark Jones in 
> "Type Classes with Functional Dependencies", Mark P. Jones, In Proceedings 
> of the 9th European Symposium on Programming, ESOP 2000, Berlin, Germany, 
> March 2000, Springer-Verlag LNCS 1782.
> 
> There should be more documentation, but there isn't (yet). Yell if you need it.

Folks, let's yell together!
This is a nice feature. It SHOULD be better known.
If Simon's team has no time to write it, perhaps it would be nice to put
the reference to Mark's paper on line?

http://www.cse.ogi.edu/~mpj/pubs/fundeps.html

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



Re: Question about use of | in a class declaration

2002-08-21 Thread Hal Daume III

This is a functional dependency.  You can probably find informationin the
GHC docs.  It's a way of telling the compiler how to derive type
information on multiparameter classes.  For example, if I have a class:

  class C a b where
f :: a -> b

the type of f is

  (C a b) => a -> b

The problem here is that you may have multiple instances of C with the
same a:

  instance C Int Bool ...
  instance C Int Char ...

so when you use f, it doesn't know which instance to use.  Writing 'a ->
b' means "a uniquely determines b" and makes it so for any given a, you
can only have one instance of C, so the two above instances would be
rejected: you could only have one.

This means that when you write 'f (5::Int)' it knows which instance to
choose, since there can only be one.

 - Hal

--
Hal Daume III

 "Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes." -Dijkstra | www.isi.edu/~hdaume

On Wed, 21 Aug 2002, Guest, Simon wrote:

> Hello all,
> 
> Please could someone explain the meaning of | in this class declaration (from 
>Andrew's example):
> 
>   class (Ord k) => Map m k v | m -> k v where
> lookupM :: m -> k -> Maybe v
> 
> I couldn't find reference to this in any of my standard Haskell tutorials, nor the 
>Haskell 98 report.  Any references?
> 
> cheers,
> Simon
> 
> -Original Message-
> From: Andrew J Bromage [mailto:[EMAIL PROTECTED]]
> Sent: 21 August 2002 04:19
> To: [EMAIL PROTECTED]
> Subject: Re: Question about sets
> 
> 
> G'day all.
> 
> On Tue, Aug 20, 2002 at 10:57:36AM -0700, Hal Daume III wrote:
> 
> > Lists with arbitrary
> > elements are possible, but not very useful.  After all, what could you do
> > with them?
> 
> It's often useful to have containers of arbitrary _constrained_ types,
> because then you can do something with them.  For example, given the
> class of partial mappings on orderable keys:
> 
>   class (Ord k) => Map m k v | m -> k v where
> lookupM :: m -> k -> Maybe v
> 
> 
>   instance (Ord k) => Map (FiniteMap k v) k v where
> lookupM = lookupFM
> 
>   instance (Ord k) => Map [(k,v)] k v where
> lookupM m k = case [ v | (k',v) <- m, k == k' ] of
>   []-> Nothing
>   (v:_) -> Just v
> 
>   instance (Ord k) => Map (k -> Maybe v) k v where
> lookupM   = id
> 
> You can make a list of elements, which can be any type so long as
> they are a member of that class:
> 
>   data MAP k v = forall m. (Map m k v) => MAP m
> 
>   type ListOfMap k v = [MAP k v]
> 
> Then you can do things with it:
> 
>   lookupLom :: (Ord k) => ListOfMap k v -> k -> [ Maybe v ]
>   lookupLom xs k = [ lookupM a k | MAP a <- xs ]
> 
>   test :: [Maybe Int]
>   test
> = lookupLom maps 1
> where
>   maps = [ MAP finiteMap, MAP assocListMap, MAP functionMap ]
>   finiteMap = listToFM [(1,2)]
>   assocListMap = [(1,3)]
>   functionMap = \k -> if k == 1 then Just 4 else Nothing
> 
> It's a little unfortunate that you have to introduce the MAP type here.
> You can in fact construct a list of this type:
> 
>   type ListOfMap k v = [ forall m. (Map m k v) => m ]
> 
> But then you can't use the elements in the list because the Haskell
> type checker can't find the (Map m k v) constraint.
> 
> Cheers,
> Andrew Bromage
> ___
> Haskell-Cafe mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/haskell-cafe
> 


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



Question about use of | in a class declaration

2002-08-21 Thread Guest, Simon

Hello all,

Please could someone explain the meaning of | in this class declaration (from Andrew's 
example):

class (Ord k) => Map m k v | m -> k v where
  lookupM :: m -> k -> Maybe v

I couldn't find reference to this in any of my standard Haskell tutorials, nor the 
Haskell 98 report.  Any references?

cheers,
Simon

-Original Message-
From: Andrew J Bromage [mailto:[EMAIL PROTECTED]]
Sent: 21 August 2002 04:19
To: [EMAIL PROTECTED]
Subject: Re: Question about sets


G'day all.

On Tue, Aug 20, 2002 at 10:57:36AM -0700, Hal Daume III wrote:

> Lists with arbitrary
> elements are possible, but not very useful.  After all, what could you do
> with them?

It's often useful to have containers of arbitrary _constrained_ types,
because then you can do something with them.  For example, given the
class of partial mappings on orderable keys:

class (Ord k) => Map m k v | m -> k v where
  lookupM :: m -> k -> Maybe v


instance (Ord k) => Map (FiniteMap k v) k v where
  lookupM = lookupFM

instance (Ord k) => Map [(k,v)] k v where
  lookupM m k = case [ v | (k',v) <- m, k == k' ] of
[]-> Nothing
(v:_) -> Just v

instance (Ord k) => Map (k -> Maybe v) k v where
  lookupM   = id

You can make a list of elements, which can be any type so long as
they are a member of that class:

data MAP k v = forall m. (Map m k v) => MAP m

type ListOfMap k v = [MAP k v]

Then you can do things with it:

lookupLom :: (Ord k) => ListOfMap k v -> k -> [ Maybe v ]
lookupLom xs k = [ lookupM a k | MAP a <- xs ]

test :: [Maybe Int]
test
  = lookupLom maps 1
  where
maps = [ MAP finiteMap, MAP assocListMap, MAP functionMap ]
finiteMap = listToFM [(1,2)]
assocListMap = [(1,3)]
functionMap = \k -> if k == 1 then Just 4 else Nothing

It's a little unfortunate that you have to introduce the MAP type here.
You can in fact construct a list of this type:

type ListOfMap k v = [ forall m. (Map m k v) => m ]

But then you can't use the elements in the list because the Haskell
type checker can't find the (Map m k v) constraint.

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


Registered Office: Roke Manor Research Ltd, Siemens House, Oldbury, Bracknell, 
Berkshire. RG12 8FZ

The information contained in this e-mail and any attachments is confidential to Roke 

Manor Research Ltd and must not be passed to any third party without permission. This 

communication is for information only and shall not create or change any contractual 

relationship.



RE: broken mail threads

2002-08-21 Thread Simon Marlow

[ off-topic ]

> I'm sorry to bring up such petty issues, but this has been nagging me
> for quite a long while now... 
> 
> The Haskell mailing lists have one rather unflattering characteristic:
> their mail threads are almost always broken.
[... snip ...]
> X-Mimeole: Produced By Microsoft Exchange V6.0.6249.0
> (Does have some very non-standard Thread-Topic: and Thread-Index:
> -headers, but no In-Reply-To: or References:)

Exchange removes In-Reply-To: headers from messages (either that or
Outlook doesn't generate them when it talks to an Exchange server).
Fortunately we also have an SMTP server here, and it's possible to coax
Outlook into using that instead of Exchange for sending mail.  Let's see
if this works...

Cheers,
Simon

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