Re: [Haskell-cafe] ANN: bimap 0.1 - a bidirectional map

2008-02-04 Thread Neil Mitchell
Hi Stuart,

 Data.Bimap is a data structure that represents a bidirectional mapping
 between two key types. A bimap has two type parameters; each value in
 the bimap is associated with exactly one value of the opposite type.
 In other words, it's a bijection between (subsets of) its argument
 types.

Very  handy, I actually wanted something similar myself a few days ago
and came up with:

http://www.cs.york.ac.uk/fp/darcs/firstify/Yhc/Core/Firstify/Mitchell/BiMap.hs

A few design differences from your one:

* I called my module BiMap rather than Bimap - I debated this with
a collegue, and we settled on the capital M, but it was a very close
call.

* I have no L/R and Either variants. I decided it was better to be a
superset of Data.Map, and then have lookupRev/memberRev functions for
the R versions. Do you think anyone is likely to use the Either
variant, without a constant Left or Right in the code? Is this an
artefact of how its easier to code, rather than to use?

* I didn't push my Bimap to completion, because I am too lazy, and
hoped others would. Only the methods I needed were implemented. Many
thanks for doing this work!

Thanks

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


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

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

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

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

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

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

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

-- 
Aaron Denney
--

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


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

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

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

 Ok, so you could create a separate component to produce the .dll / .a
 from the C code but you'd prefer the convenience of being able to just:
 c-sources: blah.c
 and have them included in the project, but built using the MS C
 compiler.
 So I think we should file a feature request about building C sources
 using gcc/ms-c directly rather than going via ghc as that would give us
 the flexibility to use alternative C compilers.
 sorry, i think it's not whole story. gcc and msvc are probably
 incompatible in the meaning that you can't link together code
 produced by two compilers. exactly dll should be generated which allow
 to avoids this incompatibility
 
 Well, the whole purpose of the ABI is to allow linking code together
 from different compilers.  This doesn't mean there won't be any problems,
 but I'd expect the ones that crop up won't *strictly* be because of
 the compilers being different, but because of the C libraries being
 different.  DLL vs object files shouldn't change things all that much.

Well, I can at least report that linking a library (.lib) produced using
cl (via CMake) with object files created by GHC works well.  I do get a
warning:

 Warning: .drectve `/manifestdependency:type='win32'
name='Microsoft.VC90.CRT' version='9.0.21022.8'
processorArchitecture='x86' publicKeyToken='1fc8b3b9a1e18e3b'
/DEFAULTLIB:uuid.lib /DEFAULTLIB:uuid.lib /DEFAULTLIB:MSVCRT
/DEFAULTLIB:OLDNAMES ' unrecognized

But it doesn't seem to have any impact on the resulting executable.

/M

-- 
Magnus Therning (OpenPGP: 0xAB4DFBA4)
magnus@therning.org Jabber: magnus.therning@gmail.com
http://therning.org/magnus

What if I don't want to obey the laws? Do they throw me in jail with
the other bad monads?
 -- Daveman



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


Re: [Haskell-cafe] ANN: bimap 0.1 - a bidirectional map

2008-02-04 Thread Stuart Cook
On Mon, Feb 4, 2008 at 7:56 PM, Neil Mitchell [EMAIL PROTECTED] wrote:
  A few design differences from your one:

  * I called my module BiMap rather than Bimap - I debated this with
  a collegue, and we settled on the capital M, but it was a very close
  call.

Mine was also originally BiMap, but I thought the capital M looked a
little ugly, so I changed it.

  * I have no L/R and Either variants. I decided it was better to be a
  superset of Data.Map, and then have lookupRev/memberRev functions for
  the R versions. Do you think anyone is likely to use the Either
  variant, without a constant Left or Right in the code? Is this an
  artefact of how its easier to code, rather than to use?

I initially had only the Either variants, because that was easier to
code, and I thought it would make the interface cleaner. Then when I
started writing tests, I realised that this was a pain, and I went
back and added the L/R variants. I never bothered to remove the Either
variants, because the L/R versions are (currently) implemented in
terms of them anyway.

I was thinking of having another module, Data.Bimap.Asymmetric, that
would expose an interface more like that of Data.Map (i.e. biased
towards treating the left type as the key), but I decided it was
better to get the first release out as soon as possible.


Thanks for the feedback,

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


module hierarchy (Re: [Haskell-cafe] parsec3 pre-release [important note])

2008-02-04 Thread Wolfgang Jeltsch
Am Samstag, 2. Februar 2008 05:53 schrieb Derek Elkins:
 I forgot to mention that the Text.Parsec modules should be preferred to
 the Text.ParserCombinators.Parsec modules as the Haddock documentation
 reveals.

I would have prefered to shorten ParserCombinators to Parsing and leave Parsec 
under the parsing category.  However, I would prefer if Parsing would move 
out of Text since parsing is not just about parsing text.  Parsec parses also 
streams other than character streams now.

Recently, there was a discussion on the Yampa mailing list about where to put 
FRP-related modules into the module hierarchy.  There was the suggestion of 
Control.FRP.  It was noted, however, that Control seems to suggest imperative 
programming while many things under Control are not restricted to that 
paradigm (like monads, for example) and others (like FRP) have nothing to do 
with imperative programming.  We finally chose to introduce a separate 
top-level module name FRP since the FRP stuff didn’t seem to really fit in 
any of the existing top-level categories.

I concluded from this discussion that the current module hierarchy is too deep 
and that it might be good to remove the current top-level layer.  So 
Parsing.Parsec, for example, or Monad.Reader.

What do you and others think?

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


[Haskell-cafe] ANN: heap-0.2

2008-02-04 Thread Stephan Friedrichs
A flexible heap implementation supporting min-, max- and custom-ordered 
heaps.


New features since version 0.1:
 - Foldable and Read instance
 - filter, partition
 - subrange functions: take, drop, splitAt, takeWhile, span, break

http://hackage.haskell.org/cgi-bin/hackage-scripts/package/heap-0.2.1

//Stephan

--

Früher hieß es ja: Ich denke, also bin ich.
Heute weiß man: Es geht auch so.

 - Dieter Nuhr



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


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

2008-02-04 Thread Alfonso Acosta
On Feb 4, 2008 12:36 PM, Wolfgang Jeltsch [EMAIL PROTECTED] wrote:
 Am Samstag, 2. Februar 2008 14:54 schrieben Sie:
  Again, if someone complains about the TH dependency, the aliases could
  be generated by TH but saved statically in a module for each release.

 Hmm, this could be a compromise although I'm not sure whether it is sensible
 to have a module with thousands of declarations.

As long as the module is automatically generated I don't see why it
would be a problem.

Bear in mind that using TH would, in practice, be equivalent to code
such a module by hand anyway.

 Another solution would be
 to put the Template Haskell convenience stuff into a separate package.  The
 core package would probably be usable with Hugs too, while the convenience
 package would be usable only with GHC.


I'm not sure if it worths it to create a separate package and add
another dependency for those who would like to use it.

I don't still know how many people would be interested in using the
type-level library so, again, I think it won't hurt to include the
TH-generated aliases and then change it if some non-GHC user rants
about it.


 So type-level + parametrized-data is my vote.  But don't let's spend too much
 time discussing the name. ;-)

Fair enough. type-level + parameterized-data it is then (unless
someone else has a better suggestion). I'm going to begin coding now.

I'll host the project in community.haskell.org, do you have an account there?

PS: BTW, I asked Oleg for permission and, as expected, agreed to
create the library under a BS-D license.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Circular enums

2008-02-04 Thread Henning Thielemann

On Sat, 2 Feb 2008, Ben Butler-Cole wrote:

 [Resend with formatting maybe fixed.]

 Hello

 I'm trying to define functions that allow you to traverse a bounded 
 enumeration, wrapping at the start and the end.

 My implementation looks like this:

 next, prev :: (Enum a, Bounded a) = a - a
 next = turn 1
 prev = turn (-1)

 turn :: (Enum a, Bounded a) = Int - a - a
 turn n e = toEnum (add (fromEnum (maxBound::a) + 1) (fromEnum e) n)
 where
   add mod x y = (x + y + mod) `rem` mod
^^^

This should give warnings about a name clash with Prelude's 'mod'
function. Actually, I think you want to use 'mod' here instead of 'rem':
  http://www.haskell.org/haskellwiki/Things_to_avoid#Forget_about_quot_and_rem

To fix the type of 'maxBound' a GHC extension is certainly overkill.
Better use `asTypeOf` instead.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] building the unix package and cabal

2008-02-04 Thread Galchin Vasili
Hello,

  I have been trying to build the unix package on RedHat RHEL 5. Over
the weekend I read through the Cabal documentation. The unix-2.2.0.0
unix.cabal specifies the build-type attribute as Configure. Based on
Cabal doc, I should run ./configure. After this step then what? Bottom line
is how do I build the unix-2.2.0.0 package on RHEL 5?

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


Re: [Haskell-cafe] modeling ANSI C structs in Haskell?

2008-02-04 Thread Peter Gammie

Vasili,

On 04/02/2008, at 10:04 PM, Galchin Vasili wrote:

  I am reading through the FFI doc. Any suggestions on enabling  
Haskell programmers to model ANSI C structs that will be passed down  
to C run-time?


The FFI spec is a wonderful document, but is of limited use in  
learning to use the FFI for practical tasks. I suggest you look into  
c2hs or some other tool that tries to help you with marshalling data  
structures (as compared to providing mechanisms sufficient for doing  
marshalling).


I suggest you do this even if you don't end up using a tool, as the  
generated Haskell has some carefully designed idioms that will  
definitely help.


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


Re: [Haskell-cafe] A handy little consequence of the Cont monad

2008-02-04 Thread Philip Armstrong

On Fri, Feb 01, 2008 at 10:19:17PM +, Lennart Augustsson wrote:

  It's a matter of taste.  I prefer the function composition in this case.
  It reads nicely as a pipeline.


(Hoping not to contribute to any flamage...)

I've always liked $ for this kind of code, if you want to keep the
arguments around:

  next xs = runCont $ sequence $ map Cont xs

seems quite natural to me.

Phil

--
http://www.kantaka.co.uk/ .oOo. public key: http://www.kantaka.co.uk/gpg.txt
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell maximum stack depth

2008-02-04 Thread Adrian Hey

Simon Peyton-Jones wrote:

| Yes, using lots of stack is clearly bad with ghc, but this is a ghc
| bug. In fact the only reason these programs do use lots of stack
| (vs. heap) is just a peculiarity of ghc rts implementation, so it
| really should be ghc that fixes the problem, or at least admits
| responsibility :-)

I don't think there's anything fundamental here. GHC allocates the stack in the heap, and 
it can grow as big as you like.  The size limit is simply to catch infinite recursion 
with a more helpful message than heap overflow.  I think.  There is one 
peculiarity though: I don't think we ever shrink the stack, so once it gets big it stays 
big.  This could be fixed, though.


Yikes!

Sorry, but if what you say is true then things are even worse than I
thought :-( This behaviour seems really bad to me, especially for
concurrent programs.

Also, I can't help thinking that the common justification for the
current limit (that it helps find alleged bugs) is a little lame.
It only helps find bugs if one expects ones program to use less than
8M of stack (hence if it's using more, it's a bug by ones *own*
definition). But if a program or library is deliberately designed to
make use of stack (in preference to heap) for efficiency reasons
(or even just to avoid the awkwardness of using explict CPS style),
then this is a source of bugs in otherwise perfectly correct and
reasonable programs.

If we want some way of investigating a programs stack use there must be
a better way of doing it than deliberately inducing a crash in any
program that exceeds 8M of stack.

Thanks for the answer though. I think I'll write a ticket about this :-)

Regards
--
Adrian Hey


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


Re: [Haskell-cafe] fmap vs. liftM

2008-02-04 Thread Miguel Mitrofanov
Problem is that from the idea Functor is a superclass of Monad, with  
the

property that fmap == liftM.


[cut]


The second relation can even not be expressed in Haskell 98.


Erm...

class Functor f where
fmap :: (a - b) - f a - f b
class Functor m = Monad m where
return :: a - m a
join :: m (m a) - m a
bind :: Monad m = m a - (a - m b) - m b
bind mx f = join $ fmap f mx

Now liftM must be exactly equal to fmap.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Haskell maximum stack depth

2008-02-04 Thread Simon Peyton-Jones

| Sorry, but if what you say is true then things are even worse than I
| thought :-( This behaviour seems really bad to me, especially for
| concurrent programs.

Which behaviour precisely?  Can you say what is wrong and what behaviour you 
expect?

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


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

2008-02-04 Thread Wolfgang Jeltsch
Am Montag, 4. Februar 2008 13:22 schrieben Sie:
 On Feb 4, 2008 12:36 PM, Wolfgang Jeltsch wrote:
[…]

 I don't still know how many people would be interested in using the
 type-level library so, again, I think it won't hurt to include the
 TH-generated aliases and then change it if some non-GHC user rants
 about it.

Okay, let’s do so for now.

  So type-level + parametrized-data is my vote.  But don't let's spend too
  much time discussing the name. ;-)

 Fair enough. type-level + parameterized-data it is then (unless
 someone else has a better suggestion). I'm going to begin coding now.

Yes, go ahead. :-)  Thanks a lot.

 I'll host the project in community.haskell.org, do you have an account
 there?

Now, I haven’t. :-( 

 PS: BTW, I asked Oleg for permission and, as expected, agreed to
 create the library under a BS-D license.

Great.  So the packages you create now will be released under BSD3, right?

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


Re: [Haskell-cafe] Haskell maximum stack depth

2008-02-04 Thread Neil Mitchell
Hi

 But if a program or library is deliberately designed to
 make use of stack (in preference to heap) for efficiency reasons
 then this is a source of bugs in otherwise perfectly correct and
 reasonable programs.

Can you give an example of a particular library or program, so
everyone can be a bit more concrete about what you think should be
allowed, but that isn't?

Thanks

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


Re: [Haskell-cafe] Bug in System.Environment - EOT inserted into argument string

2008-02-04 Thread David Fox
I think it is a bug in the emacs shell mode.

On Feb 4, 2008 9:30 AM, Clifford Beshers [EMAIL PROTECTED] wrote:

 No, I cannot reproduce this.

 2008/2/4 David Fox [EMAIL PROTECTED]:

  I'm seeing the character ^D inserted into argument strings that are
  about 256 characters long with GHC 6.8.2.  Anyone else?
 
  Test.hs:
 
  module Main where
 
  import System.Environment
  import System.IO
 
  main =
  do args - getArgs
 hPutStrLn stderr (args:  ++ show args)
 
 
  Output:
 
  $ ghc6 --make Test.hs -o test
  [1 of 1] Compiling Main ( Test.hs, Test.o )
  Linking test ...
  $ ./test
  012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789
  args:
  [01234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234\EOT5678901234567890123456789]
 
 
  ___
  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] fmap vs. liftM

2008-02-04 Thread Derek Elkins
On Mon, 2008-02-04 at 12:22 -0200, Felipe Lessa wrote:
 Hi there,
 
 Reading http://www.haskell.org/haskellwiki/Things_to_avoid I found an
 interesting saying:
 
 By the way, in the case of IO monad the Functor class method fmap and
 the Monad based function liftM are the same.
 
 I always tought that
 
 prop :: (Functor m, Monad m, Eq (m b)) = (a - b) - m a - Bool
 prop f x = fmap f x == liftM f x
 
 was True regardless of 'm'. Is there any exception?

If there is, it's a bug in the library except you wouldn't normally use
(==) but some meta-level equality*.  From one perspective, liftM is the
proof that every monad is a functor. 

* Usually observational equality, but one may want variants, e.g.
observational equality with respect to some observe function

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


Re: [Haskell-cafe] Bug in System.Environment - EOT inserted into argument string

2008-02-04 Thread Clifford Beshers
No, I cannot reproduce this.

2008/2/4 David Fox [EMAIL PROTECTED]:

 I'm seeing the character ^D inserted into argument strings that are about
 256 characters long with GHC 6.8.2.  Anyone else?

 Test.hs:

 module Main where

 import System.Environment
 import System.IO

 main =
 do args - getArgs
hPutStrLn stderr (args:  ++ show args)


 Output:

 $ ghc6 --make Test.hs -o test
 [1 of 1] Compiling Main ( Test.hs, Test.o )
 Linking test ...
 $ ./test
 012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789
 args:
 [01234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234\EOT5678901234567890123456789]


 ___
 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] building the unix package and cabal

2008-02-04 Thread Thomas Schilling
This is the GNU Multi-Precision library.  You have to install that
separately, Cabal can't do that for you.  You should use the redhat
package manager to install it. HTH

On Feb 4, 2008 4:43 PM, Galchin Vasili [EMAIL PROTECTED] wrote:
 Hi Thomas,

 Have you tried to build this package yourself? I get a linker error ..
 unresolved symbol gmp.

 Vasili




 On 2/4/08, Thomas Schilling [EMAIL PROTECTED] wrote:
  Build-type: Configure means that *Cabal uses ./configure * to build
  the package.  Nothing changes for you.  Just use the usual:
 
  runhaskell Setup.hs configure --prefix=... [--user]
  runhaskell Setup.hs build
  runhaskell Setup.hs install
 
  or with cabal-install:
 
  cabal install unix
 
  2008/2/4 Galchin Vasili [EMAIL PROTECTED]:
   Hello,
  
 I have been trying to build the unix package on RedHat RHEL 5.
 Over
   the weekend I read through the Cabal documentation. The unix-2.2.0.0
   unix.cabal specifies the build-type attribute as Configure. Based on
   Cabal doc, I should run ./configure. After this step then what? Bottom
 line
   is how do I build the unix-2.2.0.0 package on RHEL 5?
  
   Thank you, Vasili
   ___
   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] building the unix package and cabal

2008-02-04 Thread Galchin Vasili
more specifically the gmp unsatisfied ref shows up with the DynamicLinker.

On 2/4/08, Thomas Schilling [EMAIL PROTECTED] wrote:

 I don't know.  Maybe someone on @cafe can help. (I CC'd)

 On Feb 4, 2008 5:22 PM, Galchin Vasili [EMAIL PROTECTED] wrote:
  I have the gmp shared objects installed, i.e. .so's. Does ghc require
 static
  linking with .a archive files?
 
 
 
 
  On 2/4/08, Thomas Schilling [EMAIL PROTECTED] wrote:
   This is the GNU Multi-Precision library.  You have to install that
   separately, Cabal can't do that for you.  You should use the redhat
   package manager to install it. HTH
  
   On Feb 4, 2008 4:43 PM, Galchin Vasili [EMAIL PROTECTED] wrote:
Hi Thomas,
   
Have you tried to build this package yourself? I get a linker
 error
  ..
unresolved symbol gmp.
   
Vasili
   
   
   
   
On 2/4/08, Thomas Schilling [EMAIL PROTECTED] wrote:
 Build-type: Configure means that *Cabal uses ./configure * to
 build
 the package.  Nothing changes for you.  Just use the usual:

 runhaskell Setup.hs configure --prefix=... [--user]
 runhaskell Setup.hs build
 runhaskell Setup.hs install

 or with cabal-install:

 cabal install unix

 2008/2/4 Galchin Vasili [EMAIL PROTECTED]:
  Hello,
 
I have been trying to build the unix package on RedHat
 RHEL 5.
Over
  the weekend I read through the Cabal documentation. The
 unix-2.2.0.0
  unix.cabal specifies the build-type attribute as Configure.
  Based on
  Cabal doc, I should run ./configure. After this step then what?
  Bottom
line
  is how do I build the unix-2.2.0.0 package on RHEL 5?
 
  Thank you, Vasili
  ___
  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] Bug in System.Environment - EOT inserted into argument string

2008-02-04 Thread David Fox
I'm seeing the character ^D inserted into argument strings that are about
256 characters long with GHC 6.8.2.  Anyone else?

Test.hs:

module Main where

import System.Environment
import System.IO

main =
do args - getArgs
   hPutStrLn stderr (args:  ++ show args)


Output:

$ ghc6 --make Test.hs -o test
[1 of 1] Compiling Main ( Test.hs, Test.o )
Linking test ...
$ ./test
012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789
args:
[01234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234\EOT5678901234567890123456789]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] building the unix package and cabal

2008-02-04 Thread Thomas Schilling
I don't know.  Maybe someone on @cafe can help. (I CC'd)

On Feb 4, 2008 5:22 PM, Galchin Vasili [EMAIL PROTECTED] wrote:
 I have the gmp shared objects installed, i.e. .so's. Does ghc require static
 linking with .a archive files?




 On 2/4/08, Thomas Schilling [EMAIL PROTECTED] wrote:
  This is the GNU Multi-Precision library.  You have to install that
  separately, Cabal can't do that for you.  You should use the redhat
  package manager to install it. HTH
 
  On Feb 4, 2008 4:43 PM, Galchin Vasili [EMAIL PROTECTED] wrote:
   Hi Thomas,
  
   Have you tried to build this package yourself? I get a linker error
 ..
   unresolved symbol gmp.
  
   Vasili
  
  
  
  
   On 2/4/08, Thomas Schilling [EMAIL PROTECTED] wrote:
Build-type: Configure means that *Cabal uses ./configure * to build
the package.  Nothing changes for you.  Just use the usual:
   
runhaskell Setup.hs configure --prefix=... [--user]
runhaskell Setup.hs build
runhaskell Setup.hs install
   
or with cabal-install:
   
cabal install unix
   
2008/2/4 Galchin Vasili [EMAIL PROTECTED]:
 Hello,

   I have been trying to build the unix package on RedHat RHEL 5.
   Over
 the weekend I read through the Cabal documentation. The unix-2.2.0.0
 unix.cabal specifies the build-type attribute as Configure.
 Based on
 Cabal doc, I should run ./configure. After this step then what?
 Bottom
   line
 is how do I build the unix-2.2.0.0 package on RHEL 5?

 Thank you, Vasili
 ___
 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: Data.Ord and Heaps (Was: Why functional programming matters)

2008-02-04 Thread Stephan Friedrichs

Hi,

I'm sorry it took me so long to respond!

[EMAIL PROTECTED] wrote:

[newtype Ord a = Reverse a = Reverse { unReverse :: a }]

This solution should be used for all collections depending on Ord 
instances, including Data.Map, Data.Set and others. As long as I only 
include it in my tiny heap package, it is as 'non-standard' as my 
approach, isn't it?


Yes. I mean non-standard in the software-reuse sense, i.e. Ord is for 
user-defined orderings and should be the only such mechanism in order to 
enable reuse. In fact, Data.Heap clearly shows that Data.Ord is 
currently missing functionality.


Ah, now I see. The entire ordering policy mechanism - no matter how it 
is going to be solved - belongs into Data.Ord and not in Data.Heap. As 
soon as Data.Ord provides a solution, I'll use it in Data.Heap.




[...]

Note that the Heap class contains only three primitive operations 
(empty, insert, viewHead), all the others have default implementations 
in terms of those three. There is even an underappreciated unfold among 
them :)


  toAscList = unfoldr viewHead

The structure becomes especially clear by noting that any Heap is 
defined by just two primitives


  inject :: Ord a = Maybe (a, Heap a) - Heap a
  view   :: Ord a = Heap a - Maybe (a, Heap a)

We have  inject = maybe empty (uncurry insert)  . This is just like 
lists, except that  view . inject ≠ id   since  view  returns the 
smallest element.


I stumbled over the similarity of heaps and lists when implementing 
take, takeWhile, span, break, etc. (btw, they are included in heap-0.2 
which I uploaded yesterday); so a heap is really nothing but a packed 
representation of a sorted list :)




However, just that we managed to reduce the number of primitive 
operations doesn't mean that the policy approach isn't preferable. It 
needs 0 primitive operations, after all. But as foreshadowed in my 
reply, it's possible to do policies within Ord. Don't stop thinking 
about your good idea just because you can start coding :)


Here's one way to do it:

   [...]

In conclusion: the ordering policy stuff should not be part of 
Data.Heap, this is a job for Data.Ord.
As mentioned above: This sounds really useful. How about you propose 
this to the base-package maintainers? :)


What, me? :D


Where? :)

Regards, Stephan

--

Früher hieß es ja: Ich denke, also bin ich.
Heute weiß man: Es geht auch so.

 - Dieter Nuhr



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


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

2008-02-04 Thread Wolfgang Jeltsch
Am Samstag, 2. Februar 2008 14:54 schrieben Sie:
 On Feb 1, 2008 10:32 PM, Wolfgang Jeltsch wrote: 
  Am Freitag, 1. Februar 2008 13:00 schrieb Alfonso Acosta:
 […]

   To make it friendlier for the end user I thought about defining
   aliases for lets say the first 1 numbers using Template Haskell.
   That could even make error reports friendlier (not sure to what point
   though). What do you think?
 
  I have no clear opinion about that at the moment.  Maybe it's okay to use
  the representation directly.  This way, we don't introduce a dependeny on
  the Template Haskell language extension (which is only supported by GHC),
  and the actual representation will occur in error messages anyway
  whenever the message shows a computed number.

 Well, my EDSL already makes extensive use of TH. So, being selfish, it
 wouldn't be a problem for me (or any other GHC user) and I think it
 would make the library much more usable.

 Just compare

 f :: List (() :- D1 :- D0 :- D0 :- 1000) Int - List (() :- D1 :- D0 :-
 D0 :- D0) Int 

 with, let's say

 f :: List A1000 Int - List A1000 Int

 Again, if someone complains about the TH dependency, the aliases could
 be generated by TH but saved statically in a module for each release.

Hmm, this could be a compromise although I’m not sure whether it is sensible 
to have a module with thousands of declarations.  Another solution would be 
to put the Template Haskell convenience stuff into a separate package.  The 
core package would probably be usable with Hugs too, while the convenience 
package would be usable only with GHC.

At the moment, I’m not sure how often I’ll need to state type-level numbers 
explicitely.  So currently I cannot know how important aliases for type-level 
numbers are.

   So, we'll be making two separate libraries then. We should think about
   names.
  
   What about FixedVector for the vector library and DecTypArith (maybe
   too long) or DecTypes for the type-level decimal arithmetic library?
 
  Alas, there is an inconsistency in naming packages already.  Some prefer
  names which are entirely lowercase, some prefer camel case.  I prefer
  lowercase, with hyphens separating parts of the name.  And I also don't
  like unusual abbreviations like typ (not much shorter than type).  To
  mention arithmetics is not so important.  So maybe something
  like type-level-decimals?
 
  Maybe it's better to put different type-level programming things into a
  single package.  Then we could name this package type-level or
  something similar. We could start with our decimals.  Other type-level
  things could be added later.  I already have some code about type-level
  booleans.  It's not very sensible to put these few lines into a separate
  package.  It might be nice if we had a general type-level programming
  package where I could put this code into.

 Sounds sensible. However, I would rather prefer something like
 type-level-comp (from type level computations) or type-level-prog
 (from type level programming). Type level by itself doesn't describe
 the functionality of the package.

Hmm, package names don’t have to be descriptive.  Short names tend to sound 
better and be easier to remember.  My FRP GUI and graphics library is named 
Grapefruit.  This name makes hardly any sense.  It refers to the previous 
library Fruit and the fact that I like Grapefruits—nothing more.  But it’s a 
name, people can remember more easily than FRGGLER (Functional Reactive GUI 
and Graphics Library with Extensible Records). ;-) 

In addition, abbreviations like “comp” typically have the problem of being 
ambiguous: computation, composition, component, …

So I still prefer type-level.

  As for the name of the fixed-size list package, I have to say that I
  don't like the term vector in this context.  A vector is actually
  something with addition and scalar multiplication defined on it.  Maybe
  we should make also this package's scope wider.  What about something
  like safe-data or similar?

 I think safe-data is a bit too general and might lead to confusion
 with other safe data packages (namely Mitchell's Safe library). Since
 the main particularity of the library is that safety properties are
 achieved via emulating dependent types I think that
 light-dependent-types (from lightweight dependent types),
 number-parameterized-data or simply parameterized-data (this is the
 name I like best) would be more appropiate.

parametrized-data looks good.  The others seem to be too long again.

So type-level + parametrized-data is my vote.  But don’t let’s spend too much 
time discussing the name. ;-) 

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


Re: [Haskell-cafe] Haskell maximum stack depth

2008-02-04 Thread Adrian Hey

Hello Simon,

Simon Peyton-Jones wrote:

| Sorry, but if what you say is true then things are even worse than I
| thought :-( This behaviour seems really bad to me, especially for
| concurrent programs.

Which behaviour precisely?  Can you say what is wrong and what behaviour you 
expect?


Roughly..

First bad thing:
Stack size (memory consumed) doubles each time it overflows.

Second bad thing:
Arbitrary limit on stack size unrelated to overall (heap) memory
available.

Third bad thing (the really bad thing):
If a stack has temporarily grown (to 64M say), it will never shrink
back down again to something more typical ( 4K say). If I understand
correctly, it will continue to take 64M from the heap regardless.

What I would like is to be able to set an upper limit on total memory
useage and allow the program to freely use this memory as either stack
or heap. At least that should be the default behaviour, but maybe
also allow +RTS restrictions for debugging (though I don't think this
is a very good way of investigating a programs stack use).

I would also like stack memory allocation to increase (and decrease :-)
in some sane sized linear increment, not double each time. With the
current scheme, as I understand it, if 65M is needed then 128M will be
allocated.

Stefan O'Rear suggested an alternative. I don't know how hard it would
be to implement though (don't really know anything about ghc rts).

 http://haskell.org/pipermail/glasgow-haskell-users/2007-May/012472.html

Regards
--
Adrian Hey





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


[Haskell-cafe] Is Haskore dead?

2008-02-04 Thread Maurí­cio

Hi,

I've just tried using Haskore (I use Ubuntu
and GHC), with no success. Since Haskore was
started a long time ago, but it's not yet
cabalized, and the author's page can not be
reached, I can't say for sure if it's still
maintained. Does anybody know?

Thanks,
Maurício

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


Re: [Haskell-cafe] modeling ANSI C structs in Haskell?

2008-02-04 Thread Magnus Therning
On 2/4/08, Galchin Vasili [EMAIL PROTECTED] wrote:

 Hello,

   I am reading through the FFI doc. Any suggestions on enabling
 Haskell programmers to model ANSI C structs that will be passed down to C
 run-time?


Maybe this could offer some help http://therning.org/magnus/archives/315

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


Re: module hierarchy (Re: [Haskell-cafe] parsec3 pre-release [important note])

2008-02-04 Thread Johan Tibell
On Feb 4, 2008 12:11 PM, Wolfgang Jeltsch [EMAIL PROTECTED] wrote:
 Am Samstag, 2. Februar 2008 05:53 schrieb Derek Elkins:
  I forgot to mention that the Text.Parsec modules should be preferred to
  the Text.ParserCombinators.Parsec modules as the Haddock documentation
  reveals.

 I would have prefered to shorten ParserCombinators to Parsing and leave Parsec
 under the parsing category.  However, I would prefer if Parsing would move
 out of Text since parsing is not just about parsing text.  Parsec parses also
 streams other than character streams now.

 Recently, there was a discussion on the Yampa mailing list about where to put
 FRP-related modules into the module hierarchy.  There was the suggestion of
 Control.FRP.  It was noted, however, that Control seems to suggest imperative
 programming while many things under Control are not restricted to that
 paradigm (like monads, for example) and others (like FRP) have nothing to do
 with imperative programming.  We finally chose to introduce a separate
 top-level module name FRP since the FRP stuff didn't seem to really fit in
 any of the existing top-level categories.

 I concluded from this discussion that the current module hierarchy is too deep
 and that it might be good to remove the current top-level layer.  So
 Parsing.Parsec, for example, or Monad.Reader.

 What do you and others think?

I would recommend reading Ontology is Overrated [1] as it might be of
relevant to this discussion. I've been asking myself lately if it
would be beneficial for libraries that are not very core (e.g.
Data.Map) to use a unique top-level name (e.g. Parsec.SubModule) and
leave categorization to Hackage. Or should we just try to cram
everything into the same module hierarchy (e.g. Parsing.Parsec,
Parsing.Foo, etc?).

Another question: If we continue with the current approach where
should we put versions of a library specialized to a certain type?
e.g.

Parsing.ByteString.Parsec or Parsing.Parsec.ByteString?

The current preference seems to be to use the latter but that makes it
hard to find all parsing libraries that parses bytestrings as they
would not be kept under Parsing.ByteString.

1. http://www.shirky.com/writings/ontology_overrated.html

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


Re: [Haskell-cafe] fmap vs. liftM

2008-02-04 Thread Henning Thielemann

On Mon, 4 Feb 2008, Felipe Lessa wrote:

 Hi there,

 Reading http://www.haskell.org/haskellwiki/Things_to_avoid I found an
 interesting saying:

 By the way, in the case of IO monad the Functor class method fmap and
 the Monad based function liftM are the same.

 I always tought that

 prop :: (Functor m, Monad m, Eq (m b)) = (a - b) - m a - Bool
 prop f x = fmap f x == liftM f x

 was True regardless of 'm'. Is there any exception? If so, why? I've
 even done s/fmap/liftM/g and s/liftM/fmap/g in the past for
 consistency =).

Problem is that from the idea Functor is a superclass of Monad, with the
property that fmap == liftM. The first relation could have been
expressed in Haskell 98 but was not done (forgotten?) in the standard
libraries. The second relation can even not be expressed in Haskell 98. So
it's only cosmetic, if you use 'liftM' instead of 'fmap' in order to avoid
an explicit 'Functor' constraint in a function.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell maximum stack depth

2008-02-04 Thread Neil Mitchell
Hi

 First bad thing:
 Stack size (memory consumed) doubles each time it overflows.

Bad thing? Assume that allocating memory takes some constant amount of
time, such as invoking overflow behaviour etc. To get the size of the
stack to n bytes with doubling takes O(log n), to get it there with a
constant increase takes O(n). If you store the stack in a linear
block, then allocation costs O(n) and you can even risk O(n^2)
behaviour unless you double each time. I think its fairly well
understood that things like hash tables should double in size when
they overflow, rather than increasing by some small increment. Also
remember that this behaviour never wastes more than 50% of the stack,
which is a relatively small amount.

 Third bad thing (the really bad thing):
 If a stack has temporarily grown (to 64M say), it will never shrink
 back down again to something more typical ( 4K say). If I understand
 correctly, it will continue to take 64M from the heap regardless.

That would be nice. But its only beneficial if there are programs
which takes large amounts of stack at some point, but then shrink down
to very little stack and continue for a reasonable amount of time.
Console programs probably don't fit this pattern (since they tend to
be batch style and exit quickly). GUI programs probably do, so perhaps
stack reduction will be more important as the GUI toolkits mature and
Haskell starts getting used for UI type things. That said, unless
there is a real user with a real problem (rather than a theoretical
concern), priority may go to other bugs.

Thanks

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


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

2008-02-04 Thread Wolfgang Jeltsch
Am Montag, 4. Februar 2008 20:44 schrieben Sie:
   I'll host the project in community.haskell.org, do you have an account
   there?
 
  Now, I haven't. :-(

 Well, you can request one at
 http://community.haskell.org/admin/account_request.html if you want

 Otherwise I'll take the maintainer role.

I’m fine with you having the maintainer role as long as you accept a patch 
from me from time to time. :-) 


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


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

2008-02-04 Thread Alfonso Acosta
On Feb 4, 2008 8:27 PM, Wolfgang Jeltsch [EMAIL PROTECTED] wrote:
 Am Montag, 4. Februar 2008 13:22 schrieben Sie:
  I don't still know how many people would be interested in using the
  type-level library so, again, I think it won't hurt to include the
  TH-generated aliases and then change it if some non-GHC user rants
  about it.

 Okay, let's do so for now.

Actually, I was considering to conditionally include the TH code or
not depending on the compiler (using Cabal configurations).

I thought that should make everyone happy. Then, I realized we
agreed to make use of infix type constructors anyway (which seems to
be a GHC-only extension, tell me if I'm wrong), so the TH dependency
is not that important anymore (unless we decide to avoid infix type
constructors)

  I'll host the project in community.haskell.org, do you have an account
  there?

 Now, I haven't. :-(

Well, you can request one at
http://community.haskell.org/admin/account_request.html if you want

Otherwise I'll take the maintainer role.

  PS: BTW, I asked Oleg for permission and, as expected, agreed to
  create the library under a BS-D license.

 Great.  So the packages you create now will be released under BSD3, right?

Yes, that's the intention.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] fmap vs. liftM

2008-02-04 Thread Felipe Lessa
Hi there,

Reading http://www.haskell.org/haskellwiki/Things_to_avoid I found an
interesting saying:

By the way, in the case of IO monad the Functor class method fmap and
the Monad based function liftM are the same.

I always tought that

prop :: (Functor m, Monad m, Eq (m b)) = (a - b) - m a - Bool
prop f x = fmap f x == liftM f x

was True regardless of 'm'. Is there any exception? If so, why? I've
even done s/fmap/liftM/g and s/liftM/fmap/g in the past for
consistency =).

Thanks!

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


[Haskell-cafe] modeling ANSI C structs in Haskell?

2008-02-04 Thread Galchin Vasili
Hello,

  I am reading through the FFI doc. Any suggestions on enabling Haskell
programmers to model ANSI C structs that will be passed down to C run-time?

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


Re: [Haskell-cafe] Haskell maximum stack depth

2008-02-04 Thread Matthew Pocock
On Monday 04 February 2008, Adrian Hey wrote:
 Yikes!

 Also, I can't help thinking that the common justification for the
 current limit (that it helps find alleged bugs) is a little lame.
 It only helps find bugs if one expects ones program to use less than
 8M of stack (hence if it's using more, it's a bug by ones *own*
 definition). 

My experience so far is that I've only triggered stack overflows when I've had 
an infinite recursion. Getting foldl and foldr wrong on long lists has 
usually lead to disasterous memory churn, not ever to an overflow.

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


Re: [Haskell-cafe] Is Haskore dead?

2008-02-04 Thread gwern0
On 2008.02.04 16:11:55 -0200, Maurí­cio [EMAIL PROTECTED] scribbled 0.3K 
characters:
 Hi,

 I've just tried using Haskore (I use Ubuntu
 and GHC), with no success. Since Haskore was
 started a long time ago, but it's not yet
 cabalized, and the author's page can not be
 reached, I can't say for sure if it's still
 maintained. Does anybody know?

 Thanks,
 Maurício

I think the homepage http://www.haskell.org/haskore/ is more than a bit old. 
I googled a bit more, and found http://www.haskell.org/haskellwiki/Haskore 
which links to a Darcs repo at http://darcs.haskell.org/haskore/. The most 
recent modification date is for src/, 04-Dec-2007. I'm trying it out right now, 
but the darcs get is taking a while.

--
gwern
ssa NMS encryption Finksburg Panama 1071 fraud import MDA South


pgpBKsrGSxIea.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell maximum stack depth

2008-02-04 Thread Matthew Pocock
On Monday 04 February 2008, Neil Mitchell wrote:
 Hi

 That would be nice. But its only beneficial if there are programs
 which takes large amounts of stack at some point, but then shrink down
 to very little stack and continue for a reasonable amount of time.

From the 'when I was a lad' department...

Thinking back to when Java transitioned to a garbage collector that could give 
memory back to the OS, we got some unexpected benefits. Consider a machine 
that's running a load of programs, launched from some q system e.g. 
LSF/condor. If they keep memory, the box, q scheduler or admins get unhappy.

If I had £1 for each time our admins said your 200 java apps are using 500m 
each when I could see for sure that except for an initial memory burn 
during loading files in, only a few megs where resident. Magically, once Java 
could release heap, these grypes went away.

Matthew

 Thanks

 Neil
 ___
 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] A handy little consequence of the Cont monad

2008-02-04 Thread Cale Gibbard
On 04/02/2008, Philip Armstrong [EMAIL PROTECTED] wrote:

 I've always liked $ for this kind of code, if you want to keep the
 arguments around:

next xs = runCont $ sequence $ map Cont xs

 seems quite natural to me.


I'd probably write that as

nest xs = runCont . sequence . map Cont $ xs

or else as:

nest xs = runCont . sequence $ map Cont xs

so as not to abuse the fact that ($) really has the wrong
associativity. (I didn't really give that aspect of the code a
moment's thought, or else I'd probably have made it either points-free
or used the first form above. I've been bitten by the MR enough times
that I'm wary of eta-reducing the last parameter out of functions --
of course, the explicit type signature means it doesn't matter.)

It would be nice to flip the associativity of ($) someday. It loses
little in the way of expressiveness, since one can generally replace
the first (n-1) instances of ($) with (.) straightforwardly (the one
exception to this being when there are other operator symbols like
(***) acting on the functions involved, but these cases are fairly
rare, and it's arguably clearer to leave those parens in).

What it would buy us to make ($) left associative is that we could,
for instance, remove the parens from an expression like:

f (g x) (h y) (k z)

getting:

f $ g x $ h y $ k z

Perhaps for Haskell 2. :)

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


Re: [Haskell-cafe] Adding gcc type options with cabal (e.g. -mno-cygwin)

2008-02-04 Thread Duncan Coutts

On Mon, 2008-02-04 at 17:18 -0500, bbrown wrote:
 Is there a way to pass misc options to the cabal, ghc process.
 
 I tried the following:
 
 extra-libraries: sqlite3
 extra-lib-dirs:  C:\cygwin\lib
 include-dirs:C:\cygwin\usr\include
 ghc-options: -mno-cygwin
 
 runhaskell Setup.lhs build --ghc-options=-mno-cygwin -v
 
 No dice, doesn't show up.

Really? That's odd, works for me:

$ runhaskell Setup.lhs build --ghc-options=-mno-cygwin -v
...
[snip]
...
ghc-6.8.2: unrecognised flags: -mno-cygwin
Usage: For basic information, try the `--help' option.

Also works with runhaskell Setup.lhs configure --ghc-options=-mno-cygwin

Works in the sense that it passes the flag through to ghc. Of course I'm
on unix and ghc does not recognise that flag.

What version of Cabal are you using?

Duncan

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


Re: [Haskell-cafe] Adding gcc type options with cabal (e.g. -mno-cygwin)

2008-02-04 Thread bbrown
On Mon, 4 Feb 2008 14:24:12 -0800, Don Stewart wrote
 bbrown:
  Is there a way to pass misc options to the cabal, ghc process.
  
  I tried the following:
  
  extra-libraries: sqlite3
  extra-lib-dirs:  C:\cygwin\lib
  include-dirs:C:\cygwin\usr\include
  ghc-options: -mno-cygwin
  
  runhaskell Setup.lhs build --ghc-options=-mno-cygwin -v
 
 ghc-options: -optc-mno-cygwin
 cc-options:  -mno-cygwin
 
 or 
 ghc-options: -O2 -Wall
 cc-options:  -Wall
 
 or via the foo.buildinfo file.
 
 Ghc-options: [EMAIL PROTECTED]@
 Cc-options:  @CPPFLAGS@
 
 Writing a binding to sqlite3?
 
 -- Don

 Writing a binding to sqlite3?

No, one already exists.  Trying to compile that one.  My googling powers are
crippled with haskell.  I couldn't find how to add those options.

Thanks for the quick response.

--
Berlin Brown
email: berlin-dot-brown-AT-gmail-dot-com
http://botspiritcompany.com/botlist/

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


[Haskell-cafe] Adding gcc type options with cabal (e.g. -mno-cygwin)

2008-02-04 Thread bbrown
Is there a way to pass misc options to the cabal, ghc process.

I tried the following:

extra-libraries: sqlite3
extra-lib-dirs:  C:\cygwin\lib
include-dirs:C:\cygwin\usr\include
ghc-options: -mno-cygwin

runhaskell Setup.lhs build --ghc-options=-mno-cygwin -v

No dice, doesn't show up.

--
Berlin Brown
email: berlin-dot-brown-AT-gmail-dot-com
http://botspiritcompany.com/botlist/

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


Re: [Haskell-cafe] Haskell maximum stack depth

2008-02-04 Thread Adrian Hey

Neil Mitchell wrote:

Hi


First bad thing:
Stack size (memory consumed) doubles each time it overflows.


Bad thing? Assume that allocating memory takes some constant amount of
time, such as invoking overflow behaviour etc. To get the size of the
stack to n bytes with doubling takes O(log n), to get it there with a
constant increase takes O(n).


But whatever the program did to get given stack size must have
been at least O(n) anyway, so overall it's still going to be O(n)
even if the stack allocation part is O(log n). We're just talking
about a very tiny increase in constant factors, at least if Stefan
O'Rears hypothesis is correct :-). I'm inclined to agree with him.


If you store the stack in a linear
block, then allocation costs O(n) and you can even risk O(n^2)
behaviour unless you double each time. I think its fairly well
understood that things like hash tables should double in size when
they overflow, rather than increasing by some small increment.


It is? Well obviously if the entire thing is copied each time this
will be bad, but that's not what we're talking about. See Stefans
proposal.


Also
remember that this behaviour never wastes more than 50% of the stack,
which is a relatively small amount.


Only if the stack is relatively small. Would you say the same about
heap, or about a stack that only needed 50% of heap space but ended
up using all of it? Or money? Using twice as much as you need of
anything is bad IMO.


Third bad thing (the really bad thing):
If a stack has temporarily grown (to 64M say), it will never shrink
back down again to something more typical ( 4K say). If I understand
correctly, it will continue to take 64M from the heap regardless.


That would be nice. But its only beneficial if there are programs
which takes large amounts of stack at some point, but then shrink down
to very little stack and continue for a reasonable amount of time.
Console programs probably don't fit this pattern (since they tend to
be batch style and exit quickly). GUI programs probably do, so perhaps
stack reduction will be more important as the GUI toolkits mature and
Haskell starts getting used for UI type things.


The nature of the app has nothing to do with it AFAICS, this problem
can affect any program that evaluates expressions.


That said, unless
there is a real user with a real problem (rather than a theoretical
concern), priority may go to other bugs.


The point is that writing a stack greedy function definition (rather
than a heap greedy alternative) is almost always the simpler option,
and would probably be more efficent too. It would also be perfectly
OK in *most* situations.

But being OK in most situations isn't good enough. You also (as far
as is possible given finite amount of total memory) want it to be
OK in pathological situations, or at least no worse than the heap
greedy version. Why should the decision to use a stack greedy definition
cause a crash at 8M whereas a heap greedy definition can happily use
much more without crashing?

I (like everyone else) tend to avoid knowingly writing stack greedy
definitions because of this. But I do this as a workaround for ghc's
currently (IMO) poor stack management, not because I consider code
that uses the stack to be inherently buggy.

Furthermore as I said earlier, using a lot of stack is purely a
ghc rts implementation detail. Other possible Haskell implementations
may not use a lot of stack for the same function (may not use a stack
at all). So you can't say a program has bugs just because it happens
to cause a stack overflow with ghc. You might reasonably argue that
it has a bug if it uses a lot of memory with any plausible Haskell
implementation (one way or another) *and* you can show that there is
an alternative implementation which uses asymptotically less memory.

Regards
--
Adrian Hey

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


Re: [Haskell-cafe] building the unix package and cabal

2008-02-04 Thread Ian Lynagh
On Mon, Feb 04, 2008 at 10:50:13AM -0600, Galchin Vasili wrote:
 more specifically the gmp unsatisfied ref shows up with the DynamicLinker.

This works for me, with GHC 6.8.2 and
http://hackage.haskell.org/packages/archive/unix/2.2.0.0/unix-2.2.0.0.tar.gz

$ ghc --make Setup
$ ./Setup configure --user
$ ./Setup build

If it's not working for you then you might need a RHEL package called
something like gmp-devel. If that doesn't fix it, please send us the
exact commands you are running and the complete output.

Note that you wouldn't normally compile the unix package yourself,
however, as it is one of the packages that comes with GHC.


Thanks
Ian

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


[Haskell-cafe] FP and Quality

2008-02-04 Thread PR Stanley

Hi folks
I'm thinking of writing a little essay arguing the case for the 
advantages of FP for producing quality software. Can the list 
recommend any papers/articles which I can use as sources of my 
argument? I have access to the IEEE database too although earlier I 
couldn't find anything on the subject.

Thanks, Paul

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


Re: [Haskell-cafe] Adding gcc type options with cabal (e.g. -mno-cygwin)

2008-02-04 Thread Don Stewart
bbrown:
 Is there a way to pass misc options to the cabal, ghc process.
 
 I tried the following:
 
 extra-libraries: sqlite3
 extra-lib-dirs:  C:\cygwin\lib
 include-dirs:C:\cygwin\usr\include
 ghc-options: -mno-cygwin
 
 runhaskell Setup.lhs build --ghc-options=-mno-cygwin -v

ghc-options: -optc-mno-cygwin
cc-options:  -mno-cygwin

or 
ghc-options: -O2 -Wall
cc-options:  -Wall

or via the foo.buildinfo file.

Ghc-options: [EMAIL PROTECTED]@
Cc-options:  @CPPFLAGS@

Writing a binding to sqlite3?

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


Re: [Haskell-cafe] FP and Quality

2008-02-04 Thread Tim Chevalier
On 2/4/08, PR Stanley [EMAIL PROTECTED] wrote:
 Hi folks
 I'm thinking of writing a little essay arguing the case for the
 advantages of FP for producing quality software. Can the list
 recommend any papers/articles which I can use as sources of my
 argument? I have access to the IEEE database too although earlier I
 couldn't find anything on the subject.

Try:

Philip Wadler. An angry half dozen. SIGPLAN Notices 33(2):25--30,
February 1998. [NB.
http://citeseer.ist.psu.edu/article/wadler98angry.html ]

Also look for the schedules for the 2007 and 2006 CUFP (Commercial
Users of Functional Programming) workshops. The schedules have links
to slides from talks by people using FP in industry.

Cheers,
Tim

-- 
Tim Chevalier * http://cs.pdx.edu/~tjc * Often in error, never in doubt
Not only would I never want to belong to any club that would have me
for a member -- if elected I would wear street shoes onto the squash
court and set fire to the ballroom curtains.--Michael Chabon
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] FP and Quality

2008-02-04 Thread PR Stanley
Thanks, keep the tips coming. I like the ones about the type safety 
and line counts.

Cheers,
Paul
At 23:33 04/02/2008, you wrote:

Good luck with this - I'd love to see the outcome.

My experience is that FP tends to result in a lot less code, so if 
there are x

bugs per line of code, FP has less bugs per complete application.

Talking about haskell, the typesystem dissalows whole classes of bugs. Things
simply do not compile if you stitch the innards together in the wrong order
(particuarly if you are agressive about using the most general types
possible). Since this accounts for perhaps 90% of where I do things wrong in
Java, I get a corresponding decrease in run-time bugs in haskell. However,
this is somewhat compensated for by the effort needed to get haskell programs
through the compiler in the first place - debug at compile or debug at
runtime is the tradeoff here.

FP is easier to verify mechanically than imperative programming - more of the
logic is exposed directly. It's easier to do by-case proofs, even if they are
by-hand rather than mechanical.

However, all of this is annecdotal. Good luck collecting real stats, or
peer-reviewed annecdotes. You may have luck looking at bug-fix times vs
number of developers for equivalent FP and Java apps/libs. Worth a shot,
given that the bug-trackers tend to be public. You could probably tie it back
to the size of the 'fix' patches. Get some nice graphs?

Matthew

On Monday 04 February 2008, you wrote:
 Hi folks
 I'm thinking of writing a little essay arguing the case for the
 advantages of FP for producing quality software. Can the list
 recommend any papers/articles which I can use as sources of my
 argument? I have access to the IEEE database too although earlier I
 couldn't find anything on the subject.
 Thanks, 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


Re: [Haskell-cafe] Adding gcc type options with cabal (e.g. -mno-cygwin)

2008-02-04 Thread bbrown
On Mon, 4 Feb 2008 17:27:30 -0500, bbrown wrote
 On Mon, 4 Feb 2008 14:24:12 -0800, Don Stewart wrote
  bbrown:
   Is there a way to pass misc options to the cabal, ghc process.
   
   I tried the following:
   
   extra-libraries: sqlite3
   extra-lib-dirs:  C:\cygwin\lib
   include-dirs:C:\cygwin\usr\include
   ghc-options: -mno-cygwin
   
   runhaskell Setup.lhs build --ghc-options=-mno-cygwin -v
  
  ghc-options: -optc-mno-cygwin
  cc-options:  -mno-cygwin
  
  or 
  ghc-options: -O2 -Wall
  cc-options:  -Wall
  
  or via the foo.buildinfo file.
  
  Ghc-options: [EMAIL PROTECTED]@
  Cc-options:  @CPPFLAGS@
  
  Writing a binding to sqlite3?
  
  -- Don
 
  Writing a binding to sqlite3?
 
 No, one already exists.  Trying to compile that one.  My googling 
 powers are crippled with haskell.  I couldn't find how to add those options.
 
 Thanks for the quick response.
 
 --
 Berlin Brown
 email: berlin-dot-brown-AT-gmail-dot-com
 http://botspiritcompany.com/botlist/

I couldn't get hsql-sqlite (other unix libraries?) to compile on cygwin.  I
tried though.

It looks like it is passing the option.  The sqlite3 library is installed and
setup.  From googling, it looks there is an issue with compatibility between
cygwin/ and whatever ghc was compiled with.

But then again, I guess I could not try using cygwin?  I built the library
(sqlite3 under cygwin). Download ghc6.8.2 straight from the haskell.org.

Creating dist\build (and its parents)
Creating dist\build\autogen (and its parents)
Preprocessing library hsql-sqlite3-1.7...
Creating dist\build\Database\HSQL (and its parents)
c:\projects\tools\home\projects\tmp3\ghc-6.8.2\bin\hsc2hs.exe --cc=c:\projects\t
ools\home\projects\tmp3\ghc-6.8.2\bin\ghc.exe --ld=c:\projects\tools\home\projec
ts\tmp3\ghc-6.8.2\bin\ghc.exe --cflag=-optc-mno-cygwin --cflag=-package --cflag=
base-3.0.1.0 --cflag=-package --cflag=hsql-1.7 --cflag=-IC:\cygwin\usr\include -
-lflag=-optl-LC:\cygwin\lib --lflag=-optl-lsqlite3 -o dist\build\Database\HSQL\S
QLite3.hs Database\HSQL\SQLite3.hsc
dist/build/Database/HSQL/SQLite3_hsc_make.o(.text+0x5d):SQLite3_hsc_make.c: unde
fined reference to `_impure_ptr'
dist/build/Database/HSQL/SQLite3_hsc_make.o(.text+0xa1):SQLite3_hsc_make.c: unde
fined reference to `_impure_ptr'
dist/build/Database/HSQL/SQLite3_hsc_make.o(.text+0xc9):SQLite3_hsc_make.c: unde
fined reference to `_impure_ptr'
dist/build/Database/HSQL/SQLite3_hsc_make.o(.text+0xfd):SQLite3_hsc_make.c: unde
fined reference to `_impure_ptr'
dist/build/Database/HSQL/SQLite3_hsc_make.o(.text+0x131):SQLite3_hsc_make.c: und
efined reference to `_impure_ptr'
dist/build/Database/HSQL/SQLite3_hsc_make.o(.text+0x16d):SQLite3_hsc_make.c: mor
e undefined references to `_impure_ptr' follow
collect2: ld returned 1 exit status
linking dist\build\Database\HSQL\SQLite3_hsc_make.o failed
command was: c:\projects\tools\home\projects\tmp3\ghc-6.8.2\bin\ghc.exe -optl-LC
:\cygwin\lib -optl-lsqlite3 dist\build\Database\HSQL\SQLite3_hsc_make.o -o dist\
build\Database\HSQL\SQLite3_hsc_make.exe


--
Berlin Brown
email: berlin-dot-brown-AT-gmail-dot-com
http://botspiritcompany.com/botlist/

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


Re: [Haskell-cafe] building the unix package and cabal

2008-02-04 Thread Galchin Vasili
Hi Ian,

 I am trying to add new Posix functionality and it would be nice to be
able to build unix myself. In any case, I will try your suggestion and see
what happens.

Regards, Vasili


On 2/4/08, Ian Lynagh [EMAIL PROTECTED] wrote:

 On Mon, Feb 04, 2008 at 10:50:13AM -0600, Galchin Vasili wrote:
  more specifically the gmp unsatisfied ref shows up with the
 DynamicLinker.

 This works for me, with GHC 6.8.2 and

 http://hackage.haskell.org/packages/archive/unix/2.2.0.0/unix-2.2.0.0.tar.gz

 $ ghc --make Setup
 $ ./Setup configure --user
 $ ./Setup build

 If it's not working for you then you might need a RHEL package called
 something like gmp-devel. If that doesn't fix it, please send us the
 exact commands you are running and the complete output.

 Note that you wouldn't normally compile the unix package yourself,
 however, as it is one of the packages that comes with GHC.


 Thanks
 Ian


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


Re: [Haskell-cafe] RE: highlighting-kate - syntax highlighting library

2008-02-04 Thread Duncan Coutts

On Sun, 2008-02-03 at 19:38 -0200, Felipe Lessa wrote:
 On Feb 3, 2008 6:42 PM, mgsloan [EMAIL PROTECTED] wrote:
  Would this be suitable for a text editor?
 
 Note that we already have a binding to GtkSourceView, see
 http://www.haskell.org/gtk2hs/docs/current/Graphics-UI-Gtk-SourceView.html

BTW, if anyone wants to update this binding to the GtkSourceView 2.x api
that'd be great. The api has not changed much so the changes should be
pretty simple. The advantage is that the 2.x version has a much better
highlighting engine which allows more accurate highlighters.

Duncan

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


Re: [Haskell-cafe] A handy little consequence of the Cont monad

2008-02-04 Thread Derek Elkins
On Mon, 2008-02-04 at 16:56 -0500, Cale Gibbard wrote:
 On 04/02/2008, Philip Armstrong [EMAIL PROTECTED] wrote:
 
  I've always liked $ for this kind of code, if you want to keep the
  arguments around:
 
 next xs = runCont $ sequence $ map Cont xs
 
  seems quite natural to me.
 
 
 I'd probably write that as
 
 nest xs = runCont . sequence . map Cont $ xs
 
 or else as:
 
 nest xs = runCont . sequence $ map Cont xs
 
 so as not to abuse the fact that ($) really has the wrong
 associativity. (I didn't really give that aspect of the code a
 moment's thought, or else I'd probably have made it either points-free
 or used the first form above. I've been bitten by the MR enough times
 that I'm wary of eta-reducing the last parameter out of functions --
 of course, the explicit type signature means it doesn't matter.)
 
 It would be nice to flip the associativity of ($) someday. It loses
 little in the way of expressiveness, since one can generally replace
 the first (n-1) instances of ($) with (.) straightforwardly (the one
 exception to this being when there are other operator symbols like
 (***) acting on the functions involved, but these cases are fairly
 rare, and it's arguably clearer to leave those parens in).
 
 What it would buy us to make ($) left associative is that we could,
 for instance, remove the parens from an expression like:
 
 f (g x) (h y) (k z)
 
 getting:
 
 f $ g x $ h y $ k z

and also, pointedly,
f $! g x $! h y $! k z
or even just
f $! x $! y

 Perhaps for Haskell 2. :)

We'll get rid of the monomorphism restriction then too and you won't
have to be wary.

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


Re: [Haskell-cafe] fmap vs. liftM

2008-02-04 Thread Jonathan Cast

On 4 Feb 2008, at 6:22 AM, Felipe Lessa wrote:


Hi there,

Reading http://www.haskell.org/haskellwiki/Things_to_avoid I found an
interesting saying:

By the way, in the case of IO monad the Functor class method fmap and
the Monad based function liftM are the same.

I always tought that

prop :: (Functor m, Monad m, Eq (m b)) = (a - b) - m a - Bool
prop f x = fmap f x == liftM f x


Indeed, this is an equation from the equivalence of Haskell and  
category-theoretic monads.  Furthermore, the same thing is explicitly  
asserted by the Haskell 98 Report: [1]


Instances of both Monad and Functor should additionally satisfy the law:

fmap f xs = xs = return . f


was True regardless of 'm'. Is there any exception?


There is only one case I'm aware of: if the author of the type forgot  
to define a functor instance for his monad (I've been guilty of that  
before, at least).


jcc

(I fixed the wiki, btw.)

[1] http://haskell.org/onlinereport/basic.html#sect6.3.6


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


Re: [Haskell-cafe] parsec3 pre-release [attempt 2]

2008-02-04 Thread Philippa Cowderoy
On Sun, 3 Feb 2008, Antoine Latter wrote:

 Another picky nit:

 The monad transformer type is defined as such:

  data ParsecT s u m a
  = ParsecT { runParsecT :: State s u - m (Consumed (m (Reply s u
a))) }

 with the Consumed and reply types as:

  data Consumed a  = Consumed a
   | Empty !a

  data Reply s u a = Ok !a !(State s u) ParseError
   | Error ParseError

 What's the advantage of having a double-wrapping of the base monad `m'
 over the simpler type:

 data ParsecT s u m a
 = ParsecT { runParsecT :: State s u - m (Consumed (Reply s u a)) }


It's a necessary part of how Parsec works - both the Consumed and the
Reply depend on the input stream, which is now generated from within the
base monad. The Consumed result is evaluated in advance of the Reply, so
keeping the computations separate preserves an important piece of
laziness as m could be a strict monad.

For now it's probably a good idea to look for issues that're visible to
client code? Turning Parsec into a transformer was long considered an
invitation to serious confusion, so it's not surprising that a few things
look odd and a few others can be generalised in ways that aren't
immediately obvious.

-- 
[EMAIL PROTECTED]

The reason for this is simple yet profound. Equations of the form
x = x are completely useless. All interesting equations are of the
form x = y. -- John C. Baez


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


Re: [Haskell-cafe] parsec3 pre-release [attempt 2]

2008-02-04 Thread Antoine Latter
On Feb 4, 2008 9:11 PM, Philippa Cowderoy [EMAIL PROTECTED] wrote:
 It's a necessary part of how Parsec works - both the Consumed and the
 Reply depend on the input stream, which is now generated from within the
 base monad. The Consumed result is evaluated in advance of the Reply, so
 keeping the computations separate preserves an important piece of
 laziness as m could be a strict monad.

 For now it's probably a good idea to look for issues that're visible to
 client code? Turning Parsec into a transformer was long considered an
 invitation to serious confusion, so it's not surprising that a few things
 look odd and a few others can be generalised in ways that aren't
 immediately obvious.

After I determined that the pre-release worked fine for the biggest
set of parsers I have, I had to find other things to bring up :-)

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


Re: [Haskell-cafe] Haskell maximum stack depth

2008-02-04 Thread Stefan O'Rear
On Mon, Feb 04, 2008 at 10:13:12PM +, Adrian Hey wrote:
 Also
 remember that this behaviour never wastes more than 50% of the stack,
 which is a relatively small amount.

 Only if the stack is relatively small. Would you say the same about
 heap, or about a stack that only needed 50% of heap space but ended
 up using all of it? Or money? Using twice as much as you need of
 anything is bad IMO.

Apparently you don't realize that GHC normally uses twice as much heap
as is needed, due to the decision to use a two-space copying collector
by default for the oldest generation. :)

Stefan


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


[Haskell-cafe] bimap 0.2

2008-02-04 Thread Stuart Cook
I've updated the bimap package to version 0.2.

  http://hackage.haskell.org/cgi-bin/hackage-scripts/package/bimap-0.2

The main difference is a pretty comprehensive interface shakeup: the
Either variants have been dropped, all L variants have had the L
removed from their name, and a few functions have been curried. The
end result is an interface much closer to that of Data.Map. (This also
means that 0.2 isn't backwards-compatible.)

In addition, the package now supports GHC 6.8, and has a few more
tests in the test suite.


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


Re: [Haskell-cafe] Adding gcc type options with cabal (e.g. -mno-cygwin)

2008-02-04 Thread Berlin Brown
On Feb 4, 2008 5:55 PM, Duncan Coutts [EMAIL PROTECTED] wrote:

 On Mon, 2008-02-04 at 17:18 -0500, bbrown wrote:
  Is there a way to pass misc options to the cabal, ghc process.
 
  I tried the following:
 
  extra-libraries: sqlite3
  extra-lib-dirs:  C:\cygwin\lib
  include-dirs:C:\cygwin\usr\include
  ghc-options: -mno-cygwin
 
  runhaskell Setup.lhs build --ghc-options=-mno-cygwin -v
 
  No dice, doesn't show up.

 Really? That's odd, works for me:

 $ runhaskell Setup.lhs build --ghc-options=-mno-cygwin -v
 ...
 [snip]
 ...
 ghc-6.8.2: unrecognised flags: -mno-cygwin
 Usage: For basic information, try the `--help' option.

 Also works with runhaskell Setup.lhs configure --ghc-options=-mno-cygwin

 Works in the sense that it passes the flag through to ghc. Of course I'm
 on unix and ghc does not recognise that flag.

 What version of Cabal are you using?

 Duncan


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


It looked like it passed the option, but didn't resolve the issue.
Anyone seen that before?  See error in previous post.

-- 
Berlin Brown
http://botspiritcompany.com/botlist/spring/help/about.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe