Re: [Haskell-cafe] Re: Top Level etc.

2005-01-20 Thread Keean Schupke
Ben Rudiak-Gould wrote:
   > len :: [a] -> Int
   >
   > len xs = let ?accum = 0 in len' xs
   >
   > len' :: forall a. (?accum :: Int) => [a] -> Int
   >
   > len' [] = ?accum
   > len' (x:xs) = let ?accum = ?accum + (1::Int) in len' xs
   *Main> :t len'
   len' :: forall a. (?accum :: Int) => [a] -> Int
   *Main> len "hello"
   5
I don't get this. The second answer (the one quoted above) must be wrong...
len' gets a value only in the empty '[]' case. The recursion is such 
that the value
of '?accum' is incremented on the return of the recursively called 
function, therefore
the value of '?accum' in the case '[]' is always zero! How on earth does 
this get
the answer five?

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


Re: [Haskell-cafe] Re: Hugsvs GHC (again)was: Re: Somerandomnewbiequestions

2005-01-20 Thread Keean Schupke
Why is disk a special case? I have never heard that all processes under 
linux
wait for a disk read... The kernel most certainly does not busy wait for 
disks
to respond, so the only alternative is that the process that needs to wait
(and only that process) is put to sleep. In which case a second thread would
be unaffected.

Linux does not busy wait in the Kernel! (don't forget the kernel does 
read-ahead,
so it could be that read really does return 'immediately' and without 
any delay
apart from at the end of file - In which case asynchronous IO just slows 
you down
with extra context switches).

   Keean.
Simon Marlow wrote:
On 19 January 2005 16:58, Keean Schupke wrote:
 

Simon Marlow wrote:
   

This is what GHC does, if I understand you correctly.  The thread
running select() does so in its own OS thread, while another OS
thread runs the Haskell code.  As long as you use -threaded, that
is.  Oh, and before GHC 6.4 it was done a different way - the
scheduler used to do the select() between running Haskell threads.
Cheers,
Simon
 

So this means even though the IO calls block, the other Haskell
threads (when run with -threaded) keep running?
   

Yes, unless the IO is to/from disk on a Unix system.
Cheers,
	Simon
 

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


Re: [Haskell-cafe]Re: Hugsvs GHC (again)was: Re: Somerandomnewbiequestions

2005-01-20 Thread Keean Schupke
Simon Marlow wrote:
We're getting a bit confused here.  Keean: the original question was
about whether a disk read will stop all other *Haskell* threads.  Not OS
threads.  The two are quite different beasts in GHC.
Cheers,
	Simon
 

But if GHC is running with the -threaded flag, then other Haskell-threads
can keep running using the second OS-thread, even though one Haskell-thread
(and its associated OS thread) is blocking - right?
In other words even with disk IO (as I said the kernel would not 
busy-wait - so there are
only two options, this OS-thread is put to sleep, or the data is already 
in a buffer and is
returned immediately), all the other Haskell-threads should not block 
(provided it is
running with -threaded)

Have I got that right?
   Keean.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Hugsvs GHC (again)was: Re: Somerandomnewbiequestions

2005-01-20 Thread Keean Schupke
Simon Marlow wrote:
On 20 January 2005 09:56, Keean Schupke wrote:
 

Why is disk a special case? I have never heard that all processes
under linux wait for a disk read...
   

You were talking about Haskell threads, not processes!  These are quite
different things.
 

But with -threaded GHC is using multiple processes (OS-threads)
to run the Haskell threads. If one OS thread handles IO, and the other
runs the Haskell-thread-scheduler, then Haskell-threads need never
wait for IO - apart form the actual thread doing the IO.
The reason that disk I/O is different is because select() treats it
differently, and select() is what GHC's runtime currently uses to
multiplex I/O.
 

Are you sure? Its not mentioned in the manual...
   Keean.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe]Re: Hugsvs GHC (again)was: Re: Somerandomnewbiequestions

2005-01-20 Thread Keean Schupke
Simon Marlow wrote:
Yes, except that you forgot that not all foreign calls can run
concurrently with Haskell code.  Only the "safe" ones can.
 

Okay, now I understand what is going on. Why is there extra overhead
for a 'safe' call?
   Keean.
//
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe]Re: Hugsvs GHC (again)was: Re: Somerandomnewbiequestions

2005-01-20 Thread Keean Schupke
But does it matter... If the select says the read will block you schedule
another haskell thread, if select says the read will not block, you do the
read. I don't see the problem... (Okay, I can see that if select lies, 
and the
read takes a long time you might miss the next scheduling timeslot - but
as far as I am aware select doesn't lie, and read will return immediately
if select says there is data ready)...

So I guess technically other Haskell threads cannot be scheduled during
the read, but as read returns immediately they don't need to...
It seems to me this is why calling read sequentially and with 'unsafe' is
faster than calling it with 'safe' and allowing haskell-thread-scheduling to
occur during the read syscall.
   Is that about right?
   Keean.
Simon Marlow wrote:
A safe call must 

 - save its state on the Haskell stack
 - save its thread state object on a queue, so GC can find it
 - tidy up the stack so GC can take place
 - release the RTS lock
 - possibly start a new OS thread if the pool is empty
of these, releasing the RTS lock is probably the most expensive.  Also,
if another OS thread gets scheduled before the call returns, we have an
expensive context switch on return.
In contrast, an unsafe call is just an inline C call.
Cheers,
	Simon
 

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


[Haskell-cafe] Re: I/O interface

2005-01-20 Thread Keean Schupke
Andre Pang wrote:
Just because you can encode the OO idioms in Haskell doesn't mean it's 
particularly straightforward to use them.  As your example shows, 
getting the syntax right for these OOish constructs isn't easy (not to 
mention verbose), and even so, the type errors you face when you get 
things wrong are, well, long :).
This is true enough... but it really isn't as dificault as it looks. 
Once you get used to
the style it is really quite easy - and notice how you don't need class 
definitions, or
types for the objects - it is all derived by GHC. This is an advance 
over current OO
languages.

I guess my point is that in theory, Haskell can support OO right now.  
In practice, it's something that isn't very tasty.
I find it no harder than writing with monads for example... certainly 
there are some
tricky things going on in both... but that doesn't stop people using 
monads for IO,
state etc.

Syntactic sugar over the top for instance and implementation definitions 
is something
we are working on (using template-haskell) - so that end of things can 
certainly be
made neater for the user.

The big problem I guess is error messages - and that would require some user
defined way of throwing compile time errors.
   Keean.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: I/O interface

2005-01-20 Thread Keean Schupke
Andre Pang wrote:
The syntactic sugar is the killer.  (Using monads is really no fun if 
you don't have do notation, for example.  Doable: yes.  Pretty: 
definitely not!)  Even if you use Template Haskell to try to implement 
the syntactic sugar, you're very limited by the splice $(...) notation 
at the call site.  I've always argued that Haskell really should have 
a full-blown macro system: it would really help with Haskell and 
EDSLs, and of course for integrating these kinds of libraries.  TH is 
90% of the way there, and with a bit more thought, those pesky splices 
could just magically disappear ... ;)

Its not that bad... the trick I am using is lifting existing haskell 
syntax, so an interface definition looks like:

   $(interface [d| data MyInterface = MyInterface {
 method1 :: ...,
 method2 :: ...,
 method3 :: ...} |])
So we define a normal haskell98 record, and the TH lifts it to an 
interface definition
using extensible records. An implementation looks would possibly look like:

   $(implementation [MyInterface] [d|
   method1 = ...
   method2 = ...
   method3 = ... |])
Yes, also agreed.  I did some similar Haskell<->OO integration work, 
and the type errors which appeared when something went wrong are quite 
awesome.  User-defined compile-time errors would be fantastic, but 
that would require quite a lot of effort.
We can do something better than what we have at the moment, for a start 
TH can generate user defined
compile time errors - but we don't want to have to implement our own 
typechecking, so we can supplement
this with a class with no instance and empty types:

   class Fail a
   data Some_user_defined_error
   instance Fail Some_user_defined_error => Test ...
So the compiler will report an undefined instance in Fail for your error 
type, but you can at least get some
readable text, which is better than nothing.

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


Re: [Haskell-cafe]Re: Hugsvs GHC (again)was: Re: Somerandomnewbiequestions

2005-01-20 Thread Keean Schupke
Keith Wansbrough wrote:
read. I don't see the problem... (Okay, I can see that if select lies, 
and the
read takes a long time you might miss the next scheduling timeslot - but
as far as I am aware select doesn't lie, and read will return immediately
if select says there is data ready)...
   

select() _does_ lie for "ordinary files", e.g., disk files.  It
assumes the data is immediately readable, even if it hasn't pulled it
off disk yet.  If the "ordinary" file actually resides on an NFS
volume, or CD, or something else slow, then you have a problem.
--KW 8-)
 

But the kernel does read-ahead so this data should just be a buffer copy.
   Keean.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Hugsvs GHC (again)was: Re: Somerandomnewbiequestions

2005-01-21 Thread Keean Schupke
Glynn Clements wrote:
The central issue is that the Unix API doesn't distinguish between
cases 1 and 2 when it comes to non-blocking I/O, asynchronous I/O,
select/poll etc. [OTOH, NT overlapped I/O and certain Unix extensions
do distinguish these cases, i.e. data is only "available" when it's in
physical RAM.]
 

This is in direct contradiction to  the documentation for select. Select
specifically says it returns if a handle in the read list would _not_ block
on a read call.
   Keean.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Hugsvs GHC (again)was: Re: Somerandomnewbiequestions

2005-01-21 Thread Keean Schupke
Ben Rudiak-Gould wrote:
If you're reading from a random-access file, there's no way it can 
tell you when the file data is buffered, because it doesn't know which 
part of the file you plan to read. The OS may try to guess for 
readahead purposes, but select()'s behavior can't depend on that guess.

But surely it does! read only reads the next block... to skip randomly 
you must seek... therefore
the following sequence does this:

  seek
  select
  read
The select should block until one disk block from the file is in memory, 
read is defined
such that it will return if some data is ready even if it is not as much 
as you requested.
So in this case if you ask for a complete file, you may just get one 
block... or more.

In other words the API restricts reads to the 'next' block - so seek 
knows which block
needs to be read into memory...

I can see no reason why is couldn't work like this even if some unixes 
might not.

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


Re: [Haskell-cafe] Re: Hugsvs GHC (again)was: Re: Somerandomnewbiequestions

2005-01-21 Thread Keean Schupke
Udo Stenzel wrote:
The Glibc documentation says, "select determines if there is data available 
(more precisely, if a call to read(2) will not block)."  I think, this is reasonably
precise.  The OS does know, where you are going to read (at the file pointer)
and if you seek() or pread() instead, well, that is no call to read(2) and may
change everything.

Thus the question is, does select() reliably tell if read() would block or does it
check for something else?  Is the documentation wrong (on some platforms)?
 

Having read around I have found that select does return readable for all
file IO on a block device...
I wonder if ghc could use non-blocking mode (files opened with the 
O_NONBLOCK)
flag? In which case you just do the read, and it returns immediately 
with the current
contents of the buffer (up to the size in the read argument)... The 
sheduler could
allow one chance at reading, then give the other haskell-threads a go 
whilst more
data comes in.

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


Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-22 Thread Keean Schupke
Ashley Yakeley wrote:
In article <[EMAIL PROTECTED]>,
"S. Alexander Jacobson" <[EMAIL PROTECTED]> wrote:
 

I assume there is a standard name for this 
class/function:

  instance Foo [] where
foo [] = mzero
foo (x:_) = return x
  instance Foo (Maybe x) where
foo Nothing = mzero
foo Just x = return x
   

Surely they are incomplete monad definitions (has a return but no bind)...
I don't believe so. I had to write my own classes to do this sort of 
thing.

This is also a good opporunity to point out an ambiguity in the standard 
MonadPlus class. All instances satisfy these:

 mplus mzero a = a
 mplus a mzero = a
But only some instances (such as []) satisfy this:
 (mplus a b) >>= c = mplus (a >>= c) (b >>= c)
Other instances (IO, Maybe) satisfy this:
 mplus (return a) b = return a
I think mplus should be separated into two functions. This code shows 
the difference a bit more clearly:

 do
   b <- mplus (return True) (return False)
   if b then mzero else return ()
For the first kind this is the same as "return ()", for the second kind 
it's the same as "mzero".
 

But isnt the point of Monad plus, that to have a 'zero' implies failure 
(a normal
monad cannot fail) - and failure implies choice (a `mplus` b) is a if a 
succeeds or
b if a fails and b succeeds,or mzero if both fail. if you look at your 
first identity:

   mplus mzero a = a
   mplus a mzero = a
This fits the above description, but I don't see how the following can 
be true:

   (mplus a b) >>= c = mplus (a >>= c) (b >>= c)
The LHS says (if a fails run b)  then run c.
The RHS says if (a then c) fails  run (b then c)
Finally,
mplus (return a) b = return a
Is obvious because "return a" is not  "mzero", so it is true for all 
Monads that can fail. 

Or have I missed the point?
   Keean.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-22 Thread Keean Schupke
Ashley Yakeley wrote:
In article <[EMAIL PROTECTED]>,
Keean Schupke <[EMAIL PROTECTED]> wrote:
 

This fits the above description, but I don't see how the following can 
be true:

   (mplus a b) >>= c = mplus (a >>= c) (b >>= c)
   

Try it (and my test code) with [], which is an instance of MonadPlus. 
mplus is defined as (++) for [].

 

but what if (a >>= c) causes c to fail, and (b >>= c) lets c succeed. In 
this
case the LHS will fail, whereas the RHS will succeed I think?

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


Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-22 Thread Keean Schupke
Daniel Fischer wrote:
That's probably a misunderstanding due to the notation, in the [] 
monad, it's

just
concat (map c (a ++ b)) = concat (map c a) ++ concat (Map c b),
which is easily seen to be true (if applying c to an element of a causes an 
error, neither side will go past that).

Daniel
 

So do we consider [] to be fail?, Monad.hs defines:
instance MonadPlus [] where
  mzero = []
  mplus = (++)
What would happen if this was the definition?
instance MonadPlus [] where
  mzero = []
  mplus a b
  | a == [] = b
  | otherwise = a
   Keean.

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


Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-23 Thread Keean Schupke
Jorge Adriano Aires wrote:
On the list monad, I think of the mplus operation as the "union" two 
non-deterministic states. Mzero is the state that works as the identity 
(which is when you have no possible state at all). 
 

Okay... thats a definition of a monoid.
What would happen if this was the definition?
instance MonadPlus [] where
  mzero = []
  mplus a b
  | a == [] = b
  | otherwise = a
   

Isn't the above a monoid as well?
   a `mplus` [] = a
   [] `mplus` b = b
Still looks like an identity to me
Is there only on correct definition of a monad/monoid on lists - or does 
anything that satisfies the monad laws count? I got the impression you 
could define anthing you liked for mzero and mplus - providing the laws 
are upheld?

Then, I'd say you're not thinking of monadic sums, but of catching errors, and 
the appropriate place for that is the class MonadError. 
 

I am thinking about how some monads are summed - like Maybe and
the Parser monad.
It seems there are two possibilities - either the definitions of MonadPlus
for Maybe and Parser monads are in Error, or there can be two different
acceptable definitions of MonadPlus on the List?
   Keean
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-23 Thread Keean Schupke
Aaron Denney wrote:
You can, but the "other one" turns it into a copy of the Maybe Monad, so
the current one is more useful.
 

So what does this mean in terms of Ashley's question:
But only some instances (such as []) satisfy this:
(mplus a b) >>= c = mplus (a >>= c) (b >>= c)
Other instances (IO, Maybe) satisfy this:
mplus (return a) b = return a
Does it mean that both fall within the acceptable definition of the monad laws
for MonadPlus?
  1. |mzero >>= f == mzero|
  2. |m >>= (\x -> mzero) == mzero|
  3. |mzero `mplus` m == m|
  4. |m `mplus` mzero == m|
So I guess I must have missed the point because the distinction between say a monad on
[] and Maybe for example seems to me to be irrelevant to MonadPlus. The distinction comes
down to mplus being the same as skipError for Maybe and different for []. 

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


Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-23 Thread Keean Schupke
Ashley Yakeley wrote:
I think it would be helpful if all these classes came with their laws
prominently attached in their Haddock documentation or wherever. The 
trouble with MonadPlus is that the precise set of associated laws is 
either unspecified or not the most useful (I assume there's a paper on 
the class somewhere). I think everyone can agree on  these:

 mplus mzero a = a
 mplus a mzero = a
 mplus (mplus a b) c = mplus a (mplus b c)
 

I think it would be even better if the classes came with assertions
that 'enforced the laws'... I think this requires dependant types
though.
 mzero >>= a = mzero
But what about this?
 a >> mzero = mzero
 

Well it was in the list I saw... I we consider the familar arithmetic 
product
a * b * 0 -- it is clear that an mzero anywhere in a sequence should result
in mzero:

a >> b >> mzero >> c >> d = mzero
But that says nothing about the co-product... where mzero should be the
identity IE:
a `mplus` mzero = a
mzero `mplus` a = a
But I am not sure there are any requirements on commutivity or associativity
on the co-product operation?
It's satisfied by [] and Maybe, but not IO (for instance, when a is 
'putStrLn "Hello"'), but IO has been declared an instance of MonadPlus. 
And then there are the two I gave:
 

 (mplus a b) >>= c = mplus (a >>= c) (b >>= c)
 

This was not on the list I saw - guess it could either be an omission,
or it has nothing to do with "MonadPlus" ... monads with identity and
co-product?
...which is satisfied by [], but not Maybe or IO.
 mplus (return a) b = return a
...which is satisfied by Maybe and IO, but not [], although your 
alternative declaration would make [] satisfy this and not the previous 
one.
 

But one could make up any arbitrary law that is satisfied by some
definition of a Monad and not others. Presumably there has to be
some sound category-theoretic reason for including the law?
   Keean
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: File path programme

2005-01-24 Thread Keean Schupke
Marcin 'Qrczak' Kowalczyk wrote:
These rules agree on "foo", "foo." and "foo.tar.gz", yet disagree on
"foo.bar."; I don't know which is more natural.
 

Filename extensions come from DOS 8.3 format. In these kind of
names only one '.' is allowed. Unix does not have filename extensions,
as '.' is just a normal filename character (with the exception of
'.', '..', and filenames starting with a '.' which are hidden files).
As far as I know unix utilities like gzip look for specific extensions 
like '.gz',
so it would make more sense on a unix platform to just look for a filename
ending '.gz'... this applies recursively so:

fred.tar.gz
Is a tarred gzip file, so first ending is '.gz' the next is '.tar'...
So as far as unix is concerned:
"foo.bar." is just as it is... as would any other combination unless the 
extension
matches that specifically used by your application...

So the most sensible approach would be to have a list of known 
extensions which can be
recursively applied to the filenames, and leave any other filenames alone.

[".gz",".tar",".zip"] ...
In other words just splitting on a '.' seems the wrong operation. 
(Imagine gziping a file
called "a..." you get "agz", in other words simply an appended ".gz")

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


Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-24 Thread Keean Schupke
Ashley Yakeley wrote:
I disagree. Clearly (putStrLn "Hello" >> mzero) is not the same as mzero.
 

Yes it is, side effects are quite clearly not counted. The value
of (putStrLn "Hello" >> mzero") is mzero.
In reference to the idea of splitting MonadPlus, what category
would you be operating in, if you have a zero but no co-product
operation?
   Keean.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-24 Thread Keean Schupke
Just thinking about this, a monad is a Functor plus two 
natural-tranformations, Unit and Join. Is there an equivalent definition 
for MonadPlus... I am not sure I understand where MonadPlus comes from? 
Is it just a Functor and two different definitions of Unit and Join 
(from those chosen to be in the class Monad?)

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


Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-24 Thread Keean Schupke
Ashley Yakeley wrote:
I don't believe this represents a good understanding of IO actions as 
Haskell values. For instance, 'return ()' and 'putStrLn "Hello"' are the 
same type, but are clearly different actions and so are usually 
considered to be different values. That the latter prints out text might 
be better considered not so much a "side effect" as the actual action 
itself.

You've introduced the concept of "the value of" an IO action, apparently 
as something separated from "side effects". I don't believe you can 
properly define this. For instance, what is the "value" of getChar such 
that it doesn't involve "side effects"?

 

Right, but we are dealing with the type system here. Remember Haskell
monoids are functors on types, not on values ... (ie the base objects the
'category theory' is applied to are the types not the values)...
Therefore we only consider the types when considering Monads.
As such if you wished to consider the examples you gave distinct, the
type system would need to distinguish side effects... this can be
done with a linear-aliasing type system, but not Haskell's as far as I 
know...
Maybe you could write such types:

   {putStrLn "Hello"; mzero} :: IO (PutStrLn "Hello" => ()) ???
But if we look at the type of the Functor:
   fmap :: (a -> b) -> m a -> m b
Where is the IO action?
   Keean.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-24 Thread Keean Schupke
Ashley Yakeley wrote:

If you remember your category theory, you'll recall that two morphisms 
are not necessarily the same just because they're between the same two 
objects. For instance, the objects may be sets, and the morphisms may be 
functions between sets: morphisms from A to B are the same only if they 
map each element in A to the same element in B.
 

Yes, but I though the 'objects' in this case are endofunctors from a 
type to itself... the the morphisms operate on these endofunctors, the 
morphisms are unit and join such that joining 'unit' to the 
endofuntor retults in the endofunctor.

But I think that as the endofunctor is from the type to itself, the 
value does not
come into it.

   A -> A `join` unit  => A -> A
   Keean.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-24 Thread Keean Schupke
Jules Bean wrote:
I've lost track of what you mean by 'this case' and indeed of what you 
mean by 'join' (did you mean mplus? the word join is normally used for 
the operation of type m (m a) -> m a, which is not often used directly 
in haskell)

However, even addressing your point about endofunctors: for two 
endofunctors to be equal, they must be equal on all objects and all 
morphisms, which effectively means they must be pointwise equal on all 
values.

Jules
I think the endofunctors are defined on the types, not the values 
though. So the object of the category is the endofunctor (Type -> Type), 
and unit and join are the identity and binary associative operator on 
which a Monad is defined. return and bind are defined in terms of unit 
and join. So unit is the identity which when joined to the endofunctor 
(Type -> Type) results in the same endofunctor... Therefor:

   (Type -> Type) `join` unit => (Type -> Type)
Now as the type of the IO monad is "IO a" we end up with:
   (IO a -> IO a) `join` unit => (IO a -> IO a)
This is true irrespective of any side effects IO may have, as the type 
is the
same for the IO action no matter what side effects it generates.

At least thats how I understand it...
   Keean.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-25 Thread Keean Schupke
Daniel Fischer wrote:
I think, 1. should be acceptable to everybody, and 2. as a principle too, only 
the question of which effects are relevant needs to be answered. It's plain 
that not all measurable effects are relevant. My inclination to ignore the 
side-effects stemmed from the (irrational) desire to have IO's MonadPlus 
instance justified, now I'm prepared to say yes, side-effects such as output 
do count, so the instance MonadPlus IO is erroneous, but may be maintained 
for practical reasons.

 

I am sure monads in Haskell (and other functional languages like ML) are 
defined
on types not values. Therefore it only matters that the types are 
correct and that
the operator obeys the associative laws. I am reasonably sure the values 
whether
returned or side-effects are irrelevent.

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


Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-25 Thread Keean Schupke
I think I see, but if the objects are types, arn't the morphisms functions
on types not values?
   Keean.
Ashley Yakeley wrote:
In article <[EMAIL PROTECTED]>,
Keean Schupke <[EMAIL PROTECTED]> wrote:
 

I am sure monads in Haskell (and other functional languages like ML) are 
defined on types not values.
   

The objects of the category are types. The morphisms on the category are 
functions. Two functions are the same if they match each value to the 
same value. For the Functor laws and the Monad laws, the values 
certainly do matter: if they didn't, they wouldn't correspond to the 
category theory notions of functor and monad because the morphisms would 
be wrong.

 

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


Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-25 Thread Keean Schupke
Jules Bean wrote:
No. Well: they are functions 'on' types, but functions 'on' types map 
values to values.

Analogy: In the category of sets and functions, the objects are sets 
and the morphisms are functions. The functions --- from sets to sets 
--- take objects in one set to objects in another set.

Specifically:
A monad T is a (endo)functor T : * -> * where * is the category of 
types, together with a multiplication mu and a unit eta.
So, * is the category of Types, and functions on type (which map values 
to values), and T is
an endofunctor (mapping functions on type to functions on type).

How does this affect the IO monad though?
   m >>= (\a -> mzero) === mzero
If we consider the state monad, surely the above makes no comment on what
the final state should be, only the final value returned...
Or is MonadPlus not definable on State monads?
If it is then considering IO === ST RealWorld, would imply that the actions
of the IO monad are not important as long as the final value returned is
mzero?
   Keean.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-25 Thread Keean Schupke
Ashley Yakeley wrote:
Every morphism in any category has a "from" object and a "to" object: it 
is a morphism from object to object. In the "Haskell category", a 
function of type 'A -> B' is a morphism from object (type) A to object B.

But in category theory, just because two morphisms are both from object 
A to object B does not mean that they are the same morphism. And so it 
is for the Haskell category: two functions may both have type 'A -> B' 
without being the same function.
 

I guess I am trying to understand how the Monad laws are derived from 
category theory...
I can only find referneces to associativity being required.

Monads are defined on functors, so the associativity just requires the 
associativity of the
'product' operation on functors...

I guess I don't quite see how associativity of functors (of the category 
of functions on types) implies identity on values... surely just the 
identity on those functors is required?

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


Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-25 Thread Keean Schupke
Jules Bean wrote:
Well, mzero isn't a return value in the IO monad, it's an exception.  
But yes, I agree with you that the (plausible) laws I have seen for 
MonadPlus seem to say that mzero should ignore the actions. But this 
in practice is not how IO behaves.

Jules
I can see three possible solutions:
   1) IO is not an instance of MonadPlus (but may still be an instance 
of MonadError)
   2) Side effects are ignored (or state is ignored) and IO may be an 
instance of MonadPlus

   3) bind (>>=) is redefined for IO. As the IO Monad is a function 
which resturns a computation,
   bindIO can be changed such that (a >> mzero === mzero). In other 
words if the RHS is mzero, the
   LHS is not included in the final result (and its actions would not 
get executed), however this
   must be inconsistent if we consider:

  f = getChar >>= (\a -> if a == "F" then mzero else return a)
   In this case if the LHS returns "F" the LHS should not have been 
run... this contradicts itself, so
   this is a non option I guess.

Acutally looking at GHC CVS libraries, there is not a definition for 
MonadPlus on the state or IO
monads...

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


Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-25 Thread Keean Schupke
Jules Bean wrote:
It's in Control.Monad.Error. Not documented though.
Jules
Ahh, so it is:
instance MonadPlus IO where
   mzero   = ioError (userError "mzero")
   m `mplus` n = m `catch` \_ -> n
So, the author of this obviously subscribed to the view that 
side-effects are not
counted when considering function identity...

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


Re: [Haskell-cafe] Re: What are the MonadPlus laws?

2005-01-26 Thread Keean Schupke
David Menendez wrote:
Philip Wadler listed those as the laws he "would usually insist on" in a
1997 message[1].
   [1] 
He also mentions two other possible, but problematic, laws:
   m >>= \x -> mzero   == mzero
   m >>= \x -> k x `mplus` h x == m >>= k `mplus` m >>= h
The first doesn't hold when m is bottom. The second doesn't hold for
lists.
 

I would like to know what category MonadPlus represents... A Monad is a 
category
where the objects are functors and the operators are id and product both 
of which
are natural transformations... Presumably the 'laws' for a monad can be 
derived from this
statement.

I cannot find any reference to MonadPlus in category theory. At a guess 
I would say that
it was the same as a Monad except the operators are id and co-product 
(or sum)... That would mean the 'laws' would be exactly the same as a 
Monad, just with (0,+) instead of (1,*)...

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


Re: [Haskell-cafe] Re: Visual Programming Languages

2005-01-26 Thread Keean Schupke
Hmm, can't resist commenting on this one!
Bayley, Alistair wrote:
This was odd...
Some cherry-picked quotes from the manifesto:
 http://alarmingdevelopment.org/index.php?p=5
- Visual languages are not the solution: ... common idea is to replace AST
structures with some form of graphical diagram. ...
 

Agree, point and grunt is much slower than entering commands. Its like 
being stuck in a country where you don't speak the language - all you 
can do is point at things and grunt ('click') and hope they understand you.

- Programming is not Mathematics
 

Disagree strongly... Bad programming seems to have little to do with 
mathematics, good programming often has the elegance of a well thought 
out proof. Beauty in programming is like beauty in mathematics.

- Change is natural: There has been much effort expended to remove the
concept of mutable state from programming, to be replaced by immutable
values as in mathematics. This is entirely misguided. ... Monads are a
reductio ad absurdum.  [ Heresy! :-) ]
 

Change is natural, but that has nothing to do with mutable state.
Parallelism will make mutable state less attractive, as will
hardware/software co-design. Isolating changes within a verifiable
sandbox (like the ST/State monads) reduces errors due to unforseen
interactions.
- Control flow considered harmful:  ... The primary reason for this is to
permit side-effects to be ordered by the programmer. ... [ This appears to
contradict the criticism of monads. ]
 

Agree - control flow causes the possible paths (or corner cases) in the
program to increase exponentially. Program correctness verification becomes
much harder with more possible-paths.
   Keean.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] File path programme

2005-01-27 Thread Keean Schupke
Georg Martius wrote:
Hi,
I think Isaac's idea is pretty nice, to have an easy way to add 
documentation in a collaborative manner.
I have the following in mind:
A separate wiki which supports generating haddock documentation. 
Ideally one would see the haddock documentation as it is and would 
click to a function or type and change the comment for it. However, it 
would also be enough to see the complete source-code and change the 
comments there. The question is what happens if there is a parse 
error. Furthermore there must be someone who maintains it in the sense 
that changes are committed to cvs at some point and so on. 
Additionally, it seams to be complicated to keep it synchronised with 
"real" changes of the source code in the cvs.
Probably the most simple, but less "wiki" solution is the do it the 
traditional way. Just use cvs and a normal text editor and ask for a 
cvs account :-).
Or, you could set the website to check out the code from CVS and use 
tex2html (assuming the comments are put in literate programming style) 
to generate the page.

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


Re: [Haskell-cafe] File path programme

2005-01-27 Thread Keean Schupke
Ben Rudiak-Gould wrote:
I'm tentatively opposed to (B), since I think that the only 
interesting difference between Win32 and Posix paths is in the set of 
starting points you can name. (The path separator isn't very 
interesting.) But maybe it does make sense to have separate 
starting-point ADTs for each operating system. Then of course there's 
the issue that Win32 edge labels are Unicode, while Posix edge labels 
are [Word8]. Hmm.

Several assumptions here... We might want more platforms than 
windows/unix. The separator for these systems is different (\ for 
windows / for unix - who knows what other obscure systems may use).

It seems to me a type class would allow the user to add definitions for 
their platform (IE it is extensible)... datatypes tend to be hard to 
extend as you have to find every use in the code
and modify it.

For code to be portable it has to use a diffenernt path parser depending 
on the platform, but
the code must not be different... One way of doing this would be to use 
a class...

   data Windows
   data Unix
   type System = Unix
   class ParsePath a where
  parsePath' :: a -> String -> Path
   instance ParsePath Windows where
  parsePath' _ a = ...
   instance ParsePath Unix where
  parsePath' _ a = ...
If all paths can be expressed in a single type, it seems different path 
parsers and printers are required. All the other functions could operate 
on the standard datatype. This still leaves the
problem of determining what system you are compiling on... I guess I 
still don't see the problem with having:

   #ifdef Unix
  type System = Unix
   #endif
   #ifdef Windows
  type System = Windows
   #endif
In some library somewhere... Infact its the only way I can see of 
selecting the correct
instance at compile time... and using classes is the only way I can 
think of making the
system easily extensible (even if we use a single datatype for all paths)

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


Re: [Haskell-cafe] File path programme

2005-01-27 Thread Keean Schupke

I guess it's just that I'm more concerned with making possible what is
currently impossible (according to the library standards)--that is, using
FFI and IO on the same file--rather than just adding utility features that
application developers could have written themselves.  I suppose we don't
need a class for this, all we need is a couple of functions to convert
between FilePath and CString.
 

Except paths are different on different platforms... for example:
/a/b/../c/hello\ there/test
and:
A:\a\b\
notice how the backslash is used to 'escape' a space or meta-character on
unix, but is the path separator for windows. If you want to write portable
applications, then you dont want to hard code the platform type. So 
converting
from the datatype to a string is not simple:

   string = pathToString ...
one way of doing this is to have pathToString call a function to 
determine the
system type and construct the string accordingly. The problem here is 
that it is
not extensible by the user, the supported platforms are determined by 
the library.
By using a class we can let the user define translations for new 
platforms...

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


Re: [Haskell-cafe] File path programme

2005-01-27 Thread Keean Schupke
Jules Bean wrote:
only it isn't. That's a property of a shell, the underlying OS allows 
spaces in file names with no need for an escaping mechanism.
Okay, that was a mistake... but it does not change the point, that 
pathToString needs to work out what platform it
is on, and doing it without typeclasses makes it not extensible.

We need a way of allowing people to define new path printers (as members 
of a class)... whilst having the program
determine which platform it is on, and choosing the correct instance (at 
compile time).

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


<    1   2   3