Re: [Haskell] integration of functional and imperative programming concepts

2005-03-03 Thread Keith Wansbrough
> Hello,
> 
> for my diploma thesis, I need to find information about integration of 
> functional and imperative programming concepts.  Could somebody of you point 
> me to good websites, papers, etc. about this topic?

"Tackling the Awkward Squad"
and
"State in Haskell"

both probably on Simon Peyton Jones's webpage, are good places to 
start; track back their references.  You'll probably end up with Moggi, 
and Wadler's popular introductions to Moggi.

That's all the monad approach; for other approaches you could look at 
ML and all the fun they had with polymorphism and references, or you 
could look at Lisp/Scheme and see what they do ("Structure and 
Interpretation of Computer Programs" is a classic textbook here, 
introducing functional, imperative, and object paradigms, all in the 
same language (Scheme)).

HTH.

--KW 8-)

-- 
Keith Wansbrough <[EMAIL PROTECTED]>
http://www.cl.cam.ac.uk/users/kw217/
University of Cambridge Computer Laboratory.

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


Re: [Haskell] Implicit parallel functional programming

2005-01-20 Thread Keith Wansbrough
> First, there is a claim that functional languages facilitate parallel
> execution, which is undeniably true if the implementation is something
> like that of Haskell (no assignment statements mean no memory contention,
> etc.). 

Careful here... no assignments in the source language doesn't
translate to no assignments in the implementation.  For example,
laziness relies fundamentally on mutation: when you begin evaluating a
thunk, the thunk is overwritten with a "black hole" tag; once
evaluation is complete, the thunk is overwritten again with the
resulting value.  If another thread attempts to evaluate the same
thunk, it is added to a queue stored in the black hole, which is woken
when the black hole is overwritten.  (If the same thread attempts to
evaluate the thunk, the RTS prints "<< Loop >>" to warn you of an
infinite loop.)

Notice that, at least in a naive implementation, that blackhole update
must be synchronised across all processors - you don't want to
processors to evaluate the same thunk in parallel by accident because
of a race.

So there certainly is memory contention.  Whether this can be
addressed in some way is a question for those more qualified than I...

--KW 8-)

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


Re: [Haskell] Re: Parameterized Show

2004-11-15 Thread Keith Wansbrough
George Russell wrote:

> I like the idea too, not just for Show but for any instances.  It seems to
> me that in general you should be able to combine the convenience of the
> Haskell type system with the power of Standard ML's structures and functors.
> Something along these lines was done by Kahl & Scheffczyk ("Named Instances 
> for
> Haskell Type Classes", Haskell Workshop 2001).
[..]
> (3) a way of using the dictionary.  For this we need (appFn), declaraed by 
> the type
> declaration.  appFn has the unorthodox type
> 
> appFn :: ShowDict a -> (forall a . Show a => b) -> b

I've wanted this too.  Amongst other things, it would subsume all the
"fooBy" functions in the prelude and libraries - instead of having
both sort and sortBy, you could just build an Ord dictionary and pass
it to sort.

Note that there should be a way of creating a dictionary without
creating an ordinary instance - in the OP's application, you would
want two intShowDicts, one of which showed in decimal and the other of
which showed in hex.  In Haskell you can't have two instance
declarations for the same type...

--KW 8-)

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


Re: [Haskell] Re: Global Variables and IO initializers

2004-11-04 Thread Keith Wansbrough
> But I just realized that it will probably be necessary to declare (not 
> bind!) implicit parameters at the top level to avoid capture problems. 

Yep, this is the way it would have to go.

--KW 8-)
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] -allow-extension-for-bottom

2004-10-11 Thread Keith Wansbrough
> Dear Haskell implementors,
> 
> Consider the compilation flag  -allow-extension-for-bottom
> 
> which changes the language meaning so that allows to ignore
> the bottom value. For example, the programs
> 
>(1)   (\ x -> (if p x then  foo (g x)  else  foo (h x)) )
> and
>(2)   (\ x -> foo ((if p x then  g x  else  h x)) )
> 
> become equivalent, and many program transformations become 
> possible.

Is it not the case that with -allow-extension-for-bottom all programs
are equivalent to

  error "Finished"

and hence not just 1000 times faster but infinitely faster
(asymptotically)?

Seriously, I can see that something like this might be of interest,
but the details are not trivial.  For a start, you'd want to allow
refinements only - from _|_ to non-_|_ - rather than in both
directions, to disallow the above transformation.  But then you'd have
to deal with refinement relations rather than equivalences everywhere
in the theory, losing symmetry and making things more complicated.

--KW 8-)

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


Re: [Haskell] lazy printing

2004-09-10 Thread Keith Wansbrough
> Dear Haskellers,
> 
> Can you tell me how to force Haskell to output the results in a
> `lazy' way? 
[..]
> main = putStr (concat ["\n min1 = ", show min1,
>"\n min2 = ", show min2,
>"\n"
>   ]
>   )
[..]
> This prints   min1 = 1
> 
> and hangs silently -- probably, because  min2  takes long to compute.
> But why does not it print immediately
>   
>   min1 = 1
>   min2 = 

Haskell is outputting lazily, but by default stdout is set to LineBuffering - for 
efficiency, a line is only written to stdout once it is complete.  Try adding "\n" to 
the end of the "min2 =" line to see what I mean.

To get the behaviour you describe, add import IO  and hSetBuffering stdout NoBuffering 
>>  to the start of your main function.

--KW 8-)
-- 
Keith Wansbrough <[EMAIL PROTECTED]>
http://www.cl.cam.ac.uk/users/kw217/
University of Cambridge Computer Laboratory.

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


Re: [Haskell] "global variables" and code optimization

2004-09-10 Thread Keith Wansbrough
> 
> The problem is, that with optimizations turned on (using ghc V6.2.1) the
> label number is calulated only once, so each call to makeBlockName yields
> the same value. I tried a) adding a dummy parameter to makeBlockName and b)
> specifying an INLINE pragma to both getAndUpdateVar and makeBlockName, but
> that doesn't help. What can I do to prevent optimization to optimize that
> calculation away?

This is why it is called *unsafe* - code that contains unsafePerformIO is usually 
wrong, and the proof obligations on the programmer when using it are complex and 
ill-defined.

There is a noinline pragma you can use, but I'm not at all sure it will save you in 
this specific situation.  Consider: makeBlockName has type String; it's just a 
constant.  How is the compiler going to give it a different value each time?  What 
does "each time" mean, anyway?

It's possible that by putting a noinline pragma on getAndUpdateVar you might arrange 
that each call to that gives a fresh label number; but you'll have to call it directly 
from your main function, rather than from within a constant as you have here.  (note 
also that just adding an unused argument to makeBlockName probably won't help; GHC is 
cleverer than that).

Why not just thread (newLabelNr :: Int) through your code to the places that need it?  
If you do this with other things too, then put them in a record.  This is a kind of 
"poor-man's" state monad.

--KW 8-)

-- 
Keith Wansbrough <[EMAIL PROTECTED]>
http://www.cl.cam.ac.uk/users/kw217/
University of Cambridge Computer Laboratory.

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


Re: [Haskell] Sequencing of input and output, troubles in kdevelop

2004-08-27 Thread Keith Wansbrough
> "A.J. Bonnema" <[EMAIL PROTECTED]> writes:
> 
> > Why doesn't kdevelop generate code, that executes the statements in
> > order? Or should I be looking at ghc? Or is it an option I am missing?
> 
> GHCi behaves like Hugs.  My guess would be that kdevelop attaches
> pipes for standard input and output, and GHC or whatever backend it
> uses realizes it is not talking to a terminal, and applies buffering.

In other words - if kdevelop is supposed to support the use of interactive programs in 
its console window, it should allocate a pty, rather than just using ordinary Unix 
pipes.  I would consider this a bug.

The fix for now is for you to explicitly turn off buffering:

import IO

main = do hSetBuffering stdin LineBuffering
  hSetBuffering stdout NoBuffering
  hSetBuffering stderr NoBuffering
      ...

(warning: untested code)

--KW 8-)
-- 
Keith Wansbrough <[EMAIL PROTECTED]>
http://www.cl.cam.ac.uk/users/kw217/
University of Cambridge Computer Laboratory.

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


Re: [Haskell] image writing library

2004-08-05 Thread Keith Wansbrough
> 
> Hi,
> 
> I would like to write an (Array (Int,Int) Int) to a file in some kind
> of image format.  I implemented (quick and very dirty) XBM output, but
> it would be nice to have some colors, and anyway, I can't seem to show
> the XBMs as grayscale.

Just write a "plain format" PPM by hand - if you want it in a
different format, just use the pnm tools to convert.

Format is:

P3
width height maxval
r g b r g b r g b r g b
r g b r g b r g b r g b
...



where all numbers are decimal, "P3" must be the first two chars, each
token must be separated by some whitespace (newline or space, doesn't
matter which or how many), and maxval is the maximum value of a
component (usually 15 or 255).

e.g.

   P3
   4 4
   15
0  0  00  0  00  0  0   15  0 15
0  0  00 15  70  0  00  0  0
0  0  00  0  00 15  70  0  0
   15  0 150  0  00  0  00  0  0

Type "man 5 pnm" for more info.

Once you have the ppm file, do cjpeg to get jpeg, or ppmtoxpm,
ppmtobmp, or whatever else.

--KW 8-)

--KW 8-)

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


Re: [Haskell] Memo function help

2004-07-28 Thread Keith Wansbrough
Tom writes:
> > I want to use the memo function for  implementing a dynamic 
> > programming algorithm in Haskell.
> > This is needed to cache intermediate results.
> > Can anyone tell me where I can find some examples that use the memo 
> > function or even a tutorial.

You should also look at

Stretching the storage manager: weak pointers and stable names in Haskell
Simon Peyton Jones, Simon Marlow, Conal Elliott
IFL'99

http://research.microsoft.com/Users/simonpj/Papers/weak.htm

which gives an example of a general memoising function "memo", which uses weak 
pointers to manage storage sensibly.

--KW 8-)
-- 
Keith Wansbrough <[EMAIL PROTECTED]>
http://www.cl.cam.ac.uk/users/kw217/
University of Cambridge Computer Laboratory.

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


Re: [Haskell] Reading a directory tree

2004-06-22 Thread Keith Wansbrough

> BTW, one other caveat (which applies to all of the examples so far):
> doesDirectoryExist doesn't distinguish between directories and
> symlinks to directories. Consequently, any directory-traversal
> algorithm which uses doesDirectoryExist to identify directories will
> behave incorrectly in the presence of symlinks. In the worst case, you
> can get into an infinite loop.

symlinks aren't necessary to give an infinite loop: you can have upwards hard links as 
well (at least on *nix).  You have to keep a list of inodes you've already visited 
(per filesystem, of course).

--KW 8-)
-- 
Keith Wansbrough <[EMAIL PROTECTED]>
http://www.cl.cam.ac.uk/users/kw217/
University of Cambridge Computer Laboratory.

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


Re: [Haskell] IO, exceptions and error handling

2004-06-14 Thread Keith Wansbrough
> Philippa Cowderoy wrote:
> 
> > The ability to fail doesn't need the do notation, just use of 
> > return for success - similar for propagating failure.
> 
> I'm not sure I understand. Do you mean writing functions
> like:
> 
> sqr x | x < 0 = fail "less than zero"
>   | otherwise = return (sqrt x)

s/fail/error/
s/return//

Then you can easily write

> I can't (easily) write
> 
> text c = sqr x + sqr (x+1)

You just can't *catch* this outside the IO monad.

--KW 8-)
-- 
Keith Wansbrough <[EMAIL PROTECTED]>
http://www.cl.cam.ac.uk/users/kw217/
University of Cambridge Computer Laboratory.

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


Re: [Haskell] IO, exceptions and error handling

2004-06-14 Thread Keith Wansbrough
> I can't see any fundamental reason why exception handling has to occur in 
> the IO monad.

Read the paper _A Semantics for Imprecise Exceptions_.  The problem is that the 
evaluation order of Haskell would have to be fixed for this not to lose referential 
transparency.  What is the value of

catchExcept (show (makeExcept "E1" + makeExcept "E2")) (\x -> x)

?  Haskell wouldn't be "purely functional" any more.

http://research.microsoft.com/~simonpj/Papers/imprecise-exn.htm

--KW 8-)
-- 
Keith Wansbrough <[EMAIL PROTECTED]>
http://www.cl.cam.ac.uk/users/kw217/
University of Cambridge Computer Laboratory.

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


Re: [Haskell] IO question

2004-06-11 Thread Keith Wansbrough
> > (and the ghost of Launchbury whispers in my ear that this is the
> > Haskell list, and "unsafePerformIO is not Haskell"!).
> 
> John is dead?!?!?!

Not to my knowledge, just not on the mailing list...

--KW 8-)
-- 
Keith Wansbrough <[EMAIL PROTECTED]>
http://www.cl.cam.ac.uk/users/kw217/
University of Cambridge Computer Laboratory.

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


Re: [Haskell] IO question

2004-06-11 Thread Keith Wansbrough
> On Fri, Jun 11, 2004 at 01:23:11PM +0200, Tom Hofte wrote:
> > I want to have a function that unpack an IO.
> > I should have the type: IO a -> a.
> > Is this possible?
> 
> There is unsafePerformIO, but before you use it, think - do you
> really, really want to use it and you really, really know what the
> consequences can be? Perhaps you could tell us what it is that you think
> you need unsafePerformIO for? Maybe it can be done without it?


It really should be a list Rule that we don't mention unsafePerformIO
to newbies.  It should be obvious from the post that unsafePerformIO
is *not* what the poster wants, so telling them about it will just
confuse them.  The wiki pointer is much more useful.

(and the ghost of Launchbury whispers in my ear that this is the
Haskell list, and "unsafePerformIO is not Haskell"!).

--KW 8-)

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


Re: [Haskell] simulating dependent types; ghc/ghci discrepancy

2004-04-14 Thread Keith Wansbrough
> > anyway (thus providing the dictionary) there is no point in storing it.
> 
> Aren't you talking about a different declaration?
> 
>   data Show a => Show' a = Show' a

Yes, I am.  Oops, sorry.

--KW 8-)
-- 
Keith Wansbrough <[EMAIL PROTECTED]>
http://www.cl.cam.ac.uk/users/kw217/
University of Cambridge Computer Laboratory.

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


Re: [Haskell] simulating dependent types; ghc/ghci discrepancy

2004-04-14 Thread Keith Wansbrough
> data Show' = forall a . Show a => Show' a

The "forall a. Show a =>" context here has no effect on the 
representation; it merely constrains applications of the data 
constructor Show'.  Since you have to say

> print' :: Show' -> IO ()

anyway (thus providing the dictionary) there is no point in storing it.

Thus

> *DepTest> :t x
> x :: forall a. a

is indeed the type of x.

There was a thread about this in the café recently; see

http://www.haskell.org//pipermail/haskell-cafe/2004-March/005985.html
http://www.haskell.org//pipermail/haskell-cafe/2004-March/005999.html
http://www.haskell.org//pipermail/haskell-cafe/2004-March/005998.html

--KW 8-)

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


Re: [Haskell] reasons for non-portability

2004-03-22 Thread Keith Wansbrough
> Am Sonntag, 21. März 2004 12:36 schrieben Sie:
> > Wolfgang Jeltsch wrote:
> > > [...] My question is, if a module is considered non-portable only if it
> > > contains non-portable constructs itself, or if a module is also
> > > non-portable if it just imports a module which is non-portable.
> >
> > Both, otherwise stating the property "portable" wouldn't help very much.
> 
> Well, I discovered that ghci is able to load modules without the 
> -fglasgow-exts option even if they rely on non-portable modules from the 
> hierarchical libraries (like, e.g., Control.Monad.Reader).

Ultimately, *every* module depends on non-portable modules - somewhere
it all has to come down to primitives, and these are wired into each
compiler in some magic way.

--KW 8-)

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


Re: [Haskell] Per-type function namespaces (was: Data.Set whishes)

2004-02-26 Thread Keith Wansbrough
> I've had an idea stewing in my head to do with per-type function 
> namespaces, that the current module namespace discussion reminded me 
> about.  The problem is that there is a limited namespace for functions, 
> so that if you define a new data type, it is unwise to call functions 
> which work on that data type a very generic name such as 'add'.
[..]
> The idea that I've been throwing around is to be able to define a 
> separate namespace for each type; a function can either belong in a 
> "global" (default) namespace, or belong in a particular type's 
> namespace.

This feature would seem to be in competition with type classes; could
you elaborate on the relative advantages and disadvantages?  The type
class story has the advantage of being well understood and quite
effective, but there are certainly some limitations too.

--KW 8-)

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


[Haskell] Wiki manager change

2004-02-16 Thread Keith Wansbrough
Hi all... the Haskell Wiki http://haskell.org/hawiki/ is under new 
management.  From now on, please contact Shae Erisson 
<[EMAIL PROTECTED]> with your requests, comments, or feedback on 
the Wiki site - or, of course, improve and extend the site yourself!  
Thanks all for your contributions - please keep them coming, and make 
this resource even more useful.

Cheers,

--KW 8-)
Former Haskell Wiki manager

-- 
Keith Wansbrough <[EMAIL PROTECTED]>
http://www.cl.cam.ac.uk/users/kw217/
University of Cambridge Computer Laboratory.

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


Re: Inspecting reduced/optimized code

2003-11-10 Thread Keith Wansbrough
> 
> Is it possible/easy in any of the compilers/interpreters to see what the
> results of rewriting/optimisations are?  (I'm sure it is *possible*, I'm
> really asking if any produce simple output in a well documented format
> that I'm likely to understand).

Very easy in GHC.  GHC does its optimisations on code in a functional
language called "Core", which is a cut-down version of Haskell with
explicit typing.  It's quite readable (apart from the weird
automatically-chosen variable names), and you can get it to dump it at
various stages.  Take a look at

http://www.haskell.org/ghc/docs/latest/html/users_guide/options-debugging.html

for info.  You might find the following link useful for understanding
what the various passes are:

http://www.cse.unsw.edu.au/~chak/haskell/ghc/comm/

HTH.

--KW 8-)

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


Re: automaticly create the ana, cata, hylomorphisms

2003-11-07 Thread Keith Wansbrough
> Hello programmers,
> 
> I have a problem to solve and don't have a clue where to start.

This is a homework question.  Please read

http://www.haskell.org/hawiki/HomeworkHelp

for some helpful hints.

By the way, you shouldn't post the same message to multiple lists - you should choose 
the right one (haskell-cafe in this case), or if you must, cross-post one message to 
both.  This means people who subscribe to both won't see your message twice.

--KW 8-)
-- 
Keith Wansbrough <[EMAIL PROTECTED]>
http://www.cl.cam.ac.uk/users/kw217/
University of Cambridge Computer Laboratory.

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


Re: Graduate Student

2003-10-21 Thread Keith Wansbrough
> I am a graduate student who is interested in Haskell. I wanted to take a
> look at the Haskell Wish List but I get the error 
[..]
> Is there anyone who has a copy of the Wish List? 

Someone will correct me if I'm wrong I'm sure, but I don't think this
has been used for at least a couple of years.  You might find the Wiki
pages more interesting; try starting at

http://haskell.org/hawiki/HaskellTwo

and browsing around.  Otherwise, the mailing list archives are
probably the best place to look.

--KW 8-)

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


Re: "interact" behaves oddly if used interactively

2003-10-01 Thread Keith Wansbrough
> Allow me to have another opinion, if the consequence is interleaved in- 
> and output (when I don't want it).
> 
> Can actually someone supply an implementation of something like interact 
> that does no pipelining for the argument "id"? Simply doing "putStr !$ f 
> !$ s" was not enough!

Yes, of course.

Your code above only forces the evaluation of the first cons-cell of
the list, which is not enough.  You want to force the entire list.
Try

deepSeq :: [a] -> b -> b
deepSeq (x:xs) y = deepSeq xs y
deepSeq [] y = y

noninteract f = do
  s <- getContents
  putStr (f (deepSeq s s))

or if you want non-lazy output too,

reallynoninteract f = do
  s <- get Contents
  let r = f (deepSeq s s)
  putStr (deepSeq r r)

untested code!

There's a library containing such functions, called (IIRC) DeepSeq or
something similar.

HTH.

--KW 8-)

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


Re: "interact" behaves oddly if used interactively

2003-10-01 Thread Keith Wansbrough
> But looking at the two actions of interact:
> 
> interact f = do
> s <- getContents
> putStr (f s)

(The Haskell report has two more actions, btw, setting nobuffering here)

> I would expect the first action to be finished before the second, (and I 

Why?

The magic here, in any case, is in getContents, which returns a list 
that is *lazily evaluated as needed* (Haskell report, page 98 (sec 
7.1)).  hGetContents does the same for an arbitrary handle.  This 
allows you to replicate the behaviour of Unix cat, ncat, grep etc, 
without having to code it explicitly.

For the use of laziness, consider

let fib = 0 : 1 : zipWith (+) fib (tail fib) in fib

and think what would happen if "let" was strict.  Programming in 
Haskell can be much more convenient than in strict languages, and 
laziness is assumed in lots of little ways throughout idiomatic Haskell 
code (I'm thinking of the liberal use of "where" and "let" bindings, 
for example).

> would not call it "interact" anymore after this discussion).

> Therefore, the "primitives" (getContents, putStr) behave "incorrect" to 
> my taste, (although the actual behaviour may be more desirable for 
> special other purposes.)

getContents behaves according to the specification in the standard, 
which is good enough for me.  So does putStr.

> 
> Christian

HTH.

--KW 8-)

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


Beautifying Haskell programs (was: Re: pretty newby )

2003-09-24 Thread Keith Wansbrough
John Huges wrote:

> On Wed, 24 Sep 2003, Luc Taesch wrote:
> 
> > alos, Im surprised that this bland issue has not already been solved (PP
> > lib paper looks dated 96). no offence intended, but aas im newbie, i
[..]
> 
> As the author of the 96 paper (wasn't it 95?), let me defend it a bit, or
> at least explain what it offers, and what it does not.

I think the reason it "looks dated" is that it pretty much solved the
problem it was addressing.  For pretty-printing data structures, the
solution given in that paper does a rather good job, is configurable
in the ways you might want to configure it, and is fairly easy to use
and understand.  No one has needed to invent a new way of doing it
since.


Regarding beautifying Haskell programs: as John says, it's not
straightforward.  But I think the reason that there isn't such a thing
is that most people don't need it.  We mostly use editors that allow
us to get the indentation right, automatically, as we type the source
in, and we take care to preserve it as we edit, because it makes the
code easier to understand.

(note that there *are* tools for producing beautified documentation:
Haddock lists exports, type definitions, type signatures, and argument
and function documentation in HTML format, but it doesn't deal with
actual code).

And your other point, Luc, about generating type signatures
automatically, shows up something about your approach to debugging
code.  You should always put the type signatures in as you go -
preferably, before you write the function!  This is not just good
design practice and good documentation, it helps you debug the
function.  With type signatures, the compiler can see what you
intended to write, and verify that what you did write matches it.
Without type signatures, all it can see is that two things don't match
- it has no idea what you meant to type.  Try it: try putting in type
signatures, and see how much better the compiler's error messages
become.

Hope this helps..

--KW 8-)

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


Re: [GUI] Announce: wxHaskell 0.2

2003-09-19 Thread Keith Wansbrough
Jens Petersen wrote:

>   http://haskell.org/~petersen/rpms/wxhaskell/
> 
> (current public_html seems to be disabled on haskell.org).

Not so; you have a syntax error in your .htaccess (perhaps apache was
upgraded and the syntax changed?).  If you remove it or correct the
error, your page will be served.

--KW 8-)

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


Re: GHC code generation

2003-09-11 Thread Keith Wansbrough
> There is no C-- backend for GHC (search the mailing list and you'll see 
> Simon asking someone to try to do this :P).  GHC either generates code by 
> itself, or generates normal C code (with -fvia-c or -O2, iirc) and then 
> uses GCC to compile this.

Ah... for some value of "normal"!  It's very GCC-specific, and there
is a nasty hack that it does to the output assembly code to rearrange
function entry points so that the info table lives directly before the
entry point.  It's certainly not ANSI or C99 code.  But it's not C--
either.

--KW 8-)

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


Re: Libraries and hierarchies

2003-08-01 Thread Keith Wansbrough
[stuff about GUIDs]

Careful!  There are two things one might tie GUIDs to.

You could compute a hash of (or associate a GUID with) the *interface*, 
or the *implementation*.  These are different things.  Until we know 
which we want, we should support both.

Why?

One might reasonably say "this program needs version X of the 
interface".  That is, we don't care how it's implemented, but it had 
better export these functions at these types.

But one might also reasonably say "this program needs version Y of the 
implementation".  That is, it requests a particular *implementation* - 
maybe it depends on certain bugs that are fixed in that version (or are 
not fixed!).  Or it's only been tested against that implementation, and 
it wants to provide some certification guarantees ("This software is 
DoD-certified to give appropriate results with specified inputs").

A side point is that GUIDs can be generated in two ways:

1. The traditional way: make up a 128-bit random number and insert it 
into the interface or implementation (as appropriate).  Use this as the 
name for that thing.

2. The nifty way: have the compiler compute a hash (SHA-1 or MD5) of 
the interface or implementation (as appropriate).  Use this as the name 
for that thing.

Option (2) has the advantage that it's one step shorter, and it's 
safer: with (1), you can generate one GUID but accidentally use it on 
two distinct interfaces / implementations; with (2), this is 
(essentially) impossible (although it may be possible to achieve a 
collision intentionally; malice is a separate issue that should be 
addressed in other ways).

For (2), we need to agree what to hash.  The options are basically "the 
source text of the module" (or some sub-part of it for the interface 
case), or "the abstract syntax tree of the module".  The latter is 
probably nicer, but requires some agreement between compiler writers if 
it is to be valid across compilers.


For background to this discussion, see our forthcoming ICFP paper,

James J. Leifer, Gilles Peskine, Peter Sewell, Keith Wansbrough (2003). 
Global Abstraction-Safe Marshalling with Hash Types

which is available at

http://www.cl.cam.ac.uk/~kw217/research/paper-abstracts.html#Leifer*03:G
lobal


Comments?

--KW 8-)
-- 
Keith Wansbrough <[EMAIL PROTECTED]>
http://www.cl.cam.ac.uk/users/kw217/
University of Cambridge Computer Laboratory.

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


Re: User-Defined Operators

2003-07-17 Thread Keith Wansbrough
Wolfgang writes:

> I think, in both cases you don't define an *operator*. LaTeX probably won't 
> use the correct spacing around the symbol.
> 
> A related problem is that I cannot see a way to define a new "log-like 
> function" (as Lamport names them), i.e., a function with a name consisting of 
> several letters which have to be set in upright font with no spaces between 
> them. Examples are log, min, max, sin, cos and tan.

This is off-topic, but I think you want to look at the \mathop, \mathbin, \mathrel, 
\mathord, etc commands.  These declare anything as the appropriate math category, and 
so give the right spacing.

Perhaps this should move to the Haskell Cafe?

--KW 8-)
-- 
Keith Wansbrough <[EMAIL PROTECTED]>
http://www.cl.cam.ac.uk/users/kw217/
University of Cambridge Computer Laboratory.

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


Re: yet another very simple overlapping instance example

2003-06-25 Thread Keith Wansbrough
> instance Op_plus MyInt MyInt where
> instance (Num a) => Op_plus a MyInt where
> instance (Num a) => Op_plus MyInt a where
[..]
> Overlapping instance declarations:
>multi.hs:9: Op_plus a MyInt
>multi.hs:12: Op_plus MyInt a
> Failed, modules loaded: none.

The GHC manual talks about this at:

http://haskell.cs.yale.edu/ghc/docs/latest/html/users_guide/type-extensions.html#INSTANCE-DECLS

I think the issue is that GHC still requires that overlapping
instances either do not unify, or have an instantiation ordering.
Your 2nd and 3rd instances are unordered: 2 is an instance of 3, and 3
is an instance of 2.  GHC doesn't notice the first instance.

I observe that the docs above say "Yell if this restriction bites
you.", so I shall hand this over to the GHC developers to discuss
further...

--KW 8-)

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


Re: In search of: [a->b] -> a -> [b]

2003-06-20 Thread Keith Wansbrough
Derek Elkins wrote:

> Christian Sievers <[EMAIL PROTECTED]> wrote:
>
> > (and this could be a monad comprehension, if Haskell still had
> > them...)
> 
> I don't think Haskell ever had them (I'd have to check).
> Gofer did.

They were put in for Haskell 1.4, and removed again for Haskell 98
because of the horrendously confusing error messages they caused.

http://www.haskell.org/definition/

--KW 8-)
-- 
Keith Wansbrough <[EMAIL PROTECTED]>
http://www.cl.cam.ac.uk/users/kw217/
University of Cambridge Computer Laboratory.

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


Re: In search of: [a->b] -> a -> [b]

2003-06-18 Thread Keith Wansbrough
> >or breakin' out the point-free style,
> >   flist = flip (map . flip ($)) -- okay, so I wouldn't recommend this
> 
> I keep on reading about this "point free style", but can't find any 
> discussion of it.  Are there any pointers (sic) ?

Search for "Squiggol" or "Bird-Meertens Formalism".  A group of
functional programmers at Oxford.  (Richard Bird and Lambert Meertens
are the ones the formalism was named after).

I see some citations of
  Backus, J. 1978. "Can Programming Be Liberated from the von Neumann
  Style? A Functional Style and Its Algebra of Programs," Communications
  of the Association for Computing Machinery 21:613-641.
which appears to be available (as a scan) at, amongst others,
  http://www.stanford.edu/class/cs242/readings/backus.pdf

Another source is

  http://web.comlab.ox.ac.uk/oucl/work/jeremy.gibbons/publications/index.html#radix

(Jeremy Gibbons introduced me to the concept when I was an
undergraduate).

This is an introduction to Squiggol:

  
http://web.comlab.ox.ac.uk/oucl/work/jeremy.gibbons/publications/index.html#squiggolintro

This style underlies a lot of expert Haskeller's intuitions.  The mass
of cute symbols can drive you crazy, though... see Erik Meijer et
al.'s paper _Functional Programming with Bananas, Lenses, and Barbed
Wire_:

  http://www.cse.ogi.edu/~erik/Personal/classic.htm

Hope this helps.

(going on the Wiki as PointFreeStyle, linked from CommonHaskellIdioms).

--KW 8-)

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


Re: Type classes and code generation

2003-06-17 Thread Keith Wansbrough
> Does this also mean that a dictionary class is created for every class, and
> a dictionary created for every instance?

Yes, exactly.  Every class is translated to a data type declaration, 
and every instance is translated to an element of that data type - a 
dictionary.  (Note that you can't actually write those declarations in 
Haskell 98 in general, because they can have polymorphic fields; but 
this is a simple extension to the language).

Take a look at one of the references Bernard put on the bottom of the
Wiki page I just created for further information.

http://www.haskell.org/hawiki/TypeClass

--KW 8-)

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


Re: Type classes and code generation

2003-06-17 Thread Keith Wansbrough
Alistair Bayley writes:

> Warning: Defaulting the following constraint(s) to type `Integer'
>`Num a' arising from the literal `2' at Main.lhs:3
> 
> This implies to me that the compiler is generating the code for (+) for the
> particular instance, rather than using a run-time dispatch mechanism to
> select the correct (+) function. Is this correct, or am I way off?  Does the
> compiler *always* know what the actual instances being used are?

Yes, roughly.  In Haskell, the compiler always figures out the types of 
everything at compile time.  This means it can often figure out which 
bit of code to use at compile time as well - but because of 
polymorphism, not always.  Consider this bit of code:

double :: Num a => a -> a
double x = x + x

The function "double" will work on any type in the class Num, so the 
compiler can't know which "+" function to use.  But it *doesn't* solve 
this by run-time dispatch, like in C++.  Instead, it compiles double 
like this:

double' :: NumDict a -> a -> a
double' d x = let f = plus d
  in x `f` x

where NumDict is a record a bit like this:

data NumDict a = NumDict { plus :: a -> a -> a,
   minus :: a -> a -> a,
   fromInteger :: Integer -> a
   ...
 }

NumDict is called a "dictionary", and any time double' is called, the 
caller must supply the right dictionary.  If you write

double 2.0

then the compiler sees that you've written a Double, and so supplies 
the NumDict Double dictionary:

double' doubleNum 2.0

where doubleNum :: NumDict Double contains the methods for adding 
Doubles, subtracting them, and converting from Integers to them.

Whenever it can, a good optimising compiler (like GHC) will try to 
remove these extra "dictionary applications", and use the code for the 
right method directly.  This is called "specialisation".

Getting back to your original question, there's a little subtlety in 
Haskell to do with literals.  Whenever you type an integer literal like 
"2", what the compiler actually sees is "fromInteger 2".  fromInteger 
has type Num a => Integer -> a, so this means that when you type an 
integer literal it is automatically converted to whatever numeric type 
is appropriate for the context.  In the context you give, there's still 
not enough information - it could be Int, or Integer, or Double, or 
several other things.  Another little subtlety called "defaulting" (see 
the Haskell 98 Report, in section 4.3.4) arranges that in this 
situation, the compiler will assume you mean Integer if that works, and 
failing that, it will try Double before giving up.  That's what the 
warning message you give is telling you.

> Is there
> some way of preventing the type mechanism from generating code for the
> instance type, as opposed to the class? 

I don't understand this question - does the explanation above help?

> If I am correct, does it work the same way across module boundaries? (I
> would think so.)

Yes, it does work automatically across instance boundaries.

> If a module exports a class but no instances for that
> class, then a user of that class would have to install their own instances.

Instance exporting is not easy to control in Haskell; if you export a 
type, then all its instances are exported along with it automatically.

> OTOH, if the class plus one or more instances were exported, then a user
> could use the supplied instance types, and the compiler would still generate
> code to use the specific instances.

>From the explanation above, you should see that the compiler generates
polymorphic code for any function with a type class in its type (e.g.,
"Num a => ..."), and it's the *caller* that supplies the code for the
specific instances (the dictionary).  But if the type is known at
compile time, then the compiler will fill in the dictionary itself,
and may even specialise it away.

The intention is that there is only one, global "instance space" - you
can't tightly control the export or not of specific instances, they
are pretty much always exported and all visible.  This isn't quite
true in practice, but it's the idea.

Hope this helps.

If you don't mind, I'm going to put this conversation up on the Wiki,
at

http://www.haskell.org/hawiki/TypeClass

--KW 8-)

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


Re: Typesafe MRef's

2003-06-16 Thread Keith Wansbrough
> Keith Wansbrough wrote (snipped)
> 
> > I think I'm missing something... why is this?  Do you only allow one
> > value of each type?  It seems to me that updating k1's value should
> > not affect k2's.
> 
> Perhaps you could explain what "insert" is meant to do, since it doesn't
> cite a key value.

I'm thinking newSTRef - allocate a new cell.

--KW 8-)
-- 
Keith Wansbrough <[EMAIL PROTECTED]>
http://www.cl.cam.ac.uk/users/kw217/
University of Cambridge Computer Laboratory.

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


Re: Typesafe MRef's

2003-06-16 Thread Keith Wansbrough
George Russell writes:

> So what does the function
> insert2 val1 val2 =
>let
>   (m1,k1) = insert empty (Just val1)
>   (m2,k2) = insert m1 (Just val2)
>   m3 = update m2 k1 Nothing
>in
>   isJust (lookup m3 k2)
> return?  It looks to me as if it returns True if val1 and val2 have
> different types, False if they have the same type.  So you have now
> got a way of comparing two types for equality, and so a rather
> roundabout reimplementation of Dynamic.

I think I'm missing something... why is this?  Do you only allow one
value of each type?  It seems to me that updating k1's value should
not affect k2's.

--KW 8-)

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


Re: Typesafe MRef's

2003-06-13 Thread Keith Wansbrough
> Keith wrote (snipped)
>  > But George Russell's implementation relied on looking up something in
>  > one map with a key obtained from another map.  I thought type-safe
>  > MRefs should disallow this.
> 
> However if you disallow lookup up in one map with a key from another,
> then Ralf Hinze's solution of putting the value inside the key
> uses no type extentions and works perfectly well (though is probably
> not quite what was intended).

No, because update should not return a new key, it should update the 
value of the same key.  In other words,

let (m1,k) = insert empty "A"
m2 = update m1 k "B"
in
lookup m2 k

should give "B", not "A", just like with MRefs.

--KW 8-)

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


Re: Typesafe MRef with a regular monad

2003-06-13 Thread Keith Wansbrough
> In article <[EMAIL PROTECTED]>,
>  [EMAIL PROTECTED] (Carl R. Witty) wrote:
> 
> > Here's a hand-waving argument that you need either Typeable (or
> > something else that has a run-time concrete representation of types)
> > or ST/STRef (or something else, probably monadic, that can track
> > unique objects) to do this.
> 
> George Russell already showed this, didn't he? You can implement 
> Typeable given type-safe MRefs, and you can implement type-safe MRefs 
> given Typeable.

But George Russell's implementation relied on looking up something in
one map with a key obtained from another map.  I thought type-safe
MRefs should disallow this.

--KW 8-)

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


Re: a dream of databases

2003-06-13 Thread Keith Wansbrough
> now. I am pretty sure I can do the demand loading bit with some
> goddawful code (inspired by HOODs internals) using unsafePerformIO and
> Weak pointers in truly nefarious ways. The dumping to the database bit
> is straightforward when working with trees. but I can't figure out a way
> to do it for potentially complex datastructures. perhaps someone out
> there has an idea? perhaps some template haskell tricks can be pulled to
> make it happen? I realize that any solution will be quite hacky and
> unlikely to be very portable.

You probably want to use unsafePtrEq, and possibly something to give
you a hash of a pointer... or maybe you want to look at Koen
Claessen's "observable sharing" work that he developed for Lava.

  http://www.math.chalmers.se/~koen/Papers/obs-shar.ps

--KW 8-)

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


Re: problems with working with Handles

2003-06-12 Thread Keith Wansbrough
> Hello,
> 
> We're two students from the department of computer science at the 
> University of  Utrecht (the Netherlands), and we're havind some severe 
> difficulties in working
> with file handles in Haskell. Consider for example the following program:
> 
> main = do --let inputfile  = "input.txt" 
>   let inputtext  = "testit"
>   let outputfile = "output.txt"
>   writeFile outputfile ""
>   handle2 <- openFileEx outputfile (BinaryMode WriteMode)
>   hPutStr handle2 (inputtext ++ " extra")
>  
>   handle3  <- openFileEx outputfile (BinaryMode ReadMode)
>   inputtext2   <- hGetContents handle3
>   handle4 <- openFileEx outputfile (BinaryMode WriteMode)
>   hPutStr handle4 (inputtext ++ " extra2")
> 
> 
> The text which should be in the outputfile is "testit extra extra2", 
> instead "testit extra2" is written in.

The contents of output.txt in the filesystem is undefined until you
close the handle.  And what do you expect to happen with two handles
open on the same file for writing?  Bad things are going to happen...

For your other question, see the previous thread that someone else
mentioned.  hGetContents is a bit badly behaved, and should only be
used in trivial cases.  Here you should use hGetLine or hGetChar
instead.  That way you know where you are in the file, and calling
hClose is safe.

--KW 8-)



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


Re: Typesafe MRef with a regular monad

2003-06-09 Thread Keith Wansbrough
Ralf Hinze writes:

> Why is that? Ok, here is my second implementation. It uses the
> Dynamic module from our HW2002 paper. A key is a pair consisting
> of the actual key and a type representation.

[..]

> > update:: (Typable b) => FM k -> Key k a -> b -> (FM k, Key 
> > k b)
> > update (FM bs) (Key k _) b=  (FM ((k, Dyn rep b) : bs), Key k rep)
> 
> Does this fit the bill?

No, because update shouldn't return a new key, it should allow reuse
of the same key.  Restating Simon PJ's original signature, and adding
update:

   module TypedFM where
data FM k -- Abstract; finite map indexed bykeys of type k
data Key k a  -- Abstract; a key of type k, indexing a value of type a
 
empty :: FM k
insert :: Ord k => FM k -> k -> a -> (FM k, Key k a)
lookup :: Ord k => FM k -> Key k a -> Maybe a
update :: Ord k => FM k -> Key k a -> a -> FM k

If updating gives you a new key, then you might as well just store the
value in the key.  Instead, you keep the same key; and so you'd better
remain type-compatible.

--KW 8-)
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: Safe and sound STRef [Was Implementing RefMonads in Haskell without ST,IO]

2003-06-03 Thread Keith Wansbrough
> The following code shows a safe and sound implementation of a
> polymorphic heap with references and updates. The heap is capable of
> storing of polymorphic, functional and IO values. All operations are
> *statically* checked. An attempt to alter a heap reference with a
> value of a mismatched type leads to a _compile-time_ error. Everything
> is implemented in Haskell98 + multiparameter classes with functional
> dependencies + overlapping instances.

The problem you mention later, that the type of the heap returned is
different from the type of the heap passed, is fatal.  The following
expression is untypeable:

  let heap = init_gh in
  let (mr,heap1) = if 1<2 then
 let (xr,h) = alloc_gh 42 heap in (Just xr,h)
   else
 (Nothing,heap) in
  case mr of
Nothing -> ""
Just r  -> show (fetch_gh r heap1)

Heaps should be more dynamic than this; the (type of the) *reference*
should encode the type it points to, but the (type of the) *heap*
should not.

The question is still open...

--KW 8-)
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: escape from existential quantification

2003-02-27 Thread Keith Wansbrough
> I understand that existentially bound types cannot escape.
> 
> For example, say we have
> data Foo = forall a. Foo Int a
> 
> Then we cannot define a function
> extract (Foo i a) = a
> 
> However,this limitation makes it extremly difficult to program with local
> quantifications.Is there any way to by pass this?

The idea is to use a type more like this:

data Foo = forall a. Foo Int a (a -> (Int,Bool)) (a -> Int) (a -> Foo)

where the functions are the operations you want to use on the data.  So now a list of 
Foos can contain data of many different types, as long as it is paired with the 
appropriate accessor functions for those types.  You can use it like this:

case x of
  Foo n x f g h -> if snd (f x) then g x else 0

for example.

--KW 8-)
-- 
Keith Wansbrough <[EMAIL PROTECTED]>
http://www.cl.cam.ac.uk/users/kw217/
University of Cambridge Computer Laboratory.

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


Re: time since the epoch

2003-02-06 Thread Keith Wansbrough
Stefan Karrmann <[EMAIL PROTECTED]> writes:

> A sound base for a Time implementation should use TAI (temps atomique
> international), c.f. .

I disagree; I think UTC is quite sufficient, and will match the users'
expectations much better.  (executive summary: UTC is the time on your
watch (+/- timezone of course), TAI is behind by a few seconds, and
this difference changes each time there's a new leap second).

However, the reference above is not to TAI, but to a library called
libtai.  I don't know anything about this; Stefan, maybe you could
tell us some more?

--KW 8-)

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



Re: Lazy evaluation alternative

2003-01-26 Thread Keith Wansbrough
> I wonder if I could run an idea I've had by this list. It seems to
> me you could get some of the desired effects of lazy evaluation by using
> continuation passing style in code. For example, take this psuedo-code
> using CPS to represent an infinite data type.

This has been known for a long time; the CPS translation results in a 
program that has the same behaviour no matter what the underlying 
language's evaluation semantics are.  The lambdas make explicit what 
can happen now and what must be delayed until later.  Consequently 
using a strict (call-by-value) or lazy (roughly call-by-name) language 
makes no difference.

Here is what I believe to be the original paper (1975):

@Article{
   Plotkin75:Call,
   author="G. D. Plotkin",
   title="Call-By-Name, Call-By-Value and the Lambda Calculus",
   journal="Theoretical Computer Science",
   year="1975",
   volume="1",
   pages="125--159",
   abstract="This paper examines the old question of the relationship
  between ISWIM and the $\lambda$-calculus, using the distinction
  between call-by-value and call-by-name.  It is held that the
  relationship should be mediated by a standardisation theorem.
  Since this leads to difficulties, a new $\lambda$-calculus is
  introduced whose standardisation theorem gives a good
  correspondence with ISWIM as given by the SECD machine, but
  without the \emph{letrec} feature.  Next a call-by-name variant of
  ISWIM is introduced which is in an analogous correspondence with
  the usual $\lambda$-calculus.  The relation between call-by-value
  and call-by-name is then studied by giving simulations of each
  language by the other and interpretations of each calculus in the
  other.  These are obtained as another application of the
  continuation technique.  Some emphasis is placed throughout on the
  notion of operational equality (or contextual equality).  If terms
  can be proved equal in a calculus they are operationally equal in
  the corresponding language.  Unfortunately, operational equality
  is not preserved by either of the simulations.",
}

Enjoy!

--KW 8-)
-- 
Keith Wansbrough <[EMAIL PROTECTED]>
http://www.cl.cam.ac.uk/users/kw217/
University of Cambridge Computer Laboratory.

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



Re: Template Haskell

2003-01-06 Thread Keith Wansbrough
> > i tried http://haskell.org/pipermail/template-haskell/
> > to see the archive of the mailing list but i get an error :
> >
> 
> There is a stray character at the end of the URL. Delete it and you'll
> find what you're looking for.

Not so; this is the correct URL, but I guess noone has posted yet so the archive 
hasn't been created.

--KW 8-)
-- 
Keith Wansbrough <[EMAIL PROTECTED]>
http://www.cl.cam.ac.uk/users/kw217/
University of Cambridge Computer Laboratory.

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



New Wiki (was: Re: ANNOUNCE: Haskell Wiki resurrected )

2003-01-03 Thread Keith Wansbrough
There have been several suggestions that we switch from the present 
pywiki, which has proven rather unstable, to something a little more 
modern and reliable.  IIRC, the suggestions have been

  MoinMoin  http://moin.sourceforge.net/
  UseModhttp://www.usemod.com/cgi-bin/wiki.pl?UseModWiki

although I'm sure there are many possibilities.

It looks to me like UseMod would be a reasonable choice, so unless there are any 
objections I plan to attempt migration in the near future (modulo work demands, of 
course).

Any comments?

John Meacham wrote:

> What do people feel about switching to a better Wiki implementation? I
> know we all have been secretly hoping a Wiki implemented in haskell
> would surface, but this is certainly an area which is already
> overcrowded and I think the community would be better served by a fully
> functional Wiki now. I highly recommend UseMod, 
> http://www.usemod.com/cgi-bin/wiki.pl?UseModWiki
> It is very easy to set up and provides useful features like online
> browsing of Diffs and being much more robust than pywiki.

--KW 8-)
-- 
Keith Wansbrough <[EMAIL PROTECTED]>
http://www.cl.cam.ac.uk/users/kw217/
University of Cambridge Computer Laboratory.

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



ANNOUNCE: Haskell Wiki resurrected

2002-12-05 Thread Keith Wansbrough
Hi all... last night I resurrected the Haskell Wiki,

http://haskell.org/wiki/wiki

This is a set of web pages on Haskell which can be edited and updated 
by anyone.  The intention is to accumulate the combined wisdom of 
posters to the Haskell lists - if you ever reply to a FAQ with what you 
think is a particularly good answer, please add it to the Wiki.  If you 
see a FAQ that's been Frequently Asked, just point the poster at the 
appropriate page on the Wiki.

Sadly, the Wiki isn't very stable at the moment.  I'm hoping that one 
day it will be made more stable, but in the meantime, I've taken a 
snapshot of the state as it was last night, and placed a link to it on 
the haskell.org front page:

http://haskell.org/wikisnapshot/FrontPage.html

Note that no updates to the Wiki are ever lost; they're kept in a 
version control system.  So if you see a blank page on the main Wiki 
where you once spent several hours writing the perfect page, don't 
worry - it's not lost!

Hope this is useful to people!

--KW 8-)

PS: I'm not officially in charge of the Wiki, John Heron 
<[EMAIL PROTECTED]> is; I'm just helping him out at the moment.

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



Re: Design patterns in Haskell

2002-12-04 Thread Keith Wansbrough
> I spent an awful lot of time doing a brain-dump into these pages and am a 
> bit dissapointed that they seemed to have dissappeared without
> trace. Were these archived anywhere

Yes, they are in fact still there (they are all in RCS).  The problem is, the Wiki is 
broken.  I'm going to try and restore the pages statically for the moment (i.e., 
non-editable), and then look at how to make them work properly.  Assistance welcome!

--KW 8-)
-- 
Keith Wansbrough <[EMAIL PROTECTED]>
http://www.cl.cam.ac.uk/users/kw217/
University of Cambridge Computer Laboratory.

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



Re: Design patterns in Haskell

2002-12-03 Thread Keith Wansbrough
> size. while there's really no substitute for experience, i really
> believe we could benefit from some patterns.

There was a list of design patterns for Haskell on the Wiki (back in
the days when it worked):

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

--KW 8-)
-- 
Keith Wansbrough <[EMAIL PROTECTED]>
http://www.cl.cam.ac.uk/users/kw217/
University of Cambridge Computer Laboratory.

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



Re: still random number problem

2002-07-25 Thread Keith Wansbrough

> What is wrong with it? 

Take a look at the Wiki, which has some explanation of the IO monad (which you're 
using here, with the "do" notation):

http://haskell.org/wiki/wiki?UsingIo
http://haskell.org/wiki/wiki?ThatAnnoyingIoType
http://haskell.org/wiki/wiki?UsingMonads

Hope this helps!

--KW 8-)
-- 
Keith Wansbrough <[EMAIL PROTECTED]>
http://www.cl.cam.ac.uk/users/kw217/
University of Cambridge Computer Laboratory.

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



Re: text/x-haskell and text/x-literate-haskell added to the GNOME MIME database

2002-04-18 Thread Keith Wansbrough

Martin writes:

> Generally it has text for all program code in text format.
> 
> RFC 2045 says:
[..]
>[..] Such information can
>be used, for example, to decide whether or not to show a user the raw
>data from an unrecognized subtype -- such an action might be
>reasonable for unrecognized subtypes of text, but not for
>unrecognized subtypes of image or audio. [...]

OK, that convinces me.

--KW 8-)
-- 
Keith Wansbrough <[EMAIL PROTECTED]>
http://www.cl.cam.ac.uk/users/kw217/
University of Cambridge Computer Laboratory.

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



Re: text/x-haskell and text/x-literate-haskell added to the GNOME MIME database

2002-04-18 Thread Keith Wansbrough

> These MIME types has now been added to the GNOME MIME database:
> 
> text/x-haskell for *.hs
> text/x-literate-haskell for *.lhs

Note the following thread from August 1999: application/x-haskell has
already been proposed and used.

http://www.dcs.gla.ac.uk/mail-www/haskell/msg01843.html
http://www.dcs.gla.ac.uk/mail-www/haskell/msg01849.html
http://www.dcs.gla.ac.uk/mail-www/haskell/msg01853.html

"application" seems more appropriate for Fritz Ruehr's goal here,
which is a script that can be clicked on to make it run (using
runhugs, presumably).  I can see your reasoning for "text", though.
What is used for Javascript code at present?  Or for C source code?

--KW 8-)

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



Re: Lambda over types.

2002-03-22 Thread Keith Wansbrough

anatoli <[EMAIL PROTECTED]> writes:

> ghc -fglasgow-exts -fallow-undecidable-instances allows 
> constructs which amount to lambda abstraction over types. 
> I've written a small untyped lambda calculus interpreter 
> in the Haskell class/instance sublanguage, just to prove
> this point. (The terms are Haskell *types*.)

Cool!

Some time ago I wrote a Turing machine evaluator in Haskell types with undecidable 
instances.  It's described at

http://www.chttp://www.cl.cam.ac.uk/~kw217/research/misc/undec.html

Enjoy!

--KW 8-)
-- 
Keith Wansbrough <[EMAIL PROTECTED]>
http://www.cl.cam.ac.uk/users/kw217/
University of Cambridge Computer Laboratory.

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



Re: A Haskell specific preprocessor

2002-01-11 Thread Keith Wansbrough

Olaf writes:

> I faintly remember that there was once work on a Haskell specific
> preprocessor. Why was the work abandoned?

I had some ideas, which I put together in a note

http://www.cl.cam.ac.uk/~kw217/research/paper-abstracts.html#Wansbrough99:Macros

but most people seemed to believe that a lazy language shouldn't need macros or a 
preprocessor (despite the liberal use of both in GHC, for example).

--KW 8-)
-- 
Keith Wansbrough <[EMAIL PROTECTED]>
http://www.cl.cam.ac.uk/users/kw217/
University of Cambridge Computer Laboratory.


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



Re: The Wisdom of Time

2002-01-07 Thread Keith Wansbrough

> what is the wisdom behind representing a TimeDiff as a struct of year,
> month, week and so on, instead of simply the (fractional) number of
> seconds, or similar?

Firstly, I believe that the Time module is broken, and no one has yet
come up with a satisfactory design.

But the behaviour you describe is necessary.  Consider:

01-Jan-2002 plus 1 month = 01-Feb-2002
01-Feb-2002 plus 1 month = 01-Mar-2002
01-Mar-2002 plus 1 month = 01-Apr-2002
01-Apr-2002 plus 1 month = 01-May-2002

The first and third differences are 2678400 seconds, but the second is
2419200 and the fourth is 2592000.

The same is true for many other time differences.  If you want the
interval between two times, then simply subtract the seconds; but if
you want to compute things like "next week", "next month", "next
year", you need to have specific units for that.  (For "next week",
consider the impact of leap seconds...)

HTH.

--KW 8-)


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



Re: GCD

2001-12-11 Thread Keith Wansbrough

> Simon>gcd x y is the greatest POSITIVE integer that divides
> Simon> both x and y.
> 
> I find it confusing to read a definition which contains redundant
> information. Instead, I'd suggest to add something like:
> 
>   "Note: this number is always positive"

Or, perhaps easier on the eye,

  "gcd x y is the greatest (positive) integer that divides both x and y."

--KW 8-)

-- 
Keith Wansbrough <[EMAIL PROTECTED]>
http://www.cl.cam.ac.uk/users/kw217/
University of Cambridge Computer Laboratory.


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



Re: not naming modules Main

2001-11-19 Thread Keith Wansbrough

> I'm really frustrated that modules that you want to compile to
> executables have to be named Main.  I often have a module with a main
> method that I use for testing or whatever (perhaps I want the gained
> speed of an executable) but is, for the most part, a module I import
> into others.  I end up having to constantly change the module name
> whenever I want to compile it and I find this terribly frustrating.
> 
> Is there any reason you can't just compile things that simply export a
> main method with the proper type?  Is this a ghc specific thing or
> does nhc also have this restriction?  Any chance ghc will change its
> policy on this?

In GHC the "main" method has to be in module "Main", but there is no
requirement that the *file* containing module "Main" is called "Main".
Since "Main" isn't (usually) imported by any other module, there's no
concern that GHC won't be able to find the module when it looks for
it.  So you can have "Main.hs" with the real main in it, and
"TestMain.hs" with the alternative one, and just compile the right
file as appropriate.

However, after having written the above I'm not sure it answers your
question... sorry!

--KW 8-)


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



Re: What are ZMZN and ->Z1T in a ghc space profile?

2001-11-16 Thread Keith Wansbrough

> But, to answer your emmediate question:
> 
> ZMZM = []  - The list Nil constructor
> Z1T = ( )  - The 1-tuple constructor

IIRC, the "1" is the number of commas, so Z1T is the *pair* constructor.

--KW 8-)

-- 
Keith Wansbrough <[EMAIL PROTECTED]>
http://www.cl.cam.ac.uk/users/kw217/
University of Cambridge Computer Laboratory.


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



Re: Arrow notation, etc.

2001-10-12 Thread Keith Wansbrough

> Very good.  Is there a concrete proposal for such macros?  I think the
> arrow notation would be a harder test case than any of the existing
> syntactic sugar; I'd be curious to see what it looked like.  (And is
> there support for adding these macros to Haskell?)

Sadly, there's not a concrete proposal - it seems that no one sees a 
need for macros in a lazy language.  Most of what they do can be 
achieved through laziness - you can write "if" in Haskell already, for 
example, whereas you need a macro for it in Lisp.  Your arrow notation 
example may provide some motivation, though.

> > Hygiene is a key concept here; that variables bound in a macro
> > should not clash with other variables in the program (unless this is
> > explicitly required).
> 
> Off to read some Dylan manuals,

Do that, but the details of hygienic macros were first worked out in 
Scheme (a kind of Lisp), and then Dylan's was based on Scheme's.  The 
key difference is that Dylan has a rich syntax, whereas Scheme just has 
S-expressions.

>   Dylan


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



Re: Arrow notation, etc.

2001-10-12 Thread Keith Wansbrough

Dylan writes:

> Incidentally, it seems to me that this is one case where a Lisp-like
> macro facility might be useful.  With Haskell, it is impossible to
> play with bindings, while presumably you can do this with good Lisp
> macro systems.

Yes, this is one thing you can do with good macro systems as are found in Lisp and 
Dylan (the language, not the person!).  See the references in my

http://www.cl.cam.ac.uk/~kw217/research/paper-abstracts.html#Wansbrough99:Macros

Wansbrough, 1999.  Macros and Preprocessing in Haskell

especially section 8.

Hygiene is a key concept here; that variables bound in a macro should not clash with 
other variables in the program (unless this is explicitly required).

--KW 8-)
-- 
Keith Wansbrough <[EMAIL PROTECTED]>
http://www.cl.cam.ac.uk/users/kw217/
Cambridge University Computer Laboratory.


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



Re: getting started with the glasgow haskell compiler

2001-08-09 Thread Keith Wansbrough

Mikael Johansson writes:

> module Main (main) where
> main = putStrLn "Hello World"
> end
> 
> with the command
> 
> ghc Hello.lhs
> 
> I get the message on standard output:
> 
> No definitions in file 's?>


.lhs means "literate Haskell file".  Try


> module Main (main) where
> main = putStrLn "Hello World"

(the "end" isn't legal Haskell).  The ">" at the beginning of the line are called 
"Bird tracks" (after Richard Bird), and mark the lines of a literate Haskell program 
that are actually code.  Lines without them are just comments.

Or try

\begin{code}
module Main (main) where
main = putStrLn "Hello World"
\end{code}

which is another way of marking code.

The final way, probably the easiest, is simply to put your program in a file called 
Hello.hs  rather than Hello.lhs.  The .hs extension means "ordinary Haskell code".

HTH.

--KW 8-)
-- 
Keith Wansbrough <[EMAIL PROTECTED]>
http://www.cl.cam.ac.uk/users/kw217/
Cambridge University Computer Laboratory.


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



Negatively recursive data types

2001-07-04 Thread Keith Wansbrough

Hi... I'm currently looking at the semantics of recursive data types.  
One thing that Haskell allows, but the semantics for it is very hairy, 
is *negatively* recursive data types.  That is, data types where the 
recursion occurs to the left of a function arrow.  For example:

data Neg a b = MkNeg (a -> Neg a b -> b)

Here (Neg a b) occurs to the left of the function arrow.  Some members
of this data type might be:

n1, n2 :: Neg Int [Int]
n1 = MkNeg (\ x  _-> [x])
n2 = MkNeg (\ x (MkNeg f) -> x : f (x+1) n1)

This example is not a very good one.  Does anyone have an example of a 
useful data type involving negative recursion?

Thanks.

--KW 8-)


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



Re: List of words

2001-05-02 Thread Keith Wansbrough

> >Ah, but (i) not all the solutions are correct (sorry Ashley);
> 
> That rather depends on what you mean by CAPITALISE, does it not?
> 
> capitalise, -ize   to print or write with capital letters [Chambers]

I guess so.  Maybe someone at Monash University (Australia) would care 
to
enlighten us? >;->

--KW 8-)

-- 
Keith Wansbrough <[EMAIL PROTECTED]>
http://www.cl.cam.ac.uk/users/kw217/
Cambridge University Computer Laboratory.


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



Re: List of words

2001-05-02 Thread Keith Wansbrough

> I am relatively new to Haskell.
> 
> Somebody told me that it is a very good language, because all the
> people on its mailing list are so nice that they solve all 
> homeworks, even quite silly, of all students around, provided they
> ask for a solution in Haskell.
> 
> Is that true, or a little exaggerated?

Ah, but (i) not all the solutions are correct (sorry Ashley); and (ii)
some of the solutions should be recognisable by markers as not the
work of a newbie (explicit import lists, map, ...).

Essentially, though, your friend is correct.

--KW 8-)


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



Re: {-# LINE 100 "Foo.hs #-} vs. # 100 "Foo.hs"

2001-01-22 Thread Keith Wansbrough

> With all this talk of preprocessor generated information and whatnot, I
> am reminded of a paper I read not too long ago but can't seem to find
> anymore about a dedicated pre-processor for haskell based on the C
> preprocessor but made to deal with haskell constructs a bit more sanely.

This was me...

http://www.cl.cam.ac.uk/~kw217/research/papers.html#Wansbrough99:Macros

There wasn't sufficient interest, and no one has offered to implement
it.  I think people are mostly happy using CPP, and the hassle of
writing a `decent' macro preprocessor isn't worth it.  You may find
some of the ideas in the paper useful, though.

--KW 8-)


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



Re: Learning Haskell and FP

2001-01-04 Thread Keith Wansbrough

> I do not know if you actually wanted an answer to this, but I'm sick of
> hearing this FAQ everywhere when the answer is so simple. There are
> exactly two ways to do this (one of them is actually syntactic sugar for
> the other).
[..]
> Can everyone include an answer to this FAQ everywhere, phleaze!
> 
> /Lars L

Thanks Lars... I've added it to the Wiki.

HINT TO EVERYONE: *Anyone* can add this kind of thing to the Wiki.  
Just find the appropriate page and click the EditText link at the 
bottom.  To create a new page just name it (in BiCapitalised form), and 
the name becomes a hyperlink.  Click on the link, then EditText on the 
new page and you're done.

The Haskell Wiki is at:

  http://haskell.org/wiki/wiki

I *do not* maintain it, I just evangelise for it.  :-)

--KW 8-)


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



Re: Haskell Programming Environment

2000-10-25 Thread Keith Wansbrough

> I've been wanting to code one of these myself, but have had no time. Try and see
> if stg-hugs is useable yet since that would be a much better environment to do
> it in.

It's now called GHCi, and is being written right now by the GHC team.
Not sure when the estimated completion time is, but it can't be that
far off.

--KW 8-)


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



Re: Literate Programming

2000-09-26 Thread Keith Wansbrough

> 
> Huh?!? Is this a bug in Hugs? Is it confused by the `<' and
> `>' in the HTML code? No! It is just doing what the
> Haskell98 report says:
> 
>   C  Literate comments
>   [...]
>   To capture some cases where one omits an ">" by mistake,
>   it is an error for a program line to appear adjacent to a
>   non-blank comment line, where a line is taken as blank if
>   it consists only of whitespace.
> 
> What the rationale is for this, is a big mystery to me. Look
> at "to capture some cases"; what cases are captured by this?
> And what cases are not captured by this? And why does this
> silly restriction capture any of these cases?

I believe the "common case" is the following:

> data Foo a = A a | B a | C
>
> foo (A x) = f x
  foo (B x) = g x
> foo _ = error "unimplemented"

or possibly

> bar x = case e x of
Just a  -> a
Nothing -> b

Both of these are caught by the rule.

I agree that with additional block markers, this is extremely annoying
- but remember that unlit has no idea they are there.

--KW 8-)





Re: Extensible data types?

2000-09-25 Thread Keith Wansbrough

> In the Clean Object I/O library we encountered a similar challenge and 
> solved it using type constructor classes. The solution can also be used in 
> Haskell. The basic idea is as follows:
> 

I didn't read your message in detail, but I wonder if this is related
to the trick TclHaskell / FranTk use to deal with configuration lists?

--KW 8-)





Re: Patterns Catalog

2000-09-11 Thread Keith Wansbrough

> > > I think it would be a good thing to organise
> > > if anyone is willing to look ta this
> > > (If no-one is interested/ would rather do
> > > this) that person could be me as long as 
> > > folk don't mind waiting a while for results.
> > 
> > We started something like this on the Haskell Wiki, before it
> > prematurely died.  Has a certain historical authenticity to it, too,
> > given that (IIRC) the eXtreme Programming / design patterns ideas
> > started on a Wiki..

Thanks to SLPJ for pointing out that it HAS been resurrected.  It's at

http://haskell.org/wiki/wiki

and you should look at `CommonHaskellIdioms'

--KW 8-)
-- 
Keith Wansbrough <[EMAIL PROTECTED]>
http://www.cl.cam.ac.uk/users/kw217/
Cambridge University Computer Laboratory.





Re: Patterns Catalog

2000-09-11 Thread Keith Wansbrough

> I've thought of this too.
> but I dont think there is anything out there
> which fits the bill. 
> [I'd love someone to please correct me]

[..]

> I think it would be a good thing to organise
> if anyone is willing to look ta this
> (If no-one is interested/ would rather do
> this) that person could be me as long as 
> folk don't mind waiting a while for results.

We started something like this on the Haskell Wiki, before it
prematurely died.  Has a certain historical authenticity to it, too,
given that (IIRC) the eXtreme Programming / design patterns ideas
started on a Wiki..

http://c2.com/cgi/wiki?ExtremeProgramming

--KW 8-)





Re: Overlapping types

2000-08-21 Thread Keith Wansbrough

> class Subtype sub super where
> up   :: sub   -> super
> down :: super -> Maybe sub

See the extensible union types of

@InProceedings{
   Liang*95:Monad,
   author="Sheng Liang and Paul Hudak and Mark Jones",
   title="Monad Transformers and Modular Interpreters",
   crossref="ACM95:POPL",
   year="1995",
   pages="{333--343}",
}

>From the abstract:

  "... Finally, we have implemented our interpreter in Gofer,
  whose constructor classes provide just the added power over
  Haskell's type classes to allow precise and convenient
  expression of our ideas.  This implementation includes a method
  for constructing extensible unions and a form of subtyping that
  is interested in its own right."

They have a multiparameter type class SubType, with methods `inj' and
'prj', just as you describe, implemented in Gofer.

I used this in my Masters thesis,

@MastersThesis{
   Wansbrough97:Modular,
   author="Keith Wansbrough",
   title="A Modular Monadic Action Semantics",
   school="Department of Computer Science, University of Auckland",
   year="1997",
   month=feb,
   note="Available \path|http://www.cl.cam.ac.uk/users/kw217/research/msc/thesis/|",
}

--KW 8-)






Re: Haskell and the NGWS Runtime

2000-08-10 Thread Keith Wansbrough

Florian Hard <[EMAIL PROTECTED]> writes:

> How did they say on segfault.org:
> 
>Microsoft plans to expand Marketese in the future, adding a pound sign
>to every language currently in their suite of compilers and a plus
>sign to every acronym currently used to describe Microsoft technology.
> 
>http://www.segfault.org/story.phtml?mode=2&id=39897e26-060c53e0
> 
> :-)


Please:   #  -  hash / octothorp(e)
  £  -  pound
 C#  -  C sharp

Three different characters.  Down with American cultural imperialism.


--KW 8-)
-- 
Keith Wansbrough <[EMAIL PROTECTED]>
http://www.cl.cam.ac.uk/users/kw217/
Cambridge University Computer Laboratory.





Re: Precision problem

2000-07-18 Thread Keith Wansbrough

> IMHO GHC's documentation should clearly warn that programmers should
> not depend on even basic stability and exactness of floating point
> computations, and only stability is provided by -fstrictfp.


GHC is no different from any other compiler for any other language in 
this respect.  Floating-point values are *not* the mathematical `real 
numbers', and should not be treated as such.  This is second-year CS 
course material.

A good paper to read in this connection is:

@Article{
   Goldberg91:What,
   author="David Goldberg",
   title="What Every Computer Scientist Should Know About Floating
  Point Arithmetic",
   journal="Computing Surveys",
   year="1991",
   volume="23",
   number="1",
   month=mar,
}

--KW 8-)
-- 
Keith Wansbrough <[EMAIL PROTECTED]>
http://www.cl.cam.ac.uk/users/kw217/
Cambridge University Computer Laboratory.





Re: Instance of Functor for functions of >= 2 arguments

2000-06-24 Thread Keith Wansbrough

Matt Harden writes:

> That doesn't work either: Haskell98 doesn't allow type synonyms to be
> used to define instances.  GHC supposedly lifts this restriction, but it
> complains:  (I'm using version 4.02)
> 
> > type synonym `Func2' should have 3 arguments, but has been given 2
> > When checking kinds in `Func2 a b'
> > When checking kinds in `Functor (Func2 a b)'
> 
> So I guess GHC only accepts type synonyms as instances when the kind of
> the class is *.

The actual restriction is that type synonyms must always be fully applied; they can be 
at any kind.  Thus in your first example,

type Func a = (->) a
instance Functor (Func a) where
  ... 

works fine (in GHC).

This doesn't solve your problem, however.  I believe (someone will correct me if I'm 
wrong) that you're stuck here.  What you really need is a type lambda:

type Func2 a b = /\c. a->(b->c)

but this isn't provided in Haskell.

--KW 8-)
-- 
: Keith Wansbrough, MSc, BSc(Hons) (Auckland) ---:
: PhD Student, Computer Laboratory, University of Cambridge, UK. :
: Native of Antipodean Auckland, New Zealand: 174d47'E, 36d55'S. :
: http://www.cl.cam.ac.uk/users/kw217/ mailto:[EMAIL PROTECTED] :
::






Re: When is an occurrence an occurrence

2000-06-09 Thread Keith Wansbrough

> Now, would it be legal to add this type signature to the end of M?
> 
>   reverse :: [a] -> [a]
> 
> Or should it be
> 
>   M.reverse :: [a] -> [a]

Definitely (A), the unqualified form should be legal.  I always consider

foo :: [..type..]
foo  = [..defn..]

as a pair, and to require

M.foo :: [..type..]
foo= [..defn..]

would seem strange.

I'm with Ralf on this one.

--KW 8-)
-- 
: Keith Wansbrough, MSc, BSc(Hons) (Auckland) ---:
: PhD Student, Computer Laboratory, University of Cambridge, UK. :
: Native of Antipodean Auckland, New Zealand: 174d47'E, 36d55'S. :
: http://www.cl.cam.ac.uk/users/kw217/ mailto:[EMAIL PROTECTED] :
::






Re: Haskell pronounciation

2000-06-05 Thread Keith Wansbrough

> How is Haskell pronouced?
> That is, does it rhyme with "cell" like most words ending in "ell",
> or does it rhyme with "cull" like in some names?
> No one in this area has heard of Haskell.  I'd like to speak the
> correct name when I make people aware of Haskell.

Everyone I've met (including the GHC team) pronounces it roughly the way I do, which 
seems to be:

/h&skl-/

(using the IPA ASCII transcription at

http://www.hpl.hp.com/personal/Evan_Kirshenbaum/IPA/english.html
)

That is, it is pretty close to `battle', but with `hask' (`a' like in `hat') instead 
of `batt'.

Hope this helps.

--KW 8-)
-- 
: Keith Wansbrough, MSc, BSc(Hons) (Auckland) ---:
: PhD Student, Computer Laboratory, University of Cambridge, UK. :
: Native of Antipodean Auckland, New Zealand: 174d47'E, 36d55'S. :
: http://www.cl.cam.ac.uk/users/kw217/ mailto:[EMAIL PROTECTED] :
::






Re: confused

2000-06-05 Thread Keith Wansbrough

Roy Haskell (!) writes:

> I was recently browsing the web and came across an article HOW TO DO
> EXCEPTIONS IN HASKELL (I think) and I'm very curious what it's all about.
> The reason for my curiosity is simply that my name is Haskell and currently
> reside in South Africa but am originally from Manchester in the U.K.
> 
> Could you please shed some light on this matter if only to satisfy my
> curiosity.

Roy: very good question!  The `Haskell' we are discussing is a
computer programming language, designed in 1987 and currently being
used in a number of locations around the world.  It was named after a
famous mathematical logician by the name of Haskell B. Curry, who
lived 1900-1982, and who invented some of the theory on which the
language is based.

http://www-groups.dcs.st-and.ac.uk/~history/Mathematicians/Curry.html

You can find out more about Haskell at the official web site,

http://www.haskell.org/

I hope this helps!

Regards,

--KW 8-)





Re: your mail

2000-05-25 Thread Keith Wansbrough

> You can probably use the GHC & Hugs extension of pattern type signatures:
> 
>   inEnv (e::env) ma = Cont (\k ->
>do old <- rdEnv
>   inEnv e (unCont ma (inEnv (old::env) . k)))
> 
> I haven't checked this.

Or of course he can use `asTypeOf`, which is Haskell 98:

inEnv e (unCont ma (inEnv (old `asTypeOf` e) . k)))

--KW 8-)
-- 
: Keith Wansbrough, MSc, BSc(Hons) (Auckland) ---:
: PhD Student, Computer Laboratory, University of Cambridge, UK. :
: Native of Antipodean Auckland, New Zealand: 174d47'E, 36d55'S. :
: http://www.cl.cam.ac.uk/users/kw217/ mailto:[EMAIL PROTECTED] :
::






Re: more detailed explanation about forall in Haskell

2000-05-19 Thread Keith Wansbrough

Peter Hancock writes:

[..]
> Please guys, you are making clowns of yourselves. 

Amen to that!  I've just added the above subject line to my kill file, 
rather than stop reading the Haskell list altogether.

--KW 8-)

-- 
: Keith Wansbrough, MSc, BSc(Hons) (Auckland) ---:
: PhD Student, Computer Laboratory, University of Cambridge, UK. :
: Native of Antipodean Auckland, New Zealand: 174d47'E, 36d55'S. :
: http://www.cl.cam.ac.uk/users/kw217/ mailto:[EMAIL PROTECTED] :
::






Re: Type of minimumBy

2000-05-18 Thread Keith Wansbrough

> OTOH, if we were to redefine all the xxxBy functions that involve
> comparison, I'd vote for ((<=) :: a->a->Bool) over (compare ::
> a->a->Ordering) as the comparison function since (<=) is often easier to
> create a quick definition for.  I wouldn't consider such a change until
> Haskell 2, though.

I disagree... I don't think we should be making `quick-and-dirty' 
definitions easy, I think we should be doing it the Right Way.  It 
takes two `<=' comparisons to get the information obtainable from one 
`compare', but one `compare' is also enough to give a result for `<='.  
It usually requires no more computation to give the more specific 
result.

If you really want quick-and-dirty, you could add:

le2ord :: (a -> a -> Bool) -> (a -> a -> Ordering)
le2ord le a b = case (a `le` b, b `le` a) of
  (True, False) -> LT
  (True, True ) -> EQ
  (False,True ) -> GT

to the prelude (or to an Ordering library).  While you're constructing 
an Ordering library, you could add to it:

isLE :: Ordering -> Bool
isLE LT = True
isLE EQ = True
isLE GT = False

thenCmp :: Ordering -> Ordering -> Ordering
EQ `thenCmp` o2 = o2
o1 `thenCmp` _  = o1

and a partial ordering class

type POrdering = Maybe Ordering

class POrd a where
  pcompare :: a -> a -> POrdering

instance Ord a => POrd a where
  pcompare a b = Just (compare a b)

Just my £0.02 (about US$0.04 I believe).

--KW 8-)
-- 
: Keith Wansbrough, MSc, BSc(Hons) (Auckland) ---:
: PhD Student, Computer Laboratory, University of Cambridge, UK. :
: Native of Antipodean Auckland, New Zealand: 174d47'E, 36d55'S. :
: http://www.cl.cam.ac.uk/users/kw217/ mailto:[EMAIL PROTECTED] :
::






Re: Type of minimumBy

2000-05-17 Thread Keith Wansbrough

Moving this thread to the Haskell list...

Summary: the Haskell 98 Report claims

minimumBy :: (a -> a -> Ordering) -> [a] -> a

but Hugs and GHC implement

minimumBy :: (a -> a -> a) -> [a] -> a
minimumBy = foldl1

Carl writes:

> Sigbjorn Finne <[EMAIL PROTECTED]> writes:
> 
> > This a doc bug on the GHC (and Haskell report) side -
> > Hugs98's List.minimumBy type is the right one (and also
> > the type of the *defn* in the Lib Report.)
> 
> mimimumBy :: (a -> a -> Ordering) -> [a] -> a
> 
> seems much more useful than
> 
> mimimumBy = foldl1
> maximumBy = foldl1
> 
> Why do you say the latter is "right"?
> 
> Carl Witty
> [EMAIL PROTECTED]
> 

--KW 8-)
-- 
: Keith Wansbrough, MSc, BSc(Hons) (Auckland) ---:
: PhD Student, Computer Laboratory, University of Cambridge, UK. :
: Native of Antipodean Auckland, New Zealand: 174d47'E, 36d55'S. :
: http://www.cl.cam.ac.uk/users/kw217/ mailto:[EMAIL PROTECTED] :
::






Re: When is it safe to cheat?

2000-05-02 Thread Keith Wansbrough

Jan writes:

>   Just out of curiosity: Is your compiler clever enough
>   to do just what you said? Another words, would this
>   attached code fail to produce random nonce string (
>   the idea apparently criticized by Erik, but I do not care
>   where this came from. It works fine in Hugs-98,
>   February 2000 release). Humor me please :-)
> 
>   nonce :: Int -> String
>   nonce size
>   = take size (filter isAlpha
>(randoms $ mkStdGen (fst $ unsafePerformIO timeFrom1970)))
> 
> 
>   timeFrom1970 :: IO (Int, Int)
>   -- you can simulate it somehow, but
>   -- source code is available to all
>   -- at www.numeric-quest.com/haskell/bridge/

Off-topic, I know, but even if this worked as I think you intend, it would hardly be 
random and would certainly be unsuitable for use as a nonce.  Applying `mkStdGen' to 
the current time doesn't make it any more random!  You might as well use

nonce size = take size (cycle (map chr (chop_into_smaller_bits timeFrom1970)))

where chop_into_smaller_bits expresses timeFrom1970 in base 36 or something.

An attacker can certainly guess within a few seconds (= a few trials) when your 
connection was negotiated.

--KW 8-)
-- 
: Keith Wansbrough, MSc, BSc(Hons) (Auckland) ---:
: PhD Student, Computer Laboratory, University of Cambridge, UK. :
: Native of Antipodean Auckland, New Zealand: 174d47'E, 36d55'S. :
: http://www.cl.cam.ac.uk/users/kw217/ mailto:[EMAIL PROTECTED] :
::






Re: doubly linked list

2000-04-27 Thread Keith Wansbrough

Herewith the comp.lang.functional version of my article.  I may have 
tidied it up a little for the Wiki; if so, those changes are lost.  Let 
it hereby enter the Haskell List archive!




The following message is a courtesy copy of an article
that has been posted as well.

Matti Nykanen <[EMAIL PROTECTED]> writes:

> I  recently came  across an  algorithm that  constructs a  binary tree
> using single _but  not immediate_ assignments. By this  I mean that it
> attaches a newly  created node into the existing  tree, but leaves the
> children of  the totally unspecified.  Later the  algorithm returns to
> fill in the missing pieces.
> 
> I tried to  write it in Haskell,  but couldn't. If I create  a node, I
> have to give its children some  values to start with, and those cannot
> be changed later.  I don't think uniqueness types  (from, e.g., Clean)
> help here,  because the partially  constructed node is referred  to by
> two  places: its  parent in  the tree,  and the  "to do"  list  of the
> algorithm for the unfinished nodes.

The solution to this is a little trick called `tying the knot'.
Remember that Haskell is a lazy language.  A consequence of this is
that while you are building the node, you can set the children to the
final values straight away, even though you don't know them yet!  It
twists your brain a bit the first few times you do it, but it works
fine.

Here's an example (possibly topical!).  Say you want to build a
circular, doubly-linked list, given a standard Haskell list as input.
The back pointers are easy, but what about the forward ones?

data DList a = DLNode (DList a) a (DList a)

mkDList :: [a] -> DList a

mkDList [] = error "must have at least one element"
mkDList xs = let (first,last) = go last xs first
 in  first

  where go :: DList a -> [a] -> DList a -> (DList a, DList a)
go prev [] next = (next,prev)
go prev (x:xs) next = let this= DLNode prev x rest
  (rest,last) = go this xs next
  in  (this,last)

takeF :: Integer -> DList a -> [a]
takeF 0 _ = []
takeF (n+1) (DLNode _ x next) = x : (takeF n next)

takeR :: Show a => Integer -> DList a -> [a]
takeR 0 _ = []
takeR (n+1) (DLNode prev x _) = x : (takeR n prev)


(takeF and takeR are simply to let you look at the results of mkDList:
they take a specified number of elements, either forward or backward).

The trickery takes place in `go'.  `go' builds a segment of the list,
given a pointer to the node off to the left of the segment and off to
the right.  Look at the second case of `go'.  We build the first node
of the segment, using the given prev pointer for the left link, and
the node pointer we are *about* to compute in the next step for the
right link.

This goes on right the way through the segment.  But how do we manage
to create a *circular* list this way?  How can we know right at the
beginning what the pointer to the end of the list will be?

Take a look at mkDList.  Here, we simply take the (first,last)
pointers we get from `go', and *pass them back in* as the next and
prev pointers respectively, thus tying the knot.  This all works
because of lazy evaluation.

Hope this helps.

--KW 8-)
-- 
: Keith Wansbrough, MSc, BSc(Hons) (Auckland) :
: PhD Student, Computer Laboratory, University of Cambridge, England. :
:  (and recently of the University of Glasgow, Scotland. [><] )   :
: Native of Antipodean Auckland, New Zealand: 174d47' E, 36d55' S.:
: http://www.cl.cam.ac.uk/users/kw217/  mailto:[EMAIL PROTECTED] :
:-:



-- 
: Keith Wansbrough, MSc, BSc(Hons) (Auckland) ---:
: PhD Student, Computer Laboratory, University of Cambridge, UK. :
: Native of Antipodean Auckland, New Zealand: 174d47'E, 36d55'S. :
: http://www.cl.cam.ac.uk/users/kw217/ mailto:[EMAIL PROTECTED] :
::





Re: doubly linked list

2000-04-27 Thread Keith Wansbrough

Jan Brosius wrote:

> > > I wonder if it is possible to simulate a doubly linked list 
> > in Haskell.

I wrote:

> > No need to simulate it... it's perfectly possible.  See my 
> > Wiki article.

Chris Angus wrote:

> Where is this article.
> I looked on Haskell.org to no avail

Good point!  I have no idea... it looks like the Wiki has gone AWOL.  If someone would 
tell me where my article has gone, I'd be very grateful!

--KW 8-)
-- 
: Keith Wansbrough, MSc, BSc(Hons) (Auckland) ---:
: PhD Student, Computer Laboratory, University of Cambridge, UK. :
: Native of Antipodean Auckland, New Zealand: 174d47'E, 36d55'S. :
: http://www.cl.cam.ac.uk/users/kw217/ mailto:[EMAIL PROTECTED] :
::






Re: doubly linked list

2000-04-27 Thread Keith Wansbrough

> I wonder if it is possible to simulate a doubly linked list in Haskell.

No need to simulate it... it's perfectly possible.  See my Wiki article.

--KW 8-)
-- 
: Keith Wansbrough, MSc, BSc(Hons) (Auckland) ---:
: PhD Student, Computer Laboratory, University of Cambridge, UK. :
: Native of Antipodean Auckland, New Zealand: 174d47'E, 36d55'S. :
: http://www.cl.cam.ac.uk/users/kw217/ mailto:[EMAIL PROTECTED] :
::






Re: improving error messages

2000-03-31 Thread Keith Wansbrough

Malcom and Sergey write:

>   instance ShowType a => ShowType [a]
> where
> showsType xs = ('[':) . showsType x . (']':)   where ~(x:_) = xs

Perhaps 

   where [x] = [error "not used"] `asTypeOf` xs

gives the idea better.

--KW 8-)
-- 
: Keith Wansbrough, MSc, BSc(Hons) (Auckland) ---:
: PhD Student, Computer Laboratory, University of Cambridge, UK. :
: Native of Antipodean Auckland, New Zealand: 174d47'E, 36d55'S. :
: http://www.cl.cam.ac.uk/users/kw217/ mailto:[EMAIL PROTECTED] :
::






Re: ServiceShow for error messages

2000-03-31 Thread Keith Wansbrough

Sergey writes:

> Maybe, there exists another possibility to print the values in the
> error message like for 
>take (-1) xs,   y % 0 
> 
> The implementors declare the "internal" 
>  class ServiceShow where serviceShows :: ...
> invisible for the user, 
> make *everything* to be the instance of  ServiceShow,

The problem with this is that there is a performance penalty to be
paid for overloading a function in this way.  `take' is implemented as
a function of two arguments, as you would expect.  It is given a
number and a list; it has no idea what type the list has, nor does it
need to: it just picks elements off it and returns them.

But because it has no idea what type the list has, it has no idea how
to print the contents of that list.  Enter the class mechanism.  If we
have

class ServiceShow where serviceShows :: ...

mytake :: ServiceShow a => Int -> [a] -> [a]

then mytake is now implemented as a function of *three* arguments: the
number and the list, as before, but also a `dictionary' which looks
like this:

data ServiceShowDict a = ServiceShowDict { serviceShows :: ... }

mytake_implementation :: ServiceShowDict a -> Int -> [a] -> [a]

[it's no accident that class constraints `C a =>' are written the way
they are... they are really extra arguments `CDict a ->'.]

and wherever `serviceShows' is called, the code really looks like:

mytake_implementation d n (x:xs) = ...   (serviceShows d) x ...


In other words, if you implement the above proposal, every invocation
of take will be passed an extra argument, which will be only very
rarely used.  Perhaps this could be turned on with a debugging option,
but in general it would be a Very Bad Thing performance-wise.



HTH.

--KW 8-)





Partial v0.1 released

2000-03-22 Thread Keith Wansbrough

Announcing the release of a new library for Haskell:

Partial v0.1

The Partial library provides a partial order class. It also provides
routines for generating a Hasse diagram from a set and a partial
order.

Renderers are provided for the abstract Hasse diagram representation
into LaTeX (via Xy-pic) and into dot, the format for AT&T's Graphviz
tools. Since no horizontal sorting is done, the Xy-pic output is
rather poor at present; dot does a much better job with its layout
optimisation algorithm.

Available from:

http://www.cl.cam.ac.uk/users/kw217/libs/

I hope someone finds this useful!

--KW 8-)




Re: HaskellDoc?

2000-03-22 Thread Keith Wansbrough

There seems to be some agreement at least that a clean and unintrusive
syntax like POD or the ISE Eiffel stuff is preferable to something as
noisy as XML; it certainly seems to me that it would be much more
rapidly adopted.  Regarding such a system's power,

Jan Skibinski writes:

>   How come ISE Eiffel tools can handle all of this so
>   nicely from a clean ascii, readable source code? As far

[.. description of lots of neat things it generates automatically
from minimal additional comment conventions elided ..]

>   The only help a programmer gives to the Eiifel tools
>   is a bit of self-discipline. Location of comments.
>   Obligatory class comments. Preconditions and postconditions
>   that help to clarify the intended usage of the methods.
>   Licencing garbage at the bottom, not at the front of
>   the file. Well thought of comments: concise and clear.

Jan... could you write up a proposal for such a system for Haskell,
with 

  1. The exact requirements (the comment conventions the programmer
 must observe), and

  2. A list of what could be automatically generated by a system
 utilising these.

If we had a concrete proposal for something simple and usable, I'm
sure all of us here on the Haskell list would be happy to thrash out
the bugs and maybe go away and implement some of it.

Regards,

--KW 8-)






Type inference and binding groups

2000-01-19 Thread Keith Wansbrough

Type inference for Haskell (as described in Mark Jones' paper _Typing 
Haskell In Haskell_ and as performed by GHC) requires first splitting 
groups of let bindings into strongly-connected components.  It then 
assumes that all binders in such a component will be generalised over 
the same vector of type variables.

What is the justification for this assumption?  Is it always the case 
that in a strongly-connected component

let x1 = e1
x2 = e2
...
xn = en
in
e

if xi has the type forall a b c . ti for some monotype ti then xj must 
have type forall a b c . tj for some monotype tj?  (modulo 
permutations, of course)

References to published discussions of this would be useful, too, 
although I suspect this is an area where folklore rules...

Thanks.

--KW 8-)


-- 
: Keith Wansbrough, MSc, BSc(Hons) (Auckland) ---:
: PhD Student, Computer Laboratory, University of Cambridge, UK. :
: Native of Antipodean Auckland, New Zealand: 174d47'E, 36d55'S. :
: http://www.cl.cam.ac.uk/users/kw217/ mailto:[EMAIL PROTECTED] :
::





Re: type of deleteBy

1999-12-06 Thread Keith Wansbrough

Sergey:

> Maybe.  
> I propose for  Haskell-2  to add to the library
> 
>   delBy :: (a -> Bool) -> [a] -> [a]
>   delBy _ [] = []
>   delBy p (a:as) = if  p a  then  as  else  a:(delBy p as) 

So what do you propose as the definition for

del :: (Eq a) => [a] -> [a]

?

Section 7.6 of the Library Report:

"By convention, overloaded functions have a non-overloaded counterpart whose name is 
suffixed with ``By''."

--KW 8-)
-- 
: Keith Wansbrough, MSc, BSc(Hons) (Auckland) ---:
: PhD Student, Computer Laboratory, University of Cambridge, UK. :
: Native of Antipodean Auckland, New Zealand: 174d47'E, 36d55'S. :
: http://www.cl.cam.ac.uk/users/kw217/ mailto:[EMAIL PROTECTED] :
::





Re: Help with lists?

1999-10-20 Thread Keith Wansbrough

> You can also define a lifting function, that "lifts" functions on lists
> to your datatype.
> 
> liftSS :: ([Int] -> a) -> SS -> a
> liftSS f (SS xs) =3D f xs
> 
> and so write=20
> liftSS (take 5) (SS [1..100])
> for instance.
> 
> but this only works for functions with one list argument.

You probably want

lift0SS :: [Int] -> SS
lift0SS xs = SS xs

lift1SS :: ([Int] -> [Int]) -> SS -> SS
lift1SS f (SS xs) = SS (f xs)

lift2SS :: ([Int] -> [Int] -> [Int]) -> SS -> SS -> SS
lift2SS f (SS xs) (SS ys) = SS (f xs ys)

etc.

--KW 8-)
-- 
: Keith Wansbrough, MSc, BSc(Hons) (Auckland) :
: PhD Student, Computer Laboratory, University of Cambridge, England. :
:  (and recently of the University of Glasgow, Scotland. [><] )   :
: Native of Antipodean Auckland, New Zealand: 174d47' E, 36d55' S.:
: http://www.cl.cam.ac.uk/users/kw217/  mailto:[EMAIL PROTECTED] :
:-:





Re: Question on graphics

1999-10-12 Thread Keith Wansbrough

> > "Ronald" == Ronald J Legere <[EMAIL PROTECTED]> writes:
> 
> > I am wondering however if there is anykind of small package
> > to enable me to make simple plots (of functions for example)..
> > This is for windows (98) machine, so I cant use Gif Writer, which
> > seems sort of how to do it on unix machines
> 
> I don't know.  If there isn't I think there is a postscript driver
> of some kind described in The functional approach to programming by
> Cousineau and Mauny CUP 98.  (In Caml, but maybe it is cribbable.)

In a similar vein, although I haven't tried it, there's fun->pdf,
which writes Acrobat PDF files (compressed Postscript).  It's on the
Haskell libraries page, under "Various".

--KW 8-)







Re: Haskell mailing list

1999-10-11 Thread Keith Wansbrough

Ralf Muschall writes:
> [EMAIL PROTECTED] wrote:
> >  > set up comp.lang.haskell?
> > I agree with the above.
> 
> This is IMHO the best solution for a lot of reasons:

I disagree.  One major reason is the spam problem: a post to a
newsgroup essentially guarantees putting your name on a spam mailing
list, and receiving large quantities of Make Money Fast postings.

> 2. The decision problem (high volume list without the important
>people or having to hesitate before every article) goes away.

Many "important people" have a policy of no longer reading Usenet.

> 3. There is no human work needed to maintain a group once it exists.

This is just as true for a mailing list as for a newsgroup.

Also, news is not distributed everywhere, and even if news is
available there's no guarantee everyone will be able to convince their
sysadmin to accept the new group c.l.h.  Email is surely available
everywhere.

> Technical question: Are there people *writing* to this list without
> being subscribed? I very often see other people answering with
> header lines like
> "To: [EMAIL PROTECTED], [EMAIL PROTECTED]"
> The first of these addresses would be redundant if there were no such
> participants.

It's polite to cc: the author.  This ensures they get the message
first (before everyone else), and that it ends up in their inbox
rather than just in amongst 345 other messages in their Haskell
folder[1].  It's also easier in most mail clients to just click "reply
all"; "reply to author" doesn't send the message to the list also.

> Ralf

HTH.

--KW 8-)

[1] Actual count in my folder after two weeks away (!!).






Re: Wishlist: MixFix syntax

1999-10-11 Thread Keith Wansbrough

> This is a repost of an earlier post from before there was an explicit
> wishlist so it might make it onto the wishlist.
> 
> The idea was inspired by OBJs syntax. Something similar is also
> available in Isabelle.
> 
> I always liked the possibility to declare infix operators, may we
> extend this to mixfix? E.g.

Please see my note _Macros and Preprocessing in Haskell_, which makes a 
proposal for just this feature.

http://www.cl.cam.ac.uk/users/kw217/research/papers.html

Enjoy!

--KW 8-)

-- 
: Keith Wansbrough, MSc, BSc(Hons) (Auckland) :
: PhD Student, Computer Laboratory, University of Cambridge, England. :
:  (and recently of the University of Glasgow, Scotland. [><] )   :
: Native of Antipodean Auckland, New Zealand: 174d47' E, 36d55' S.:
: http://www.cl.cam.ac.uk/users/kw217/  mailto:[EMAIL PROTECTED] :
:-:








Re: tuple component functions

1999-09-16 Thread Keith Wansbrough

> As Haskell has the standard functions  fst, snd  to decompose  (a,b),
> maybe, it worths to provide also
>   tuple31, tuple31, tuple31,
>   ...
>   tuple51, tuple52, tuple53, tuple54, tuple55
> 
> for the tuples of  n = 3,4,5 ?

Yes!  I often want fst3, snd3, thd3, at least.

I suggest calling them "pi13" or "prj13" rather than "tuple31", though.

--KW 8-)
-- 
: Keith Wansbrough, MSc, BSc(Hons) (Auckland) :
: PhD Student, Computer Laboratory, University of Cambridge, England. :
:  (and recently of the University of Glasgow, Scotland. [><] )   :
: Native of Antipodean Auckland, New Zealand: 174d47' E, 36d55' S.:
: http://www.cl.cam.ac.uk/users/kw217/  mailto:[EMAIL PROTECTED] :
:-:







Re: Haskell Wish list: library documentation

1999-09-16 Thread Keith Wansbrough

Lars Lundgren writes:

> [EMAIL PROTECTED] writes:
>
> > the problem of doing stateful things and IO at the same time. Eventually I
> > realised it is not possible to nest monads,
> 
> But it is possible! You just need to use a monadtransformer:
> 
> class MonadTrans t where
>   lift ::  Monad m => m a -> (t m) a
> 
> 
> A requirement for this to work is that one of the monadic types can carry
> the other monad inside, so to say. t m.
> 
> This is no solution to the problem of mixing ST and IO though, because
> none of them can be instances of MonadTrans.

But it is a reasonable extension to expect.  If we ever have a prelude 
using monad transformers, an IO monad transformer should be provided.  
This is discussed in my 1997 MSc thesis[1], where I implemented such a 
beast in Gofer (Haskell did not have MPTCs at the time).  These days an 
implementation in Hugs or GHC should be straightforward.

It would be nice if generic state and environment monad transformers were provided in 
the prelude also, to avoid users having roll their own every time.

Not sure if this should be a wish, though; it's a bit more blue-sky than that.

--KW 8-)

[1]
@MastersThesis{
   Wansbrough97:Modular,
   author="Keith Wansbrough",
   title="A Modular Monadic Action Semantics",
   school="Department of Computer Science, University of Auckland",
   year="1997",
   month=feb,
   documentURL="http://www.cl.cam.ac.uk/users/kw217/research/msc/thesis/index.html",
}








  1   2   >