[Haskell-cafe] Tutorial: Curry-Howard Correspondence

2007-10-16 Thread Tim Newsham

A tutorial on the Curry-Howard Correspondence in Haskell:
  http://www.thenewsh.com/%7Enewsham/formal/curryhoward/

Feedback appreciated.

Tim Newsham
http://www.thenewsh.com/~newsham/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Bug in runInteractiveProcess?

2007-10-16 Thread Donn Cave

On Oct 16, 2007, at 9:52 PM, Brandon S. Allbery KF8NH wrote:



On Oct 17, 2007, at 0:39 , Donn Cave wrote:
...
As for closing file descriptors explicitly - if I remember right  
what I've seen

in the NetBSD source, the UNIX popen() implementation may years ago
have closed all file descriptors, but now it keeps track of the  
ones it created,

and only closes them.  I think that's the way to go, if closing fds.


Either implementation causes problems; security folks tend to  
prefer that all file descriptors other than 0-2 (0-4 on Windows?)  
be closed, and 0-2(4) be forced open (on /dev/null if they're not  
already open).  But in this case, the idea is to set FD_CLOEXEC on  
(and only on) file descriptors opened by the Haskell runtime, so  
you would get the same effect as tracking file descriptors manually.


I can't speak for security folks, but for me, the way you put it goes  
way too far.

The file descriptors at issue were opened by runInteractiveProcess, and
FD_CLOEXEC on them would solve the whole problem (I think.)  Is that
what you mean?  To set this flag routinely on all file descriptors  
opened in
any way would require a different justification, and it would have to  
be a

pretty good one!

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


Re: [Haskell-cafe] Functional Programming Books

2007-10-16 Thread Justin Bailey
On 10/16/07, Dan Piponi <[EMAIL PROTECTED]> wrote:
>
> I was just putting together my Amazon wish list and was wondering if
> there are any great books on Haskell and/or functional programming
> that people think are must-reads. Okasaki's "Purely Functional
>

Hudak's "The Haskell School of Expression" is an excellent way to get
started. Though it may abe outside what you are looking for, "The Structure
and Interpretation of Computer Programs" is an amazing and still relevant
tour of all the styles of programming.

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


Re: [Haskell-cafe] Bug in runInteractiveProcess?

2007-10-16 Thread Donn Cave


On Oct 16, 2007, at 1:48 PM, John Goerzen wrote:



I have been trying to implement a Haskell-like version of shell
pipelines using runInteractiveProcess.  I am essentially using
hGetContents to grab the output from one command, and passing that to
(forkIO $ hPutStr) to write to the next.  Slow, but this is just an
experiment.


As an aside, I personally would look to System.Posix.Process for this.
Something like this would deal with the file descriptors in the fork ...

fdfork fn dupfds closefds = do
pid <- forkProcess $ execio
return pid
where
dupe (a, b) = do
dupTo a b
closeFd a
execio = do
mapM_ dupe dupfds
mapM_ closeFd closefds
fn

... and then you can put the pipes directly between the processes ...

 -- date | tr '[A-Z]' '[a-z]' | read
 (a0, a1) <- createPipe
 (b0, b1) <- createPipe
 p1 <- fdfork tr [(b0, 0), (a1, 1)] [a0, b1]
 closeFd a1
 p2 <- fdfork date [(b1, 1)] [a0, b0]
 closeFd b1
 readfd a0-- implementation left to reader
where
 date = executeFile "/bin/date" False [] Nothing
 tr = executeFile "/usr/bin/tr" False ["[A-Z]", "[a-z]"] Nothing

There's probably a nice way to wrap that up, so you're not keeping
track of the file descriptors for all the pipes.

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


Re: [Haskell-cafe] Re: Bug in runInteractiveProcess?

2007-10-16 Thread Brandon S. Allbery KF8NH


On Oct 17, 2007, at 0:39 , Donn Cave wrote:


On Oct 16, 2007, at 7:31 PM, Brandon S. Allbery KF8NH wrote:

I could dig for official confirmation, but this is my  
understanding of both POSIX and SUS, and portable C programs  
generally #define FD_CLOEXEC to 1 if it doesn't already exist,  
since the value *is* standard even though the name is not.


I find `runInteractiveProcess' in System.Process, in the  
documentation -

not System.Posix.Process.  Possibly the C macro is less important than
the cross-platform semantics relating to this problem.  I.e., what  
happens
on Microsoft Windows.  I sure wouldn't know.  Does a process even  
inherit

pipe file descriptors?


The context of my message was a proposal for how to fix it on POSIX  
systems.  I do not claim to have sufficient understanding of Win32  
APIs to fix that implementation --- but I suspect that there are  
already many other implementation differences between the POSIX and  
Win32 versions of System.Process, if only because popen(), fork(),  
and exec() are entirely foreign concepts in Win32.


As for closing file descriptors explicitly - if I remember right  
what I've seen

in the NetBSD source, the UNIX popen() implementation may years ago
have closed all file descriptors, but now it keeps track of the  
ones it created,

and only closes them.  I think that's the way to go, if closing fds.


Either implementation causes problems; security folks tend to prefer  
that all file descriptors other than 0-2 (0-4 on Windows?) be closed,  
and 0-2(4) be forced open (on /dev/null if they're not already  
open).  But in this case, the idea is to set FD_CLOEXEC on (and only  
on) file descriptors opened by the Haskell runtime, so you would get  
the same effect as tracking file descriptors manually.


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


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


Re: [Haskell-cafe] Re: Bug in runInteractiveProcess?

2007-10-16 Thread Donn Cave

On Oct 16, 2007, at 7:31 PM, Brandon S. Allbery KF8NH wrote:

I could dig for official confirmation, but this is my understanding  
of both POSIX and SUS, and portable C programs generally #define  
FD_CLOEXEC to 1 if it doesn't already exist, since the value *is*  
standard even though the name is not.


I find `runInteractiveProcess' in System.Process, in the documentation -
not System.Posix.Process.  Possibly the C macro is less important than
the cross-platform semantics relating to this problem.  I.e., what  
happens
on Microsoft Windows.  I sure wouldn't know.  Does a process even  
inherit

pipe file descriptors?

Or pseudo-ttys - or does it even have them?  A design with a two or  
three-way
pipe connection like this is asking for trouble - begging for it,  
with a name like
`runInteractiveProcess' - because most of the commands that you might  
invoke
will block-buffer output, confounding the application that expects to  
conduct
a dialogue with a forked command.  Pseudo-ttys are pipe-like devices  
that
won't be block-buffered, and they're really the only more or less  
reliable way

to have an `interactive' I/O exchange with another command that wasn't
written specifically to support this.

As for closing file descriptors explicitly - if I remember right what  
I've seen

in the NetBSD source, the UNIX popen() implementation may years ago
have closed all file descriptors, but now it keeps track of the ones  
it created,

and only closes them.  I think that's the way to go, if closing fds.

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


Re: [Haskell-cafe] Functional Programming Books

2007-10-16 Thread Albert Y. C. Lai
Richard Bird's "Introduction to Functional Programming using Haskell, 
second edition" exceeds other introductory books by introducing laws 
(e.g., fold laws, fusion laws), efficiency issues (including the stack 
overflow question, deforestation), and monad transformers.


IMO these are under-represented and greatly FUDed topics.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] OzHaskell?!?

2007-10-16 Thread Don Stewart
chak:
> I wrote a while ago,
> >There is AngloHaskell and now AmeroHaskell.  Doesn't that call for 
> >OzHaskell?
> >
> >  http://haskell.org/haskellwiki/OzHaskell
> 
> In the meantime a number of interested people put their name down on 
> the wiki page.  So, let's talk more concretely about a first 
> meeting.  I have put two (very rough) options for a date of a first 
> meeting on the wiki page as well as notes about the possible format. 
>  Please note your preferences and any additional ideas and 
> suggestions on the wiki page.
> 
> I also started a section to collect possible talks and demos we 
> could have.  Again, add anything you'd like to contribute.  (It's 
> fine to be speculative, you commit to nothing at this stage.)

There's also a move on to organise a North West USA (Portland...) group
too, probably with a talk or two, some demos, and beer afterwards.

Those who've been to a London, New York or Bay Area meetup -- what
works, what doesn't? 

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


[Haskell-cafe] job opportunity

2007-10-16 Thread jeff p
Hello,

  Here are the essential details...

Location: NYC

Industry: finance

Salary: enough to live comfortably in Manhattan

Hard Requirements:
Must be able to work in the USA (we can't get you a worker's visa).

Must be an expert level Haskell user; must be comfortable with
monads, monad transformers, type level programming (i.e. MPTC,
overlapping and undecidable instances), and lazy evaluation (i.e. know
how to find and eliminate space leaks).

   Must have a desire to use modern PL research in the real world.

Soft Requirements:
Experience with low-level Haskell programming (i.e. FFI).

Experience with Linux and Cygwin/Windows.

Knowledge/experience in dependently typed programming.

Knowledge/experience in logic programming.


If anyone is interested, please contact me to find out more.

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


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

2007-10-16 Thread John Meacham
On Wed, Oct 17, 2007 at 03:13:23AM +0100, Lennart Augustsson wrote:
> If naturals have a perfectly reasonable subtraction then they also have a
> perfectly reasonable negate; the default is 0-x.
> 
> (Oh, subtraction wasn't THAT reasonable, you say. :) )


I suppose I was overextending the use of 'perfectly reasonable' here. :)

tangent:

if anyone is interested, Although I bet this has been implemented a
hundred times over, I have attached my lazy naturals module below just
for larks. It is quite efficient as such things go and very lazy. for
instance (genericLength xs > 5) will only evaluate up to the 5th element
of the list before returning a result. and ((1 `div` 0) > 17) is true,
not bottom.

Anyone have any comments on my lazy multiplication algorithm? since each
number is of the form (x + rx) (an integer, plus the lazy remainder) I
just did the multiplicitive expansion 

(x + rx) * (y + ry) -> x*y + x*ry + y*rx + rx*ry
then I simplify to 
(x + rx) * (y + ry) -> x*y + x*ry + rx*(y + ry)
which saves a nice recursive call to * speeding thinsg up signifigantly.
but is there a better way?

since (+) is lazy, we can still get a good lazy result without
evaluating the tails when multiplying... that is nice.

also, what do you think 
n `mod` 0 should be? I can see arguments for it being 'n', 0, or
Infinity depending on how you look at it.. hmm..


If anyone wants me to clean this up and package it as a real module, I
would be happy to do so.

sorry for the tangent. just one of those days.

John


-- 
John Meacham - ⑆repetae.net⑆john⑈

-- Copyright (c) 2007 John Meacham (john at repetae dot net)
-- 
-- Permission is hereby granted, free of charge, to any person obtaining a
-- copy of this software and associated documentation files (the
-- "Software"), to deal in the Software without restriction, including
-- without limitation the rights to use, copy, modify, merge, publish,
-- distribute, sublicense, and/or sell copies of the Software, and to
-- permit persons to whom the Software is furnished to do so, subject to
-- the following conditions:
-- 
-- The above copyright notice and this permission notice shall be included
-- in all copies or substantial portions of the Software.
-- 
-- THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS
-- OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF
-- MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT.
-- IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY
-- CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT,
-- TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE
-- SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE.

-- efficient lazy naturals

module Util.LazyNum where

-- Nat data type is eqivalant to a type restricted lazy list that is strict in
-- its elements.
--
-- Invarients: (Sum x _) => x > 0
-- in particular (Sum 0 _) is _not_ valid and must not occur.

data Nat = Sum !Integer Nat | Zero
deriving(Show)

instance Eq Nat where
Zero == Zero = True
Zero == _ = False
_ == Zero = False
Sum x nx == Sum y ny = case compare x y of
EQ -> nx == ny
LT -> nx == Sum (y - x) ny
GT -> Sum (x - y) nx == ny


instance Ord Nat where
Zero <= _ = True
_ <= Zero = False
Sum x nx <= Sum y ny = case compare x y of
EQ -> nx <= ny
LT -> nx <= Sum (y - x) ny
GT -> Sum (x - y) nx <= ny

Zero `compare` Zero = EQ
Zero `compare` _ = LT
_`compare` Zero = GT
Sum x nx `compare` Sum y ny = case compare x y of
EQ -> nx `compare` ny
LT -> nx `compare` Sum (y - x) ny
GT -> Sum (x - y) nx `compare` ny

x < y = not (x >= y)
x >= y = y <= x
x > y = y < x


instance Num Nat where
Zero + y = y
x + Zero = x
Sum x n1 + Sum y n2 = Sum (x + y) (n1 + n2)

Zero - _ = zero
x - Zero = x
Sum x n1 - Sum y n2 = case compare x y of
GT -> Sum (x - y) n1 - n2
EQ -> n1 - n2
LT -> n1 - Sum (y - x) n2
negate _ = zero
abs x = x
signum Zero = zero
signum _ = one
fromInteger x = if x <= 0 then zero else Sum x Zero

Zero * _ = Zero
_ * Zero = Zero
(Sum x nx) * (Sum y ny) = Sum (x*y) ((f x ny) + (nx * (fint y + ny))) where
f y Zero = Zero
f y (Sum x n) = Sum (x*y) (f y n)



instance Real Nat where
toRational n = toRational (toInteger n)

instance Enum Nat where
succ x = Sum 1 x
pred Zero = Zero
pred (Sum n x) = if n == 1 then x else Sum (n - 1) x
enumFrom x = x:[ Sum n x | n <- [1 ..]]
enumFromThen x y = x:y:f (y + z) where
z = y - x
f x = x:f (x + z)
toEnum = fromIntegral
fromEnum = fromIntegral

-- d > 0
doDiv :: Nat -> Integer -> Nat
doDiv n d = f 0 n where
f _ Zero = 0
f cm (Sum x nx) = sum d (f m nx) where
(d,m) = (x + cm) `quotRem` d
sum 0 x = x
sum n x = Sum n x

doMod :: Nat -> Integer -> Nat
doMod n

Re: [Haskell-cafe] Re: Bug in runInteractiveProcess?

2007-10-16 Thread Brandon S. Allbery KF8NH


On Oct 16, 2007, at 21:40 , Richard A. O'Keefe wrote:


F_GETFD and F_SETFD are the things to look for; FD_CLOEXEC is a fancy
way of saying 1 in historic UNIXes.  The OSF/1 /usr/include/sys/
fcntl.h says that FD_CLOEXEC is "POSIX REQUIRED".  This facility is
most certainly part of the Single Unix Specification.  The MacOS 10.4
manual page for fcntl() doesn't mention FD_CLOEXEC, but it *does*
mention F_GETFD and F_SETFD and identifies the close-on-execute flag
as being the "low-order bit" of that flags word, so what may possibly
be missing from some editions of POSIX is the *name* FD_CLOEXEC but
not the facility (F_SETFD) or the value (1).


I could dig for official confirmation, but this is my understanding  
of both POSIX and SUS, and portable C programs generally #define  
FD_CLOEXEC to 1 if it doesn't already exist, since the value *is*  
standard even though the name is not.


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


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


Re: [Haskell-cafe] Strange subtract operator behavior

2007-10-16 Thread Lennart Augustsson
If naturals have a perfectly reasonable subtraction then they also have a
perfectly reasonable negate; the default is 0-x.

(Oh, subtraction wasn't THAT reasonable, you say. :) )

  -- Lennart


On 10/17/07, John Meacham <[EMAIL PROTECTED]> wrote:
>
> On Tue, Oct 16, 2007 at 06:27:19PM -0300, Isaac Dupree wrote:
> > Peter Verswyvelen wrote:
> > >Personally I could also live with allowing no space between the minus
> > >sign and the number... If you leave a space, - becomes the subtract
> > >operator.
> >
> > I once thought that... there was the opposition that (x-1) subtraction
> > of a constant appears too often.  And I found that I myself wrote that
> > several times.  And saying "whitespace on the left but not the right"
> > seems too complicated for Haskell lexer semantics.  So the current
> > situation is just unhappy, that's all. (and maybe compiler warnings
> > could still be implemented)
>
> not just unhappy, but inefficient.
> -10 tranlates to (negate (fromInteger 10)) requiring 2 indirect class
> calls rather than what one might expect (fromInteger -10)
>
> also, negate in Num is sort of ugly IMHO. It would be nice if it wern't
> there. Things like naturals have a perfectly reasonable subtract, but no
> negate.
>
> I think losing x-1 would be worth it. but I know there were some other
> ideas out there that might be preferable but could still be handled at
> the lexing stage rather than the parsing one...
>
> John
>
>
> --
> John Meacham - ⑆repetae.net⑆john⑈
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Bug in runInteractiveProcess?

2007-10-16 Thread Richard A. O'Keefe

On 17 Oct 2007, at 10:58 am, John Goerzen wrote:
Do you mean FD_CLOEXEC, which can be set with fcntl()?  If so, it's  
not

defined in POSIX according to the Linux manpage.  I couldn't find
CLOSE_ON_EXEC in either open(2) or fcntl(2).


F_GETFD and F_SETFD are the things to look for; FD_CLOEXEC is a fancy
way of saying 1 in historic UNIXes.  The OSF/1 /usr/include/sys/
fcntl.h says that FD_CLOEXEC is "POSIX REQUIRED".  This facility is
most certainly part of the Single Unix Specification.  The MacOS 10.4
manual page for fcntl() doesn't mention FD_CLOEXEC, but it *does*
mention F_GETFD and F_SETFD and identifies the close-on-execute flag
as being the "low-order bit" of that flags word, so what may possibly
be missing from some editions of POSIX is the *name* FD_CLOEXEC but
not the facility (F_SETFD) or the value (1).


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


Re: [Haskell-cafe] Strange subtract operator behavior

2007-10-16 Thread John Meacham
On Tue, Oct 16, 2007 at 06:27:19PM -0300, Isaac Dupree wrote:
> Peter Verswyvelen wrote:
> >Personally I could also live with allowing no space between the minus 
> >sign and the number... If you leave a space, - becomes the subtract 
> >operator.
> 
> I once thought that... there was the opposition that (x-1) subtraction 
> of a constant appears too often.  And I found that I myself wrote that 
> several times.  And saying "whitespace on the left but not the right" 
> seems too complicated for Haskell lexer semantics.  So the current 
> situation is just unhappy, that's all. (and maybe compiler warnings 
> could still be implemented)

not just unhappy, but inefficient. 
-10 tranlates to (negate (fromInteger 10)) requiring 2 indirect class
calls rather than what one might expect (fromInteger -10)

also, negate in Num is sort of ugly IMHO. It would be nice if it wern't
there. Things like naturals have a perfectly reasonable subtract, but no
negate.

I think losing x-1 would be worth it. but I know there were some other
ideas out there that might be preferable but could still be handled at
the lexing stage rather than the parsing one...  

John


-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] OzHaskell?!?

2007-10-16 Thread Manuel M T Chakravarty

I wrote a while ago,
There is AngloHaskell and now AmeroHaskell.  Doesn't that call for 
OzHaskell?


  http://haskell.org/haskellwiki/OzHaskell


In the meantime a number of interested people put their name down on 
the wiki page.  So, let's talk more concretely about a first 
meeting.  I have put two (very rough) options for a date of a first 
meeting on the wiki page as well as notes about the possible format. 
 Please note your preferences and any additional ideas and 
suggestions on the wiki page.


I also started a section to collect possible talks and demos we 
could have.  Again, add anything you'd like to contribute.  (It's 
fine to be speculative, you commit to nothing at this stage.)


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


[Haskell-cafe] Re: [Haskell] IN Doubt...

2007-10-16 Thread ajb

[Moved to haskell-cafe]

G'day all.

Quoting Don Stewart <[EMAIL PROTECTED]>:


You can't pattern match 'a' and 'a' like that -- there's no implicit
unification.


Since we're being nostalgic in other threads, this is #1 on my list of
things I miss from Miranda.

It's also high on my "things that are damned useful in 1000-line programs
but would wreak silent havoc in large applications" list.

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


[Haskell-cafe] using quickcheck to generate test (table) data

2007-10-16 Thread Thomas Hartman
I wanted to generate some random table data, and decided to use quickcheck 
to do this. I didn't want to be checking properties, I actually wanted to 
output the examples that quickcheck came up with using arbitrary. In this 
case, I wanted to generate lists of lists of strings.

In case this is of use to anyone else here's an example...

One thing I don't understand is the purpose of the first argument to 
generate. If it's zero it's always the same data, so I made it a larger 
number (1). Seems ok, but it would be nice to understand why. Or if 
there is a better bway to accomplish this.

t.


{-# OPTIONS -fno-monomorphism-restriction #-}
module GenTestData where

import Test.QuickCheck
import Control.Monad
import System.Random
import Test.QuickCheck

import Misc
import ArbitraryInstances

f >>=^ g = f >>= return . g
infixl 1 >>=^


rgenIntList = rgen (arbitrary :: Gen [Int]) :: IO [Int]
rgenInt = rgen (arbitrary :: Gen Int) :: IO Int
rgenFoo = rgen (arbitrary :: Gen Foo ) :: IO Foo
rgenFoos = rgen (arbitrary :: Gen [Foo]) :: IO [Foo]
rgenString' = rgen (arbitrary :: Gen [Char]) :: IO [Char]
rgenString len = rgenString' >>=^ take len 
rgenStringRow' = rgen (arbitrary :: Gen [[Char]]) :: IO [[Char]]
rgenStringRow maxlenstr maxcols  = do
  rgenStringRow'
  >>=^ take maxcols 
  >>=^ map ( take maxlenstr )
rgenStringTable' = rgen (arbitrary :: Gen [[[Char]]]) :: IO [[[Char]]]
rgenStringTable maxlenstr maxcols maxrows = do
  rgenStringTable' 
  >>=^ take maxrows
  >>=^ map ( take maxcols )
  >>=^ ( map . map ) (take maxlenstr)

rgen gen = do
  sg <- newStdGen
  return $ generate 1 sg gen


module ArbitraryInstances where

import Test.QuickCheck
import Data.Char
import Control.Monad

instance Arbitrary Char where
arbitrary = choose ('\32', '\128')
coarbitrary c = variant (ord c `rem` 4)

-- joel reymont's example I think
data Foo
 = Foo Int
 | Bar
 | Baz
   deriving Show

instance Arbitrary Foo where
 coarbitrary = undefined
 arbitrary   = oneof [ return Bar
 , return Baz
 , liftM Foo arbitrary
 


---

This e-mail may contain confidential and/or privileged information. If you 
are not the intended recipient (or have received this e-mail in error) 
please notify the sender immediately and destroy this e-mail. Any 
unauthorized copying, disclosure or distribution of the material in this 
e-mail is strictly forbidden.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] Re: Trying to install binary-0.4

2007-10-16 Thread Ian Lynagh

[would it be possible to pick a single list to discuss this on please,
so there is no danger of some people missing some subthreads if they
aren't on all the lists, or getting messages 3 times if they are?]

On Tue, Oct 16, 2007 at 01:08:49PM +0100, Simon Marlow wrote:
> 
> 2. Precise dependencies.

While not directly related to this, I have the impression some people
want precise dependencies so that things work properly when multiple
versions of a library are installed.

Personally I'm not a fan of that, as if I have

package foo:
module Foo where
data T

package bar:
module Bar where
bar :: T

package baz:
module Baz where
baz :: T -> ()

then
baz bar
might be a type error if I have multiple versions of foo installed and
bar and baz have been compiled against different versions.


Thanks
Ian

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


[Haskell-cafe] Re: Proposal: register a package as providing several API versions

2007-10-16 Thread Daniel McAllansmith
On Wednesday 17 October 2007 01:32, ChrisK wrote:
> Simon Marlow wrote:
> > Several good points have been raised in this thread, and while I might
> > not agree with everything, I think we can all agree on the goal: things
> > shouldn't break so often.
>
> I have another concrete proposal to avoid things breaking so often.  Let us
> steal from something that works: shared library versioning on unixy
> systems.
>
> On Max OS X, I note that I have, in /usr/lib:
> > lrwxr-xr-x1 root  wheel15 Jul 24  2005 libcurl.2.dylib ->
> > libcurl.3.dylib lrwxr-xr-x1 root  wheel15 Jul 24  2005
> > libcurl.3.0.0.dylib -> libcurl.3.dylib -rwxr-xr-x1 root  wheel   
> > 201156 Aug 17 17:14 libcurl.3.dylib lrwxr-xr-x1 root  wheel15
> > Jul 24  2005 libcurl.dylib -> libcurl.3.dylib
>
> The above declaratively expresses that libcurl-3.3.0 provides the version 3
> API and the version 2 API.
>
> This is the capability that should be added to Haskell library packages.
>
> Right now a library can only declare a single version number.  So if I
> update hsFoo from 2.1.1 to 3.0.0 then I cannot express whether or not the
> version 3 API is a superset of (backward compatible with) the version 2
> API.

If 3.0.0 is a superset of 2.1.1 why was it necessary to bump to 3.0.0?  Why 
not 2.2.0?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] Re: Trying to install binary-0.4

2007-10-16 Thread Daniel McAllansmith
Following is a summary of my thoughts on the matter, in large part so I can 
figure out what I'm thinking... apologies if it's a bit of a ramble.  All 
comments welcome.


Basically
 - version numbering which differs from Simon's proposal
 - precise dependencies, I think the same as Simon is proposing
 - 'permanent' availability of compatible package versions
 - never a need to update working cabal files
 - a cabal file installs exactly one version of a package


1)
Package version numbers are of the form x.y.z


2)
There are version-segment ordering functions cmpX, cmpY, and cmpZ.

cmpX and cmpY are globally defined and operate over non-negative integers.  
Perhaps cmpZ is globally defined, or could be defined per package, or be 
lexicographic, or... something else.  cmpZ could even be a partial ordering I 
suppose.


3)
A cabal file specifies how to build a single version of a package.
name: foo
version: 2.12.5

This cabal file will build version 2.12.5 of package foo.


4)
The dependencies in a cabal file define baseline versions of required 
packages.
depends: bar [3.4]
 baz [1.2.6, 3]

Version 2.12.5 of foo requires a version of bar that is API-compatible with 
3.4.0 and a version of baz that is API-compatible with 1.2.6 _or_ 
API-compatible with 3.0.0.
Note that this doesn't imply that baz 3.0.0 is API-compatible with baz 1.2.6 
(by definition it is not), it implies that foo is using a subset of the 
intersection of those two baz APIs.
Note that baz 2.y.z would not satisfy the dependency.  Perhaps a function was 
removed with the bump to 2 and restored only with the bump to 3.


5)
Package version numbers encode whether one version of a package is 
API-compatible with another version of the package.

Given two versions x.y.z and i.j.k of a package:

 - x == i && y == j
==> x.y.z is API-identical (hence API-compatible) with i.j.k, cmpZ can be 
used to determine preferred version

 - x == i && y > j
==> x.y.z is API-compatible with i.j.k, it has undergone 
compatibility-preserving changes, x.y.z is preferred to i.j.k

 - x > i
==> x.y.z is not API-compatible with i.j.k, it has undergone 
non-compatibility-preserving changes

 - otherwise
==> x.y.z is not API-compatible with i.j.k, it is a lower version that has 
less functionality


6)
A compatibility-preserving change is generally a change which just adds to the 
API.  Ross Paterson points out adding extra data constructors or instances 
may not be compatibility-preserving.

A non-compatibility-preserving change is generally a change which includes the 
removal of some part of the API.  It might also include changes which leave 
the API unmodified but significantly degrade usability, e.g. worse time or 
space performance.


7)
Once a version of a package is building successfully it remains available for 
a 'long time'.  If sufficient versions of a package remain available then 
API-compatible versions of required packages are always available, so the 
building of packages should never break.  An uploaded cabal file should never 
need to be changed, regardless of what happens to the packages it depends 
upon.


8)
If a version of a package is discovered to have security flaws or serious bugs 
it should remain available in a quarantined state until a fixed 
API-compatible version is available.


9)
Something (hackage?) could enforce adherence to version numbering policy.  At 
the least any new version uploaded that claims to be API-compatible can be 
test compiled against packages which depend on it.

Something (hackage?) could assist package maintainers in releasing a new 
version of their package with updated dependency information.  Hackage could 
attempt to compile against non API-compatible versions and report the 
outcome, for example foo 2.12.5 compiles with the new baz 3.0.0 but not the 
latest baz 2.y.z


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


[Haskell-cafe] RE: [Haskell] Re: Trying to install binary-0.4

2007-10-16 Thread Duncan Coutts
On Tue, 2007-10-16 at 14:01 +0100, Bayley, Alistair wrote:
> > From: Simon Marlow [mailto:[EMAIL PROTECTED] 
> > 
> > The lexicographical ordering would make 10.0 > 9.3.  In 
> > general, A.B > C.D 
> > iff A > C or A == C && B > D.  When we say the "latest" 
> > version we mean 
> > "greatest", implying that version numbers increase with time. 
> >  Does that help?
> 
> 
> Sort of. It's what I'd expect from a sensible version comparison. It's
> just not something I'd ever choose to call lexicographic ordering. IMO,
> lexicographgic ordering is a basic string comparision so e.g.
> 
> max "10.0" "9.3" = "9.3"
> 
> I'd call what you're doing numeric ordering. Does it have a better name,
> like version-number-ordering, or section-number-ordering (e.g. Section
> 3.2.5, Section 3.2.6)?

It's lexicographic ordering on the list of numbers, not on the string
representation. 

ie it's

[10, 0] > [9, 3]

not 

"10.0" > "9.3"


Internally we represent version numbers as lists of integers and use the
default Ord instance.

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


[Haskell-cafe] Re: Bug in runInteractiveProcess?

2007-10-16 Thread John Goerzen
On 2007-10-16, Jules Bean <[EMAIL PROTECTED]> wrote:
> John Goerzen wrote:
>> Many systems will just try to close *all* FDs except the ones they need
>> after a fork().  Another approach would be to maintain a global list of
>> FDs that the Haskell thread is using, and close all of them except the
>> pipe ends in the child.
>
>> Does this make sense to everyone?  If so, I'll submit the bug on GHC.
>
> Yes, it does make sense.
>
> On POSIX systems it should suffice to just have haskell set 
> CLOSE_ON_EXEC on all its fds except std{in,out,err} and special pipe 
> fds, shouldn't it?

Do you mean FD_CLOEXEC, which can be set with fcntl()?  If so, it's not
defined in POSIX according to the Linux manpage.  I couldn't find
CLOSE_ON_EXEC in either open(2) or fcntl(2).

If FD_CLOEXEC is set in the Haskell process atomically, before anything
has a chance to fork off and use it, this would be an ideal solution on
platforms that support it.

-- John


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


Re: [Haskell-cafe] Bug in runInteractiveProcess?

2007-10-16 Thread Jules Bean

John Goerzen wrote:

Many systems will just try to close *all* FDs except the ones they need
after a fork().  Another approach would be to maintain a global list of
FDs that the Haskell thread is using, and close all of them except the
pipe ends in the child.



Does this make sense to everyone?  If so, I'll submit the bug on GHC.


Yes, it does make sense.

On POSIX systems it should suffice to just have haskell set 
CLOSE_ON_EXEC on all its fds except std{in,out,err} and special pipe 
fds, shouldn't it?


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


Re: [Haskell-cafe] Strange subtract operator behavior

2007-10-16 Thread Isaac Dupree

Peter Verswyvelen wrote:
Personally I could also live with allowing no space between the minus 
sign and the number... If you leave a space, - becomes the subtract 
operator.


I once thought that... there was the opposition that (x-1) subtraction 
of a constant appears too often.  And I found that I myself wrote that 
several times.  And saying "whitespace on the left but not the right" 
seems too complicated for Haskell lexer semantics.  So the current 
situation is just unhappy, that's all. (and maybe compiler warnings 
could still be implemented)


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


Re: [Haskell-cafe] Functional Programming Books

2007-10-16 Thread Don Stewart
dpiponi:
> I was just putting together my Amazon wish list and was wondering if
> there are any great books on Haskell and/or functional programming
> that people think are must-reads. Okasaki's "Purely Functional
> Programming", Pierce's "Types and Programming Languages" are frequent
> recommendations. Smullyan's "To Mock a Mockingbird" seems like it
> might be a good example from the lighter end. Are there any other
> classics I should know about?

http://www.labri.fr/perso/casteran/CoqArt/index.html

Is on my wishlist :)

You might find some other things here,

http://haskell.org/haskellwiki/Books_and_tutorials#Textbooks

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


Re: [Haskell-cafe] Strange subtract operator behavior

2007-10-16 Thread Peter Verswyvelen
Concurrent Clean uses the ~ symbol for unary negation. That's also a way 
of fixing it.


Personally I could also live with allowing no space between the minus 
sign and the number... If you leave a space, - becomes the subtract 
operator.


Coming from C++ I always make the mistake to forget parentheses around 
negative numbers in Haskell, which is very often needed.


Neil Mitchell wrote:

Hi

  

I think you should have to write negative numbers using the syntax
0-10, since currently having one single unary operator is ugly.
  

I think writing 0-10 is ugly.



Ugly - yes. But very clear as to its meaning. How often do people
actually write negative numeric literals? My guess is that -1 is the
most common by a long way, but even that is quite rare. Of course,
real statistics of real programs are the only answer.

Thanks

Neil


  


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


[Haskell-cafe] Functional Programming Books

2007-10-16 Thread Dan Piponi
I was just putting together my Amazon wish list and was wondering if
there are any great books on Haskell and/or functional programming
that people think are must-reads. Okasaki's "Purely Functional
Programming", Pierce's "Types and Programming Languages" are frequent
recommendations. Smullyan's "To Mock a Mockingbird" seems like it
might be a good example from the lighter end. Are there any other
classics I should know about?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Bug in runInteractiveProcess?

2007-10-16 Thread John Goerzen
Hi everyone,

I have been trying to implement a Haskell-like version of shell
pipelines using runInteractiveProcess.  I am essentially using
hGetContents to grab the output from one command, and passing that to
(forkIO $ hPutStr) to write to the next.  Slow, but this is just an
experiment.  This works OK to link together two external commands, but
deadlocks when linking together three processes.

After staring at straces all afternoon, I think I have found the
culprit.

I observed that when I have three commands linked together, the second
never sees EOF on its input.  This even though I saw an explicit close
on the other end of the pipe from the Haskell side.  Why is this, I
wondered?

I stared at the source for the C runInteractiveProcess function for a
bit, but then the answer was right there: this function does not
sanitize FDs.

What that means is that the write end of the stdin pipe for command 2
was open in the Haskell process.  The Haskell process then forked off
for command 3 later on.  This write end of the stdin pipe for command 2
was never closed in the command 3 child environment.  Therefore, closing
it in the Haskell thread did not cause command 2 to get an EOF.  Does
that make sense?

Many systems will just try to close *all* FDs except the ones they need
after a fork().  Another approach would be to maintain a global list of
FDs that the Haskell thread is using, and close all of them except the
pipe ends in the child.

Without something like this, it is not possible to use
runInteractiveProcess more than twice simultaneously in a single
program.  That renders it almost useless for some tasks.

Does this make sense to everyone?  If so, I'll submit the bug on GHC.

-- John

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


Re: [Haskell-cafe] Help parsing dates and times

2007-10-16 Thread Bjorn Bringert

On Oct 16, 2007, at 21:39 , Carl Witty wrote:


On Tue, 2007-10-16 at 09:25 -0700, Justin Bailey wrote:

On 10/16/07, Bjorn Bringert <[EMAIL PROTECTED]> wrote:

Should we just add XX:XX as an alternative time zone offset
format
accepted by %z and %Z? Is this a standard format?


Yes, this is standard; see below.


I'm not sure, but I am getting this date from Google in their XML
feeds representing calendar data. The specific element is "gd:when",
documented here:

http://code.google.com/apis/gdata/elements.html#gdWhen


That refers to XML Schema; the dateTime type in XML Schema is  
standardized here:

http://www.w3.org/TR/xmlschema-2/#dateTime
(and time zone offsets are required to have a colon in this format).


Thanks, I have added this to the parser now. I can't push right now  
because of performance problems, but it'll be in darcs soon.


Now it works:

Prelude Data.Time System.Locale> parseTime defaultTimeLocale "%FT%T%Q% 
z" "2008-06-26T11:00:00.087-07:00" :: Maybe ZonedTime

Just 2008-06-26 11:00:00.087 -0700

Note that I use %Q for the second decimals instead of .000, this  
makes it accept non-integer seconds.


/Björn



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


Re: [Haskell-cafe] Performance problem with random numbers

2007-10-16 Thread Stefan O'Rear
On Tue, Oct 16, 2007 at 06:07:39PM +0200, Peter Verswyvelen wrote:
> Does the GHC code generator makes use of SIMD instructions? Maybe via the C 
> compiler?

No.

GHC uses GCC extensions, and GCC doesn't support automatic SIMD use.

(You could use -unreg and an advanced compiler.  Good luck finding a
compiler smart enough to work around the idiocies incurred translating
Haskell to ANSI C; -unreg is very slow)

Stefan


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


[Haskell-cafe] Re: [Haskell] Re: Trying to install binary-0.4

2007-10-16 Thread Isaac Dupree

Neil Mitchell wrote:

Hi


I agree. >= 1.0 isn't viable in the long term. Rather, a specific list,
or bounded range of tested versions seems likely to be more robust.


In general, if it compiles and type checks, it will work. It is rare
that an interface stays sufficiently similar that the thing compiles,
but then crashes at runtime.


True..

GoboLinux's package system records the exact set of versions something 
compiles with (just for reference), and uses min version bounds (and max 
bounds where needed) for dependencies.


It's always possible for Haskell library implementation-bug-fixes to 
change relied-on behavior, as discussed in the original ECT description. 
 I agree that compiling and type-checking is a pretty good sign of 
working.  Passing tests (e.g. QuickCheck) could be tested too, where 
available.


If optimizations and unsafePerformIO interact differently, different 
compiler versions could also affect whether something works correctly, 
but still compiles... But, the issue here is much more limited:


we assume that there were some set of versions of these libraries that 
DID work, and,
that every version of each library, on its own (or with only the 
libraries it depends on), works.


So it might be valuable to record subjectively-working exact version 
sets, somewhere.


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


[Haskell-cafe] Re: [Haskell] Re: Trying to install binary-0.4

2007-10-16 Thread Neil Mitchell
Hi

> I agree. >= 1.0 isn't viable in the long term. Rather, a specific list,
> or bounded range of tested versions seems likely to be more robust.

In general, if it compiles and type checks, it will work. It is rare
that an interface stays sufficiently similar that the thing compiles,
but then crashes at runtime. Given that, shouldn't the tested versions
be something a machine figures out - rather than something each
library author has to tend to with every new release of every other
library in hackage?

Thanks

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


[Haskell-cafe] Re: [Haskell] Re: Trying to install binary-0.4

2007-10-16 Thread Don Stewart
simonmarhaskell:
> Several good points have been raised in this thread, and while I might not 
> agree with everything, I think we can all agree on the goal: things 
> shouldn't break so often.
> 
> So rather than keep replying to individual points, I'd like to make some 
> concrete proposals so we can make progress.
> 
> 1. Document the version numbering policy.
> 
> We should have done this earlier, but we didn't.  The proposed policy, for 
> the sake of completeness is: x.y where:
> 
>   x changes ==> API changed
>   x constant but y changes ==> API extended only
>   x and y constant ==> API is identical
> 
> further sub-versions may be added after the x.y, their meaning is 
> package-defined.  Ordering on versions is lexicographic, given multiple 
> versions that satisfy a dependency Cabal will pick the latest.
> 
> 2. Precise dependencies.
> 
> As suggested by various people in this thread: we change the convention so 
> that dependencies must specify a single x.y API version, or a range of 
> versions with an upper bound.  Cabal or Hackage can refuse to accept 
> packages that don't follow this convention (perhaps Hackage is a better 
> place to enforce it, and Cabal should just warn, I'm not sure).

I agree. >= 1.0 isn't viable in the long term. Rather, a specific list,
or bounded range of tested versions seems likely to be more robust.

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


Re: [Haskell-cafe] Help parsing dates and times

2007-10-16 Thread Carl Witty
On Tue, 2007-10-16 at 09:25 -0700, Justin Bailey wrote:
> On 10/16/07, Bjorn Bringert <[EMAIL PROTECTED]> wrote:
> 
> Should we just add XX:XX as an alternative time zone offset
> format
> accepted by %z and %Z? Is this a standard format?

Yes, this is standard; see below.

> I'm not sure, but I am getting this date from Google in their XML
> feeds representing calendar data. The specific element is "gd:when",
> documented here: 
> 
> http://code.google.com/apis/gdata/elements.html#gdWhen

That refers to XML Schema; the dateTime type in XML Schema is standardized here:
http://www.w3.org/TR/xmlschema-2/#dateTime
(and time zone offsets are required to have a colon in this format).

Carl Witty


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


Re: [Haskell-cafe] Equality Question

2007-10-16 Thread Dan Weston
Your intuition that id is related to const is a good one, since id can 
be defined in terms of const. Here is one of many:


id' = flip const const

[This is also called a CKK combinator. See 
http://en.wikipedia.org/wiki/S_combinator#Combinatory_calculi for more 
examples, such as SKK, SKS, and various other identity equivalents.]


Whether these are "different" identity functions is an interesting 
question. Ask yourself how you could tell them apart. What if they both 
always gave the same answer, but one always took longer than the other? 
Are you allowed to "peek at the code" before deciding on equality? Does 
it even matter whether there is only one identity? [AKA, is function 
application faithful?] Interesting stuff. More at:


http://en.wikipedia.org/wiki/Semiautomaton

Dan

PR Stanley wrote:

Hi
is const = id?
const 'x' 'y'
'x'
id 'x'
'x'

Cheers,
Paul

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





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


[Haskell-cafe] Re: [Haskell] Re: Trying to install binary-0.4

2007-10-16 Thread Isaac Dupree

Ross Paterson wrote:

I would make "API extended only" a bit more precise: any module that uses
explicit import lists will not be affected by the changes.  So one can
add classes, types and functions, but not instances (except where either
the class or the type is new).


okay


You probably can't add data constructors
or fields, and have to be careful with new methods.


If they're exported and new members of existing classes/datatypes, then 
you can't add them, because they might be imported with 
"class/typename(..)". (right?)


What about semantic changes to the API?  Including, adding a default to 
a class method changes the default from 'undefined', which someone might 
have relied on as the default (although it seems unlikely).


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


Re: [Haskell-cafe] System.Posix

2007-10-16 Thread Bjorn Bringert
If you want to try and implement some of the System.Posix API using  
the win32 API, a good place to put that would be in the unix-compat  
package.


Darcs repo: http://www.cs.chalmers.se/~bringert/darcs/unix-compat/
Hackage page: http://hackage.haskell.org/cgi-bin/hackage-scripts/ 
package/unix-compat-0.1


It currently re-exports the unix package if available, and if not,  
tries to fake it using the standard libraries or sensible defaults.  
Using the win32 package would be a nice addition.


/Björn

On Oct 16, 2007, at 20:35 , Galchin Vasili wrote:


Hi Bjorn (and everybody),

What would it entail to get System.Posix working on Windows?  
Would a mininum requirement e.g. be teh installation of http:// 
www.cygwin.com? Or write a POSIX API to Win32 API binding? If I  
understand the problem, I wouldn't mind giving a run at it!


Regards, Bill


On 10/16/07, Bjorn Bringert <[EMAIL PROTECTED]> wrote: On Oct  
16, 2007, at 3:25 , Galchin Vasili wrote:


> Hello,
>
> In a Hugs environment, I am able to import System.Directory but
> not to import System.Posix. Here is my environment ... .;{Hugs}
> \packages\*;C:\ftp\CatTheory\Haskell\SOE\graphics\lib\win32\*. I
> really want to use the Posix module. Help!!!
>
> Kind regards, Bill Halchin

Hi Bill,

it seems like you are using Hugs under Windows. As far as I know
System.Posix is not available on Windows.

/Björn






/Björn



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


[Haskell-cafe] Re: [Haskell] Re: Trying to install binary-0.4

2007-10-16 Thread Ross Paterson
On Tue, Oct 16, 2007 at 01:08:49PM +0100, Simon Marlow wrote:
> So rather than keep replying to individual points, I'd like to make some 
> concrete proposals so we can make progress.
>
> 1. Document the version numbering policy.
>
> We should have done this earlier, but we didn't.  The proposed policy, for 
> the sake of completeness is: x.y where:
>
>   x changes ==> API changed
>   x constant but y changes ==> API extended only
>   x and y constant ==> API is identical
>
> further sub-versions may be added after the x.y, their meaning is 
> package-defined.

This should be required for at least the GHC boot packages (and encouraged
for others).

I would make "API extended only" a bit more precise: any module that uses
explicit import lists will not be affected by the changes.  So one can
add classes, types and functions, but not instances (except where either
the class or the type is new).  You probably can't add data constructors
or fields, and have to be careful with new methods.

I'd also prefer that major versions used two numbers, because that's
common now, it supports the experimental versions 0.x apfelmus mentioned,
and it makes it easier to leave room for development versions (possibly
using an odd-even scheme).  If you make your development repository
available, and it contains API changes, you'll want its version number
to have a larger major number.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Strange subtract operator behavior

2007-10-16 Thread David Christensen

I think you should have to write negative numbers using the syntax
0-10, since currently having one single unary operator is ugly.


I think writing 0-10 is ugly.


Ugly - yes. But very clear as to its meaning. How often do people
actually write negative numeric literals? My guess is that -1 is the
most common by a long way, but even that is quite rare. Of course,
real statistics of real programs are the only answer.


If you were doing away with unary minus, I'd prefer going for it  
entirely and going for negate :: (Num a) => a -> a.  It could also be  
compile-time folded, so no performance impact obviously.


It also expresses intent without looking as ugly:

minusTen:: negate 10

David


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


Re: [Haskell-cafe] System.Posix

2007-10-16 Thread Galchin Vasili
Hi Bjorn (and everybody),

What would it entail to get System.Posix working on Windows? Would a
mininum requirement e.g. be teh installation of http://www.cygwin.com? Or
write a POSIX API to Win32 API binding? If I understand the problem, I
wouldn't mind giving a run at it!

Regards, Bill


On 10/16/07, Bjorn Bringert <[EMAIL PROTECTED]> wrote:
>
> On Oct 16, 2007, at 3:25 , Galchin Vasili wrote:
>
> > Hello,
> >
> > In a Hugs environment, I am able to import System.Directory but
> > not to import System.Posix. Here is my environment ... .;{Hugs}
> > \packages\*;C:\ftp\CatTheory\Haskell\SOE\graphics\lib\win32\*. I
> > really want to use the Posix module. Help!!!
> >
> > Kind regards, Bill Halchin
>
> Hi Bill,
>
> it seems like you are using Hugs under Windows. As far as I know
> System.Posix is not available on Windows.
>
> /Björn
>
>
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Strange subtract operator behavior

2007-10-16 Thread Michael Campbell
On 10/16/07, Neil Mitchell <[EMAIL PROTECTED]> wrote:

> Ugly - yes. But very clear as to its meaning. How often do people
> actually write negative numeric literals?

Any time I need one.  And I can guarantee I don't make the compiler
perform an arithmetic computation to get one, either.



-- 
Wise men talk because they have something to say; fools, because they
have to say something. -- Plato
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Strange subtract operator behavior

2007-10-16 Thread Neil Mitchell
Hi

> > I think you should have to write negative numbers using the syntax
> > 0-10, since currently having one single unary operator is ugly.
>
> I think writing 0-10 is ugly.

Ugly - yes. But very clear as to its meaning. How often do people
actually write negative numeric literals? My guess is that -1 is the
most common by a long way, but even that is quite rare. Of course,
real statistics of real programs are the only answer.

Thanks

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


Re: [Haskell-cafe] Distributed haskell using Hadoop

2007-10-16 Thread Adam Langley
On 10/16/07, Brad Clow <[EMAIL PROTECTED]> wrote:
> I would prefer a more Haskell orientated solution and welcome any
> suggestions. If not maybe this will be of use to others.

Well, Hadoop is aiming towards a Google style of cluster processing
and the path towards that is pretty clear:

1) An XDR like serialisation scheme with support for backwards
compatibility (which involves unique-for-all-time ids in the IDL and
"required", "optional" etc tag). Data.Binary would be a great start
for this, but it's sadly lazy in parsing and they never applied my
patch for optional strictness so one would probably have to start from
scratch.

2) An RPC system which handles the most common use case: arguments and
replies are serialised using the above system, TCP transport, simple
timeouts, STM for concurrency.

Then you can start doing cool stuff like using the GHC API for code
motion and building a simple MapReduce like framework etc.

-- 
Adam Langley  [EMAIL PROTECTED]
http://www.imperialviolet.org   650-283-9641
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Strange subtract operator behavior

2007-10-16 Thread Derek Elkins
On Tue, 2007-10-16 at 17:02 +0100, Neil Mitchell wrote:
> Hi
> 
> >  (/ 10) means the function that divides its argument by 10
> >  (- 10) however is just the number -10, even if I put a space between the -
> > and 10.
> >
> >  How can I create a function that subtracts 10 from its argument in a clean
> > way then?
> 
> subtract is the way to go. (`subtract` 10)

subtract 10 not (`subtract` 10) (that would be flip subtract 10 which
would just be (10 -)

> I think you should have to write negative numbers using the syntax
> 0-10, since currently having one single unary operator is ugly.

I think writing 0-10 is ugly.

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


Re: [Haskell-cafe] Re: Proposal: register a package asprovidingseveral API versions

2007-10-16 Thread Claus Reinke

are those tricks necessary in this specific case? couldn't we
have a list/range of versions in the version: field, and let cabal
handle the details?


I don't understand what you're proposing here.  Surely just writing

version: 1.0, 2.0

isn't enough - you need to say what the 1.0 and 2.0 APIs actually *are*, 
and then wouldn't that require more syntax?  I don't yet see a good reason 
to do this in a single .cabal file instead of two separate packages.  The 
two-package way seems to require fewer extensions to Cabal.


yes, and no. cabal is currently not symmetric in this: providers
specify apis (at the level of exposed modules), clients only specify
api numbers as dependencies.

the idea was for the cabal file to specify a single provided api,
but to register that as sufficient for a list of dependency numbers.
so the package would implement the latest api, but could be used
by clients expecting either the old or the new api.


aside: what happens if we try to combine two modules M and N
that use the same api A, but provided by two different packages
P1 and P2? say, M was built when P1 was still around, but when
N was built, P2 had replaced P1, still supporting A, but not necessarily 
with the same internal representation as used in P1.


Not sure what you mean by "try to combine".  A concrete example?


lets see - how about this:

-- package P-1, Name: P, Version: 0.1
module A(L,f,g) where
newtype L a = L [a]
f  a (L as) = elem a as
g as = L as

-- package P-2, Name: P, Version: 0.2
module A(L,f,g) where
newtype L a = L (a->Bool)
f  a (L as) = as a
g as = L (`elem` as)

if i got this right, both P-1 and P-2 support the same api A, right
down to types. but while P-1's A and P-2's A are each internally
consistent, they can't be mixed. now, consider

module M where
import A
m = g [1,2,3]

module N where
import A
n :: Integer -> A.L Integer -> Bool
n = f

so, if i install P-1, then build M, then install P-2, then build N, 
wouldn't N pick up the "newer" P-2, while M would use the 
"older" P-1? and if so, what happens if we then add


module Main where
import M
import N
main = print (n 0 m)

i don't seem to be able to predict the result, without actually
trying it out. can you?-) i suspect it won't be pretty, though.

claus

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


Re: [Haskell-cafe] Help parsing dates and times

2007-10-16 Thread Justin Bailey
On 10/16/07, Bjorn Bringert <[EMAIL PROTECTED]> wrote:
>
>
> Should we just add XX:XX as an alternative time zone offset format
> accepted by %z and %Z? Is this a standard format?


I'm not sure, but I am getting this date from Google in their XML feeds
representing calendar data. The specific element is "gd:when", documented
here:

http://code.google.com/apis/gdata/elements.html#gdWhen

Hmm, ok, parsedate allows garbage at the end. I wonder what is the
> right thing to do here.


A wildcard that allowed me to say "don't care" would work. If parseDate was
built on regular expressions, then you could do whatever you wanted. I'm not
familiar with the C roots of this function, though, so maybe it's best to do
whatever it does.

Regardless, I'm glad to have something. I can always filter/chop the string
to remove the bits I don't care about. It's a good library.

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


Re: [Haskell-cafe] Distributed haskell using Hadoop

2007-10-16 Thread Murray Gross



At Brooklyn College we have been running distributed Haskell (release 5, 
though) under Linux/Mosic for several years. There are some problems, but 
we think they are well under control.


Murray Gross
Brooklyn College,
City University of New York





On Tue, 16 Oct 2007, Brad Clow wrote:


I was looking around for a haskell solution for distributing a
computation across multiple machines and couldn't find anything that
looked current and alive. I found out that the Hadoop project (java
based) can interact with binary executables via stdin and stdout. So I
have set up a Hadoop cluster of 5 machines, wrapped my Haskell code to
accept data via stdin and write results to stdout and successfully
executed it on the cluster.

I would prefer a more Haskell orientated solution and welcome any
suggestions. If not maybe this will be of use to others.

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


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


Re: [Haskell-cafe] Help parsing dates and times

2007-10-16 Thread Bjorn Bringert

On Oct 16, 2007, at 17:54 , Justin Bailey wrote:


On 10/16/07, Bjorn Bringert <[EMAIL PROTECTED]> wrote:

Hmm, perhaps I should clarify this: parsedate and time-1.1.1 (which
comes with GHC 6.6.1) have different APIs. parsedate produces
CalendarTimes, and the code in time-1.1.1 produces the new time and
date data types. So I guess parsedate isn't actually obsolete,
rather, it's for use with the package currently known as 'old-time'.

Given this date string:

  2008-06-26T11:00:00.000-07:00

The problem is the parseTime function in Data.Time.Format is a  
little too strict. The following GHCi session shows the different  
behaviors. Notice how %Z is unable to parse the time zone offset in  
any case. First we try parseTime:


  > :m + Data.Time System.Time.Parse System.Locale
  > let dateStr = "2008-06-26T11:00:00.000-07:00"
  > parseTime defaultTimeLocale "%FT%X.000%z" dateStr :: Maybe UTCTime
  Nothing
  > parseTime defaultTimeLocale "%FT%X.000-%z" dateStr :: Maybe  
UTCTime

  Nothing
  > parseTime defaultTimeLocale "%FT%X.000" dateStr :: Maybe UTCTime
  Nothing


I guess you really want a ZonedTime here, if you want to retain the  
time zone info.


It seems like %z and %Z require 4 digits for a time zone offset,  
without a colon. This works:


> parseTime defaultTimeLocale "%FT%X.000%z"  
"2008-06-26T11:00:00.000-0700" :: Maybe ZonedTime

Just 2008-06-26 11:00:00 -0700

Should we just add XX:XX as an alternative time zone offset format  
accepted by %z and %Z? Is this a standard format?



Now parseCalendarTime from the parseDate package:

  > parseCalendarTime defaultTimeLocale "%Y-%m-%dT%H:%M:%S" dateStr
  Just (CalendarTime {ctYear = 2008, ctMonth = June, ctDay = 26,  
ctHour = 11, ctMin = 0, ctSec = 0, ctPicosec = 0, ctWDay

= Thursday, ctYDay = 1, ctTZName = "UTC", ctTZ = 0, ctIsDST = False})
  > parseCalendarTime defaultTimeLocale "%Y-%m-%dT%H:%M:%S.000%Z"  
dateStr

  Nothing


Hmm, ok, parsedate allows garbage at the end. I wonder what is the  
right thing to do here.


/Björn



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


Re: [Haskell-cafe] Performance problem with random numbers

2007-10-16 Thread Peter Verswyvelen
Does the GHC code generator makes use of SIMD instructions? Maybe via 
the C compiler?


Cheers,
Peter

Simon Peyton-Jones wrote:

We'd be delighted if someone offered a more performant library to put into 
future GHC releases.

| I've seen similar results switching to the SIMD mersenne twister C
| implementation for randoms:


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


Re: [Haskell-cafe] Strange subtract operator behavior

2007-10-16 Thread Neil Mitchell
Hi

>  (/ 10) means the function that divides its argument by 10
>  (- 10) however is just the number -10, even if I put a space between the -
> and 10.
>
>  How can I create a function that subtracts 10 from its argument in a clean
> way then?

subtract is the way to go. (`subtract` 10)

I think you should have to write negative numbers using the syntax
0-10, since currently having one single unary operator is ugly.

Thanks

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


[Haskell-cafe] Strange subtract operator behavior

2007-10-16 Thread Peter Verswyvelen

(/ 10) means the function that divides its argument by 10
(- 10) however is just the number -10, even if I put a space between the 
- and 10.


How can I create a function that subtracts 10 from its argument in a 
clean way then?


I could use (flip (-) 10) but that looks like a hack.

Thanks,
Peter








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


Re: [Haskell-cafe] Help parsing dates and times

2007-10-16 Thread Justin Bailey
On 10/16/07, Bjorn Bringert <[EMAIL PROTECTED]> wrote:
>
>
> Hmm, perhaps I should clarify this: parsedate and time-1.1.1 (which
> comes with GHC 6.6.1) have different APIs. parsedate produces
> CalendarTimes, and the code in time-1.1.1 produces the new time and
> date data types. So I guess parsedate isn't actually obsolete,
> rather, it's for use with the package currently known as 'old-time'.


Given this date string:

  2008-06-26T11:00:00.000-07:00

The problem is the parseTime function in Data.Time.Format is a little too
strict. The following GHCi session shows the different behaviors. Notice how
%Z is unable to parse the time zone offset in any case. First we try
parseTime:

  > :m + Data.Time System.Time.Parse System.Locale
  > let dateStr = "2008-06-26T11:00:00.000-07:00"
  > parseTime defaultTimeLocale "%FT%X.000%z" dateStr :: Maybe UTCTime
  Nothing
  > parseTime defaultTimeLocale "%FT%X.000-%z" dateStr :: Maybe UTCTime
  Nothing
  > parseTime defaultTimeLocale "%FT%X.000" dateStr :: Maybe UTCTime
  Nothing

Now parseCalendarTime from the parseDate package:

  > parseCalendarTime defaultTimeLocale "%Y-%m-%dT%H:%M:%S" dateStr
  Just (CalendarTime {ctYear = 2008, ctMonth = June, ctDay = 26, ctHour =
11, ctMin = 0, ctSec = 0, ctPicosec = 0, ctWDay
= Thursday, ctYDay = 1, ctTZName = "UTC", ctTZ = 0, ctIsDST = False})
  > parseCalendarTime defaultTimeLocale "%Y-%m-%dT%H:%M:%S.000%Z" dateStr
  Nothing


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


Re: [Haskell-cafe] Re: Proposal: register a package as providingseveral API versions

2007-10-16 Thread Simon Marlow

Claus Reinke wrote:

It could be done using the tricks that Claus just posted and I 
followed up on.  You'd need a separate package for hsFoo-2 that 
specifies exactly which bits of hsFoo-3 are re-exported.  Given some 
Cabal support and a little extension in GHC, this could be made 
relatively painless for the library maintainer.


are those tricks necessary in this specific case? couldn't we
have a list/range of versions in the version: field, and let cabal
handle the details?


I don't understand what you're proposing here.  Surely just writing

version: 1.0, 2.0

isn't enough - you need to say what the 1.0 and 2.0 APIs actually *are*, 
and then wouldn't that require more syntax?  I don't yet see a good reason 
to do this in a single .cabal file instead of two separate packages.  The 
two-package way seems to require fewer extensions to Cabal.



aside: what happens if we try to combine two modules M and N
that use the same api A, but provided by two different packages
P1 and P2? say, M was built when P1 was still around, but when
N was built, P2 had replaced P1, still supporting A, but not necessarily 
with the same internal representation as used in P1.


Not sure what you mean by "try to combine".  A concrete example?

Cheers,
Simon

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


Re: [Haskell-cafe] Re: Proposal: register a package as providingseveral API versions

2007-10-16 Thread Claus Reinke

I have another concrete proposal to avoid things breaking so often.  Let us
steal from something that works: shared library versioning on unixy systems.


indeed!-) there are established workarounds that are needed to 
make that system work as it does, so it is a good idea to check

whether cabal has the means to cover those situations.


The above declaratively expresses that libcurl-3.3.0 provides the version 3 API
and the version 2 API.

This is the capability that should be added to Haskell library packages.

Right now a library can only declare a single version number.  So if I update
hsFoo from 2.1.1 to 3.0.0 then I cannot express whether or not the version 3 API
is a superset of (backward compatible with) the version 2 API.


Certainly, this is something we want to support.  However, there's an 
important difference between shared-library linking and Haskell: in 
Haskell, a superset of an API is not backwards-compatible, because it has 
the potential to cause new name clashes.


yes, one would need to define what it means for one api to be 
compatible with another. even so, i think that permitting a single 
package to act as a provider for multiple versions of an api is

a necessary feature, even more so if loose dependency specs
like 'base', or 'base >= 1.0' are going to be discouraged.

It could be done using the tricks that Claus just posted and I followed up 
on.  You'd need a separate package for hsFoo-2 that specifies exactly which 
bits of hsFoo-3 are re-exported.  Given some Cabal support and a little 
extension in GHC, this could be made relatively painless for the library 
maintainer.


are those tricks necessary in this specific case? couldn't we
have a list/range of versions in the version: field, and let cabal
handle the details?

aside: what happens if we try to combine two modules M and N
that use the same api A, but provided by two different packages
P1 and P2? say, M was built when P1 was still around, but when
N was built, P2 had replaced P1, still supporting A, but not 
necessarily with the same internal representation as used in P1.


claus

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


Re: [Haskell-cafe] Re: [Haskell] Re: Trying to install binary-0.4

2007-10-16 Thread Claus Reinke

If the convention for modifying package versions of form x.y.z is:
- increment z for bugfixes/changes that don't alter the interface
- increment y for changes that consist solely of additions to the interface, 
parts of the interface may be marked as deprecated
- increment x for changes that include removal of deprecated parts of the 
interface


i like this, but i doubt it will catch on (see my reply to Simon's summary).


The 'foo' package name is just an indicator of lineage.
foo-2.xxx is not the same package as foo-1.xxx, it's interface is missing 
something that foo-1.xxx's interface provided.


yes, that is the troublesome part.

Dependencies of "foo" shouldn't appear in published cabal files.  There is a 
case for their use in development where you are specifying that you want to 
depend on the very latest version of foo available, perhaps from darcs.  When 
you publish that latest version number gets burned in, eg "foo-2.1.20071016".


agreed, because of your point above. though i think we'll need 
to find a similarly convenient replacement.. or we'll be changing 
old cabal files forever.


As for provides/expects and imported-modules instead, isn't that just an 
arbitrary line drawn in the granularity sand?
Perhaps package versions could be expanded to include the type of every 
function they expose, plus more information to indicate which bugfix version 
of those functions is present.  That's maybe the Right Way... and probably a 
lot of work.


as with all type systems, there is a balance between preciseness,
decidability, and useability. just adding an imported-modules: field
would do no harm (like the exposed-modules: field, it should be 
inferred), but it would allow cabal to make better choices.


in the context of the base split, or similar api refactorings, package
names don't tell us much, package versions at best tell us that there
is a problem (and may not even tell us that); if existing packages
had an additional imported-modules: field, cabal could try to suggest
alternative providers - in the current case, that would be the new
base and its spin-off packages. then the user could just accept
those alternatives, and be happy.

claus

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


Re: [Haskell-cafe] Re: [Haskell] Re: Trying to install binary-0.4

2007-10-16 Thread Claus Reinke

1. Document the version numbering policy.


agreed. just making everybody's interpretation explicit has
already exposed subtle differences, so documenting common
ground will help.

We should have done this earlier, but we didn't.  The proposed policy, for 
the sake of completeness is: x.y where:


  x changes ==> API changed
  x constant but y changes ==> API extended only
  x and y constant ==> API is identical

further sub-versions may be added after the x.y, their meaning is 
package-defined.  Ordering on versions is lexicographic, given multiple 
versions that satisfy a dependency Cabal will pick the latest.


referring to a haskell function to compute ordering, or to parse
version strings into lists of numbers, might remove ambiguities
here. for instance, some people use patch-levels as sub-versions,
some use dates.

also, compare Simon's (S) with Daniel's (D) version:

| If the convention for modifying package versions of form x.y.z is:
|  - increment z for bugfixes/changes that don't alter the interface
|  - increment y for changes that consist solely of additions to the interface, 
|parts of the interface may be marked as deprecated
|  - increment x for changes that include removal of deprecated parts of the 
|   interface


version D gives us strictly more information from a version 
number: just from number differences, we can tell what kind 
of changes happened to the api. i like that.


version S is closer to current practice, which is less informative
but psychologically motivated:-) if one does a substantial
rewrite without changing the api, or if one adds fundamentally
new features without breaking backwards compatibility, one 
likes to bump the leading number (that is no doubt inspired by
commercialism: paying customers are said to prefer higher 
version numbers, and to focus on new features). 


corollary: after fixing the version numbering policy (policies?),
the implications on usage need to be investigated (sorting wrt
dates? does a version number tell us anything about which
version can stand in for which dependency?).


2. Precise dependencies.

As suggested by various people in this thread: we change the convention so 
that dependencies must specify a single x.y API version, or a range of 
versions with an upper bound.  Cabal or Hackage can refuse to accept 
packages that don't follow this convention (perhaps Hackage is a better 
place to enforce it, and Cabal should just warn, I'm not sure).


Yes, earlier I argued that not specifying precise dependencies allows some 
packages to continue working even when dependencies change, and that having 
precise dependencies means that all packages are guaranteed to break when 
base is updated.  However, I agree that specifying precise dependencies is 
ultimately the right thing, we'll get better errors when things break,


agreed. please note, however, that this is likely to flush out
issues that have so far been swiped under the carpet. this is
a good thing, as it will lead to proposals for making cabal deal
with these issues properly (replacing unspecified user complaints
with concrete bugs and fixes). but it will increase the noise!-)

claus

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


Re: [Haskell-cafe] Help parsing dates and times

2007-10-16 Thread Bjorn Bringert

On Oct 16, 2007, at 16:16 , Bjorn Bringert wrote:


On Oct 16, 2007, at 2:25 , Don Stewart wrote:


jgbailey:
   I am trying to parse various date and time formats using the  
parseTime
   function found in (GHC 6.6.1) Data.Time.Format. The one that  
is giving me

   trouble looks like this:

 2008-06-26T11:00:00.000-07:00

   Specifically, the time zone offset isn't covered by the format  
parameters

   given. I can almost parse it with this:

 %FT%X.000

   But that doesn't take into account the "-07:00" bit. I'm sure  
this has
   been solved - can someone point me to the solution? Thanks in  
advance.


Try %z

(see http://www.haskell.org/ghc/docs/latest/html/libraries/time/ 
Data-Time-Format.html#v%3AformatTime for all the format specifiers).



Is there anything in the parsedate library?

http://hackage.haskell.org/cgi-bin/hackage-scripts/package/ 
parsedate-2006.11.10
http://hackage.haskell.org/packages/archive/parsedate/ 
2006.11.10/doc/html/System-Time-Parse.html


-- Don


parsedate is obsolete, unless you have ghc < 6.6.1. It was  
rewritten to become what is now the date parsing code in the time  
package.


Hmm, perhaps I should clarify this: parsedate and time-1.1.1 (which  
comes with GHC 6.6.1) have different APIs. parsedate produces  
CalendarTimes, and the code in time-1.1.1 produces the new time and  
date data types. So I guess parsedate isn't actually obsolete,  
rather, it's for use with the package currently known as 'old-time'.


/Björn

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


[Haskell-cafe] Re: Proposal: register a package as providing several API versions

2007-10-16 Thread Ketil Malde
ChrisK <[EMAIL PROTECTED]> writes:

> Once it is possible to have cabal register the hsFoo-3.0.0 also as hsFoo-2 it
> will be easy to upgrade to hsFoo.  No old programs will fail to compile.

> Who here knows enough about the ghc-pkg database to say how easy or hard this
> would be?

Ignoring disk space, I suppose the motivation is that it will ease the
user experience by only having to download, compile and install a
single package?  And perhaps ease the maintenance a bit for the
library author, too.

One way to do this would be to have multiple .cabal files in the
package, with small differences like different version numbering.
You can use a Makefile or other hack to automate switching.

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Help parsing dates and times

2007-10-16 Thread Bjorn Bringert

On Oct 16, 2007, at 2:25 , Don Stewart wrote:


jgbailey:
   I am trying to parse various date and time formats using the  
parseTime
   function found in (GHC 6.6.1) Data.Time.Format. The one that is  
giving me

   trouble looks like this:

 2008-06-26T11:00:00.000-07:00

   Specifically, the time zone offset isn't covered by the format  
parameters

   given. I can almost parse it with this:

 %FT%X.000

   But that doesn't take into account the "-07:00" bit. I'm sure  
this has
   been solved - can someone point me to the solution? Thanks in  
advance.


Try %z

(see http://www.haskell.org/ghc/docs/latest/html/libraries/time/Data- 
Time-Format.html#v%3AformatTime for all the format specifiers).



Is there anything in the parsedate library?

http://hackage.haskell.org/cgi-bin/hackage-scripts/package/ 
parsedate-2006.11.10
http://hackage.haskell.org/packages/archive/parsedate/ 
2006.11.10/doc/html/System-Time-Parse.html


-- Don


parsedate is obsolete, unless you have ghc < 6.6.1. It was rewritten  
to become what is now the date parsing code in the time package.


/Björn



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


Re: [Haskell-cafe] Haskell libraries for computer vision

2007-10-16 Thread Paul Hudak

Henning Thielemann wrote:

On Mon, 15 Oct 2007, Don Stewart wrote:
  

http://alberrto.googlepages.com/easyvision
"An experimental Haskell system for fast prototyping of computer vision
and image processing applications."
Looks ridiculously cool.



Image processing with Haskell - really interesting.

I know of an older approach:
  "Prototyping Real-Time Vision Systems: An Experiment in DSL Design"
 by Alastair Reid et.al.

Yes, see:

   http://haskell.org/yale/papers/padl01-vision/index.html
   http://haskell.org/yale/papers/icse99/index.html

-Paul


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


Re: [Haskell-cafe] Re: Proposal: register a package as providing several API versions

2007-10-16 Thread Stefan O'Rear
On Tue, Oct 16, 2007 at 01:57:01PM +0100, Simon Marlow wrote:
> Certainly, this is something we want to support.  However, there's an 
> important difference between shared-library linking and Haskell: in 
> Haskell, a superset of an API is not backwards-compatible, because it has 
> the potential to cause new name clashes.

This is the case on Unixy .so systems too, because the namespace is
flat.  If libreadline suddenly starts exporting a symbol named SDL_init,
programs which use both readline and sdl will break.  I have not seen
this happen in practice.  (Which might have something to do with the
aforementioned name mangling :))

Stefan


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


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

2007-10-16 Thread Thomas Hartman
>Indeed, I don't want to waste time but have no choice (rpm needs root),

not sure if this'll help (never tried it myself) but this claims there's a 
non-root way to use rpm

http://www.techonthenet.com/linux/build_rpm.php

cheers, t.

---

This e-mail may contain confidential and/or privileged information. If you 
are not the intended recipient (or have received this e-mail in error) 
please notify the sender immediately and destroy this e-mail. Any 
unauthorized copying, disclosure or distribution of the material in this 
e-mail is strictly forbidden.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] RE: [Haskell] Re: Trying to install binary-0.4

2007-10-16 Thread Brandon S. Allbery KF8NH


On Oct 16, 2007, at 9:01 , Bayley, Alistair wrote:


From: Simon Marlow [mailto:[EMAIL PROTECTED]

The lexicographical ordering would make 10.0 > 9.3.  In
general, A.B > C.D
iff A > C or A == C && B > D.  When we say the "latest"
version we mean
"greatest", implying that version numbers increase with time.
 Does that help?


Sort of. It's what I'd expect from a sensible version comparison. It's
just not something I'd ever choose to call lexicographic ordering.  
IMO,

lexicographgic ordering is a basic string comparision so e.g.

max "10.0" "9.3" = "9.3"

I'd call what you're doing numeric ordering. Does it have a better  
name,

like version-number-ordering, or section-number-ordering (e.g. Section
3.2.5, Section 3.2.6)?


"Lexicographic ordering", to me, means ordering by the collation  
sequence for individual characters.  I'd call this multi-field  
numeric ordering with "." as the field separator.


"Version number ordering" is a bit trickier:  it's used by Linux/*BSD  
package systems that need to deal with versions like  
"1.2a3_4,1" (which in FreeBSD means package version 1.2a3 (which is  
defined by the package originator and usually means the alpha-3  
release of version 1.2), FreeBSD package version 4 thereof, with an  
epoch of 1 to force higher sorting because at some point a new  
version was retracted (say, 1.2a4 was packaged, then turned out to  
have major bugs that caused a rollback to 1.2a3, so the epoch is  
bumped to indicate that this 1.2a3 is actually later than the  
1.2a4).  RPM and APT have similar mechanisms, although syntactically  
different.


(I don't *think* we need to care about this.  Unfortunately, while  
Cabal version numbers are fairly clearly only the upstream part of  
it, and defined such that we don't need to determine whether 1.2a4  
sorts before or after 1.2 (a rat's nest pretty much every OS  
distribution packaging system needs to fight with), I can imagine  
Hackage needing something like an epoch to handle regressions while  
allowing cabal-install to do the right thing.)


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


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


Re: [Haskell-cafe] Re: [Haskell] Re: Trying to install binary-0.4

2007-10-16 Thread Brandon S. Allbery KF8NH


On Oct 16, 2007, at 4:21 , Ketil Malde wrote:


The major/minor scheme has worked nicely for .so for ages.



i'm not so sure about that. it may be better than alternatives,
but [..]


Also, it sees a lot of testing, at least in current Linux
distributions.  The point is that the end-user experience is pretty
good.


Except it doesn't, quite; note how many packages have started  
embedding the version in the soname (e.g. foo-1.2.so.*).


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


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


Re: [Haskell-cafe] Equality Question

2007-10-16 Thread Thomas Hartman
a good sanity check for saneness of two fxs is to "quickcheck" them, as I 
believe I provided an example to for a previous question of yours.

Though I think in this case that's impossible because, as someone else 
pointed out, not even the function tyes agree.

t.



PR Stanley <[EMAIL PROTECTED]> 
Sent by: [EMAIL PROTECTED]
10/15/2007 06:56 PM

To
haskell-cafe@haskell.org
cc

Subject
[Haskell-cafe] Equality Question






Hi
is const = id?
const 'x' 'y'
'x'
id 'x'
'x'

Cheers,
Paul

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



---

This e-mail may contain confidential and/or privileged information. If you 
are not the intended recipient (or have received this e-mail in error) 
please notify the sender immediately and destroy this e-mail. Any 
unauthorized copying, disclosure or distribution of the material in this 
e-mail is strictly forbidden.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Equality Question

2007-10-16 Thread Thomas Hartman
not quite the same issue, but you might be interested by 

http://people.cs.uu.nl/stefan/blog/00012.html which notes: 

Prelude> let apply  = \f x -> f x

Prelude> let apply' = \f   -> f

Prelude> apply  undefined `seq` ()
()

Prelude> apply' undefined `seq` ()
*** Exception: Prelude.undefined

mulling this over helped me think about functions that were similar but 
had different numbers of params. (the first only takes a function as its 
first arg, the second, which I believe is the same as "id" takes 
anything.)

t.





PR Stanley <[EMAIL PROTECTED]> 
Sent by: [EMAIL PROTECTED]
10/15/2007 06:56 PM

To
haskell-cafe@haskell.org
cc

Subject
[Haskell-cafe] Equality Question






Hi
is const = id?
const 'x' 'y'
'x'
id 'x'
'x'

Cheers,
Paul

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



---

This e-mail may contain confidential and/or privileged information. If you 
are not the intended recipient (or have received this e-mail in error) 
please notify the sender immediately and destroy this e-mail. Any 
unauthorized copying, disclosure or distribution of the material in this 
e-mail is strictly forbidden.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Help parsing dates and times

2007-10-16 Thread Thomas Hartman
dons's blog entry on parsing dates might point somewhere useful

http://cgi.cse.unsw.edu.au/~dons/blog/2006/11/12#rpn-reloaded

t.



Don Stewart <[EMAIL PROTECTED]> 
Sent by: [EMAIL PROTECTED]
10/15/2007 08:25 PM

To
Justin Bailey <[EMAIL PROTECTED]>
cc
Haskell-Cafe 
Subject
Re: [Haskell-cafe] Help parsing dates and times






jgbailey:
>I am trying to parse various date and time formats using the 
parseTime
>function found in (GHC 6.6.1) Data.Time.Format. The one that is 
giving me
>trouble looks like this:
> 
>  2008-06-26T11:00:00.000-07:00
> 
>Specifically, the time zone offset isn't covered by the format 
parameters
>given. I can almost parse it with this:
> 
>  %FT%X.000
> 
>But that doesn't take into account the "-07:00" bit. I'm sure this 
has
>been solved - can someone point me to the solution? Thanks in 
advance.

Is there anything in the parsedate library?


http://hackage.haskell.org/cgi-bin/hackage-scripts/package/parsedate-2006.11.10


http://hackage.haskell.org/packages/archive/parsedate/2006.11.10/doc/html/System-Time-Parse.html


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



---

This e-mail may contain confidential and/or privileged information. If you 
are not the intended recipient (or have received this e-mail in error) 
please notify the sender immediately and destroy this e-mail. Any 
unauthorized copying, disclosure or distribution of the material in this 
e-mail is strictly forbidden.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] Re: Trying to install binary-0.4

2007-10-16 Thread Simon Marlow

Bayley, Alistair wrote:
From: Simon Marlow [mailto:[EMAIL PROTECTED] 

The lexicographical ordering would make 10.0 > 9.3.  In 
general, A.B > C.D 
iff A > C or A == C && B > D.  When we say the "latest" 
version we mean 
"greatest", implying that version numbers increase with time. 
 Does that help?



Sort of. It's what I'd expect from a sensible version comparison. It's
just not something I'd ever choose to call lexicographic ordering. IMO,
lexicographgic ordering is a basic string comparision so e.g.

max "10.0" "9.3" = "9.3"

I'd call what you're doing numeric ordering. Does it have a better name,
like version-number-ordering, or section-number-ordering (e.g. Section
3.2.5, Section 3.2.6)?


I've heard it called lexicographical ordering before, but I'm happy to call 
it by whatever name induces the least confusion!


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


[Haskell-cafe] RE: [Haskell] Re: Trying to install binary-0.4

2007-10-16 Thread Bayley, Alistair
> From: Simon Marlow [mailto:[EMAIL PROTECTED] 
> 
> The lexicographical ordering would make 10.0 > 9.3.  In 
> general, A.B > C.D 
> iff A > C or A == C && B > D.  When we say the "latest" 
> version we mean 
> "greatest", implying that version numbers increase with time. 
>  Does that help?


Sort of. It's what I'd expect from a sensible version comparison. It's
just not something I'd ever choose to call lexicographic ordering. IMO,
lexicographgic ordering is a basic string comparision so e.g.

max "10.0" "9.3" = "9.3"

I'd call what you're doing numeric ordering. Does it have a better name,
like version-number-ordering, or section-number-ordering (e.g. Section
3.2.5, Section 3.2.6)?

Alistair
*
Confidentiality Note: The information contained in this message,
and any attachments, may contain confidential and/or privileged
material. It is intended solely for the person(s) or entity to
which it is addressed. Any review, retransmission, dissemination,
or taking of any action in reliance upon this information by
persons or entities other than the intended recipient(s) is
prohibited. If you received this in error, please contact the
sender and delete the material from any computer.
*
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Proposal: register a package as providing several API versions

2007-10-16 Thread Simon Marlow

ChrisK wrote:

Simon Marlow wrote:

Several good points have been raised in this thread, and while I might
not agree with everything, I think we can all agree on the goal: things
shouldn't break so often.


I have another concrete proposal to avoid things breaking so often.  Let us
steal from something that works: shared library versioning on unixy systems.

On Max OS X, I note that I have, in /usr/lib:

lrwxr-xr-x1 root  wheel15 Jul 24  2005 libcurl.2.dylib -> 
libcurl.3.dylib
lrwxr-xr-x1 root  wheel15 Jul 24  2005 libcurl.3.0.0.dylib -> 
libcurl.3.dylib
-rwxr-xr-x1 root  wheel201156 Aug 17 17:14 libcurl.3.dylib
lrwxr-xr-x1 root  wheel15 Jul 24  2005 libcurl.dylib -> 
libcurl.3.dylib


The above declaratively expresses that libcurl-3.3.0 provides the version 3 API
and the version 2 API.

This is the capability that should be added to Haskell library packages.

Right now a library can only declare a single version number.  So if I update
hsFoo from 2.1.1 to 3.0.0 then I cannot express whether or not the version 3 API
is a superset of (backward compatible with) the version 2 API.


Certainly, this is something we want to support.  However, there's an 
important difference between shared-library linking and Haskell: in 
Haskell, a superset of an API is not backwards-compatible, because it has 
the potential to cause new name clashes.



Once it is possible to have cabal register the hsFoo-3.0.0 also as hsFoo-2 it
will be easy to upgrade to hsFoo.  No old programs will fail to compile.

Who here knows enough about the ghc-pkg database to say how easy or hard this
would be?


It could be done using the tricks that Claus just posted and I followed up 
on.  You'd need a separate package for hsFoo-2 that specifies exactly which 
bits of hsFoo-3 are re-exported.  Given some Cabal support and a little 
extension in GHC, this could be made relatively painless for the library 
maintainer.


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


[Haskell-cafe] Re: [Haskell] Re: Trying to install binary-0.4

2007-10-16 Thread Simon Marlow

Bayley, Alistair wrote:
From: [EMAIL PROTECTED] 
[mailto:[EMAIL PROTECTED] On Behalf Of Simon Marlow


   x changes ==> API changed
   x constant but y changes ==> API extended only
   x and y constant ==> API is identical

Ordering on versions is lexicographic, given multiple 
versions that satisfy a dependency Cabal will pick the latest.


Just a minor point, but would mind explaining exactly what lexicographic
ordering implies? It appears to me that e.g. version 9.3 of a package
would be preferred over version 10.0. That strikes me as
counter-intuitive.


The lexicographical ordering would make 10.0 > 9.3.  In general, A.B > C.D 
iff A > C or A == C && B > D.  When we say the "latest" version we mean 
"greatest", implying that version numbers increase with time.  Does that help?


Cheers,
Simon

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


[Haskell-cafe] Re: [Haskell] Re: Trying to install binary-0.4

2007-10-16 Thread Simon Marlow

Simon Marlow wrote:

Claus Reinke wrote:

- if you provide a 'base' configuration that pulls in the stuff that
  used to be in base, the package will work


I don't know of a way to do that.  The name of the package is baked 
into the object files at compile time, so you can't use the same 
compiled module in more than one package.


i've been wrong about this before, so check before you believe,-) but 
here is a hack i arrived at the last time we discussed this:


[using time:Data.Time as a small example; ghc-6.6.1]

1. create, build, and install a package QTime, with default Setup.hs

...

2. create, build, and install a package Time2, with default Setup.hs

...

3. write and build a client module


Ok, when I said above "I don't know a way to do that", I really meant 
there's no way to do it by modifying the package database alone, which I 
think is what Udo was after.


Your scheme does work, and you have discovered how to make a package 
that re-exports modules from other packages (I made a similar discovery 
recently when looking into how to add support to Cabal for this).  As 
you can see, it's rather cumbersome, in that you need an extra dummy 
package, and two stub modules for each module to be re-exported.


Ah, I should add that due to technical limitations this scheme can't be 
used to make a base-2 that depends on base-3.  Base is special in this 
respect, GHC only allows a single package called base to be linked into any 
given executable.  The reason for this is that GHC can be independent of 
the version of the base package, and refer to it as just "base"; in theory 
it's possible to upgrade the base package independently of GHC.


So we're restricted at the moment to providing only completely independent 
base-2 and base-3 in the same installation, and essentially that means 
having (at least) two copies of every package, one that depends on base-2 
and one that depends on base-3.


Perhaps we should revisit this decision, it would be better for GHC to 
depend explicitly on base-3, but allow a separate backwards-compatible 
base-2 that depends on base-3 to be installed alongside.


OTOH, this will still lead to difficulties when you try to mix base-2 and 
base-3.  Suppose that the Exception type changed, so that base-2 needs to 
provide its own version of Exception.  The base-2:Exception will be 
incompatible with the base-3:Exception, and type errors will ensue if the 
two are mixed.


If the base-3:Exception only added a constructor, then you could hide it in 
base-2 instead of defining a new type.  However, if base-3 changed the type 
of a constructor, you're stuffed.  Ah, I think we've discovered a use for 
the renaming feature that was removed in Haskell 1.3!


Cheers,
Simon

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


Re: [Haskell-cafe] Re: [Haskell] Re: Trying to install binary-0.4

2007-10-16 Thread Lutz Donnerhacke
* Simon Marlow wrote:
> further sub-versions may be added after the x.y, their meaning is
> package-defined.  Ordering on versions is lexicographic, given multiple 
> versions that satisfy a dependency Cabal will pick the latest.

x.y.z should be ordered numerically, if possible.

> As suggested by various people in this thread: we change the convention so 
> that dependencies must specify a single x.y API version, or a range of 
> versions with an upper bound.  Cabal or Hackage can refuse to accept 
> packages that don't follow this convention (perhaps Hackage is a better 
> place to enforce it, and Cabal should just warn, I'm not sure).

Ack. Hackage is a good place to reject.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] RE: [Haskell] Re: Trying to install binary-0.4

2007-10-16 Thread Stuart Cook
On 10/16/07, Bayley, Alistair <[EMAIL PROTECTED]> wrote:
> Just a minor point, but would mind explaining exactly what lexicographic
> ordering implies? It appears to me that e.g. version 9.3 of a package
> would be preferred over version 10.0. That strikes me as
> counter-intuitive.

I believe the intent is "lexicographic" in the sense that a version
number is a dot-separated sequence of integers. So if you interpret
"9.3" as [9, 3] and "10.0" as [10, 0], then

  Prelude> max [9, 3] [10, 0]
  [10,0]

and

  Prelude> max [1, 9] [1, 10]
  [1,10]

work in the expected way.


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


[Haskell-cafe] Proposal: register a package as providing several API versions

2007-10-16 Thread ChrisK
Simon Marlow wrote:
> Several good points have been raised in this thread, and while I might
> not agree with everything, I think we can all agree on the goal: things
> shouldn't break so often.

I have another concrete proposal to avoid things breaking so often.  Let us
steal from something that works: shared library versioning on unixy systems.

On Max OS X, I note that I have, in /usr/lib:
> lrwxr-xr-x1 root  wheel15 Jul 24  2005 libcurl.2.dylib -> 
> libcurl.3.dylib
> lrwxr-xr-x1 root  wheel15 Jul 24  2005 libcurl.3.0.0.dylib -> 
> libcurl.3.dylib
> -rwxr-xr-x1 root  wheel201156 Aug 17 17:14 libcurl.3.dylib
> lrwxr-xr-x1 root  wheel15 Jul 24  2005 libcurl.dylib -> 
> libcurl.3.dylib

The above declaratively expresses that libcurl-3.3.0 provides the version 3 API
and the version 2 API.

This is the capability that should be added to Haskell library packages.

Right now a library can only declare a single version number.  So if I update
hsFoo from 2.1.1 to 3.0.0 then I cannot express whether or not the version 3 API
is a superset of (backward compatible with) the version 2 API.

Once it is possible to have cabal register the hsFoo-3.0.0 also as hsFoo-2 it
will be easy to upgrade to hsFoo.  No old programs will fail to compile.

Who here knows enough about the ghc-pkg database to say how easy or hard this
would be?

-- 
Chris

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


[Haskell-cafe] Re: [Haskell] Re: Trying to install binary-0.4

2007-10-16 Thread Simon Marlow

Claus Reinke wrote:

- if you provide a 'base' configuration that pulls in the stuff that
  used to be in base, the package will work


I don't know of a way to do that.  The name of the package is baked 
into the object files at compile time, so you can't use the same 
compiled module in more than one package.


i've been wrong about this before, so check before you believe,-) but 
here is a hack i arrived at the last time we discussed this:


[using time:Data.Time as a small example; ghc-6.6.1]

1. create, build, and install a package QTime, with default Setup.hs

...

2. create, build, and install a package Time2, with default Setup.hs

...

3. write and build a client module


Ok, when I said above "I don't know a way to do that", I really meant 
there's no way to do it by modifying the package database alone, which I 
think is what Udo was after.


Your scheme does work, and you have discovered how to make a package that 
re-exports modules from other packages (I made a similar discovery recently 
when looking into how to add support to Cabal for this).  As you can see, 
it's rather cumbersome, in that you need an extra dummy package, and two 
stub modules for each module to be re-exported.


One way to make this easier is to add a little extension to GHC, one that 
we've discussed before:


module Data.Time (module Base1.Data.Time) where
import "base-1.0" Data.Time as Base1.Data.Time

the extension is the "base-1.0" package qualifier on the import, which GHC 
very nearly supports (only the syntax is missing).


Now you don't need the dummy package, and only one stub module per module 
to be re-exported.  Cabal could generate these automatically, given some 
appropriate syntax.  Furthermore, this is better than doing something at 
the package level, because you're not stuck with module granularity, you 
can re-export just parts of a module, which is necessary if you're trying 
to recreate an old version of an API.


I was going to propose this at some point.  Comments?

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


Re: [Haskell-cafe] Haskell libraries for computer vision

2007-10-16 Thread Henning Thielemann

On Mon, 15 Oct 2007, Don Stewart wrote:

> http://alberrto.googlepages.com/easyvision
>
> "An experimental Haskell system for fast prototyping of computer vision
> and image processing applications."
>
> Looks ridiculously cool.

Image processing with Haskell - really interesting.

I know of an older approach:
  "Prototyping Real-Time Vision Systems: An Experiment in DSL Design"
 by Alastair Reid et.al.

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


[Haskell-cafe] RE: [Haskell] Re: Trying to install binary-0.4

2007-10-16 Thread Bayley, Alistair
> From: [EMAIL PROTECTED] 
> [mailto:[EMAIL PROTECTED] On Behalf Of Simon Marlow
> 
>x changes ==> API changed
>x constant but y changes ==> API extended only
>x and y constant ==> API is identical
> 
> Ordering on versions is lexicographic, given multiple 
> versions that satisfy a dependency Cabal will pick the latest.

Just a minor point, but would mind explaining exactly what lexicographic
ordering implies? It appears to me that e.g. version 9.3 of a package
would be preferred over version 10.0. That strikes me as
counter-intuitive.

Alistair
*
Confidentiality Note: The information contained in this message,
and any attachments, may contain confidential and/or privileged
material. It is intended solely for the person(s) or entity to
which it is addressed. Any review, retransmission, dissemination,
or taking of any action in reliance upon this information by
persons or entities other than the intended recipient(s) is
prohibited. If you received this in error, please contact the
sender and delete the material from any computer.
*
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] Re: Trying to install binary-0.4

2007-10-16 Thread Simon Marlow
Several good points have been raised in this thread, and while I might not 
agree with everything, I think we can all agree on the goal: things 
shouldn't break so often.


So rather than keep replying to individual points, I'd like to make some 
concrete proposals so we can make progress.


1. Document the version numbering policy.

We should have done this earlier, but we didn't.  The proposed policy, for 
the sake of completeness is: x.y where:


  x changes ==> API changed
  x constant but y changes ==> API extended only
  x and y constant ==> API is identical

further sub-versions may be added after the x.y, their meaning is 
package-defined.  Ordering on versions is lexicographic, given multiple 
versions that satisfy a dependency Cabal will pick the latest.


2. Precise dependencies.

As suggested by various people in this thread: we change the convention so 
that dependencies must specify a single x.y API version, or a range of 
versions with an upper bound.  Cabal or Hackage can refuse to accept 
packages that don't follow this convention (perhaps Hackage is a better 
place to enforce it, and Cabal should just warn, I'm not sure).


Yes, earlier I argued that not specifying precise dependencies allows some 
packages to continue working even when dependencies change, and that having 
precise dependencies means that all packages are guaranteed to break when 
base is updated.  However, I agree that specifying precise dependencies is 
ultimately the right thing, we'll get better errors when things break,



There's lots more to discuss, but I think the above 2 proposals are a step 
in the right direction, agreed?


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


Re: [Haskell-cafe] ANNOUNCE: metaplug

2007-10-16 Thread Axel Mannhardt
Hello,

There is one limitation to this, however. compileCall expects to compile a
> dynamic via GHC.dynCompileExpr;
> what this means is your resource must be monomorphic (for Typeable to
> work.) As of right now, the easiest
> way I can see to get around this is to simply define a datatype like such:
>
> data Plugin {
> rsrc :: ... -- your type here
> } deriving Typeable


I have the same problem, although from a different direction. I am only
interested in an eval-myDynamicFunction functionality not general modules,
so I did it on a per function basis, using hs-plugins eval.
A typeable data wrapper would be fine for me, although I have not yet found
a non-ugly way to import needed modules for the plugin, as the plugin source
would not be necessarily in the same place as the API. But thats rather an
implementation detail.

The real problem is, that I do not know, if there is an appropriate way to
represent functions with a dynamic parameter count. As of now, I think it
would need a bigger amount of hacking than it is worth to get rid of the
workarounds I already have, but it would be interesting anyway.


> (unsafeCoerce# is an option but there's not a version
> of compileCall to support this as of right now. I might add it if it seems
> needed.)
>

As I am relatively new, and since I have not found any introduction what
unsafeCoerce is actually capable of (and how), I have ignored this
possibility. Could someone give me some pointers? (the most useful thing I
found is http://osdir.com/ml/lang.haskell.glasgow.bugs/2005-03/msg00048.html
)

The approach I stopped working at was:


type TestSpecs = (String, String, String)

data FunctionTest = forall a b
. (Show a, Show b,
Eq b) =>
FunctionTest (String
, [a], (a
->b), [b])
deriving Typeable

readFunctionTest :: TestSpecs
-> IO (Either [String]
(Maybe FunctionTest))
readFunctionTest (
params,fn,predicted) = eval_
 str ["FunctionTest"] ["-i"++libDir] [] [libDir]

where str = "FunctionTest("++show
fn++", "++params++", "
++fn++", "++predicted++")"


applyFunctionTest :: FunctionTest -> [Bool
]
applyFunctionTest (FunctionTest (_
,parameters,function,predicted)
) = zipWith (==) (map
 function parameters) predicted

..what works for general Functions with one Parameter. The wrapper ensures
that the function takes one value to produce another value comparable to the
other given value. So far, this looks ok to me, I can 'read' a function once
and apply it to multiple tests. However, if the function has more than one
curried parameter, it has to be extended. I see the following approaches:

-Do everything inside the eval (returning a [Bool] for example). That works,
and I use it right now, but apart from being ugly, the function has to be
read more than once. This might be a non-practical issue though.

-Introduce constructors for each parameter count (up to a limit).

FunctionTest2 (String,
[(a,a')], (a->a'->
b), [b])
applyFunctionTest
 (FunctionTest2 ...{-this might be generalizeable-}

That is a lot more redundant and not as general as the inside-eval approach,
but the function has to be read only once.

-Convert any functions into ones that take one list/tuple parameter within
the eval (assume there is no type ambiguity for simplicity). Partial
application is not the goal here anyway and information about the parameter
count could be obtained from the "parameter"-parameter or from additional
information in the function String itself.
But for that a wrapper has to be added to the code inside eval that turns a
function with unknown parameter count into the one actually exported. The
type of this transformer function could be distinguished at eval compile
time, but that means the implementation would have to be included in each
eval...

uncurry3 fn (a, b, c) = fn a b c
uncurryN = --would be defined using template Haskell or recursive data
structures or something else I do not know yet

--simpler as a list
uncurryL fn [] = fn
uncurryL fn (x:xs) = uncurryL (fn (fromValue x)) xs
-- but then the values would have to be wrapped for type ambiguity:
data Value = IntV Int | ...


I had a look on some techniques to deal with dynamic parameter count, but
they are either decided at runtime (as my understanding of QuickCheck and
its recursive data types is) or they do not represent functions with unknown
parameter count but only process one at a time (as Printf does). Tell me if
I am wrong.

So, I end up with three possibilities how to do the job (although I have not
tried to implement all of them), but I am unhappy with each. How would one
express a type "a->...->b" in Haskell (GHC)? Are you able to express the
second approach without the redundant FunctionTestN definitions? I am
willing to do ugly things, as long as I can restrict the effects to that
particular place.

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


Re: [Haskell-cafe] Re: [Haskell] Re: Trying to install binary-0.4

2007-10-16 Thread Claus Reinke

- if you provide a 'base' configuration that pulls in the stuff that
  used to be in base, the package will work


I don't know of a way to do that.  The name of the package is baked into 
the object files at compile time, so you can't use the same compiled module 
in more than one package.


i've been wrong about this before, so check before you believe,-) 
but here is a hack i arrived at the last time we discussed this:


[using time:Data.Time as a small example; ghc-6.6.1]

1. create, build, and install a package QTime, with default Setup.hs

   -- QTime.cabal
   Name: QTime
   Version: 0.1
   Build-depends: base, time
   Exposed-modules: QTime.Data.Time

   -- QTime/Data/Time.hs
   module QTime.Data.Time(module Data.Time) where
   import Data.Time

2. create, build, and install a package Time2, with default Setup.hs

   -- Time2.cabal
   Name: Time2
   Version: 0.1
   Build-depends: base, QTime
   Exposed-modules: Data.Time

   -- Data/Time.hs
   module Data.Time(module QTime.Data.Time) where
   import QTime.Data.Time

3. write and build a client module

   -- Main.hs
   import Data.Time
   main = print =<< getCurrentTime

   $ ghc -hide-all-packages -package base  Main.hs

   Main.hs:1:0:
   Failed to load interface for `Data.Time':
 it is a member of package Time2-0.1, which is hidden

   $ ghc -hide-all-packages -package base -package Time2 Main.hs

   $ ./main.exe
   2007-10-16 11:09:05.859375 UTC

   $ rm main.exe Main.hi Main.o
   
   $ ghc -hide-all-packages -package base -package time Main.hs
   
   $ ./main.exe

   2007-10-16 11:09:29.34375 UTC

as i said, i've misinterpreted such symptoms before, but it seems
to me that Time2's Data.Time acts as a drop-in replacement for
time's Data.Time here. doesn't it? 

it is rather tedious, having to do something for every module in 
the package, twice (once to get a package-qualified name that

differs from the original name, the second time to re-expose it
under its original name), but that could be automated. and there
would be an extra QBase package. but until cabal supports 
such renamings directly, it might be a workaround for the 
current base issue?


claus

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


Re: [Haskell-cafe] Re: [Haskell] Re: Trying to install binary-0.4

2007-10-16 Thread Daniel McAllansmith
On Tuesday 16 October 2007 21:16, Simon Marlow wrote:
> > - when GHC 6.8 comes out containing base-3, will it be possible to
> >   additionally install something calling base-2 with both being
> >   available to packages?
>
> In theory yes - the system was designed to allow this.  In practice we've
> never tried it, and base-2 might not compile unmodified with GHC 6.8.
>
> > - If so, will existing Cabal packages automatically pick up the
> >   compatible base-2 despite base-3 being available?
>
> Only if they specify an upper bound on the base dependency, which most
> don't, but it's an easy change to make.

It seems more sensible to me for dependencies to always have an upper bound of 
the next major version.  foo-3.y.z won't satisfy foo-2.3.4.

If it so happens that a package depends on the subset of foo's interface that 
was retained from foo-2.3.4 through to foo-3.0.0 then the dependency can be 
changed to foo-2.3.4,3.0.0 (modulo syntax) once it has been tested.

If dependencies on foo often end up like this due to use of a distinct subset 
of the interface it's probably a good sign that foo is too coarse-grained.


If a major version increment, by definition, implies a removal of 
functionality from a package then having no upper bound on the dependency 
pushes work out to the user that would be better done by the maintainer.  
With an upper bound users are still able to try and get the package going 
with a later version of a dependency if they want.

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


[Haskell-cafe] Distributed haskell using Hadoop

2007-10-16 Thread Brad Clow
I was looking around for a haskell solution for distributing a
computation across multiple machines and couldn't find anything that
looked current and alive. I found out that the Hadoop project (java
based) can interact with binary executables via stdin and stdout. So I
have set up a Hadoop cluster of 5 machines, wrapped my Haskell code to
accept data via stdin and write results to stdout and successfully
executed it on the cluster.

I would prefer a more Haskell orientated solution and welcome any
suggestions. If not maybe this will be of use to others.

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


Re: [Haskell-cafe] Re: [Haskell] Re: Trying to install binary-0.4

2007-10-16 Thread Claus Reinke

Be happy: we're about 15 years ahead of the lisp guys. 'cabal install
xmonad' works, for example.


- not on windows (and since it is popular, it will seduce more
   good haskellers not to bother with windows compatibility.. :-(

- from xmonad.cabal (version 0.3, from hackage):

   build-depends:  base>=2.0, X11>=1.2.1, X11-extras>=0.3, mtl>=1.0, 
unix>=1.0

so, you guarantee that it will work with base-3.0, X11-2.0, 
X11-extras-1.0, mtl-2.0, unix-2.0. even though all of those

will -if i now understand the versioning intentions correctly-
lack features of the current versions?

claus

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


RE: [Haskell-cafe] Performance problem with random numbers

2007-10-16 Thread Simon Peyton-Jones
We'd be delighted if someone offered a more performant library to put into 
future GHC releases.

Simon

| -Original Message-
| From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On Behalf Of Don
| Stewart
| Sent: 13 October 2007 22:38
| To: Isaac Dupree
| Cc: haskell-cafe@haskell.org
| Subject: Re: [Haskell-cafe] Performance problem with random numbers
|
| isaacdupree:
| > ntupel wrote:
| > >Thanks for your reply Stefan. Unfortunately I could measure only a
| > >relatively small improvement by changing to concrete types
| >
| > >the sample code was about one second faster when compiled with -O2.
| > >Profiling again indicated that most time was spend in random and randomR
| >
| > GHC StdGen's random and randomR are somewhat slow.  I found that
| > changing to a custom ((x*a + b) `mod` c) random-generator (instance of
| > RandomGen) much sped things up (since nothing depended on the random
| > numbers being good quality).  (Then I switched to a small C function to
| > do the randomization and make all the OpenGL calls, and it sped up by
| > another factor of 4.)
| >
|
| I've seen similar results switching to the SIMD mersenne twister C
| implementation for randoms:
|
| http://www.math.sci.hiroshima-u.ac.jp/~m-mat/MT/SFMT/index.html
|
| If there's interest, I can package up the bindings for hackage.
|
| -- Don
| ___
| Haskell-Cafe mailing list
| Haskell-Cafe@haskell.org
| http://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] System.Posix

2007-10-16 Thread Bjorn Bringert

On Oct 16, 2007, at 3:25 , Galchin Vasili wrote:


Hello,

In a Hugs environment, I am able to import System.Directory but  
not to import System.Posix. Here is my environment ... .;{Hugs} 
\packages\*;C:\ftp\CatTheory\Haskell\SOE\graphics\lib\win32\*. I  
really want to use the Posix module. Help!!!


Kind regards, Bill Halchin


Hi Bill,

it seems like you are using Hugs under Windows. As far as I know  
System.Posix is not available on Windows.


/Björn



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


Re: [Haskell-cafe] Re: [Haskell] Re: Trying to install binary-0.4

2007-10-16 Thread Ketil Malde
"Claus Reinke" <[EMAIL PROTECTED]> writes:

>> You need a way to specify "foo > 1.2 && foo < 2", which is a
>> suggestion that was tossed around here recently.   

> but what does such a version range say? that i haven't tested any
> versions outside the range (because they didn't exist when i wrote
> my package)? or that i have, and know that later versions won't do?

IMO, it says that it works with interface version 1, and needs some
stuff from sublevel 2, and as long as the foo developers keep their
end of the bargain, it will continue to work with new releases in the
1-series.  For foo-2, the interface may change, and all bets are off. 

The dependency could be expressed more in a more succinct (albeit less
flexible) manner with a different syntax (e.g. "foo-1.2").

> if that decision is based on version numbers alone, we need to
> be specific about the meaning of version numbers in dependencies.

Yes.

> and if the major/minor scheme is to be interpreted as Simon
> summarised, the only acceptable form of a dependency is an
> explicit version range (the range of versions known to work).

I'm happy with "expected to work".

>> The major/minor scheme has worked nicely for .so for ages. 

> i'm not so sure about that. it may be better than alternatives,
> but [..]

Also, it sees a lot of testing, at least in current Linux
distributions.  The point is that the end-user experience is pretty
good. 

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] Re: Trying to install binary-0.4

2007-10-16 Thread Simon Marlow

Udo Stenzel wrote:

Simon Marlow wrote:
So a package that depends on 'base' (with no upper version bound) *might* 
be broken in GHC 6.8.1, depending on which modules from base it actually 
uses.  Let's look at the other options:


  - if we rename base, the package will *definitely* be broken

  - if the package specified an upper bound on its base dependency, it will
*definitely* be broken


- if you provide a 'base' configuration that pulls in the stuff that
  used to be in base, the package will work


I don't know of a way to do that.  The name of the package is baked into 
the object files at compile time, so you can't use the same compiled module 
in more than one package.



I hate betting, but I'd like to know if...

- it is okay to give GHC 6.4/6.6 a castrated configuration of the base
  libraries to remove the conflict with recent ByteString?


Sure, that's what I suggested before.  Moving modules of an existing 
package from 'exposed-modules' to 'hidden-modules' is safe (I wouldn't 
recommend removing them entirely).



- when GHC 6.8 comes out containing base-3, will it be possible to
  additionally install something calling base-2 with both being
  available to packages?


In theory yes - the system was designed to allow this.  In practice we've 
never tried it, and base-2 might not compile unmodified with GHC 6.8.



- If so, will existing Cabal packages automatically pick up the
  compatible base-2 despite base-3 being available?


Only if they specify an upper bound on the base dependency, which most 
don't, but it's an easy change to make.


Cheers,
Simon



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


Re: [Haskell-cafe] Re: [Haskell] Re: Trying to install binary-0.4

2007-10-16 Thread Ketil Malde
Daniel McAllansmith <[EMAIL PROTECTED]> writes:

>>> I think what you're asking for is more than that: you want us to provide
>>> base-1.0, base-2.0 and base-3.0 at the same time, so that old packages
>>> continue to work without needing to be updated.  

Yes.

>>> That is possible, but much more work for the maintainer.

How much more work, really?  If the dependencies of your library have
similar backwards compatible support, you only have to keep track of
backwards-incompatible changes to the compiler, and I think those are
relatively few and far apart.

>>> Ultimately when things settle down it might make sense to do this
>>> kind of thing, but right now I think an easier approach is to just
>>> fix packages when dependencies change, and to identify sets of
>>> mutually-compatible packages (we've talked about doing this on
>>> Hackage before).

I'm surprised you think this is easier - There's an awful lot of
possible version combinations, and for every library that breaks,
there is - at least potentially - a lot of applications that needs
updating.  Many of those will be web orphans that some curious newbie
will download and fail to get to work.  (SOE, anybody?  FiniteMap to
Data.Map?)

I think a library is more likely to be supported than an application,
and likely to be supported by more and more competent developers.

> I think it's a no-brainer that old versions of packages should remain 
> available for people to use for 'a long time'.  If their dependencies are 
> specified properly they should continue building successfully as time passes.

Amen.

> Presumably it's not usually a problem if indirect package dependencies 
> require 
> incompatible versions of a package.

If it is, I think this is a strong argument in favor of "package
bundles" that are released and upgraded together as something
resembling a standard library.

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] Re: Trying to install binary-0.4

2007-10-16 Thread ChrisK
Don Stewart wrote:
> stefanor:
>> On Mon, Oct 15, 2007 at 10:57:48PM +0100, Claus Reinke wrote:
>>> so i wonder why everyone else claims to be happy with the status quo?
>> We aren't happy with the status quo.  Rather, we know that no matter how
>> much we do, the situation will never improve, so most of us have stopped
>> wasting out time.  Furthermore, we know that people who DO offer
>> alternatives instantly lose all public credibility - look at what
>> happened to Alex Jacobson.
>>
>> Stefan (who will readily admit his bleak outlook)
> 
> Be happy: we're about 15 years ahead of the lisp guys. 'cabal install
> xmonad' works, for example.
> 
> -- Don

And that, I think, will be the key to the solution.

Keeping the repository of interdependent libraries consistent is hard, but it is
only a means to an goal.

That goal is applications, not libraries.  My definition of the right version of
libFoo to use is whatever is needed to make an application, such as xmonad, 
work.

-- 
Chris

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


[Haskell-cafe] Re: [Haskell] Re: Trying to install binary-0.4

2007-10-16 Thread ChrisK
Simon Marlow wrote:
 > Ultimately when things settle down
> it might make sense to do this kind of thing, but right now I think an
> easier approach is to just fix packages when dependencies change, and to
> identify sets of mutually-compatible packages (we've talked about doing
> this on Hackage before).
> 
> Cheers,
> Simon

When coordinating distribution of separately maintained libraries and projects,
the linux distributions do indeed "identify sets of mutually-compatible
packages", quite often including small patchfiles to ensure compilation.

Thus for linux, cabal is a layer below such apt and rpm repositories and
blessing sets of packages would be done at a higher level.

Once cabal is being used to automatically retrieve sets of working packages then
 it is easiest to write cabal to assume that hackage is fixed when dependencies
change.

As a practical matter, it is easy to see how to identify such sets.  Since such
sets must be installed by at least one person, that person's ghc-pkg listing is
already a precise definition of the working set.  All that might need to be done
is to publish such a working set on hackage where cabal (or another tool) can
see it.

Cheers,
  Chris

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