[Haskell-cafe] Re: Why Either = Left | Right instead of something like Result = Success | Failure

2010-06-01 Thread Aaron Denney
On 2010-05-27, aditya siram aditya.si...@gmail.com wrote:
 Monstro
 I'm going to call it that from now on. Stay out of the IO Monstro.

Monstro is Show (think demonstrate), not Monad.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: Curl UTF8

2010-04-26 Thread Aaron Denney
On 2010-04-23, Khudyakov Alexey alexey.sklad...@gmail.com wrote:
 В сообщении от 23 апреля 2010 02:36:07 Rickard Karlsson написал:
 Hi,
 
 I'm trying to download a file in UTF-8 with libcurl(1.3.5) and GHC 6.12:
 import Network.Curl
 
 u = http://www.cl.cam.ac.uk/~mgk25/ucs/examples/UTF-8-demo.txt;
 main = curlGetString u [] = putStrLn . snd
 
 Which doesn't print the characters correctly. If i read the file from local
 storage with getFile it is displayed properly.

 I think curl knows nothing about encoding and convert one byte to one Char 
 and 
 getFile uses new IO which uses system locale to choose encoding.

Then clearly curl should not return Strings, but byte arrays.  Of
course, curl can very well look at the headers which in this case do
specify UTF-8, and so perhaps it should do the translation itself.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: The instability of Haskell libraries

2010-04-26 Thread Aaron Denney
On 2010-04-24, John Goerzen jgoer...@complete.org wrote:
 It is a funny thing, because our fundamental libraries *have* had time 
 to settle down, in a sense.  In another sense, I must say that the 
 innovations we have seen recently have been sorely needed and are 
 unquestionably a good thing.

Overall, agreed.  It still makes it a pain to write to the current
standard, because it is moving.

 Unicode support in IO,

This was just a bugfix in GHC, made more painful by people writing
code dependent on the old behaviour.

 I guess this is the price of failing to avoid 
 success, to borrow Simon's phrase.  And again, not entirely bad.

I despair that a better Numeric hierarchy will never make it into
Haskell.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: A few ideas about FRP and arbitrary access in time

2010-03-09 Thread Aaron Denney
On 2010-03-08, Brandon S. Allbery KF8NH allb...@ece.cmu.edu wrote:
 There is a discrete time quantum.  But unless you're doing simulations  
 at the quantum level, you really don't want to go there (even ignoring  
 that one second of real time would take a really long time to  
 calculate on current hardware :); stick to macrocosmic physics, which  
 is statistically continuous.

That's ... contentious.  In both quantum mechanics and GR, time is
completely, flattly, continuous.  In certain extremely speculative
frameworks attempting to combine the regimes in which they are
applicable, that may not be the case.  But for accepted physics models,
time really is continous.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: Darcs or Perforce

2009-03-17 Thread Aaron Denney
On 2009-03-01, Erik de Castro Lopo mle...@mega-nerd.com wrote:
 Colin Paul Adams wrote:

 Any advantages over Perforce?

 I have used Bzr, CVS, Darcs, Git, Hg (Mercurial), Perforce and SVN.

 While Perforce is definitely better than CVS (anything is better than
 CVS), Perforce's client workspace concept is a bad idea for complex
 projects (it bit my group of 4 developers time after time).

There are far far more vile version control systems than CVS out there.
I'll say to beware of InterCapped product names, and leave it at that.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: package for algebraic structures

2009-02-24 Thread Aaron Denney
On 2009-02-19, Wolfgang Jeltsch g9ks1...@acme.softbase.org wrote:
 In addition, I wouldn’t include algebraic structures in a
 *numerical* prelude since the cool thing about them is that they are
 so abstract that they are not only about numbers.

But the thing is that to have the numerical classes support the proper
abstractions we want them to support, we need to define the algebraic
structures as well.  So the rework goes together...

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: Complex C99 type in Foreign

2009-02-16 Thread Aaron Denney
On 2009-02-14, Maurí­cio briqueabra...@yahoo.com wrote:
 The way you wrote CComplex a, is it possible to write

 foreign import ccall somename somename
:: CComplex CDouble - IO CComplex CDouble

Ah, no, I'm afraid not,  I misunderstood what you wanted.  You do indeed
need to go through CPtr (CComplex CDouble) with this scheme.  I think
having direct access at this level requires modifying the compiler.  The
FFI spec really does need to be updated to C99.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: Complex C99 type in Foreign

2009-02-13 Thread Aaron Denney
On 2009-02-03, Maurí­cio briqueabra...@yahoo.com wrote:
 Are there plans to include C99 'complex' type
 in Foreign, maybe as CFloatComplex, CDoubleComplex

 A separate library for new types to add to Foreign would be the easiest
 way forward. Just put the foreign-c99 package on Hackage?

 (...) I could actually have some
 arbitrary sized parameter as argument to a function
 or as a return value (and not its pointer), what
 did I saw wrong? I understand only Foreign.C.C*
 types or forall a. = Foreign.Ptr.Ptr a can be used
 like that.
 
 Oh, you mean you need to teach the compiler about unboxed complex types?
 

 I'm sorry, maybe I didn't understand you well. Are
 you saying that I could get this 'CComplex' type using
 unboxed types and other things already available?

Yes, because the C standard guarantees that a complex type is
stored as type[2].

I have been using the following, for binding to FFTW:

-
-- |
-- Module  : CComplex
-- Copyright   : (c) Aaron Denney 2004
-- License : BSD, 2-clause
-- 
-- Maintainer  : wnoise-hask...@ofb.net
-- Stability   : experimental
-- Portability : FFI
--
-- Aims to provide CComplex a parameterized type representing C99's
-- complex types and provide Storable instances for both it and
-- Haskell's Complex a types.  Note that C99 can parameterize over
-- integral types -- I think it's a mistake for Complex to not be
-- defined over all Real types.
--
-- For efficiency of common use, we use C's representation for easy
-- conversion.  So, we can be sloppy and use Complex CDouble instead of
-- CComplex CDouble.  In fact, for now CComplex is merely a type synonym
-- for Complex.
--
-- Will hopefully become obsolete when the FFI is revised to include the
-- complex types of C99.


module CComplex (CComplex) where
import Complex (Complex(..))
import Foreign.Ptr (castPtr)
import Foreign.Storable

-- C 99 specifies that a variable v of type complex t is stored as
-- t v [2], with v[0] the real part and v[1] the imaginary part.
-- elem off and byte off are defaulted, but perhaps shouldn't be,
-- for efficiency.

instance (RealFloat a, Storable a) = Storable (Complex a) where
sizeOf x= 2 * sizeOf (f x)
alignment x = alignment  (f x)
poke  x (a :+ b) = do let y = castPtr x
  poke y a
  pokeElemOff y 1 b
peek  x  = do let y = castPtr x
  a - peek y
  b - peekElemOff y 1
  return (a :+ b)

type CComplex a = Complex a

f :: Complex a - a
f _ = undefined 


HTH.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: Why 'round' does not just round numbers ?

2008-10-27 Thread Aaron Denney
On 2008-10-27, Bart Massey [EMAIL PROTECTED] wrote:
 Peter Gavin pgavin at gmail.com writes:
 The reason for doing it this way is that e.g. 2.5 is
 exactly between 2 and 3, and rounding *up* every time
 would cause an uneven bias toward 3.  To counteract that
 effect, rounding to the nearest even integer is used,
 which causes the half of the x.5 values to round up, and
 the other half to round down.

 Everyone keeps providing this rationale, but of course if
 you want half the values to round up and the other half
 down it does just as well to round positive values up and
 negative values down.

Except, of course, that it is quite common to work with just positive
numbers.  Working just with numbers near (even + 0.5) or (odd + 0.5)
is extremely rare.

 I have written floating point code that depends on
 consistent rounding in the past.  Being able to depend on
   round (1 + x) = 1 + round x
 is sometimes useful, but not possible for round-to-even.

Also not for round-up -- consider floating point values where the
precision changes and it rounds differently than you, or the point where
adjacent floating point values are now 2 apart.  You basically can't
depend on any nice behaviour once floating point enters the room.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: The container problem

2008-09-28 Thread Aaron Denney
On 2008-09-27, Andrew Coppin [EMAIL PROTECTED] wrote:
 Brandon S. Allbery KF8NH wrote:
 Oleg Kiselyov.  http://okmij.org/ftp/
 He's somewhat legendary in the Haskell community for his ability to 
 make Haskell do what people think it can't, and his tendency to 
 program at the type level instead of at the value level like most 
 people.  :)

 Ah - so the Prolog programs as type signatures thing is *his* fault?! ;-)

No, he merely takes advantage of it.  The fault is that constraint
satisfaction is natural match for type-inference, because it's
essentially what type-inference is.  Given that that's essentially what
Prolog is too, it shouldn't be surprising that you can express quite 
a lot with the type system.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: Float instance of 'read'

2008-09-17 Thread Aaron Denney
On 2008-09-17, Mauricio [EMAIL PROTECTED] wrote:
 
 Localized reading should be somewhere else, perhaps related to Locales.

 No! If we had that, string from a program would not
 be readable by some program running in other machine,
 or other locale. As, actually, you describe below.
 Show and Read are for programs reading, not for
 user reading. That's a work for Pango :)

UI can be done with text, and in any case includes text and there
should be some nice way to localize that.  The locale system is the
standard way to do that on Unix.  These strings are not meant for
program-to-program communication, whereas read and show are.

IMAO, it's bloody well stupid to use commas for either the decimal
separator or the thousands separator, as it has a well established
role in separating the items in a list that conflicts with this.
While a thousands separator can improve readability, it's not strictly
necessary.  OTOH, a decimal separator is necessary.  As the comma's not
usable, that leaves us with the decimal point, and no thousands separator.
Lo and behold, that's exactly what Haskell uses.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: Python's big challenges, Haskell's big advantages?

2008-09-17 Thread Aaron Denney
On 2008-09-17, Arnar Birgisson [EMAIL PROTECTED] wrote:
 Hi Manlio and others,

 On Wed, Sep 17, 2008 at 14:58, Manlio Perillo [EMAIL PROTECTED] wrote:
 http://www.heise-online.co.uk/open/Shuttleworth-Python-needs-to-focus-on-future--/news/111534

 cloud computing, transactional memory and future multicore processors


 Multicore support is already supported in Python, if you use
 multiprocessing, instead of multithreading.

 Well, I'm a huge Python fan myself, but multiprocessing is not really
 a solution as much as it is a workaround. Python as a language has no
 problem with multithreading and multicore support and has all
 primitives to do conventional shared-state parallelism. However, the
 most popular /implementation/ of Python sacrifies this for
 performance, it has nothing to do with the language itself.

Huh.  I see multi-threading as a workaround for expensive processes,
which can explicitly use shared memory when that makes sense.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: Python's big challenges, Haskell's big advantages?

2008-09-17 Thread Aaron Denney
On 2008-09-17, Jonathan Cast [EMAIL PROTECTED] wrote:
 On Wed, 2008-09-17 at 18:40 +, Aaron Denney wrote:
 On 2008-09-17, Arnar Birgisson [EMAIL PROTECTED] wrote:
  Hi Manlio and others,
 
  On Wed, Sep 17, 2008 at 14:58, Manlio Perillo [EMAIL PROTECTED] wrote:
  http://www.heise-online.co.uk/open/Shuttleworth-Python-needs-to-focus-on-future--/news/111534
 
  cloud computing, transactional memory and future multicore processors
 
 
  Multicore support is already supported in Python, if you use
  multiprocessing, instead of multithreading.
 
  Well, I'm a huge Python fan myself, but multiprocessing is not really
  a solution as much as it is a workaround. Python as a language has no
  problem with multithreading and multicore support and has all
  primitives to do conventional shared-state parallelism. However, the
  most popular /implementation/ of Python sacrifies this for
  performance, it has nothing to do with the language itself.
 
 Huh.  I see multi-threading as a workaround for expensive processes,
 which can explicitly use shared memory when that makes sense.

 That breaks down when you want 1000s of threads.

This really misses the point I was going for.  I don't want 1000s of
threads.  I don't want *any* threads.  Processes are nice because you
don't have other threads of execution stomping on your memory-space
(except when explicitly invited to by arranged shared-memory areas).
It's an easier model to control side-effects in.  If this is too
expensive, and threads in the same situation will work faster, than I
might reluctantly use them instead.

 I'm not aware of any program, on any system, that spawns a new process
 on each event it wants to handle concurrently;

inetd

 systems that don't use an existing user-space thread library (such as
 Concurrent Haskell or libthread [1]) emulate user-space threads by
 keeping a pool of processors and re-using them (e.g., IIUC Apache does
 this).

Your response seems to be yet another argument that processes are too
expensive to be used the same way as threads.  In my mind pooling vs
new-creation is only relevant to process vs thread in the performance
aspects.  The fact that people use thread-pools means that they think
that even thread-creation is too expensive.  The central aspect in my
mind is a default share-everything, or default share-nothing.  One is
much easier to reason about and encourages writing systems that have
less shared-memory contention.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: Python's big challenges, Haskell's big advantages?

2008-09-17 Thread Aaron Denney
On 2008-09-17, Jonathan Cast [EMAIL PROTECTED] wrote:
 In my mind pooling vs new-creation is only relevant to process vs
 thread in the performance aspects.

 Say what?  This discussion is entirely about performance --- does
 CPython actually have the ability to scale concurrent programs to
 multiple processors?  The only reason you would ever want to do that is
 for performance.

I entered the discussion as which model is a workaround for the other --
someone said processes were a workaround for the lack of good threading
in e.g. standard CPython.  I replied that most languages thread support can be
seen as a workaround for the poor performance of communicating processes.
(creation in particular is usually cited, but that cost can often be reduced
by process pools, context switching costs, alas, is harder.)

 Kernel threads /are/ expensive.  Which is why all the cool kids use
 user-space threads.

Often muxed on top of kernel threads, because user-threads can't use
multiple CPUs at once.

 The central aspect in my mind is a default share-everything, or
 default share-nothing.

 I really don't think you understand Concurrent Haskell, then.  (Or
 Concurrent ML, or stackless Python, or libthread, or any other CSP-based
 set-up).

Or Erlang, Occam, or heck, even jcsp.  Because I'm coming at this from a
slightly different perspective and place a different emphasis on things
you think I don't understand?  No, trust me, I do understand them[1],
and think CSP and actor models (the differences in nondeterminism is a
minor detail that doesn't much matter here) are extremely nice ways of
implementing parallel systems.

These are, in fact, process models.  They are implemented on top of thread 
models,
but that's a performance hack.  And while putting this model on top
restores much of the programming sanity, in languages with mutable
variables and references that can be passed, you still need a fair
bit of discipline to keep that sanity.  There, the implementation detail
of thread, rather than process allows and even encourages shortcuts that
violate the process model.  In languages that are immutable, taking
advantage of the shared memory space really can gain efficiency without
any noticeably downside.

[1] I used to work for a company designing and modeling CSP-based
hardware designs.  In my spare time I started writing a compiler from
our HDL to Concurrent Haskell, but abandoned it when I left for
grad school.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: about openTempFile

2008-09-17 Thread Aaron Denney
On 2008-09-17, Brandon S. Allbery KF8NH [EMAIL PROTECTED] wrote:
 On 2008 Sep 17, at 8:17, Manlio Perillo wrote:
 The Python tempfile module, as an example, implements a wrapper  
 around mkstemp function that does exactly this, and the code is  
 portable; on Windows it uses O_TEMPORARY_FILE flag, on POSIX systems  
 the file is unlink-ed as soon as it is created (but note that the  
 code is not signal safe - well, many functions in the Python  
 standard library are not signal safe).

 There are reasons why GHC library does not implement this?

 POSIX doesn't guaranteed that open-and-unlink works; HP-UX is a  
 POSIX platform on which it doesn't.

Huh.  SuS does indeed allow EBUSY for The file named by the path
argument cannot be unlinked because it is being used by the system or
another process and the implementation considers this an error.

Did HPUX's behavior change at some point?  This is a standard idiom,
and I don't remember having any trouble with it, but I haven't used
anything earlier than 9.  The manpages for 11 only document being a
mount point as cause for EBUSY.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: Python's big challenges, Haskell's big advantages?

2008-09-17 Thread Aaron Denney
On 2008-09-17, Arnar Birgisson [EMAIL PROTECTED] wrote:
 Hi Aaron,

 On Wed, Sep 17, 2008 at 23:20, Aaron Denney [EMAIL PROTECTED] wrote:
 I entered the discussion as which model is a workaround for the other
 -- someone said processes were a workaround for the lack of good
 threading in e.g. standard CPython.  I replied that most languages
 thread support can be seen as a workaround for the poor performance
 of communicating processes. (creation in particular is usually
 cited, but that cost can often be reduced by process pools, context
 switching costs, alas, is harder.)

 That someone was probably me, but this is not what I meant. I meant
 that the processing [1] Python module is a workaround for CPython's
 performance problems with threads.

Ah, on rereading that's much clearer.  Thank you for the clarification.

 The processes vs. threads depends on definitions. There seem to be two
 sets floating around here. One is that processes and threads are
 essentially the same, the only difference being that processes don't
 share memory but threads do. With this view it doesn't really matter
 if processes are implemented as proper OS processes or OS threads.
 Discussion based on this definition can be interesting and one model
 fits some problems better than the other and vice versa.

 The other one is the systems view of OS processes vs. OS threads.
 Discussion about the difference between these two is only mildly
 interesting imo, as I think most people agree on things here and they
 are well covered in textbooks that are old as dirt.

I think from the OS point of view, these two distinctions are nearly
equivalent.  There is only a difference when you start talking about
non-OS threads, such as those provided by various language runtimes.

 There, the implementation detail of thread, rather than process
 allows and even encourages shortcuts that violate the process model.

 Well, this is a viewpoint I don't totally agree with. Correct me if
 I'm not understanding you, but you seem to be making the point that
 OS processes are often preferred because with threads, you *can* get
 yourself in trouble by using shared memory.

That's exactly it.  Or rather, you can get in exactly as much trouble
with processes, but because accessing a variable in another memory space
is more cumbersome, you have to actually think when you do so.  Looking
at all uses of a = b to see what invariants might be broken is unfeasible.
Looking at all requests for updating a remote variable might be
manageable.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: Threads vs. processes [Was: Re: Re: Python's big challenges, Haskell's big advantages?]

2008-09-17 Thread Aaron Denney
On 2008-09-17, Jonathan Cast [EMAIL PROTECTED] wrote:
 On Wed, 2008-09-17 at 21:20 +, Aaron Denney wrote:
 On 2008-09-17, Jonathan Cast [EMAIL PROTECTED] wrote:
  In my mind pooling vs new-creation is only relevant to process vs
  thread in the performance aspects.
 
  Say what?  This discussion is entirely about performance --- does
  CPython actually have the ability to scale concurrent programs to
  multiple processors?  The only reason you would ever want to do that is
  for performance.
 
 I entered the discussion as which model is a workaround for the other --

 Well, I thought the discussion was about implementations, not models.  I
 also assumed remarks would be made in the context of the entire thread.
 I shall have to remember that in the future.

 someone said processes were a workaround for the lack of good threading
 in e.g. standard CPython.

 I replied that most languages thread support

 Using a definition of `thread' which, apparantly, excludes Concurrent
 Haskell.

Can't I exclude it based on most languages'.  CSP models are still the
minority.

 Different enough we're talking past each other.  The idea that the thing
 you make with forkIO doesn't count as a thread never crossed my mind,
 sorry.

I think it's fair to consider it a thread interface, because there's
still a huge amount of shared state.  Mostly immutable, but not
completely as you later point out, even discounting updates of
lazy-evaluation thunks.  It is a lot less pure CSP than Erlang and
Occam, which both call them processes (though I see thread being
used more and more these days for Erlang).  Then there's apparently a
tradition in mainstream languages of calling language-level parallelism
threads.  Of course most are thread models.

 and use completely different definitions for key terms and make
 statements which, substituting in the definitions I was using, are (as
 I hope you grant) non-sensical

Yes, I can see how my rants sounded bizarre, even though I think we're
mostly in agreement.

 Not any more.  I just think your definition of `thread' is unexpected in
 this context (without rather more elaboration).

 These are, in fact, process models.

 OK.  I think that perspective is rather unique, but OK.

Well, what's the P in CSP stand for?

 They are implemented on top of thread models,
 but that's a performance hack.

 Maybe.  It's done for performance, but I don't see why you call it a
 hack.  Does it sacrifice some important advantage I'm missing?  (Vs.
 kernel-scheduled threads).

Vs kernel threads, not much -- just parallelism on SMP systems, which is
often regained by muxing on top of kernel threads.

Vs kernel processes, yes, I think some is lost.  Privilege separation,
isolation in the event of crashes, larger memory spaces, the ability
to span multiple machines (necessary for true fault tolerance).  How
important are these vs raw speed?  Well, it depends on the domain
and problem.  Take postfix for instance -- different parts of postfix are
implemented in different processes, with different OS privileges.
Subverting one doesn't give you carte blanche with the others, as it
would if these were all threads in one process.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: Can you do everything without shared-memory concurrency?

2008-09-11 Thread Aaron Denney
On 2008-09-10, David Roundy [EMAIL PROTECTED] wrote:
 On Wed, Sep 10, 2008 at 03:30:50PM +0200, Jed Brown wrote:
 On Wed 2008-09-10 09:05, David Roundy wrote:
  I should point out, however, that in my experience MPI programming
  involves deadlocks and synchronization handling that are at least as
  nasty as any I've run into doing shared-memory threading.

 Absolutely, avoiding deadlock is the first priority (before error
 handling).  If you use the non-blocking interface, you have to be very
 conscious of whether a buffer is being used or the call has completed.
 Regardless, the API requires the programmer to maintain a very clear
 distinction between locally owned and remote memory.

 Even with the blocking interface, you had subtle bugs that I found
 pretty tricky to deal with.  e.g. the reduce functions in lam3 (or was
 it lam4) at one point didn't actually manage to result in the same
 values on all nodes (with differences caused by roundoff error), which
 led to rare deadlocks, when it so happened that two nodes disagreed as
 to when a loop was completed.  Perhaps someone made the mistake of
 assuming that addition was associative, or maybe it was something
 triggered by the non-IEEE floating point we were using.  But in any
 case, it was pretty nasty.  And it was precisely the kind of bug that
 won't show up except when you're doing something like MPI where you
 are pretty much forced to assume that the same (pure!) computation has
 the same effect on each node.

Ah, okay.  I think that's a real edge case, and probably not how most
use MPI.  I've used both threads and MPI; MPI, while cumbersome, never
gave me any hard-to-debug deadlock problems.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: 2 modules in one file

2008-09-05 Thread Aaron Denney
On 2008-08-30, Brandon S. Allbery KF8NH [EMAIL PROTECTED] wrote:
 On 2008 Aug 30, at 4:22, Aaron Denney wrote:
 On 2008-08-27, Henrik Nilsson [EMAIL PROTECTED] wrote:
 And there are also potential issues with not every legal module name
 being a legal file name across all possible file systems.

 I find this unconvincing.  Broken file systems need to be fixed.

 Language people trying to impose constraints on filesystems is the  
 tail wagging the dog.

I'd say it's just the opposite.  The purpose of a filesystem is to
hold user data, in ways convenient to the user, which means dictating
a usable interface.  Dictating the implementation would be closer to
tail wagging the dog, though even that's not quite the right metaphor --
it's just a layering violation.  The user is in this case GHC or other
compiler adopting the suggestion in the Hierarchical modules extension.
Just as non-hierarchical file systems have long been considered broken,
I think it's safe to now declare that one that doesn't support unicode
in some fashion, even if only a userland convention of using UTF-8, is
indeed less usable, and hence broken.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: Hackage - MacPorts?

2008-09-04 Thread Aaron Denney
On 2008-09-04, Don Stewart [EMAIL PROTECTED] wrote:
 The complication to support multiple implementations et al isn't done by
 any other language group (i.e. libs aren't bundled for multiple python
 impls, or different C compilers), so I don't see why we should waste
 time on that either. Pragmatic, I know.

It's indeed not done for C libraries, because that, unlike Haskell, has
a stable ABI, even between compilers.  Python is in a fairly similar
situation, with on-demand compilation and caching being cheap enough
that distributing source is good enough.  This of course requires a
small bit of care in making the source work with multiple revisions of
the standard C implementation.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: Research language vs. professional language

2008-09-01 Thread Aaron Denney
On 2008-09-01, Don Stewart [EMAIL PROTECTED] wrote:
 ryani.spam:
 On Sun, Aug 31, 2008 at 7:27 PM, Jonathan Cast
 [EMAIL PROTECTED] wrote:
  This concept of `day-to-day work' is a curious one.  Haskell is not a
  mature language, and probably shouldn't ever be one.
 
 I see where you are coming from here, but I think that train has
 already started and can't be stopped.

 Yeah, it's too late. Too many people have their pay checks riding on
 GHC, the Hackage library set (now up to 740 libraries and tools!), and
 the continued development of the language in general.

 If Haskell's not mature yet, then perhaps it has reached its early
 twenties, with an reliable heavy duty optimizing compiler, fast runtime,
 large library set, standard documentation, testing, debugging and
 packaging tools, and large community.

 And a community with a lot of energy.

 We're serious about this thing.

So, what fills its shoes as a great research language with great tools?

-- 
Aaron Denney
--

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


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

2008-08-30 Thread Aaron Denney
On 2008-08-28, Yitzchak Gale [EMAIL PROTECTED] wrote:
 However we work that out, right now we need a working
 idiom to get out of trouble when this situation comes up.
 What we have is a hack that is not guaranteed to work.
 We are abusing the NOINLINE pragma and assuming
 things about it that are not part of its intended use.
 We are lucky that it happens to work right now in GHC.

 So my proposal is that, right now, we make the simple
 temporary fix of adding an ONLYONCE pragma that does
 have the proper guaranteed sematics.

 In the meantime, we can keep tackling the awkward squad.

What keeps this a temporary fix.  Even now, industrial user demands
keep us from making radical changes to the languages and libraries.  If
we adopt a not entirely satisfactory solution, it's never going away.
If we keep the NOINLINE pragma hack, we can claim it was never supported
and do away with it.  If we don't have a real solution, perhaps in this
case we haven't worn the hair shirt long enough?

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: 2 modules in one file

2008-08-30 Thread Aaron Denney
On 2008-08-27, Henrik Nilsson [EMAIL PROTECTED] wrote:
 And there are also potential issues with not every legal module name
 being a legal file name across all possible file systems.

I find this unconvincing.  Broken file systems need to be fixed.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: Parsec and network data

2008-08-30 Thread Aaron Denney
On 2008-08-30, Johannes Waldmann [EMAIL PROTECTED] wrote:
 apfelmus wrote:

 Design your language in a way that the *parse* tree does not depend
 on import statements? I.e. Chasing imports is performed after you've
 got an abstract syntax tree.

 OK, that would work.

 This property does not hold for Haskell,
 because you need the fixities of the operators
 (so, another language design error :-)

Yes, but you can partially parse into a list, which later gets
completely parsed.  It's not like C with its textual inclusion, and
constructs changing what counts as a type.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: Cyclic Inclusions

2008-08-20 Thread Aaron Denney
On 2008-08-13, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote:
 If you only change the implementation of a module, not its interface,
 you don't need to recompile anything that imports it.  (At least, this
 is true at -O0, which if you care about fast recompilation because
 you're deep in development, you're probably doing.)

This is only true if the interface can be tracked separately from the
implementation.  Which, despite the flaws, C's header files can be
coaxed into doing.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: Is there anything manifestly stupid about this code?

2008-07-07 Thread Aaron Denney
On 2008-07-07, Luke Palmer [EMAIL PROTECTED] wrote:
 On Mon, Jul 7, 2008 at 2:21 PM, Michael Feathers
[EMAIL PROTECTED] wrote:
 BTW, I only noticed the Complex type late.  I looked at it and noticed that
 all I'd be using is the constructor and add.  Didn't seem worth the  change.

 You would also be using the multiply and magnitude functions!

Well, he should continue to use a custom magnitude squared function,
to save the square-rooting.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: [ANNOUNCE] git-darcs-import 0.1

2008-06-04 Thread Aaron Denney
On 2008-06-04, Peter Hercek [EMAIL PROTECTED] wrote:
 But what about this git rebasing option? How to do it more easily
   (than the solution I know and I described it later) in darcs?

 using git-rebase --onto master next topic to get from:
  o---o---o---o---o  master
   \
o---o---o---o---o  next
 \
  o---o---o  topic
 to:

  o---o---o---o---o  master
  |\
  | o'--o'--o'  topic
   \
o---o---o---o---o  next

apfelmus answered this.  I might expand on his reply.

 There is one thing that git rebase does easily (and correctly) that darcs
 doesn't do nicely: rewriting history by merging commits prior to the
 head.  I put prior in quotes, because darcs doesn't preserve history
 in the first place.  I don't find that a compelling use, as opposed to
 maintaing topic branches.

 I do not know what you mean here. Can you point me to some example?

Letting capitals be commits, and lowercase be trees at the point of
these commits.

Suppose your history is:

A - B - C - D
||||
abcd

And that B somehow doesn't make sense except with the additional changes
in C.  You don't want to deal with this, or have anyone see B.  All it
does is clutter up the history.  So you want to expunged it from the
history.

git rebase can rewrite this to

A -- C' - D'
| | |
a c d

Doing this in darcs would require unrecording B and C, and then
rerecording C'.  But, if D is in the repo, then it is likely that B and
C can't be commuted past it to be unrecorded.  (If they can, no
problem!)

Unrecording D (and possible E, F, G, etc.) lets you do this, but if you
then pull it back from another repo, it will depend on B and C, and pull
these in, which are now doppelgangers of C'.  Not having used darcs 2,
I'm not sure if that's still quite so fatal, but it remains bad news
AIUI.

The bottom line is that darcs is a tool for managing sets of always
existing patches. and ordering them lazily, as needed.  In particular,
no history generally exists, unless each patch depends on exactly one
previous.  It has a differential view of software development, in that
the changes, and not the sum at each point matter (though of course, the
current sum does matter.)

On the other hand, git is a tool for managing (and munging) histories
of development in many weird and wacky ways.  It has an integral
view of software development, the changes are lazily derived from the
saved state at each point, and are strictly ordered even when they're
independent.  It can, when needed, work with these changes to accomplish
fairly interesting history-altering tasks, but as soon as they're used
to construct a new history, they're discarded.  (Yes, git uses deltas,
but this is merely an optimization.)

The two models are dual to each other in many ways.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: [ANNOUNCE] git-darcs-import 0.1

2008-06-04 Thread Aaron Denney
On 2008-06-04, apfelmus [EMAIL PROTECTED] wrote:
 Peter Hercek wrote:
 But what about this git rebasing option? How to do it more easily
  (than the solution I know and I described it later) in darcs?
 
 using git-rebase --onto master next topic to get from:
 to:

 o---o---o---o---o  master
  \
   o---o---o---o---o  next
\
 o---o---o  topic
 
 o---o---o---o---o  master
 |\
 | o'--o'--o'  topic
  \
   o---o---o---o---o  next
 
 This is the reason why I mentioned reordering depending patches AB
  to BA (with manual conflict resolution) would be needed in darcs
  to support (I believe a better) alternative to git rebase.

 I don't understand (probably because I haven't use either dvcs).

 Either the changes in the  next-topic  path don't depend on the changes 
 in the  fork-next  path. Then, the patches commute and it's no problem 
 for darcs.

Right.  Then 

 o---o---o---o---o  master
  \
   o---o---o---o---o  next
\
 o---o---o  topic

is not a good model for what darcs has.  What it has is more like

 o---o---o---o---o  master
 |\
 | o---o---o---o---o  next
 \ |
  o---o---o+  topic

The patches in topic that are in next are indepent of the ones that
aren't in next, so it's another (virtual) line-of-development, that
darcs can lazily construct as needed.  These lines-of-development are
similar to branches of git that have been merged, but you also have
access to the unmerged versions until a patch comes in that depends on
the merger.

If I commit three new features that don't interact, a darcs repo will
essentially look like:

    topicA -
  / \
history --- topicB --+--
  \ /
    topicC -

Where the merger is virtual.  Darcs will implicitly linearize this to
any of 
  
history --- topicA --- topicB --- topicC ---
history --- topicA --- topicC --- topicB ---
history --- topicB --- topicA --- topicC ---
history --- topicB --- topicC --- topicA ---
history --- topicC --- topicA --- topicB ---
history --- topicC --- topicB --- topicA ---

/as needed/. git constructs one of these, based on how you did the
commits, and gives you ways to alter it to the others.

 Or the  next-topic  path relies on features from  next  that are not 
 present in  master . But then, you're screwed anyway

Yep.

 and should merge some parts from next into master so as to advance the
 point where master and next fork.

That's one solution.  Of course, darcs doesn't have semantic dependency,
but syntactic dependency.  (You can add extra dependencies to
model semantic dependencies, but you can't take away the syntactic
dependencies.)  Another solution, if there's syntactic,
but not semantic dependencies, is to manually use patch and diff to get
90% there, and then cleanup and record.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: [ANNOUNCE] git-darcs-import 0.1

2008-06-03 Thread Aaron Denney
On 2008-06-03, Peter Hercek [EMAIL PROTECTED] wrote:
 Loup Vaillant wrote:
 2008/6/3 Darrin Thompson [EMAIL PROTECTED]:
 --cut--
 What's the appeal of this? I personally love git, but I thought all
 the cool kids at this school used darcs and that was that.
 
 Disclaimer: I'm no expert, this is what I've heard. Anyone please
 confirm or deny the following?
 
 Basically, git is waaay faster than Darcs on a number of use cases.

 Other reason can be git rebase. Of course there is a question
   how good practice it is ... but it is being used.

Darcs patches are pretty much an implicit rebase.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: [ANNOUNCE] git-darcs-import 0.1

2008-06-03 Thread Aaron Denney
This is drifting off-topic, but...
On 2008-06-03, Peter Hercek [EMAIL PROTECTED] wrote:
 Aaron Denney wrote:
 On 2008-06-03, Peter Hercek [EMAIL PROTECTED] wrote:
 Loup Vaillant wrote:
 2008/6/3 Darrin Thompson [EMAIL PROTECTED]:
 --cut--
 What's the appeal of this? I personally love git, but I thought all
 the cool kids at this school used darcs and that was that.
 Disclaimer: I'm no expert, this is what I've heard. Anyone please
 confirm or deny the following?

 Basically, git is waaay faster than Darcs on a number of use cases.
 Other reason can be git rebase. Of course there is a question
   how good practice it is ... but it is being used.
 
 Darcs patches are pretty much an implicit rebase.

 You cannot push patch B if it depends on patch A without also
   pushing A. And darcs currently does not alow you to reorder
   B before A

True.  This is a *feature* not a bug.  You shouldn't be able to do this
automatically, because it can't be done right.  You need to do this sort
of thing manually.  If you don't, the heuristics used will bite you at
some point.  When they do commute, there is no problem.

 Git rebase works quite well even in cloned repositories.

Meh.  It can, if you're really really lucky.

 See: http://bugs.darcs.net/issue891
 Some discussin about it is also here:
 http://lists.osuosl.org/pipermail/darcs-users/2008-February/011564.html

 When the issue is fixed then darcs will be really patch based and
   will become the ultimate DSCM :-)

Rebasing is doable in git as a one-repository operation because each
repository has multiple branches.  As darcs has one repo per branch,
it fundamentally needs to be done in multiple repos.

There are naturally two repos, upstream, and your-feature-development.

your-feature-development has a patch A that you want to rebase.

What you should do is pull upstream into new-tracking, then pull patch A
from your-feature-development into new-tracking.

If it applies with no problem, great: mv your-feature-development
your-feature-development-old; new-tracking your-feature-development.
Of course, in this case, you could have just pulled into
your-feature-development.  If there weren't any other patches to save in
the old your-feature-development, you can delete it instead of moving
it.

When there is a conflict, then you need to handle it somehow.  Neither
git nor darcs can do it automatically.  You can just record the merge
conflict and your resolution.  This keeps repos that pulled from you
valid, but this won't give you the clean history that you presumably
want.  So you need to combine the merger and cleanup into a new patch
with the same log message, etc.  It's true that git does make *this*
process very nice.

There is one thing that git rebase does easily (and correctly) that darcs
doesn't do nicely: rewriting history by merging commits prior to the
head.  I put prior in quotes, because darcs doesn't preserve history
in the first place.  I don't find that a compelling use, as opposed to
maintaing topic branches.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: [ANN] bloomfilter 1.0 - Fast immutable and mutable Bloom filters

2008-05-31 Thread Aaron Denney
On 2008-05-30, Achim Schneider [EMAIL PROTECTED] wrote:
 Bryan O'Sullivan [EMAIL PROTECTED] wrote:

 A Bloom filter is a probabilistic data
 structure that provides a fast set membership querying capability.
 It does not give false negatives, but has a tunable false positive
 rate.  (A false positive arises when the filter claims that an
 element is present, but in fact it is not.)
 
 /me squints.

 Please tell me that this isn't reversible.

Tell me what you mean by reversible.  You can't, for instance,
extract the items in the set.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: Performance: MD5

2008-05-18 Thread Aaron Denney
On 2008-05-18, Andrew Coppin [EMAIL PROTECTED] wrote:
 (did you look at the C implementation?)
   

 I can't read C. (FWIW, I think I did briefly stare at the sources, but 
 eventually gave up because I simply had no clue what's going on.)

It's worth learning.  It's still the only widely used abstract
portable assembler with fairly standard ABIs for each platform.

Go read KR[1].  It shouldn't take more than a week's worth of spare time.

[1]
The C Programming Language (2nd Edition), Kernigan and Ritchie, Prentice Hall, 
1998
http://www.amazon.com/Programming-Language-Prentice-Hall-Software/dp/0131103628/

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: Performance: MD5

2008-05-18 Thread Aaron Denney
On 2008-05-18, Achim Schneider [EMAIL PROTECTED] wrote:
 Aaron Denney [EMAIL PROTECTED] wrote:

 Go read KR[1].  It shouldn't take more than a week's worth of spare
 time.
 
 HELL NO!

 There's a reason why my lecturer always refered to it as Knall  Rauch
 C (Bang and Smoke C).

 Get the Harbison  Steele instead:
 http://careferencemanual.com/

C is a little language.  It doesn't /need/ a 500 page tome.  KR is not
something to learn programming, and of course, does quite poorly when
used as a textbook for that purpose.  It is, instead, for programmers to
learn C.

-- 
Aaron Denney
--

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


[Haskell-cafe] Endianess (was Re: GHC predictability)

2008-05-13 Thread Aaron Denney
On 2008-05-12, Andrew Coppin [EMAIL PROTECTED] wrote:
 (Stupid little-endian nonsense... mutter mutter...)

I used to be a big-endian advocate, on the principle that it doesn't
really matter, and it was standard network byte order.  Now I'm
convinced that little endian is the way to go, as bit number n should
have value 2^n, byte number n should have value 256^n, and so forth.

Yes, in human to human communication there is value in having the most
significant bit first.  Not really true for computer-to-computer
communication.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: Function Precedence

2008-04-07 Thread Aaron Denney
On 2008-04-03, Chris Smith [EMAIL PROTECTED] wrote:
 Hans Aberg wrote:
 This problem is not caused by defining f+g, but by defining numerals as
 constants.

 Yup.  So the current (Num thing) is basically:

 1. The type thing is a ring
 2. ... with signs and absolute values
 3. ... along with a natural homomorphism from Z into thing
 4. ... and with Eq and Show.

 If one wanted to be perfectly formally correct, then each of 2-4 could be 
 split out of Num.  For example, 2 doesn't make sense for polynomials or n 
 by n square matrices.  4 doesn't make sense for functions.  3 doesn't 
 make sense for square matrices of dimension greater than 1.  And, this 
 quirk about 2(x+y) can be seen as an argument for not wanting it in the 
 case of functions, either.  I'm not sure I find the argument terribly 
 compelling, but it is there anyway.

Just a nit, but 3 seems to make perfect sense for square matrices -- n
gets mapped onto I_d for any dimension d.

fromInteger (n*m) == fromInteger n * fromInteger m
fromInteger (n+m) == fromInteger n + fromInteger m

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: Shouldn't this loop indefinitely = take (last [0..]) [0..]

2008-04-07 Thread Aaron Denney
On 2008-04-04, Neil Mitchell [EMAIL PROTECTED] wrote:
  What do you mean by proper Lazy naturals? Peano ones?

 Yes

Not _strictly_ necessary.  And I'd definitely like some suitable
typeclass put in place.  This represents positive arithmetic with
a list homomorphism that forgets the elements and remembers only length.
It's pretty much exactly equivalent to the function map (const ()).

This essentially unary representation isn't the only way to way to
manipulate numbers by structure.  You can do the same thing with many
other data structures, such as trees, heaps, etc.

In this case, yes, lists are the cleanest, being the underlying
structure we're getting information about.  (Aside: might as well just
define the less than operation directly on the lists in this case --
or for any other arithmetic operation where we're not getting a list
back.  When we are, we usually can too, but it's a bit more fraught with
concerns over whether that's really what we want -- we're throwing away
information by replacing all elements with (), and perhaps we should
have the typechecker warn us.[1])

But we can pull this trick with any container class.  + corresponds to
some merger or catenation, * to some cross product, zero to an empty
data structure, and so forth.  If you do this with Binomial heaps, out
pop binary numbers.  If you do this to certain types of efficient
queues, skew binary numbers which support efficient increment and
decrument pop out.  This isn't surprising, as they were built using
skew binary number for precisely this property.  Those that haven't
should take a look at Okasaki's _Purely Functional Data Structures_,
particularly chapter 9: Numerical Structures.

http://books.google.com/books?id=SxPzSTcTalAC

[1]:
smallerThan :: [a] - [b] - Bool
smallerThan [] [] = False
smallerThan [] _  = True
smallerThan _  [] = False
smallerThan (_:as) (_:bs) = smallerThan as bs

noGreaterThan :: [a] - [b] - Bool
noGreaterThan [] _  = True
noGreaterThan _  [] = False
noGreaterThan (_:as) (_:bs) = noGreaterThan as bs

are perfectly reasonable, but it's less clear that

nattify = map const ()
(+) xs ys = (++) (nattify xs) (nattify ys)

would be good universal definitions.

-- 
Aaron Denney
--



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


[Haskell-cafe] Re: floating point operations and representation

2008-03-17 Thread Aaron Denney
On 2008-03-17, John Meacham [EMAIL PROTECTED] wrote:
 On Mon, Mar 17, 2008 at 12:59:09PM -0400, David Roundy wrote:
 foreign import ccall unsafe math.h log10 log10 :: Double - Double
 
 since in ghc CDouble and Double are identical.
 
 It's a bit sloppier, but shouldn't cause any trouble.  And I've no
 idea how realToFrac is implemented, but would worry about it behaving
 oddly... for instance when given NaNs.

 Yes. 'realToFrac' is inherently pretty broken and should be avoided
 whenever possible. It is not all all obvious to me what the correct
 primitive should be.. but we really should do something better for
 haskell'. relying on RULES firing as ghc currently does doesn't seem
 ideal..

 hmm.. maybe a 'FloatMax' type and have 'fromFloatMax' and 'toFloatMax'
 in 'Fractional' and 'Real' respectively? hmm.. hc has 'fromDouble' and
 'toDouble' there, but jhc also supports a 'Float128' type (when the
 underlying hardware does). so this still isn't quite right.

Well, the whole numeric hierarchy needs to be redone to support proper
mathematical structures like groups, rings, and fields.  Once that's
done, this might end up being clarified a bit.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: (flawed?) benchmark : sort

2008-03-15 Thread Aaron Denney
On 2008-03-15, Conor McBride [EMAIL PROTECTED] wrote:
 Hi

 On 14 Mar 2008, at 21:39, Aaron Denney wrote:

 On 2008-03-14, Conor McBride [EMAIL PROTECTED] wrote:
 Hi

 On 13 Mar 2008, at 23:33, Aaron Denney wrote:

 On 2008-03-13, Conor McBride [EMAIL PROTECTED] wrote:
 For a suitable notion of = on quotients, and with a
 suitable abstraction barrier at least morally in place,
 is that really too much to ask?

 I really think it is.  I don't think the case of equivalent for  
 this
 purpose, but not that purpose can be ignored.

 Sure. But use the right tools for the job.

 So what are the right tools then?  Why is a typeclass not the right
 tool?

 I guess I mean to distinguish *equality*, which is
 necessarily respected by all observations (for some
 notion of observation which it's important to pin
 down), from coarser equivalences where respect takes
 careful effort.

Which is worth doing.  But I think, in the end very little
interesting could end up passing that muster totally.  Once
you weaken it a bit, the guarantees are gone.  In practice,
I think there are significant number of user defined type
that implement Eq that just don't pass this test.  We can
recognize this, or declare all that code bad.

 I'm perfectly happy having equivalences around,
 but if Eq means has an equivalence rather
 than has equality, then I'm not very happy
 about the use of the == sign.

Well, no, it's not ideal.  In fact, it's downright
misleading.  I also think it's the best we can do before
Haskell', in terms of not causing gratuitous code breakage.

 So you're probably right that

x = y \/ y = x

 should hold for the order relation used by
 library sort. That's not the axiom I was
 thinking of dropping when I said sort's type
 was too tight (it was you who brought up
 incomparability): I was thinking of dropping
 antisymmetry.

 If a sort can't support the standard sort on this key
 technique, and don't munge everything for two keys that
 compare equal, something is wrong.  And I don't think
 sort is that special a case.

 I quite agree. That's why I'm suggesting we
 drop antisymmetry as a requirement for sorting.

Ah.  The normal weakening of a total order is a partial
order, and I was stuck on that, instead of this weakening,
which technically makes it a total preorder.

And I think that's the right semantics for the Ord class,
because that's the common case for programming.

Can we make a reasonable class hierarchy that supports all
these notions?

class Equiv a where
(~=~), (~/~) :: a - a - Bool

class Equiv a = Equal a where
(==), (/=) :: a - a - Bool
(==) = (~=~)
(/=) = (~/~)

class Equiv a = PreOrd a where
compare :: a - a - Ordering
(), (~), (~), () :: a - a - Bool

class (PreOrd a, Equal a) = Ord a where 
(=), (=) :: a - a - Bool
(=) = (~)
(=) = (~)

(And both are orderings are total.)
How do we nicely add partial orders?

semantically we want
class (PartialOrder a) = Order a where
compare = narrow partialCompare

but narrow by necessity has an incomplete pattern match.

An easy thing would be

instance (Order a) = PartialOrder a where
partialCompare = inject compare

but this lacks flexibility.  Will this flexibility ever be
necessary?  Quite possibly.  But, as usual, newtypes can
come to the rescue, at the cost of some akwardness.

Should this also be done for Equiv, Equal, PreOrder and Ord?

 Instances, rather than explicit functions, are nice because they let
 us use the type system to ensure that we never have incompatible
 functions used when combining two data structures, or pass in a
 function that's incompatible with the invariants already in a data
 structure built with another function.

 I'm not sure what you mean here.

Consider
data Treehelp a = Leaf | Branch (Treehelp a) a (Treehelp a)
data Tree a = (a - a - Ordering, Treehelp a)

how do we implement
merge :: Tree a - Tree a - Tree a
so that two incompatible orderings aren't used?

Okay, you say, let's not embed the functions in the tree:

data Tree a = Leaf | Branch (Tree a) a (Tree a)

insert :: (a - a - Ordering) - Tree a - Tree a
merge :: (a - a - Ordering) - Tree a - Tree a - Tree a

But these two will do something wrong if the trees were
constructed with a different function.

Instead, if we have 

merge :: Ord a = Tree a - Tree a - Tree a

The ordering is carried along in the dictionary, and the
typechecker ensures that only trees using the same ordering
are merged.  Different orders on the same underlying type
can be achieved with newtype wrappers.

 My main concern is that we should know where we
 stand. I think it would be a very good thing if
 we knew what the semantic notion of equality
 should be for each type. What notion of equality
 should we use in discussion? What do we mean when
 we write laws like

map f . map g = map (f . g)

 ? I write = to distinguish it from whatever
 Bool-valued function at some type or other
 that we might call ==.

Right.  My point of view

[Haskell-cafe] Re: (flawed?) benchmark : sort

2008-03-14 Thread Aaron Denney
On 2008-03-14, Conor McBride [EMAIL PROTECTED] wrote:
 Hi

 On 13 Mar 2008, at 23:33, Aaron Denney wrote:

 On 2008-03-13, Conor McBride [EMAIL PROTECTED] wrote:
 For a suitable notion of = on quotients, and with a
 suitable abstraction barrier at least morally in place,
 is that really too much to ask?

 I really think it is.  I don't think the case of equivalent for this
 purpose, but not that purpose can be ignored.

 Sure. But use the right tools for the job.

So what are the right tools then?  Why is a typeclass not the right
tool?

 Now, it may be the case that fooBy functions are then the right
 thing, but it's not clear to me at all that this is true.

 And if the fooBy option works, then why would the foo option fail for
 equivalence classes?

 It seems reasonable to construct quotients from
 arbitrary equivalences: if fooBy works for the
 carrier, foo should work for the quotient. Of
 course, if you want to expose the representation
 for some other legitimate purpose, then it wasn't
 equality you were interested in, so you should
 call it something else.

I'm perfectly happy calling it Equivalence.

 -- what should a sort algorithm do in such a
 situation?

 Not care. Produce a resulting list where for any

[..., x, ..., y, ...]

 in the result, y = x implies x = y. Vacuously
 satisfied in the case of incomparable elements.
 In the case of a total order, that gives you
 y = x implies x = y (and everything in between),
 but for a preorder, you put less in, you get less
 out.

That's a workable definition, but I don't know if I'd call it a
sort, precisely.  The standard unix tool tsort (for topological
sort, a bit of a misnomer) does this.

 Will that do?

Unfortunately, one can't just reuse the standard algorithms.  One
might think that one could reuse any standard algorithm by munging the
comparison so that incomparable gets mapped to equivalent, but the
following two chains shows that's not possible:

a - b - c - d
a - e - d

Instead, it seems that one has to use actual graph algorithms, which
are both more complicated to reason about, and have worse performance.

If a sort can't support the standard sort on this key technique, and
don't munge everything for two keys that compare equal, something is
wrong.  And I don't think sort is that special a case.

Instances, rather than explicit functions, are nice because they let us
use the type system to ensure that we never have incompatible functions
used when combining two data structures, or pass in a function that's
incompatible with the invariants already in a data structure built with
another function.

So we surely do need an equivalence relation typeclass.  And there are
Eq instances that aren't quite equality, but are equivalences, and work
with almost all code that takes Eq instances.

The only time treating equalities as equivalences won't work is when we
need to coalesce equivalent elements into one representative, and the
choice of representative matters.  (If it doesn't matter, we can just
pick arbitrarily).  If it does matter, a simple biasing scheme usually
isn't going to be sufficient -- we really do need a coalescing function.

So, do we mark equivalencies as special, or observational equality as
special?  Which is the tagging class, and which has the methods?  I
think it's pretty clear that the way to go is have (==) and (/=) live
in Equiv, and have Equal be a tagging class.  An equivalence is not a
special type of equality, but equality is a special type of equivalence.

Given all that, I think current Eq as Equivalence makes sense, and we
need to add an Equal class for things where we truly can't tell
equivalent elements apart.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: (flawed?) benchmark : sort

2008-03-14 Thread Aaron Denney
On 2008-03-14, Robert Dockins [EMAIL PROTECTED] wrote:
 Blah, blah, blah, its all in the documentation.  The point is that making 
 loose assumptions about the meaning of the operations provided by Eq and Ord 
 complicates things in ways that can't be made to go away.

Thanks.  All of these seem to me to be a case of Well, it's arbitrary,
so we don't guarantee anything but that we did something consistent.
Which seems perfectly reasonable, and not a problem at all.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: (flawed?) benchmark : sort

2008-03-14 Thread Aaron Denney
On 2008-03-10, Dan Weston [EMAIL PROTECTED] wrote:
 However, the report text is normative:

 6.3.2 (The Ord Class):

 The Ord class is used for totally ordered datatypes.

 This *requires* that it be absolutely impossible in valid code to 
 distinguish equivalent (in the EQ sense, not the == sense) things via 
 the functions of Ord. The intended interpretation of these functions is 
 clear and can be taken as normative:

forall f . (compare x y == EQ and (f x or f y is defined))
   == f x == f y)

That depends a great deal on your definitions.  Is the (=) in
the set theory structure equality, or is it merely a binary relation
with the appropriate properties?

If we take the result of the compare function being EQ to mean
structural equality, that throws out the possibility of even safe
semantic equality, and no interesting data structures can be made
instances of Ord.  That's less than useful.

Certainly, for the domain of /just the ordering comparisons/, yes, equal
elements are equal, and cannot be distinguished, but that just means
cannot be distinguished by the provided binary relations.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: (flawed?) benchmark : sort

2008-03-13 Thread Aaron Denney
On 2008-03-13, Adrian Hey [EMAIL PROTECTED] wrote:
 But the trouble is the report says practically *nothing* about Eq
 class or what the (==) operator means. It all seems to be assumed,
 and even when it does talk about it informally it talks about
 equality, not equivalence or some other word.

 The report doesn't state that for all Ints, (x==y = True) implies that
 x=y.

No, it doesn't.  However, for Ints, it's the most reasonable natural
(and generic) definition.

The report should be clarified on this point.

 There's no reason to suppose the Int instance is in any way
 special,

Well, what do you mean by special?  That it has this additional
guarantee?  I don't see that as unusual for Eq instances, no.  In fact,
I expect typical Eq instances to satisfy this.  However, if all I know
is Eq a, I don't think it can be counted on, so it is special in that
sense.

Just as, say Maybe a, along with many, or even most other common Monads
might satisfy more laws than a generic Monad a, doesn't necessarily make
it special.  But you can't still write generic Monad code assuming these
other properties.  Instead, you require MonadPlus instances, or similar 
for whatever additional properties you need.

 so do you really seriously consider the possibility that
 this might not hold in your Int related code?

 if (x==y) then f x else g x y

 might not mean the same as..

 if (x==y) then f y else g x y

In Int code, of course not, because I know the types, and I know the
behaviour of (==) on Ints.  But f is specialized to work on Ints, isn't
it, so it's reasonable to know what semantics (==) has for Ints, and
depend on them?

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: Some clarity please! (was Re: Re: (flawed?) benchmark : sort)

2008-03-13 Thread Aaron Denney
 and use it.

Generally, you're the one that gets to make this trade off, because
you're writing the code.  Whether someone else uses your code, or
others', or writes their own is then their own trade off.  Because,
indeed, many many types inhabiting Eq do obey observational equality,
the consequences of (b) may be minor.

With regards to Haskell 98, my best guess is that some of the committee
members thought hard about the code so that Eq a would usually work for
any equivalence class, and others took it to mean observational equality
and wrote prose with this understanding.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: (flawed?) benchmark : sort

2008-03-13 Thread Aaron Denney
On 2008-03-13, Adrian Hey [EMAIL PROTECTED] wrote:
 Aaron Denney wrote:
 so do you really seriously consider the possibility that
 this might not hold in your Int related code?

 if (x==y) then f x else g x y

 might not mean the same as..

 if (x==y) then f y else g x y
 
 In Int code, of course not, because I know the types, and I know the
 behaviour of (==) on Ints.  But f is specialized to work on Ints, isn't
 it, so it's reasonable to know what semantics (==) has for Ints, and
 depend on them?

 Why are Ints special in this way? Couldn't you use say exacly the same
 about any type (just substitute type X of your choice for Int)

About any /type/, yes.  When I'm writing code specific to type X, I can
be expected to know more about the type than what guarantees a generic
type inhabiting the same type classes will have.  In fact, I better know
more, because I'm calling specialized functions that take X, rather than
a, or Eq a = a.  If I didn't, I'd be writing a more or less generic
function, that could operate on more types than X.

But this doesn't hold for any old use of (==), or compare.  The function
sort (to go back to the beginning of this thread) as a generic function,
need not assume /anything/ about observation equality to sort a list.
All it needs do is use the comparison function on the elements to
reorder them.  This makes it /more useful/ than one that gets cute by
duplicating elements that compare equal, because it can be used in more
situations.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: Some clarity please!

2008-03-13 Thread Aaron Denney
On 2008-03-13, Ketil Malde [EMAIL PROTECTED] wrote:
 Aaron Denney [EMAIL PROTECTED] writes:

 Well, the way the report specifies that max's default definition
 is.  I'd actually favor making that not an instance function at
 all, and instead have max and min be external functions.

 If you permit a naïve question:

 Prelude :i Ord
 class (Eq a) = Ord a where
   compare :: a - a - Ordering
   () :: a - a - Bool
   (=) :: a - a - Bool
   () :: a - a - Bool
   (=) :: a - a - Bool
   max :: a - a - a
   min :: a - a - a

 ..while all functions could be easily derived from 'compare'.  Or from
 the Eq instance's (==) and (), say.

 What is the reason for this?  Efficiency?  (Which couldn't be handled
 equally well by RULES?)  Otherwise, it looks like an invitation for
 writing inconsistent instances.

My impression (which may not be entirely accurate) is not primarily for
efficiency (though that is one reason), but for ease of implementation.

It may be easier in some cases to think through the various cases of
compare, or to just figure out what (=) is.  Either of these is
sufficient (perhaps in combination with (==) from the superclass).

You can write things so that any of (), (=), (), or (=) are
sufficient, but for writing the default compare, it's easiest to know
ahead of time which you are basing it on, so definitions don't get
circular.

max and min seem to have neither justification going for them, although
I suppose it's technically possible to write compare in terms of them
and (==).

I don't think GHC's RULES were around when Haskell 98 was being formalized,
nor is it clear that one compiler's method should let other efficiency
concerns go by the wayside.

Of course, it would be nice to be able to write (==) in terms of
compare.  While doable manually there's no way to default it to that
smartly.  There are similar issues with Functor and Monad.  ISTR
some discussion about this on the list previously.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: (flawed?) benchmark : sort

2008-03-13 Thread Aaron Denney
On 2008-03-13, Conor McBride [EMAIL PROTECTED] wrote:
 Hi

 On 13 Mar 2008, at 22:28, [EMAIL PROTECTED] wrote:

 G'day all.

 Quoting Adrian Hey [EMAIL PROTECTED]:
 What's disputed is whether or not this law should hold:
  (a == b) = True implies a = b

 Apart from possibly your good self, I don't think this is disputed.
 Quotient types, as noted elsewhere in this thread, are very useful.

 For a suitable notion of = on quotients, and with a
 suitable abstraction barrier at least morally in place,
 is that really too much to ask?

I really think it is.  I don't think the case of equivalent for this
purpose, but not that purpose can be ignored.  Now, it may be the case
that fooBy functions are then the right thing, but it's not clear to me
at all that this is true.

And if the fooBy option works, then why would the foo option fail for
equivalence classes?

I've seen mention of difficulties with Data.Map, and edison, but not
in enough detail to really grasp what the problems are.  Until I do, my
natural bias (which I'm trying to resist, really) is that it's a matter
of lazy coding, not any inherent difficulty.

 Their common use predates Miranda, so it's way too late to unbless
 them now.

 How depressing! Untyped programming also predates
 Miranda. We can always aspire for better. It's not
 that we need to get rid of Quotients: it's just that
 we need to manage information hiding properly, which
 is perhaps not such a tall order.

 Meanwhile, the sort/Ord/OrdWrap issue may be a storm
 in a different teacup: the type of sort is too tight.
 Ord (total ordering) is way too strong a requirement
 for sorting. Antisymmetry isn't needed for sorting
 and isn't possessed by OrdWrap. A bit more structure
 for order-related classes would surely help here.

Say what?  If I don't have a total ordering, then it's possible two
elements are incomparable -- what should a sort algorithm do in such a
situation?

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: (flawed?) benchmark : sort

2008-03-13 Thread Aaron Denney
On 2008-03-13, David Menendez [EMAIL PROTECTED] wrote:
 On Wed, Mar 12, 2008 at 4:29 PM, Aaron Denney [EMAIL PROTECTED] wrote:

  When defining max, yes, you must take care to make sure it useable for
  cases when Eq is an equivalence relation, rather than equality.

  If you're writing library code, then it won't generally know whether
  Eq means true equality rather than equivalence.  If this would let
  you optimize things, you need some other way to communicate this.

  The common typeclasses are for generic, parameterizable polymorphism.
  Equivalence is a more generally useful notion than equality, so that's
  what I want captured by the Eq typeclass.

 I agree that equivalence is more general than equality, but I think
 equality makes more sense for Eq. Unfortunately, my reasons are mostly
 circumstantial.

Despite the circumstantial nature, still strong though.

 (1) You get at most one instance of Eq per type, and you get at most
 one equality relation per type. On the other hand, you have at least
 one equivalence (trivial equivalence) and will usually have several.
 Type classes don't work well when you have more than one of something
 per type (consider monoids).

Right.  But wrapping in newtypes gets around that somewhat.

 (2) Libraries like Data.Set and the Edison have to go through a lot of
 hoops because they can't assume that an Eq tests equality. (The Edison
 API, in particular, has to create a distinction between observable and
 non-observable collections, in order to support, e.g., a bag that
 doesn't store multiple copies of equivalent elements.)

Why is this a distinction in the API, rather than just the same API by
coalescing and non-coalescing collections?

 (3) Eq uses (==), which is commonly known as the equality sign, not
 the equivalence sign.

Meh.  Having the names be right is important, but choosing the right
semantics comes first.  Eq should be renamed (to either Equal or
Equivalent, depending).

 (4) The Prelude already provides alternative functions that support
 any equivalence (sortBy, nubBy, etc.).

Consider the old if we have trees with different comparison operators, how
do we keep the user from merging them together.  Well, phantom types,
and different instances provides a way to ensure this statically.

 If I were creating Haskell right now, I'd use Eq for equality and
 provide an additional class for equivalences along these lines:

Well, Haskell' isn't yet finished...

 data P r
 class Equivalence r where
 type EqOver r :: *
 equiv :: P r - EqOver r - EqOver r - Bool

 data Equality a

 instance (Eq a) = Equivalence (Equality a) where
 type EqOver (Equality a) = a
 equiv _ = (==)

 data Trivial a

 instance Equivalence (Trivial a) where
 type EqOver (Trivial a) = a
 equiv _ _ _ = True

Hmm.  Pretty nice, but I might prefer an MPTC solution.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: (flawed?) benchmark : sort

2008-03-12 Thread Aaron Denney
On 2008-03-11, Adrian Hey [EMAIL PROTECTED] wrote:
 Neil Mitchell wrote:
 Hi
 
  (sort [a,b]) in the case we have: (compare a b = EQ)

  Which of the following 4 possible results are correct/incorrect?
  1- [a,a]
  2- [a,b]
  3- [b,a]
  4- [b,b]
 
 Fortunately the Haskell sort is meant to be stable,

 I would have said it is meant to be *correct* first and *efficient*
 second. You're ruling out a whole bunch of possibly more efficient
 and correct sorts on the grounds that they may give observably different
 results for a tiny minority of (IMO broken) Eq/Ord instances.

It's exactly your opinion that these are broken that we're arguing
about.  My view is that they are just equivalence and ordering
relations, not complete equality relations.  Using sortBy, or wrapping
in a newtype with a different ordering instance and then using sort
should be equivalent.

 Wrt to *sortBy* (vs. *sort*), I would be inclined to agree with you.
 I sure hope someone has proven that the (apparently) different sortBy
 implementations provided by ghc,nhc and h98 library report are precisely
 equivalent for all (type legal) function arguments.
 and sorting is
 meant to be a permutation, so we happily have the situation where this
 has a correct answer: 2.

 Anything else is incorrect.

 Isn't 3 also a permutation? Why is it incorrect?

Stability --  see Fortunately the Haskell sort is meant to be stable, above.

 Adrian: I think its fairly clear we disagree about these things.
 However, we both understand the others point of view, so I guess its
 just a question of opinion - and I doubt either of us will change. As
 such I think any further discussion may just lead to sleep deprivation
 [1]. I think I'm coming from a more discrete maths/theoretical
 background while you are coming from a more practical/pragmatist
 background.

 If the discrete maths/theoretical POV necessatates to the kind of
 biasing madness of Data.Map/Set (for example) then it *sucks* bigtime
 IMO :-)


 Having tried this approach myself too (with the clone) I can confirm
 that *this way lies madness*, so in future I will not be making
 any effort to define or respect sane, unambiguous and stable behaviour
 for insane Eq/Ord instances for any lib I produce or hack on. Instead
 I will be aiming for correctness and optimal efficiency on the
 assumption that Eq and Ord instances are sensible.

Good.  But sensible only means that the Eq and Ord instances agree, not that
x == y = f x == f y.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: (flawed?) benchmark : sort

2008-03-12 Thread Aaron Denney
On 2008-03-12, Adrian Hey [EMAIL PROTECTED] wrote:
 Aaron Denney wrote:
 On 2008-03-11, Adrian Hey [EMAIL PROTECTED] wrote:
 Having tried this approach myself too (with the clone) I can confirm
 that *this way lies madness*, so in future I will not be making
 any effort to define or respect sane, unambiguous and stable behaviour
 for insane Eq/Ord instances for any lib I produce or hack on. Instead
 I will be aiming for correctness and optimal efficiency on the
 assumption that Eq and Ord instances are sensible.
 
 Good.  But sensible only means that the Eq and Ord instances agree, not that
 x == y = f x == f y.

 So can I assume that max x y = max y x?

No.  You can, however, assume that max x y == max y x.  (Okay, this
fails on Doubles, because of NaN.  I'll agree that the Eq and Ord
instances for Double are not sane.)

 If not, how can I tell if I've made the correct choice of argument
 order.

When calling, or when defining max?

It depends on what types you're using, and which equivalence and
ordering relations are being used.

When calling, and when it might matter which representative of an
equivalence class comes back out (such as in sorts) you have no choice
but to look at the documentation or implementation of max.

The Haskell report guarantees that x == y = max x y = y (and hence max
y x = x), and the opposite choice for min.  This is to ensure that (min
x y, max x y) = (x,y) or (y,x).  IOW, the report notices that choice of
representatives for equivalence classes matters in some circumstances,
and makes it easy to do the right thing.  This supports the reading that
Eq a is not an absolute equality relation, but an equivalence relation.

 If I can't tell then I guess I have no alternative but document
 my arbitrary choice in the Haddock, and probably for the (sake of
 completeness) provide 2 or more alternative definitions of the same
 function which use a different argument order.

When defining max, yes, you must take care to make sure it useable for
cases when Eq is an equivalence relation, rather than equality.

If you're writing library code, then it won't generally know whether
Eq means true equality rather than equivalence.  If this would let
you optimize things, you need some other way to communicate this.

The common typeclasses are for generic, parameterizable polymorphism.
Equivalence is a more generally useful notion than equality, so that's
what I want captured by the Eq typeclass.

And no, an overloaded sort doesn't belong in Ord, either.  If the
implementation is truly dependent on the types in non-trivial,
non-susbstitutable ways (i.e. beyond a substition of what = means),
then they should be /different/ algorithms.

It would be possible to right an Equal a typeclass, which does
guarantee actual observable equality (but has no methods).  Then you can
write one equalSort (or whatever) of type
equalSort :: (Eq a, Ord a, Equal a) = [a] - [a]
that will work on any type willing to guarantee this, but rightly fail
on types that only define an equivalence relation.

A stable sort is more generally useful than an unstable one.  It's
composable for radix sorting on compound structures, etc.
Hence we want to keep this guarantee.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: ANN: Hoogle 3.1

2008-02-29 Thread Aaron Denney
On 2008-02-29, Neil Mitchell [EMAIL PROTECTED] wrote:
 Hi

 Interesting to know people are looking for \where\. As a fairly new
  Haskeller, I bumped into frequent indentation issues (if-then-else,
  case, where, let, do, etc) and sometimes not sure where to place
  \where\ properly. Maybe beginners are having problem with syntax
  more than other things and they are asking Hoogle to get some
  suggestions...

  Or they are using Hoogle as Ask.com. Where is this? Where can I find that?

 No, they are just searching for where on its own. I'm not entirely
 sure why - if a new user who actually did it would let me know, I'd be
 very interested. Originally, Hoogle did not search for keywords - as a
 result of real users actually searching for them it got modified to
 include them. Because they are a new addition, they got tacked on
 lightly, which is why keywords actually have a module in Hoogle :-)

How's about modifying hoogle to put up a message asking them before the
normal response?

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: A question about monad laws

2008-02-14 Thread Aaron Denney
On 2008-02-14, Roman Leshchinskiy [EMAIL PROTECTED] wrote:
 Richard A. O'Keefe wrote:
 Presumably the reason for having Int in the language at all is speed.
 As people have pointed out several times on this list to my knowledge,
 Integer performance is not as good as Int performance, not hardly,
 and it is silly to pay that price if I don't actually need it.

 Do I understand correctly that you advocate using overflowing ints (even 
 if they signal overflow) even if Integers are fast enough for a 
 particular program? I strongly disagree with this. It's premature 
 optimisation of the worst kind - trading correctness for unneeded 
 performance.

Fast enough is not absolute.  It's not trading correctness, it's
trading /completion/.  And if you expect everything to fit in
[-2^31..2^31-1] or [0..2^32-1], finding out it doesn't might be valuable
information about your problem domain.  For exploratory coding, speed
and knowing when something breaks can be more important than knowing
that all possible corner case are covered, even ones you don't expect to
hit.

 SafeInt is what you should use when you *THINK* your results should all fit
 in a machine int but aren't perfectly sure.  (And this is nearly all the 
 time.)

 Again, I strongly disagree. You should use Integer unless your program 
 is too slow and profiling shows that Integer is the culprit. If and only 
 if that is the case should you think about alternatives. That said, I 
 doubt that your SafeInt would be significantly faster than Integer.

Why?  GMP is pretty good, but it's not going to be anywhere near
hardware speeds.

 The checking I am talking about is done by the hardware at machine speeds
 and provides *certainty* that overflow did not occur.

 So you advocate using different hardware?

At a minimum, any usable hardware sets flags on overflow.
Testing on those is pretty cheap.  Much cheaper than calling a GMP
routine to compare with 2^32, for instance.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: Implementing fixed-sized vectors (using datatype algebra?)

2008-02-08 Thread Aaron Denney
On 2008-02-05, Alfonso Acosta [EMAIL PROTECTED] wrote:
 On Feb 5, 2008 4:10 PM, Henning Thielemann
[EMAIL PROTECTED] wrote:

 On Fri, 1 Feb 2008, Aaron Denney wrote:

  On 2008-02-01, Bjorn Buckwalter [EMAIL PROTECTED] wrote:
   If Naturals had been sufficient for me I wouldn't have done my own
   implementation (I'm unaware of any other implementation of Integers).
   And there is certainly a lot of value to the clearer error messages
   from a decimal representation.
 
  I did a balanced-base-three (digits are 0, and +- 1) representation to
  get negative decimals.

 Nice. In German the digit values are sometimes called eins, keins, meins. 
 :-)

 I'm almost done with the decimal library but it would be nice to check
 some Integer implementations for future inclusion. So, Aaron, Björn,
 are your implementations available somewhere?

http://ofb.net/~wnoise/repos/dimensional/

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: Re[2]: Cabal, GHC, FFI and Visual Studio on Windows

2008-02-04 Thread Aaron Denney
On 2008-02-03, Bulat Ziganshin [EMAIL PROTECTED] wrote:
 Hello Duncan,

 Sunday, February 3, 2008, 5:24:22 AM, you wrote:

 Ok, so you could create a separate component to produce the .dll / .a
 from the C code but you'd prefer the convenience of being able to just:
 c-sources: blah.c
 and have them included in the project, but built using the MS C
 compiler.

 So I think we should file a feature request about building C sources
 using gcc/ms-c directly rather than going via ghc as that would give us
 the flexibility to use alternative C compilers.

 sorry, i think it's not whole story. gcc and msvc are probably
 incompatible in the meaning that you can't link together code
 produced by two compilers. exactly dll should be generated which allow
 to avoids this incompatibility

Well, the whole purpose of the ABI is to allow linking code together
from different compilers.  This doesn't mean there won't be any problems,
but I'd expect the ones that crop up won't *strictly* be because of
the compilers being different, but because of the C libraries being
different.  DLL vs object files shouldn't change things all that much.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: Implementing fixed-sized vectors (using datatype algebra?)

2008-02-01 Thread Aaron Denney
On 2008-02-01, Bjorn Buckwalter [EMAIL PROTECTED] wrote:
 If Naturals had been sufficient for me I wouldn't have done my own
 implementation (I'm unaware of any other implementation of Integers).
 And there is certainly a lot of value to the clearer error messages
 from a decimal representation.

I did a balanced-base-three (digits are 0, and +- 1) representation to
get negative decimals.  Again, for a proof-of-concept dimensional
analysis arithmetic.  No problem with the stack, but the error messages
are still less than clear.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: code.haskell.org vs darcs.haskell.org (was Enterprise Haskell AMQP library)

2008-01-29 Thread Aaron Denney
On 2008-01-29, Alistair Bayley [EMAIL PROTECTED] wrote:
 On 29/01/2008, Henning Thielemann [EMAIL PROTECTED] wrote:

 Thanks for the clarification! I added it to
   http://www.haskell.org/haskellwiki/Haskell.org_domain
  Can you insert the link to the web-submission system?

 I've done this.

 I also tried to request an account on code.haskell.org, but the server
 complains about my public key:

   500 Internal Server Error
   SSH key looks incorrect

 I pasted the key from this path (I use Putty and Pagaent on WinXP):
   C:\bayleya\putty\putty\id_dsa_pub.txt

 This folder also contains id_dsa.ppk (that's what Pagaent uses), which
 contains the same key, and also the private bit. The public key looks
 like this:

  BEGIN SSH2 PUBLIC KEY 
 Comment: dsa-key-20040309
 B3NzaC1kc3MAAACBAKs9yeNP35s4rSBDlJKQCC1nemVGd0zQAROFKeziCOGm
blah blah blah
 W5zrOSga/U/Cfa2rIM8Ko/9QmjNCJKsJioC5OTZMwOF0+zBWFCNN73z5+Dz/+PL+
 Xw==
  END SSH2 PUBLIC KEY 

 and this is what I've pasted into the form. I've also tried trimming
 it (removing the -- BEGIN and END, and the Comment) but no joy. Is
 this the right thing to put into the form? If not, where can I find
 it?

It is for certain ssh servers, but apparently not the one that
code.haskell.org uses.  See sections 8.2.{9,10}, and 8.3 in the PuTTY
documentation.

http://the.earth.li/~sgtatham/putty/0.60/htmldoc/Chapter8.html#puttygen-savepub
http://the.earth.li/~sgtatham/putty/0.60/htmldoc/Chapter8.html#puttygen-pastekey
http://the.earth.li/~sgtatham/putty/0.60/htmldoc/Chapter8.html#pubkey-gettingready

IIRC, it should look something like

ssh-dss B3NzaCXw== comment-string

So joining the lines into one might be sufficient.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: An idea - Feasibility and effort

2008-01-23 Thread Aaron Denney
On 2008-01-23, Ketil Malde [EMAIL PROTECTED] wrote:
 Achim Schneider [EMAIL PROTECTED] writes:

 Just out of curiosity: how do you plan to find out server locations
 (beyond the obvious top-level domain - country heuristics)?

 $ whois ip | grep Country

 Some also have location in the TXT field in DNS (Sometimes called an
 ICBM record).  I think 'xt(raceroute)' uses this.

LOC RR.  TXT is freeform.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: Wikipedia on first-class object

2008-01-06 Thread Aaron Denney
On 2008-01-06, Jonathan Cast [EMAIL PROTECTED] wrote:
 To wit, I do not believe the term `declarative' has any single
 referent, even in the sense that the term `functional' has any single
 referent.  I find the only similarity between Haskell and Prolog to be
 that neither is imperative.

Have you tried comparing Prolog to GHC's multiparameter type-classes?

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: Quanta. Was: Wikipedia on first-class object

2008-01-06 Thread Aaron Denney
On 2008-01-06, ChrisK [EMAIL PROTECTED] wrote:
 Brandon S. Allbery KF8NH wrote:
 
 On Jan 6, 2008, at 15:02 , Ketil Malde wrote:
 
 More seriously, perhaps quantum enters into the equation in how the
 brain works, perhaps it is even necessary for thought.  However, I
 get worried it's just another mystical mantra, a gratuitous factor
 that, lacking any theory about how and what it does, adds nothing to
 help understanding the issue.

 The brain, being real, is best modeled by a final theory that physicists have 
 not yet (noticed) written down.

 how the brain works appears to be though electro- and bio- chemistry, which 
 are best modeled/described right now by quantum mechanics.

Quantum mechanics models these, but for most domains it's a substrate
that is unnecessary -- modeling at the level of chemistry works.

 There are observable quantum correlations that cannot be described by a 
 classical theory.

Not in the brain.  It's *way* too warm and squishy.

 So long as the processes you care about (e.g. whatever the hell consciousness 
 is) do not use these non-classical correlations then you can create a 
 simplified 
 model that avoids the complexity of quantum theory.

Right.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: Wikipedia on first-class object

2007-12-30 Thread Aaron Denney
On 2007-12-28, ChrisK [EMAIL PROTECTED] wrote:
 Other note:
   An imperative language, such as C++ or Java, specified the binary output of
 any instance of the compiler.  Class methods will have very specific names and
 addresses.  In C++ you can even get the member-function pointer values and
 examine the byte offsets in the object.  In Java one gets a very specific 
 layout
 of bytecode in a class file.

These are specified by the ABI, not the language, in most cases.  Java
happens to specify this, but C and C++ do not.  Almost all platforms
define a C ABI.

   Haskell is a declarative language.  It does not specify anything about the
 implementation's internals.

Neither do most languages.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: [Haskell] Nested guards?

2007-12-06 Thread Aaron Denney
On 2007-12-06, Wolfgang Jeltsch [EMAIL PROTECTED] wrote:
 list comprehensions deal with specific operations (map, filter, etc.)
 of a specific type ([]).

Ah, so we should bring back monad comprehensions?

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: Why is this strict in its arguments?

2007-12-04 Thread Aaron Denney
On 2007-12-04, Paulo J. Matos [EMAIL PROTECTED] wrote:
 Hello all,

 As you might have possibly read in some previous blog posts:
 http://users.ecs.soton.ac.uk/pocm06r/fpsig/?p=10
 http://users.ecs.soton.ac.uk/pocm06r/fpsig/?p=11

 we (the FPSIG group) defined:
 data BTree a = Leaf a
| Branch (BTree a) a (BTree a)

Totally avoiding your question, but I'm curious as to why you
deliberately exclude empty trees.

Come to think of it, how can you represent a tree with two elements?

Wouldn't 

 data BTree a = Empty
  | Branch (BTree a) a (BTree a)

be better?

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: More problems [Tetris]

2007-11-21 Thread Aaron Denney
On 2007-11-21, Andrew Coppin [EMAIL PROTECTED] wrote:
 In short, lots of Haskell-related things seem to be extremely
 Unix-centric and downright unfriendly towards anybody trying to set
 things up on Windows. If I didn't already know a bit about Unix, I'd
 be *really* stuck!

I'd say, rather, that windows is unfriendly towards open and working
common standards.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: Sillyness in the standard libs.

2007-11-19 Thread Aaron Denney
On 2007-11-19, Andrew Coppin [EMAIL PROTECTED] wrote:
 Arthur van Leeuwen wrote:
 A closely related issue: fromIntegral is in Integral which also 
 requires quotRem. However,
 the two are semantically quite disjoint. I can *easily* see the 
 semantics of fromIntegral
 on EpochTime, but not the semantics of quotRem on EpochTime. 
 Having fromIntegral
 would solve the above puzzle... :)

 As I understand it, it's widely recognised that Haskell's current 
 numeric class hierachy is broken (or at best, not very well chosen), but 
 nobody came up with a better suggestion yet.

Oh, there are /lots/ of suggestions.  Perhaps too many.  But this is
one area that could really be improved by the use of ATs or MPTCs with
fundeps, and that's stalled some of the concrete proposals, as what
exactly is happening for Haskell' isn't too clear.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: MD5?

2007-11-17 Thread Aaron Denney
On 2007-11-17, Andrew Coppin [EMAIL PROTECTED] wrote:
   pack8into16 :: [Word8] - Word16
   pack8into32 :: [Word8] - Word32
   unpack16into8 :: Word16 - [Word8]
   unpack32into8 :: Word32 - [Word8]
   pack8into16s :: [Word8] - [Word16]
   pack8into32s :: [Word8] - [Word32]
   etc.

 I had to write all these myself, by hand, and then check that I got 
 everything the right way round and so forth. (And every now and then I 
 find an edge case where these functions go wrong.)

Well, you know, some of these are really the wrong signatures:

pack8into16 :: (Word8, Word8) - Word16
pack8into32 :: (Word8, Word8, Word8, Word8) - Word32
unpack16into8 :: Word16 - (Word8, Word8)
unpack32into8 :: Word32 - (Word8, Word8, Word8, Word8)

curry the above to taste.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: Guidance on using asynchronous exceptions

2007-11-16 Thread Aaron Denney
On 2007-11-16, Yang [EMAIL PROTECTED] wrote (quoting a paper):
 This style of concurrency is, of course, not new. Component
 architectures where data flows through components (rather than
 control) have been called 'actor-oriented' [35]. These can take many
 forms. Unix pipes resemble PN, although they are more limited in that
 they do not support cyclic graphs.

This isn't quite true.  Unix pipes support cyclic graphs just fine.
Many programs can't handle this due to buffering (on both input and
output).  Further, most Unix shells can't set them up.  C programs,
or anything else that exposes the underlying calls, can set them up
easily enough.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: Weird ghci behaviour?

2007-11-13 Thread Aaron Denney
On 2007-11-13, Jules Bean [EMAIL PROTECTED] wrote:
 Simon Peyton-Jones wrote:
 | For technical reasons, GHCi can only support the *-form for modules
 | which are interpreted, so compiled modules and package modules can
 | only contribute their exports to the current scope. But it does mean
 | the interpreter isn't referentially transparent, which is weird for a
 | language that puts so much stress on referential transparency.
 
 Well it depends on what you mean by referential transparency -- but I'll 
 agree 100% that the behaviour you described in your original message is 
 surprising, and therefore unwelcome.
 
 Nevertheless, I think there's a good reason for it.  The technical reasons 
 are not just laziness on our part.  By exporting only the functions named in 
 the export list, GHC can inline everything else vigorously, and that can in 
 turn give big performance improvements.  We don't want to arrange that every 
 top-level definition is treated as exported *just in case* someone wants to 
 GHCi that module.
 
 This is behaviour that could be changed. E.g. we could say that the 
 top-level scope remains available unless you optimise with -O2.  Or 
 something.  But there has to be a surprise lurking somewhere.

 I don't suggest a  change to your ABI or anything like that.

 I just suggest that the interpreter - ghci - should, by default, always 
 load a .hs file in interpreted mode, ignoring the .hi and .o already 
 present. After all, a .hs file contains source code and ghci is a 
 source code interpreter; I submit this would be the least surprising 
 thing to do.

 When it loads dependent modules, I think it can safely load the .o/.hi 
 versions as it does now if they exist, since we don't expect full symbol 
 table access there.

I _like_ being able to interactively apply bits of code, whether
compiled or not, and I like being able to compile them and get it to go
faster.  This would be a step back, for me.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: Memory-mapped arrays? (IArray interfaces, slices, and so on)

2007-11-08 Thread Aaron Denney
On 2007-11-08, David Roundy [EMAIL PROTECTED] wrote:
 On Wed, Nov 07, 2007 at 10:10:16PM +, Jules Bean wrote:
 Joel Reymont wrote:
 Is there such a thing as memory-mapped arrays in GHC?
 
 In principle, there could be an IArray instance to memory-mapped files.
 
 (There could also be a mutable version, but just the IArray version 
 would be useful).

 The IArray instance would be unsafe, however, because the contents of the
 file could change after you opened it, breaking referential transparency.

Or even crashing, if the size becomes smaller than the mapped area.

 I don't know what all is possible with file open modes, but I don't think
 you can guarantee that once you've opened a file it won't change (unless
 you unlink it, and know that noone else has an opened file handle to it).

File open modes won't do it, and I don't think any thing else will do
it using just POSIX behavior, either.  Linux's mmap() used to support a
DENY_WRITE flag, but it enabled DoS attacks, so it's gone.

 It may be that by opening it in write mode you could ensure that noone else
 modifies it (although I don't think this would work e.g. on nfs),

It doesn't even work locally.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: Strange subtract operator behavior - and lazy naturals

2007-10-22 Thread Aaron Denney
On 2007-10-21, Yitzchak Gale [EMAIL PROTECTED] wrote:
 I wrote:

 Yitzchak Gale wrote:
 So why not make the laziness available
 also for cases where 1 - 2 == 0 does _not_ do
 the right thing?
 data LazyInteger = IntZero | IntSum Bool Integer LazyInteger
 or
 data LazyInteger = LazyInteger Bool Nat
 or whatever.

 Luke Palmer wrote:
 data LazyInteger = IntDiff Nat Nat
 The only value which would diverge when
 compared to a constant would be infinity - infinity.

 Hmm. But then you could have integers that are
 divergent and non-infinite. What do we gain by
 doing it this way?

IntDiff is essentially fail-lazily for (Infinity - Infinity), rather
than fail-quickly of the other two.  Sometimes fail-lazily is
appropriate, sometimes not.  I don't think it makes too much difference
here though.  My actual concern is about having to compute with IntDiff
(large) (large + x) many times instead of IntDiff 0 x.  I'd rather one
of the two above, though I think I'd prefer explicity PosInt and NegInt
branches over an inscrutable boolean flag.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: New slogan... (A long speculation)

2007-10-15 Thread Aaron Denney
On 2007-10-15, [EMAIL PROTECTED] wrote:
 ok writes: 

 
 On 11 Oct 2007, at 1:00 pm, [EMAIL PROTECTED] wrote: 
 
 An anonymous called ok writes:
 
 I am not anonymous.  That is my login and has been since 1979.

 Oh, bother...
 According to my imperfect knowledge of English, an anonymous is somebody
 who doesn't sign his/her letters. And doesn't unveil his name. Just OK as
 login, even since 1979, is still anonymous, whatever you may say. 

In my dialect, anonymous is never used as noun, solely an adjective.

Further, maintaining the same identity but not revealing the
corresponding legal identity is pseudonymous.  Pseudonym can be used
as a noun, but it refers strictly to the name itself, and never the
bearer.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: How to thoroughly clean up Haskell stuff on linux

2007-10-13 Thread Aaron Denney
On 2007-10-12, Brandon S. Allbery KF8NH [EMAIL PROTECTED] wrote:

 On Oct 12, 2007, at 17:38 , Lihn, Steve wrote:

   Installing: --prefix=~/cabal/lib/haddock-0.8/ghc-6.4 

 This looks suspicious to me:  the ~ metacharacter is only  
 understood by shells, and only in certain circumstances (i.e. only at  
 the beginning of a word, not after a =),

This likely the problem, but a reasonable shell (i.e. zsh) will expand in
this circumstance:

% echo --foo=~
--foo=/home/wnoise

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: more functions to evaluate

2007-10-13 Thread Aaron Denney
On 2007-10-12, Dan Weston [EMAIL PROTECTED] wrote:
 applyNtimes f n | n  0 = f . applyNtimes f (n-1)
 | otherwise = id

Why not some variant of:

applyNtimes f n = foldl' (.) id (replicate n f)

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: pi

2007-10-11 Thread Aaron Denney
On 2007-10-11, Jonathan Cast [EMAIL PROTECTED] wrote:
 Yes.  I am very eager to criticize your wording.  To wit, I'm still
 failing to understand what your position is.  Is it fair to say that
 your answer to my question, why pi has no default implementation, is `in
 fact, pi shouldn't be a method of Floating anyway'?

That was how I was reading him.

 Btw: I am arguing that I (still) don't understand why the line

 pi = acos (-1)

 or something like it doesn't appear at an appropriate point in the
 Standard Prelude, given that the line

 pi :: a

 appears nearby said point.  I am eager to be enlightened.  But I haven't
 been, yet.

You would have to ask the committee.  But I think it's a bad idea to
have such a default (or 4 * atan 1, or ...) because of calculational
issues.  It's not a useful default, except for toy uses.  Yeah, it works
fine for float and double on hardware with FPUs.  But I want to be
told that I haven't implemented it, rather than it getting a really
awful default.  Most of the defaulting in other classes are minor
wrappers, such as converting between (=) and compare, not actual
algorithmic implementations, which can pull in strongly less efficient
implementations.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: pi

2007-10-10 Thread Aaron Denney
On 2007-10-10, [EMAIL PROTECTED] wrote:
 ChrisK writes: 

 Putting 'pi' in the same class as the trigonometric functions is good design.

 If you wish so... But:
 Look, this is just a numeric constant.
 Would you like to have e, the Euler's constant, etc., as well, polluting
 the name space? What for? 

It's there in the form (exp 1), after all.  Yeah, you can get pi from
(log i), but the multi-valuedness is annoying.  Not an issue with exp.

 The power is an abomination for a mathematician. With rational exponent it
 may generate algebraic numbers, with any real - transcendental... The
 splitting should be more aggressive. It would be good to have *integer*
 powers, whose existence is subsumed by the multiplicative s.group structure.
 But the Haskell standard insists that the exponent must belong to the same
 type as the base... 

Yes, this is an issue.  I wish there were a serious plan for reworking
the numeric hierarchy for Haskell', but no one seems to interested.
I've thought about writing something up, but with it not entirely clear
what subset of MPTCs, FunDeps, and ATs will be in, that makes a design
a bit trickier.

class Exponential a where
(^) :: (Integral b) = a - b - a

 What??
 But it is just a numerical constant, no need to put it into a class, and
 nothing to do with the type_classing of related functions. e is not
 std. defined, and it doesn't kill people who use exponentials. 

As I said above, it effectively is.  And, after all, 1, 2, 3, are
constants of the typeclass Integral a = a, 
and 0.0, 1.348, 2.579, 3.7, etc. are in Floating a = a.
So why not pi?

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: pi

2007-10-10 Thread Aaron Denney
On 2007-10-10, [EMAIL PROTECTED] wrote:
 Oh yes, everybody in the world uses in ONE program several overloaded
 versions of pi, of the sine function, etc.

They don't have to be in the same program for overloaded versions to be
semantically useful.  They're not strictly necessary, but so?
Having different programs use compatible conventions really is a win.

 How often *you* needed simultaneously overloaded pi and trigs in such a way
 that a default could help you? Answer sincerely (if you wish to answer at
 all...) 

Oh, just about never.   But the defaults are the issue, not the
simultaneously overloaded pi and trig functions.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: New slogan for haskell.org

2007-10-10 Thread Aaron Denney
On 2007-10-10, Andrew Coppin [EMAIL PROTECTED] wrote:
 (Indeed, the number of times my Haskell programs have locked up due to 
 me accidentally writing let x = foo x...)

For me, that's small.  I have seen useful program not lock up
that depend on let x = foo x though.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: New slogan for haskell.org

2007-10-05 Thread Aaron Denney
On 2007-10-05, Aaron Denney [EMAIL PROTECTED] wrote:
 On 2007-10-05, Peter Verswyvelen [EMAIL PROTECTED] wrote:
 But where is the great IDE Haskell deserves??? :-) Seriously, 99% of the 
 programmers I know don't want to look at it because when they see Emacs 
 or VIM, they say what the f*ck, I don't want to go back to the 
 stone age. If you want to attract more people that are inside the 
 imperative-OO-with-nice-IDE-blob, create a great looking and 
 functional IDE.

 Bluntly, I don't see why the Haskell community needs those sorts of
 programmers.  I like Haskell with a big enough community to have useful
 libraries, but a small enough community such that the language can
 readily evolve and serve as a useful research platform.

This is not say that nice tools aren't useful or that we should be less
than welcoming to anyone interested in Haskell.

But the best tool that makes a language more useful is the language
itself.  If I don't have as much boilerplate all over the place, then I
don't need a tool that goes and finds all this boilerplate and changes
it.  When the language manages memory for me, I don't need valgrind.
If I write a program that can't crash, I don't need crash-analysis
tools.  If my programs minimize state-change, I have less need of
traditional debuggers with watchpoints and breakpoints.  If my functions
are guaranteed by the compiler to be pure, /semantic/ debuggers, that
algebraicly manipulate definitions and can iteratively zero in on
meanings being wrong rather than just implementations glitching become
useable.  When I can autogenerate test data for my functions based
solely on the type, testing can be much easier.

We already have a lot of nice tools that do what we want.  Slapping a
GUI on them and maintaining integration while they're evolving is less
useful to me than programmers exploring other additional useful tools.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: bizarre memory usage with data.binary

2007-10-04 Thread Aaron Denney
On 2007-10-04, Jules Bean [EMAIL PROTECTED] wrote:
 Thomas Conway wrote:
 On 10/4/07, Jules Bean [EMAIL PROTECTED] wrote:
 ...and indeed it can't be done, except by the naive brute-force method
 of comparing every subtree, possibly optimised by cryptographically
 hashing a representation of every subtree, since sharing isn't an
 observable property.
 
 At least one Prolog implementation (I forget which, I'm sorry), had a
 [de]serialisation library which used a hash-consing approach.
 Basically, it did its serialization using a post-order traversal and
 emitted references to previous values when the same value had already
 been emitted. Not rocket science. Actually, I've heard a Prolog guy -
 Bart Demoen - talk about doing pretty much this during GC to improve
 sharing.

 Not rocket science at all, but relatively expensive. A time/space 
 tradeoff. And these days, with memory and disks feeling cheap, most 
 people want to trade time for space, not the other way around.

Caches are still limited sizes, and that can make a huge difference for
time.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: Space and time leaks

2007-10-04 Thread Aaron Denney
On 2007-10-04, Ronald Guida [EMAIL PROTECTED] wrote:
 I need some help with space and time leaks.

 I know of two types of space leak.  The first type of leak occurs when
 a function uses unnecessary stack or heap space.

 GHCi sum [1..10^6]
 *** Exception: stack overflow

 Apparently, the default definition for sum has a space leak.
 I can define my own sum in terms of strict foldl ...

  sum' xs = foldl' (+) 0 xs

 ... and it doesn't overflow the stack.

 GHCi sum' [1..10^6]
 5050
 (0.27 secs, 112403416 bytes)

 GHCi sum' [1..10^7]
 500500
 (2.73 secs, 1161223384 bytes)

 GHCi sum' [1..10^8]
 50005000
 (27.83 secs, 11645261144 bytes)

 I think there's still a space leak; I don't understand why GHCi using
 10^8, 10^9, 10^10 bytes of memory for these calculations.

This isn't a space leak.  The memory reported is the total amount of
allocation done, not the most used at a given time.  A C program that
did x = malloc(20); free(x); x = malloc(20); free(x); would be
reporting 40.  The run-time system is essentially constructing all of
these Integers (and functions returning them) at one point or another,
and these need to be represented.

Compare with last on these structures:
Prelude last [1..10^6]
100
(0.06 secs, 40895096 bytes)
Prelude last [1..10^7]
1000
(0.50 secs, 402118492 bytes)
Prelude last [1..10^8]
1
(4.74 secs, 4016449660 bytes)

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: [Haskell] Seemingly impossible Haskell programs

2007-09-29 Thread Aaron Denney
On 2007-09-29, Roberto Zunino [EMAIL PROTECTED] wrote:
 Graham Hutton wrote:
 Readers of this list may enjoy the following note by
 Martin Escardo, which shows how to write a number of
 seemingly impossible Haskell programs that perform
 exhaustive searches over spaces of infinite size, by
 exploiting some ideas from topology:
 

 http://math.andrej.com/2007/09/28/seemingly-impossible-functional-programs/#more-69

 Very nice! The note shows that you can actually compute (forall p) where
 p is a *total* predicate over streams of Bool (a.k.a. infinite lazy
 lists). Indeed, (writing [] for streams)

   forall :: ([Bool] - Bool) - Bool

 seems impossible to compute.

 Here's what I understood: (which might be wrong, of course!)

 This apparent magic relies on the fact that any total predicate over
 (total) bool streams, i.e.

   p :: [Bool] - Bool

 can only inspect a _finite_ prefix of the input list.

Well, any /computable/ total predicate.  This distinction isn't
that relevant when we're talking about predicates we might want to
implement and run, but there is a mathematical distinction.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: PROPOSAL: New efficient Unicode string library.

2007-09-27 Thread Aaron Denney
On 2007-09-27, Deborah Goldsmith [EMAIL PROTECTED] wrote:
 On Sep 26, 2007, at 11:06 AM, Aaron Denney wrote:
 UTF-16 has no advantage over UTF-8 in this respect, because of  
 surrogate
 pairs and combining characters.

 Good point.

 Well, not so much. As Duncan mentioned, it's a matter of what the most  
 common case is. UTF-16 is effectively fixed-width for the majority of  
 text in the majority of languages. Combining sequences and surrogate  
 pairs are relatively infrequent.

Infrequent, but they exist, which means you can't seek x/2 bytes ahead
to seek x characters ahead.  All such seeking must be linear for both
UTF-16 *and* UTF-8.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: PROPOSAL: New efficient Unicode string library.

2007-09-27 Thread Aaron Denney
On 2007-09-27, Ross Paterson [EMAIL PROTECTED] wrote:
 Combining characters are not an issue here, just the surrogate pairs,
 because we're discussing representations of sequences of Chars (Unicode
 code points).

You'll never want to combine combining characters or vice-versa?  Never
want to figure out how much screen space a sequence will take?  It _is_
an issue.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: PROPOSAL: New efficient Unicode string library.

2007-09-27 Thread Aaron Denney
On 2007-09-27, Ross Paterson [EMAIL PROTECTED] wrote:
 On Thu, Sep 27, 2007 at 07:26:07AM +, Aaron Denney wrote:
 On 2007-09-27, Ross Paterson [EMAIL PROTECTED] wrote:
  Combining characters are not an issue here, just the surrogate pairs,
  because we're discussing representations of sequences of Chars (Unicode
  code points).
 
 You'll never want to combine combining characters or vice-versa?  Never
 want to figure out how much screen space a sequence will take?  It _is_
 an issue.

 It's an issue for a higher layer, not for a compact String representation.

Yes, and no.  It's not something the lower layer should be doing, but
enabling the higher layers to do so efficiently is a concern.


-- 
Aaron Denney
--

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


[Haskell-cafe] Re: PROPOSAL: New efficient Unicode string library.

2007-09-27 Thread Aaron Denney
On 2007-09-27, Aaron Denney [EMAIL PROTECTED] wrote:
 On 2007-09-27, Deborah Goldsmith [EMAIL PROTECTED] wrote:
 On Sep 26, 2007, at 11:06 AM, Aaron Denney wrote:
 UTF-16 has no advantage over UTF-8 in this respect, because of  
 surrogate
 pairs and combining characters.

 Good point.

 Well, not so much. As Duncan mentioned, it's a matter of what the most  
 common case is. UTF-16 is effectively fixed-width for the majority of  
 text in the majority of languages. Combining sequences and surrogate  
 pairs are relatively infrequent.

 Infrequent, but they exist, which means you can't seek x/2 bytes ahead
 to seek x characters ahead.  All such seeking must be linear for both
 UTF-16 *and* UTF-8.

 Speaking as someone who has done a lot of Unicode implementation, I
 would say UTF-16 represents the best time/space tradeoff for an
 internal representation. As I mentioned, it's what's used in Windows,
 Mac OS X, ICU, and Java.

I guess why I'm being something of a pain-in-the-ass here, is that 
I want to use your Unicode implementation expertise to know what
these time/space tradeoffs are.

Are there any algorithmic asymptotic complexity differences, or all
these all constant factors?  The constant factors depend on projected
workload.  And are these actually tradeoffs, except between UTF-32
(which uses native wordsizes on 32-bit platforms) and the other two?
Smaller space means smaller cache footprint, which can dominate.

Simplicity of algorithms is also a concern.  Validating a byte sequence
as UTF-8 is harder than validating a sequence of 16-bit values as UTF-16.  

(I'd also like to see a reference to the Mac OS X encoding.  I know that 
the filesystem interface is UTF-8 (decomposed a certain a way).  Is it
just that UTF-16 is a common application choice, or is there some
common framework or library that uses that?)

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: PROPOSAL: New efficient Unicode string library.

2007-09-27 Thread Aaron Denney
On 2007-09-27, Duncan Coutts [EMAIL PROTECTED] wrote:
 In message [EMAIL PROTECTED] [EMAIL PROTECTED] writes:
 On 2007-09-27, Deborah Goldsmith [EMAIL PROTECTED] wrote:
  On Sep 26, 2007, at 11:06 AM, Aaron Denney wrote:
  UTF-16 has no advantage over UTF-8 in this respect, because of  
  surrogate
  pairs and combining characters.
 
  Good point.
 
  Well, not so much. As Duncan mentioned, it's a matter of what the most  
  common case is. UTF-16 is effectively fixed-width for the majority of  
  text in the majority of languages. Combining sequences and surrogate  
  pairs are relatively infrequent.
 
 Infrequent, but they exist, which means you can't seek x/2 bytes ahead
 to seek x characters ahead.  All such seeking must be linear for both
 UTF-16 *and* UTF-8.

 And in [Char] for all these years, yet I don't hear people complaining. Most
 string processing is linear and does not need random access to characters.

Yeah.  I'm saying the differences between them are going to be in the
constant factors, and that these constant factors will differ between 
workloads.  

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: PROPOSAL: New efficient Unicode string library.

2007-09-26 Thread Aaron Denney
On 2007-09-26, Johan Tibell [EMAIL PROTECTED] wrote:
 If UTF-16 is what's used by everyone else (how about Java? Python?) I
 think that's a strong reason to use it. I don't know Unicode well
 enough to say otherwise.

The internal representations don't matter except in the case of making
FFI linkages.  The external representations do, and UTF-8 has won on
that front.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: PROPOSAL: New efficient Unicode string library.

2007-09-26 Thread Aaron Denney
On 2007-09-26, Johan Tibell [EMAIL PROTECTED] wrote:
 On 9/26/07, Aaron Denney [EMAIL PROTECTED] wrote:
 On 2007-09-26, Johan Tibell [EMAIL PROTECTED] wrote:
  If UTF-16 is what's used by everyone else (how about Java? Python?) I
  think that's a strong reason to use it. I don't know Unicode well
  enough to say otherwise.

 The internal representations don't matter except in the case of making
 FFI linkages.  The external representations do, and UTF-8 has won on
 that front.

 It could matter for performance. However, you can encode your
 UnicodeString into any external representation you want for your I/O
 needs, including UTF-8.

Right.  I was trying to say other languages internal representations
shouldn't affect the choice of those doing a Haskell implementation.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: PROPOSAL: New efficient Unicode string library.

2007-09-26 Thread Aaron Denney
On 2007-09-26, Tony Finch [EMAIL PROTECTED] wrote:
 On Wed, 26 Sep 2007, Aaron Denney wrote:

 It's true that time-wise there are definite issues in finding character
 boundaries.

 UTF-16 has no advantage over UTF-8 in this respect, because of surrogate
 pairs and combining characters.

Good point.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: Very crazy

2007-09-25 Thread Aaron Denney
On 2007-09-25, Andrew Coppin [EMAIL PROTECTED] wrote:
 BTW, one *extremely* common function that I've never seen mentioned 
 anywhere is this one:

   map2 :: (a - b) - [[a]] - [[b]]
   map2 f = map (map f)

Because someone would have to think of a name for it, when (map . map)
is likely to be clearer.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: Very crazy

2007-09-25 Thread Aaron Denney
On 2007-09-25, Andrew Coppin [EMAIL PROTECTED] wrote:
 Aaron Denney wrote:
 On 2007-09-25, Andrew Coppin [EMAIL PROTECTED] wrote:
   
 BTW, one *extremely* common function that I've never seen mentioned 
 anywhere is this one:

   map2 :: (a - b) - [[a]] - [[b]]
   map2 f = map (map f)
 

 Because someone would have to think of a name for it, when (map . map)
 is likely to be clearer.
   

 OK, *now* I'm puzzled... Why does map . map type-check?

(map . map) = (.) map map

(.) :: (a - b) - (b - c) - a - c
= (a - b) - (b - c) - (a - c)

The first two arguments of (.) are 1-argument functions.

map :: (d - e) - [d] - [e]
=  (d - e) - ([d] - [e])

map is either a two argument function _or_ a function that takes one
argument (a function) and returns a function.

In this latter view, for the first argument, of (.), we need:

a = d - e
b = [d] - [e]

And for the second we know
b = [d] - [e]
so 
c = [[d]] - [[e]]

for everything to be consistent.  

It's much clearer when you think of map not as running this function
over this list, but rather turning this function that operates on
elements into a function that operates on lists.  Doing that twice (by
composing) turns a function that operates on elements into a function
that operates on lists of lists.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: Very crazy

2007-09-25 Thread Aaron Denney
On 2007-09-25, Andrew Coppin [EMAIL PROTECTED] wrote:
 I just found it rather surprising. Every time *I* try to compose with 
 functions of more than 1 argument, the type checker complains. 
 Specifically, suppose you have

   foo = f3 . f2 . f1

 Assuming those are all 1-argument functions, it works great. But if f1 
 is a *two* argument function (like map is), the type checker refuses to 
 allow it, and I have to rewrite it as

   foo x y = f3 $ f2 $ f1 x y

 which is really extremely annoying...

 I'm just curiose as to why the type checker won't let *me* do it, but it 
 will let *you* do it. (Maybe it hates me?)

Don't anthropomorphize computers.  They hate it when you do that.

I'm guessing the problem is probably incorrect parenthesizing.

foo x y = f3 . f2 . f1 x y

won't typecheck, but 

foo x y = (f3 . f2 . f1) x y

should.  

Function application is the highest precedence, so 
the first definition is parsed as 

foo x y = f3 . f2 . (f1 x y)

which will only type-check if f1 has 3 or more arguments, as (f1 x y)
must be a function.

The trickier parts are more than 1 argument functions as the first
argument to (.).  Are you sure your failed attempts weren't of this
form?

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: Very crazy

2007-09-25 Thread Aaron Denney
On 2007-09-25, Philippa Cowderoy [EMAIL PROTECTED] wrote:
 On Tue, 25 Sep 2007, Lennart Augustsson wrote:

 It's reasonably easy to read.
 But you could make it more readable.  Type signatures, naming the first
 lambda...
 

 It might be reasonable to define something like mapMatrix that happens to 
 be map . map, too. Along with at least a type synonym for matrices.

Yes, that's a good idea.  Because it lets you change from the often
annoying list-of-lists implementation to something more reasonable for
e.g. transpose, as recently mentioned.

 Name domain constructs rather than expecting people to reconstruct
 them from their implementations, in other words.

Right.  But a list-of-lists isn't a terribly specific domain construct.
When it's used without further semantics, I think map . map is the best
translation of intent.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: PROPOSAL: New efficient Unicode string library.

2007-09-25 Thread Aaron Denney
On 2007-09-26, Deborah Goldsmith [EMAIL PROTECTED] wrote:
  From an implementation point of view, UTF-16 is the most efficient  
 representation for processing Unicode.

This depends on the characteristics of the text being processed.
Spacewise, English stays 1 byte/char in UTF-8.  Most European languages
go up to at most 2, and on average only a bit above 1.  Greek and
Cyrillic are 2 bytes/char.  It's really only the Asian, African, Arabic,
etc, that lose space-wise.

It's true that time-wise there are definite issues in finding character
boundaries.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: Shouldnt this be lazy too?

2007-09-24 Thread Aaron Denney
On 2007-09-24, Andrew Coppin [EMAIL PROTECTED] wrote:
 Neil Mitchell wrote:
 Hi

 lengthNat [1..]  10

 Couldn't be clearer, and can be made to work perfectly. If anyone does
 want to pick up the lazy naturals work, I can send over the code (or
 write it yourself - its not hard!)
   

 Um... isn't a lazy natural just a list with no data, where the list 
 length encodes a number?

That's one particularly simple representation, yes.  Lazy Unary.
One can also construct other representations that may be more efficient
in certain situations.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: getting crazy with character encoding

2007-09-13 Thread Aaron Denney
On Thu, Sep 13, 2007 at 11:07:03AM +0200, Stephane Bortzmeyer wrote:
 On Thu, Sep 13, 2007 at 12:23:33AM +,
  Aaron Denney [EMAIL PROTECTED] wrote 
  a message of 76 lines which said:
 
  the characters read and written should correspond to the native
  environment notions and encodings.  These are, under Unix,
  determined by the locale system.
 
 Locales, while fine for things like the language of the error messages
 or the format to use to display the time, are *not* a good solution
 for things like file names and file contents.

I never claimed it was a good system, merely that it was the system.
Yes, serious applications should use byte oriented I/O and explicitly
manage character sets when necessary.  STDIO in general and terminal
interaction in particular should use the locale selected by the user.

 Even on a single Unix machine (without networking), there are
 *several* users. Using the locale to find out the charset used for a
 file name won't work if these users use different locales.
 
 Same thing for file contents. The charset used must be marked in the
 file (XML...) or in the metadata, somehow.

For file system and network access, the justification is a bit more
clouded, but the interfaces there _should not_ be character interfaces.
Character interfaces are _lies_; Word8s are what actually get passed,
and trying to treat them as unicode characters with any fixed mapping
breaks.  At best we get an extremely leaky abstraction.

Filesystems are not uniform across systems, yet Haskell tries to present
a uniform view that manages to capture exactly no existing system.

File contents (almost) everywhere are streams of bytes (ignoring, say,
old record-based OSes, palm databases, and mac resource forks etc.)
Almost all file systems use a hierarchical directory system, but with
significant differences.  Under unixes the names are NUL-terminated
bytestrings that can't contain slashes.  New Macs and Windows have
specific character encodings (UTF-8, and UTF-16, respectively).  DOS,
old Macs, and windows have multiple roots and various directory
seperators and forbidden characters.

Trying to specify some API that is usable for robust programs that work
on any of these is hard.  I'd actually have preferred that the standard
didn't even try, and instead provided system-specific annexes.
Then an external library that was freer to evolve could try to solve
the problem of providing a uniform interface that would not defy
platform expectations.

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


[Haskell-cafe] Re: getting crazy with character encoding

2007-09-13 Thread Aaron Denney
On 2007-09-13, Stefan O'Rear [EMAIL PROTECTED] wrote:
 In any case, we already have hGetBuf / hPutBuf in the standard base
 libaries for raw binary IO, so code that uses getChar for bytes really
 has no excuse.

Except, of course, that hGetBuf and hPutBuf are
(a) allocating the memory for the buffers is a pain (does it require the
FFI?)
(b) are something of a pain to use, requiring explicitly managing what's
valid in these buffers (though a wrapper only need be written once)
(c) while in the standard base libraries are not in the report or
library report.  i.e. there's no guarantee that a conforming Haskell
implementation will have them.  It'd be silly for an implementation to
not support them, of course, but...

The ByteString library at least fixes (a) and (b).

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: Monad.Reader 8: Haskell, the new C++

2007-09-12 Thread Aaron Denney
On 2007-09-12, Don Stewart [EMAIL PROTECTED] wrote:
 ok:
 I've been told that functional dependencies are old hat and there is
 now something better.  I suspect that better here means worse.

 Better here means better -- a functional language on the type system,
 to type a functional language on the value level.

Meh.  I prefer functional languages for general problems, but as
type-checking is a rather specific problem, I don't see why logic
programming isn't more appropriate.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: getting crazy with character encoding

2007-09-12 Thread Aaron Denney
Hi.  I believe that everything I've said has been said by another
responder, but not all together in one place.

On 2007-09-12, Andrea Rossato [EMAIL PROTECTED] wrote:
 supposed that, in a Linux system, in an utf-8 locale, you create a file
 with non ascii characters. For instance:
 touch abèèè
 

 Now, I would expect that the output of a shell command such as 
 ls ab*
 would be a string/list of 5 chars. Instead I find it to be a list of 8
 chars...;-)

 That is to say, each non ascii character is read as 2 characters, as
 if the string were an ISO-8859-1 string - the string is actually
 treated as an ISO-8859-1 string. But when I print it, now it is
 displayed correctly.

The Linux kernel doesn't really have a notion of characters, only bytes
in its interfaces.  (This isn't strictly true: it needs to in some cases
when it's interacting with other systems, but it's 99% true.)  In the
UTF-8 representation of these 5 characters are 8 bytes, as indeed each
non-ASCII character takes two bytes.

The various C runtimes do have some notion of various character sets,
and locales, and so forth, and build on top of the byte interface to
represent characters.  But not all programs use these.  Your example of
ls just takes the bytes from the kernel, and perhaps does some minimal
sanitizing (munging control codes) before sending them to the tty.  If
the terminal understands UTF-8, everything works great.

On the other hand, GHC's runtime always interprets these bytes as
meaning the characters in ISO-8859-1 (this just takes the bytes to the
unicode code points), and does not pay attention to locale settings
such as LC_CHARSET, etc.  While this has some nice properties (totally
invertible, no code to maintain (as the first 256 code points of Unicode
are ISO-8859-1), etc.), personally, I think this is a bug.  The Haskell
standard talks about characters, not bytes, and the characters read
and written should correspond to the native environment notions and
encodings.  These are, under Unix, determined by the locale system.

Unfortunately, at this point it is a well entrenched bug, and changing
the behaviour will undoubtedly break programs.

There should be another system for getting the exact bytes in and out
(as Word8s, say, rather than Chars), and there are in fact external
libraries using lower level interfaces, rather than the things like
putStr, getLine, etc. that do this.  An external library works, of
course, but it should be part of the standard so implementors know that
character based routines actually are character based, not byte based.

 After reading about character encoding, the way the linux kernel
 manages file names, I would expect that a file name set in an utf-8
 locale should be read by locale aware application as an utf-8 string,
 and each character a unicode code point which can be represented by a
 Haskell char. What's wrong with that?

That's a reasonable assumption.  The problem is that GHC doesn't support
locales.  But byte-sequences do round-trip, as long as you don't try to
process them, so not as much breaks as one might think.

I don't know what NHC and hugs do, though I assume they also provide
no translations.  I'm also not sure what JHC does, though I do see
mentions of UTF-8, UTF-16 (for windows), and UTF-32 (for internal usage
of C libraries), and I do know that John is fairly careful about locale
issues.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: Elevator pitch for Haskell.

2007-09-10 Thread Aaron Denney
On 2007-09-08, Neil Mitchell [EMAIL PROTECTED] wrote:
 All these things are minor. The Prelude numeric classes aren't
 broken - they don't quite match what a mathematician might have
 picked, but its certainly easy enough to do numeric operations!

They can be used, but they don't break down in nice ways to make
extensions easier, precisely because they don't match what a
mathematician would have picked.  They are indeed broken.

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: interaction between OS processes

2007-08-30 Thread Aaron Denney
On 2007-08-30, Andrea Rossato [EMAIL PROTECTED] wrote:
 Hi,

 there's something I don't get about interaction among OS processes and
 Haskell handles/channels.

This looks like a buffering problem.  You might be able to make it work by
explicitly setting line buffering with hSetBuffering

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: Parsing binary data.

2007-08-20 Thread Aaron Denney
On 2007-08-19, Matthew Sackman [EMAIL PROTECTED] wrote:
 Recently, Adam Langley responded so:
 On 8/18/07, Matthew Sackman [EMAIL PROTECTED] wrote:
  Also, one thing to watch out for is the fact the existing Get and Put
  instances may not do anything like what you expect. For example, for
  some reason I expected that the instances of Get and Put for Float and
  Double would send across the wire Floats and Doubles in IEEE floating
  point standard. How wrong I was...
 
 Ah, those aren't instances of Get and Put, but of Binary[1]. You use
 the Binary instances via the functions 'get' and 'put' (case is
 important).

 Gah, that'll teach me to post from memory without checking the code.
 Indeed, that is what I meant, the instances of Binary.

 Get and Put provide actions like putWord32be, for which the
 resulting bits are pretty much universally accepted. Binary has
 default instances which uses Get and Put to serialise Haskell types
 like [Int], or (Float, Float). Here the resulting bits aren't
 documented, but you can read the code and I have some C code for
 dealing with them somewhere if anyone is interrested. The
 serialisation of Float is, indeed, nothing like IEEE in either
 endianness.

 Quite. Whilst we're on the subject (and I realise I might be hijacking
 this thread a little), it does seem rather odd that it's very easy to
 take a Word8/16/32/64 and interpret it as an integer. Similarly, it's
 very easy to take an integer and convert it to a Word of some sort.

That's because there's basically only one way to interpret a given word
as an integer, and store a given integer as a word.

 But it's vastly harder to do that for floats / non-integers. Now I know
 that the number classes in the Prelude are basically broken anyway and
 all really need rewriting, but it does seem completely arbitrary that
 Words somehow are only allowed to contain whole numbers!

It's more that for floats, there are a zillion plausible ways to store
them, and many have been used.

-- 
Aaron Denney
--

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


  1   2   >