[Haskell-cafe] Takusen and strictness, and perils of getContents

2007-03-02 Thread oleg
Takusen permits on-demand processing on three different levels. It is specifically designed for database processing in bounded memory with predictable resource utilization and no resource leaks. But first, about getContents. It has been mentioned a while ago that getContents should be renamed to

Re: [Haskell-cafe] Very Basic IO question

2007-03-02 Thread Bryan O'Sullivan
Joe Olivas wrote: However, changing 'putStrLn' to 'putStr' does not do what I would expect. The prompt doesn't get displayed until after there is input: This isn't a Haskell issue per se. The runtime is putting stdout into line-buffered mode, so you need to import System.IO and use hFlush

Re: [Haskell-cafe] Very Basic IO question

2007-03-02 Thread Donald Bruce Stewart
olivasj: > I am VERY new to Haskell, and just getting my feet wet with functional > programming in general. I've been going over a few examples online, but I > can't figure out the behavior I'm seeing on a very basic example: > > --- > module Main where > > import System.IO > > main :: IO (

[Haskell-cafe] Very Basic IO question

2007-03-02 Thread Joe Olivas
I am VERY new to Haskell, and just getting my feet wet with functional programming in general. I've been going over a few examples online, but I can't figure out the behavior I'm seeing on a very basic example: --- module Main where import System.IO main :: IO () main = do putStrLn

Re: [Haskell-cafe] Hi I need help for very simple question!

2007-03-02 Thread Bryan Donlan
Taillefer, Troy (EXP) wrote: Hi there 1. First of all never forget your base case for exiting your recursion 2. you need to break up the problem like so import Char -- get the first word word :: String -> String word [] = [] word ( x : x1 : xs ) | isSpace x = [] | isSpace x1 =

Re: [Haskell-cafe] Proposal: simple interface to libraries Haddock

2007-03-02 Thread Claus Reinke
http://docs.haskell.org/Data.Map.funcname this reminded me that haddock has long generated files with paths and relative urls that allow you to do that kind of thing, if slightly cryptically, and that i have long wanted to access the local haddocs from vim. since i'm a bit slow learning about

Re: [Haskell-cafe] numeric minimization in Haskell

2007-03-02 Thread Dan Weston
> Did I just read an admission that Sony Imageworks use Haskell for > movie post-production? Nice try, but I do not speak for Sony Pictures Imageworks. Whatever things they do or do not do in post-production would no doubt fall under some kind of trade secret thing and I would not mention them

Re: [Haskell-cafe] Implementation of "Dynamic" datatype

2007-03-02 Thread Stefan O'Rear
On Fri, Mar 02, 2007 at 07:10:32PM -0500, Isaac Dupree wrote: > Stefan O'Rear wrote: > > the current type: > > > > data Dynamic = Dynamic TypeRep Obj > > > > the new type, if lucky: > > Meaning the one with "Typeable a =>" instead of TypeRep? Yes > > data Dynamic = Dynamic !(a -> TypeRep) a >

Re: [Haskell-cafe] Implementation of "Dynamic" datatype

2007-03-02 Thread Isaac Dupree
-BEGIN PGP SIGNED MESSAGE- Hash: SHA1 Stefan O'Rear wrote: > the current type: > > data Dynamic = Dynamic TypeRep Obj > > the new type, if lucky: Meaning the one with "Typeable a =>" instead of TypeRep? > > data Dynamic = Dynamic !(a -> TypeRep) a > > if unlucky: > > data TypeableD

Re: [Haskell-cafe] Implementation of "Dynamic" datatype

2007-03-02 Thread Stefan O'Rear
the current type: data Dynamic = Dynamic TypeRep Obj the new type, if lucky: data Dynamic = Dynamic !(a -> TypeRep) a if unlucky: data TypeableD a = TypeableD (a -> TypeRep) data Dynamic = Dynamic (TypeableD a) a either way, the typeclass approach gives a lot more boxing.

[Haskell-cafe] Implementation of "Dynamic" datatype

2007-03-02 Thread Isaac Dupree
-BEGIN PGP SIGNED MESSAGE- Hash: SHA1 Currently we have data Dynamic = Dynamic TypeRep Obj where Obj is {-in GHC up to 6.6-} type Obj = forall a . a {-in GHC 6.7.something-} type Obj = Any -- Use GHC's primitive 'Any' type to hold the dynamically typed value. {-in some other compilers (li

Re: [Haskell-cafe] Proposal: simple interface to libraries Haddock

2007-03-02 Thread Neil Mitchell
Hi And when will Hoogle 4 be more than vapourwear? :) I guess the answer is 'whenever people stop asking me and start contributing patches' ;) Patches are not what I need, since all the ideas/designs are in my head. I'll try and get somewhere on it soon, but my time is pretty well booked for t

Re: [Haskell-cafe] Proposal: simple interface to libraries Haddock

2007-03-02 Thread David House
On 02/03/07, Neil Mitchell <[EMAIL PROTECTED]> wrote: If this is what you want, this is what Hoogle 4 shall have! It is purely a question of a very very light interface around Hoogle - absolutely all the code is already there. And when will Hoogle 4 be more than vapourwear? :) I guess the answe

Re: [Haskell-cafe] Proposal: simple interface to libraries Haddock

2007-03-02 Thread Neil Mitchell
Hi David, I realise it's similar. I don't they fulfill quite the same aim though. Hoogle might give me two dozen results when I roughly know the name of a function, but this isn't what I want. hoodoc doesn't, it gives you the exact result. The main reason this is hard at the moment, incident

[Haskell-cafe] haskell zlib on win32

2007-03-02 Thread Tim Newsham
Building haskell's zlib library for win32 is not trivial since it relies on an external C library. Most of the required tools are shipped with the ghc binary distribution though. I finally bit the bullet and jumped through the build hoops to install it. My notes are attached below. The build c

Re: [Haskell-cafe] Proposal: simple interface to libraries Haddock

2007-03-02 Thread Dan Piponi
dmhouse said: Hoogle might give me two dozen results when I roughly know the name of a function, but this isn't what I want. Agreed. I would *love* to have the interface you propose and I think it would make a significant difference to the ease of writing Haskell code. -- Dan _

Re[2]: [Haskell-cafe] Takusen and strictness

2007-03-02 Thread Bulat Ziganshin
Hello Alistair, Friday, March 2, 2007, 5:48:17 PM, you wrote: > sure if it would be possible. I don't really understand how getContents > works; is there any advice or guidelines as to how to use (or abuse) > unsafeInterleaveIO? Some googling has found: i think i can explain this dark side of IO

Re: [Haskell-cafe] Proposal: simple interface to libraries Haddock

2007-03-02 Thread David House
On 02/03/07, Bryan O'Sullivan <[EMAIL PROTECTED]> wrote: Like this? http://haskell.org/hoogle/?q=map I realise it's similar. I don't they fulfill quite the same aim though. Hoogle might give me two dozen results when I roughly know the name of a function, but this isn't what I want. I know the

Re: [Haskell-cafe] Proposal: simple interface to libraries Haddock

2007-03-02 Thread Neil Mitchell
Hi David, I'm proposing something simple that should make it easier for both Haskell programmers and Haskell tool writers to find the documentation for a function. We need a simple URL for the Haddock docs of any function. PHP has this already: just hit php.net/funcname for the documentation for

Re: [Haskell-cafe] Proposal: simple interface to libraries Haddock

2007-03-02 Thread Bryan O'Sullivan
David House wrote: I'm proposing something simple that should make it easier for both Haskell programmers and Haskell tool writers to find the documentation for a function. Like this? http://haskell.org/hoogle/?q=map http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Proposal: simple interface to libraries Haddock

2007-03-02 Thread David House
Hey all, I'm proposing something simple that should make it easier for both Haskell programmers and Haskell tool writers to find the documentation for a function. We need a simple URL for the Haddock docs of any function. PHP has this already: just hit php.net/funcname for the documentation for f

Re: [Haskell-cafe] wanted: haskell one-liners (in the perl sense of one-liners)

2007-03-02 Thread David Roundy
On Fri, Mar 02, 2007 at 08:12:19PM +0100, Thomas Hartman wrote: > Great tip! One question though. > > What condition is > > if which ghc >/dev/null > > checking? > > What bad thing will happen if you don't do this check? > > Sorry this is more a bash question than a haskell question. It just

Re: [Haskell-cafe] wanted: haskell one-liners (in the perl sense of one-liners)

2007-03-02 Thread Thomas Hartman
Great tip! One question though. What condition is if which ghc >/dev/null checking? What bad thing will happen if you don't do this check? Sorry this is more a bash question than a haskell question. 2007/3/2, Bas van Dijk <[EMAIL PROTECTED]>: On Friday 02 March 2007 14:48, Thomas Hartman wr

Re: [Haskell-cafe] Takusen and strictness

2007-03-02 Thread Bryan O'Sullivan
Paul Moore wrote: ... ie, there's deep dark magic involved in the seemingly simple getContents, which isn't easily available to mere mortals (or even semi-immortal library designers). That's really not true. getContents looks simple from the outside, and it *can* be simple underneath, too.

Re: [Haskell-cafe] wanted: haskell one-liners (in the perl sense of one-liners)

2007-03-02 Thread Joachim Breitner
Hi, Am Freitag, den 02.03.2007, 09:25 -0800 schrieb David Roundy: > echo hello world | hmap toUpper $ echo hello world | hmap 'map Char.toUpper' HELLO WORLD (Whereas hmap is as defined in the original blog entry) Greetings, Joachim -- Joachim Breitner e-Mail: [EMAIL PROTECTED] Homepage: ht

Re: [Haskell-cafe] Hi I need help for very simple question!

2007-03-02 Thread ivan gomez
Well, your function only remove space chars at string beginning. You may use Prelude.words :: String -> [String] or some as: intoWords s = aux s [] 2007/3/2, iliali16 <[EMAIL PROTECTED]>: Hi Haskell People, I hav

Re: [Haskell-cafe] Hi I need help for very simple question!

2007-03-02 Thread Marc Weber
On Fri, Mar 02, 2007 at 08:22:46AM -0800, iliali16 wrote: > suggestions. Also I don't know how to produce a base case for my recursion. > > import Char > > intoWords ::String -> [String] > > intoWords (x:xs) > |isSpace x = intoWords xs > |otherwise = xs He. You got the type signat

RE: [Haskell-cafe] Hi I need help for very simple question!

2007-03-02 Thread Taillefer, Troy (EXP)
Hi there 1. First of all never forget your base case for exiting your recursion 2. you need to break up the problem like so import Char -- get the first word word :: String -> String word [] = [] word ( x : x1 : xs ) | isSpace x = [] | isSpace x1 = x : [] | otherwise = x

Re: [Haskell-cafe] wanted: haskell one-liners (in the perl sense of one-liners)

2007-03-02 Thread David Roundy
On Fri, Mar 02, 2007 at 03:17:10PM +0100, Bas van Dijk wrote: > On Friday 02 March 2007 14:48, Thomas Hartman wrote: > > ... > > But I couldn't figure out how to use them directly from the shell, and > > of course that's what most readers will probably wnat. > > ... > > From Dons wiki article http

Re: [Haskell-cafe] Takusen and strictness

2007-03-02 Thread Chris Kuklewicz
> > There's a big difference between getContents and Takusen: getContents > has a non-trivial implementation (using unsafeInterleaveIO) that allows > it to return data lazily. Takusen has no such implementation. I'm not > sure if it would be possible. I don't really understand how getContents > w

[Haskell-cafe] Hi I need help for very simple question!

2007-03-02 Thread iliali16
Hi Haskell People, I have problem implementing one function. I think my idea is write but I have minor mistakes which I cannot get right since I progrem Haskell from very recently. No the function is called intoWords and has to take a string of any size and kind of characters.No I have to produce

Re: [Haskell-cafe] Takusen and strictness

2007-03-02 Thread Stefan O'Rear
On Fri, Mar 02, 2007 at 02:58:21PM +, Paul Moore wrote: > On 02/03/07, Bayley, Alistair <[EMAIL PROTECTED]> > wrote: > >There's a big difference between getContents and Takusen: getContents > >has a non-trivial implementation (using unsafeInterleaveIO) that allows > >it to return data lazily.

Re: [Haskell-cafe] Takusen and strictness

2007-03-02 Thread Nicolas Frisby
The "deep, dark, Aslan magic" of getContents is usually safe to use because it's a read-only operation. Some of the dangerous corners of getContents are: what happens if the file is altered while we read it lazily? This is the sort of question that the sequencing notion of the IO monad is supposed

Re: [Haskell-cafe] Takusen and strictness

2007-03-02 Thread Paul Moore
On 02/03/07, Bayley, Alistair <[EMAIL PROTECTED]> wrote: There's a big difference between getContents and Takusen: getContents has a non-trivial implementation (using unsafeInterleaveIO) that allows it to return data lazily. Takusen has no such implementation. ... ie, there's deep dark magic in

RE: [Haskell-cafe] Takusen and strictness

2007-03-02 Thread Bayley, Alistair
> From: Paul Moore [mailto:[EMAIL PROTECTED] > > > If you don't need the entire list at once, then push your processing > > into the iteratee. > > Hmm, that's what I was trying to avoid. The article I mentioned made a > strong point that laziness allows you to factor out processing from IO > - s

Re: [Haskell-cafe] wanted: haskell one-liners (in the perl sense of one-liners)

2007-03-02 Thread Bas van Dijk
On Friday 02 March 2007 14:48, Thomas Hartman wrote: > ... > But I couldn't figure out how to use them directly from the shell, and > of course that's what most readers will probably wnat. > ... From Dons wiki article http://haskell.org/haskellwiki/Blog_articles I noticed this blog with a nice ti

Re: [Haskell-cafe] Takusen and strictness

2007-03-02 Thread Paul Moore
On 02/03/07, Bayley, Alistair <[EMAIL PROTECTED]> wrote: [...] What you're interested in, I think, is what the iteratee does with the data. That's correct. In your case, it conses each username onto the front of a list, which is initially empty. Because you're using result (not result') this

RE: [Haskell-cafe] Takusen and strictness

2007-03-02 Thread Bayley, Alistair
> From: [EMAIL PROTECTED] > [mailto:[EMAIL PROTECTED] On Behalf Of Paul Moore > > But, will this read the database lazily, or will it get all the rows > into memory at once? How will using result' instead of result (in > runSql) affect this? And as I said above, how can I learn to work this > out

[Haskell-cafe] wanted: haskell one-liners (in the perl sense of one-liners)

2007-03-02 Thread Thomas Hartman
Okay, I am aware of http://haskell.org/haskellwiki/Simple_unix_tools which gives some implementation of simple unix utilities in haskell. But I couldn't figure out how to use them directly from the shell, and of course that's what most readers will probably wnat. Or let me put it another way.

Re: [Haskell-cafe] Re: [Haskell] Laziness and the IO Monad (randomness)

2007-03-02 Thread Matthew Brecknell
Dave Tapley wrote: > However this latter case gets stuck in an infinite loop, terminating on a > stack overflow. Kirsten Chevalier said: > You didn't say which function you had narrowed down the stack overflow > to, but I suspect it's here: > > > firstTen :: IO [Int] > > firstTen = do > > in

[Haskell-cafe] Takusen and strictness

2007-03-02 Thread Paul Moore
I'm still fiddling with simple database queries using Takusen. One question I have is regarding strictness. I've just been reading "Haskell IO for Imperative Programmers" and loved the idea that laziness (rather than monads) is what makes IO in Haskell so simple. What I'm not sure about, is whethe

[Haskell-cafe] Re: splitting strings

2007-03-02 Thread h .
Thanks a lot. I hope I can learn from your lines and ideas used here to improve future code in quality. -- Best regards h. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Literate haskell format unclear (implementation and specification inconsistencies)

2007-03-02 Thread Isaac Dupree
-BEGIN PGP SIGNED MESSAGE- Hash: SHA1 Nice, I pretty much agree with you on everything :) Ian Lynagh wrote: > On Wed, Feb 28, 2007 at 05:48:09PM -0500, Isaac Dupree wrote: >> Trying to implement literate haskell[*], I realized several >> ways in which the correct behavior for unliterating

Re: [Haskell-cafe] Re: bytestring vs polymorphic contiguous lists

2007-03-02 Thread Bulat Ziganshin
Hello Duncan, Thursday, March 1, 2007, 1:21:49 PM, you wrote: > We're now looking at stream fusion for lists in general and as Don says, > there's also the NDP work which is looking at arrays of arbitrary > element type and with complex structure. shortly speaking, this may become the most impor