joelr1:
> Would someone kindly explain why we need co-arbitrary in QuickCheck
> and how to define it?
Generating random function generators.
A nice explanation was given recently on the programming subreddit:
"The CoArbitrary class continues to confuse me"
http://programming.reddit.com
cyril.schmidt:
> I noticed recently that the website of CUFP conference (Commercial Uses of
> Function Programming), which used to be at http://www.galois.com/cufp,
> is not accessible anymore.
>
> Does anybody know where it moved?
Try http://cufp.galois.com/
-- Don
_
eeoam:
> H|i,
>
> Does anyone know of a simple and straightforward way to use global
> variables in Haskell?
>
> E.
The usual way is to run the code that needs a global variable in a State monad.
The next answer is: you don't really need global variables, since you
don't have mutable variables
eeoam:
> H|i,
>
> Does anyone know of a simple and straightforward way to use global
> variables in Haskell?
>
> E.
As other posters have said, you'll need to state what you're trying to
do. For one particular case, that of a program that needs access to
state over its lifetime, State monads ar
andrewcoppin:
> Hi everybody.
>
> Is there any circumstances under which an expression like map (2*) would
> perform an in-place update rather than generating a new list? (Obviously
Yes, should be fine, if the result is consumed. We have fusion
frameworks that do this.
> this depends on which
matt:
> It occurred to me that the predicate will generally be a monadic function
> itself, so here's a
> refined version:
>
> :: Monad m => (a -> m Bool) -> (a -> m a) -> a -> m a
> untilM pred f x = do c <- pred x
> if c then return x
> else f x >
lpenz:
>
> Hi
>
> I made a program that detects user presence in a linux box by checking
> for keyboard interruptions in /proc/interrupts.
>
> Problem is, it is supposed to run for a long time, and it keeps about
> 40MB for itself.
>
> Yeah, this is one more "help me with this memory problem"
andrewcoppin:
> Greetings.
>
> I was thinking... we already have Lambdabot sitting in an IRC channel.
> How hard would it be to mangle Lambdabot to the point where it works
> over HTTP? You know - so you could type some Haskell into a form on a
Lambdabot web server is here:
http://lambdab
When working on xmonad, we're trying to produce very clean, correct
code -- a window manager that just works. To do this, we're looking to
employ more static checking tools to the code base. Currently we use:
* QuickCheck (checks high level window manager behaviour)
* Catch (Neil's patter
Alistair_Bayley:
> > > I'm sure that I can quite reliably hit the command editor
> > keybindings I
> > > use many, many times faster than if I had to select them
> > from a menu.
> >
> > Note that the claimed time-consuming part is not to actually press the
> > keybinding, but to chose and remem
prstanley:
>
> >> Hi
> >> What is the rationale behind currying? is it for breaking subroutines
> >into
> >> pure one-to-one mappings?
> >
> >We don't have 'subroutines' as such, but otherwise yes. Also, it gives us
> >partial application - we don't have to apply all the parameters at once,
> >an
Bryan O'Sullivan, Don Stewart and John Goerzen are pleased, and frankly,
very excited to announce that were developing a new book for O'Reilly, on
practical Haskell programming. The working title is Real-World Haskell.
The plan is to cover the major techniques used to write serious,
real-world Ha
leaveye.guo:
> Hi MailList Haskell-Cafe:
>
> Till now, which module / package / lib can i use to access binary
> file ? And is this easy to use in GHC ?
Data.Binary? Or perhaps just Data.ByteString, available on hackage,
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/bina
leaveye.guo:
> Thanks for your suggestion, and sorry for the subject.
>
> I have read the introduction of Data.ByteString, it is helpful.
>
> And also, there is one problem left. When i read a binary file, data
> is truncated at the charactor EOF.
>
> Which function could do this work correctly
marco-oweber:
> On Thu, May 24, 2007 at 02:38:05PM +0800, L.Guo wrote:
> > Thanks for your suggestion, and sorry for the subject.
> >
> > I have read the introduction of Data.ByteString, it is helpful.
> >
> > And also, there is one problem left. When i read a binary file, data is
> > truncated
leaveye.guo:
> to Ketil :
>
> Tring openBinaryFile, I notice that I cannot make one usable buffer,
> just because I can not find one function to "malloc" a memory or just
> get one "change-able" buffer.
>
> :-$
No 'malloc' here in Haskell land: that's done automatically. Recall
that 'getContent
leaveye.guo:
> To read the handle openBinaryFile returns, both the hGetBuf and
> hGetBufNonBlocking needs one parameter _buf_ of type Ptr a.
> I can not get one data of that type.
>
> In the doc, there is only nullPtr, and also some type cast functions.
> I failed to find some other buffer-maker f
bos:
> I'll condense my remaining replies to this thread into a single message,
> to save people a little noise.
I'd just add that the response is literally overwhelming! Some 100-odd
volunteers to review, and a lot of mail besides.
Please bear with us as we try to surface under this mountain of
leaveye.guo:
> Hi.
>
> In GHCi ver 6.6, why this happens ?
>
> Prelude Data.ByteString> Data.ByteString.pack $! Prelude.map (`rem` 256) $
> [0..511]
> "*** Exception: divide by zero
Interesting...
Is that just,
Data.ByteString.pack $ [0..255] ++ [0..255]
?
-- Don
_
leaveye.guo:
> Hi.
>
> In GHCi ver 6.6, why this happens ?
>
> Prelude Data.ByteString> Data.ByteString.pack $! Prelude.map (`rem` 256) $
> [0..511]
> "*** Exception: divide by zero
It's the use of `rem` on Word8, by the way:
Prelude> (0 `rem` 256) :: Data.Word.Word8
*** Exception: di
dons:
> leaveye.guo:
> > Hi.
> >
> > In GHCi ver 6.6, why this happens ?
> >
> > Prelude Data.ByteString> Data.ByteString.pack $! Prelude.map (`rem` 256) $
> > [0..511]
> > "*** Exception: divide by zero
>
> It's the use of `rem` on Word8, by the way:
>
> Prelude> (0 `rem` 256) :: Data.Wor
ketil:
> On Fri, 2007-05-25 at 17:33 +1000, Donald Bruce Stewart wrote:
>
> > Sorry, I should clarify, think about how to represent:
> >
> > 256 :: Word8
>
> So the error isn't really divide by zero, but overflow. I've been
> bitten by this, too,
greenrd:
> The following Haskell 98 module implements a generalisation of
> Prelude.ShowS for any type. Should be pretty easy to incorporate this
> into code which currently uses the list monad non-trivially, and get
> better performance - but can this be right? Surely someone would have
> publishe
aneumann:
> -BEGIN PGP SIGNED MESSAGE-
> Hash: RIPEMD160
>
> Hi,
>
> I installed the Network.CGI package and tried to compile the Hello World
> example on my Ubuntu machine.
>
> >ghc cgi.hs -o cgi
Missing --make to link against the cgi and network and mtl packages.
Also, -O or -O2, you
andrewcoppin:
> Since the online lambdabot still doesn't seem to want to talk to me,
> I've been thinking about how I might rectify the situation...
>
> Apparently GHC has a flag that makes it execute a Haskell expression
> directly. For example,
>
> C:\> ghc -e "map (2*) [1,2,3]"
> [2,4,6]
>
On 26/05/07, Matthew Sackman <[EMAIL PROTECTED]> wrote:
>(On the other hand, I don't know of anyone outside immediate
>"haskellers" using Darcs.)
Good idea to get some data on this, instead of speculating. Let's do that.
A quick google reveals the Haskell crew is far from alone as users.
h
claus.reinke:
> >>Oh, but there is the *minor* detail that I am literally allowing
> >>unauthenticated users to perform arbitrary code execution. For example,
> ..
> >>AFAIK, Lambdabot dissalows any expression that performs IO. In Haskell,
> >>this is beautifully easy: reject any expression having
> it would really be nice if someone would sit down and sort this all out
> in detail. there'd still be no guarantee that such a Haskell sandbox was
> totally safe, but at least all issues and solutions could be shared, making
> it as safe as the community knows how.
The #haskell people have been
isaacdupree:
> -BEGIN PGP SIGNED MESSAGE-
> Hash: SHA1
>
> Donald Bruce Stewart wrote:
> > Lambdabot uses 1) type guarantee of no-IO at the top level, along with
> > 2) a trusted module base (pure module only, that are trusted to not
> > export evil things),
overdrigzed:
>
> As far as I know, hs-plugins works by taking an
> expression, writing it
> to a file, calling GHC to parse it, transform it to Core,
> optimise it,
> transform it to STG, optimise it, transform it to C--,
> optimise it,
> transform it to ANSI C,
claus.reinke:
> >The #haskell people have been working on this for about 3 years now.
> >The result is the 'runplugs' program, which I've talked about in
> >previous mails.
> >
> > http://www.cse.unsw.edu.au/~dons/code/lambdabot/scripts/RunPlugs.hs
> >
> >It uses hs-plugins for the evaluation, al
claus.reinke:
> >The #haskell people have been working on this for about 3 years now.
> >The result is the 'runplugs' program, which I've talked about in
> >previous mails.
> >
> > http://www.cse.unsw.edu.au/~dons/code/lambdabot/scripts/RunPlugs.hs
> >
> >It uses hs-plugins for the evaluation, al
bos:
> Jason Dagit wrote:
>
> >I think, given my simple algorithm that means that (==) for
> >ByteStrings is slower than (==) for String. Is this possible?
>
> Yes indeed. Over ByteStrings, (==) is implemented as a call to memcmp.
> For small strings, this loses by a large margin because it h
junkywunky:
>
> type Person = (NI, Age, Balance)
> type Bank = [Person]
>
> credit :: Bank -> [Person]
> credit [(a,b,c)] = [(a,b,c)]
>
> This code works when I type in:
>
> credit [(1,2,3)]
>
> but doesn't work when I type in:
>
> credit [(1,2,3),(4,5,6)]
You're pattern matching in 'credit'
junkywunky:
>
> That's the thing. I want to return a list of people who are not overdrawn.
> Something like:
>
> type NI = Int
> type Age = Int
> type Balance = Int
> type Person = (NI, Age, Balance)
> type Bank = [Person]
>
> credit :: Bank -> [Person]
> credit [(a,b,c)] = [(a,b,c)] if c >= 0
isaacdupree:
> -BEGIN PGP SIGNED MESSAGE-
> Hash: SHA1
>
> Isaac Dupree wrote:
> > "The expression is bound to a random top level identifier (harmless to
> > guess)"
> >
> > What about the non-recursive
> >
> > case ...expr... of x -> take 2048 (show x)
> >
> > this way expr can't refer
pvolgger:
> I wonder if there are any Coding Standards or Coding Conventions for
> Haskell. Does anybody know something about it?
We've collected some style guides on the wiki. You could also look at
projects whose code you think is in good style.
http://haskell.org/haskellwiki/Category:Styl
conrad:
> On 28/05/07, Donald Bruce Stewart <[EMAIL PROTECTED]> wrote:
> >Our small little window manager, xmonad, also has a pretty strict style
> >guide.
>
> where? Perhaps I need coffee, but I couldn't find this in the source
> (xmonad, x11-extras, XMonadC
bulat.ziganshin:
> Hello Bryan,
>
> Sunday, May 27, 2007, 3:30:50 AM, you wrote:
> >> I think, given my simple algorithm that means that (==) for
> >> ByteStrings is slower than (==) for String. Is this possible?
>
> > Yes indeed. Over ByteStrings, (==) is implemented as a call to memcmp.
> >
This thread should end, guys. It is inappropriate for the Haskell lists,
and appears to have been a simple misunderstanding anyway.
Thanks everyone. Please stay friendly!
-- Don
P.S. Have some cute code:
Control.Monad.Fix.fix ((1:) . scanl (+) 1)
___
kahl:
> >
> > P.S. Have some cute code:
> >
> > Control.Monad.Fix.fix ((1:) . scanl (+) 1)
>
>
> Cute!
>
> But what an un-cute qualified name:
>
> :t Control.Monad.Fix.fix
> Control.Monad.Fix.fix :: (a -> a) -> a
>
>
> Has nothing to do with monads,
> and would perhaps be considered
We got the names wrong!
data PLZ a = AWSUM_THX a | O_NOES String
instance Monad PLZ where
return= AWSUM_THX
fail = O_NOES
O_NOES s>>= _ = O_NOES s
AWSUM_THX x >>= f = f x
Thanks to mauke on #haskell.
-- Don
___
d.w.mead:
>
>is that your implementation of LOLCODE?
>:P
>
> On 5/29/07, Donald Bruce Stewart <[EMAIL PROTECTED]>
>wrote:
>
> We got the names wrong!
>
> data PLZ a = AWSUM_THX a | O_NOES String
>
> inst
vincent:
> i see that the definition of fix (from Control.Monad.Fix) could not be
> any simpler:
>
> > fix f = let x = f x in x
>
> same goes for the type:
>
> Prelude> :t Control.Monad.Fix.fix
> Control.Monad.Fix.fix :: (a -> a) -> a
>
> it's just that i find it difficult to get concrete intel
rwiggerink:
>
> I'm pretty new to Haskell, so forgive me if my question is due to my
> non-functional way of thinking...
>
> I have the following code:
>
> module Main where
>
> main = print solution
>
> solution = solve 100
>
> solve d = countUniqueFractions d 2 1 0
>
> canBeSimplified
jon:
> On Wednesday 30 May 2007 06:58:36 Ketil Malde wrote:
> > On Tue, 2007-05-29 at 14:05 -0500, Doug Kirk wrote:
> > > I *want* people (and companies) to move to Haskell
>
> As a complete noob considering making a commercial venture into Haskell, may
> I
> ask what people's opinions are on th
pupeno:
> It seems I have found a hole in Haskell... :(
> Before I start to develop a library with functions such us those on
> http://haskell.org/hawiki/BinaryIo (hGetWord8, hGetWord16le, hGetWord16be,
> etc), is there some reliable library that can help me ?
> I basically need a set of function
mcqueenorama:
> How is this different from the (un)pickle process that has been
> discussed here recently? Recently I've seen the Binary discussions,
> and the pickeling discussions, and I noticed they seemed to be talking
> about the same process.
Yep, same thing.
-- Don
__
I've added an entry on the hawiki[1] for the regex-dna benchmark, and
posted a smaller (down to 15 lines), faster entry for
[2]reverse-complement, using string indexing from Alex.
Cheers,
Don
[1] http://haskell.org/hawiki/ShootoutEntry
[2] http://haskell.org/hawiki/ReverseComplementEntry
haskell:
> Simon Marlow wrote:
> > Hi Chris,
> >
> > Rather than try to explain what I'm going on about, I decided to tweak
> > the code a bit myself. My version is about 10% faster than yours, and
> > doesn't use any explicit unboxery. I've put it in the wiki after your
> > version.
> >
> > ht
haskell:
> Summary of things entered and of things being worked on.
>
> Things that are on the wiki at http://haskell.org/hawiki/ShootoutEntry
> but that have not been submitted:
>
> Fannkuch entry by Bertram Felgenhauer
> Mandelbrot entry
I've done some benchmarking of the current entries for f
dons:
> haskell:
> > Summary of things entered and of things being worked on.
> >
> > Things that are on the wiki at http://haskell.org/hawiki/ShootoutEntry
> > but that have not been submitted:
> >
> > Fannkuch entry by Bertram Felgenhauer
> > Mandelbrot entry
>
> I've done some benchmarking of
haskell:
> Summary of things entered and of things being worked on.
>
> Donald Bruce Stewart wrote:
> > haskell:
> >
> >>Simon Marlow wrote:
> >>
> >>>Hi Chris,
> >>>
> >>>Rather than try to explain what I'm going
dons:
> haskell:
> > Summary of things entered and of things being worked on.
> >
> > Donald Bruce Stewart wrote:
> > > haskell:
> > >
> > >>Simon Marlow wrote:
> > >>
> > >>>Hi Chris,
> > >>>
> &
bmaxa:
>
> This pidigit program is not mine, but original authors of algorithm.
> I've just added print function. It is idiomatic Haskell, pi is pure function
> that generates inifinite list of digits, and on two machinas I've
> tested p4 2.4 ghz and amd athlon 64 3000 it's about some
> small perc
neubauer:
> [EMAIL PROTECTED] (Donald Bruce Stewart) writes:
>
> >> > Fannkuch entry by Bertram Felgenhauer
> >> > Mandelbrot entry
> >>
> >> I've done some benchmarking of the current entries for fannkuch and
> >> mandelbrot, a
bulatz:
> Hello
>
> yes, i did it! today i spend time to optimize my own Binary library
> and got the (de)serialization speed about 50 mb/s with my 1 ghz cpu.
> it is a peek speed for unboxed arrays, in real life GC times and other
> overhead expenses will need much more time than (de)serializatio
bmaxa:
>
>
>
> >From: Chris Kuklewicz <[EMAIL PROTECTED]>
> >To: [EMAIL PROTECTED], Haskell Cafe
> >Subject: Re: [Haskell-cafe] x86 code generation going wrong?
> >Date: Sun, 08 Jan 2006 20:33:57 +
> >
> >Brian Sniffen wrote:
> >> The first couldn't even complete on my 2.26 GHz Celeron! It'
d:
> Regarding the Fannkuch Shootout Entry:
>
> If we are willing to specialize flop in the way shown on the wiki,
> another 8% can be gained by similarly specializing rotate:
>
> rotate 2 (x1:x2:xs) = x2:x1:xs
> rotate 3 (x1:x2:x3:xs) = x2:x3:x1:xs
...
Cheers, I've updated the proposed entry
ekarttun:
> On 09.01 12:56, Donald Bruce Stewart wrote:
> > Entries that may currently be worth submitting:
> >takfp - http://www.haskell.org/hawiki/TakfpEntry
>
> Committed.
>
> >pidigits (currently 2nd!) - http://www.haskell.org/hawiki
bertram.felgenhauer:
> The flop machinery can still be made faster, stealing an idea from the
> icc entry (namely, treating the first entry separately):
Great. This pushes the pure version up a notch.
I've updated the wiki, showing how the code has progressed:
Author Time in
daniel.is.fischer:
> Am Dienstag, 10. Januar 2006 19:11 schrieben Sie:
> > Hello Daniel,
> >
> > Tuesday, January 10, 2006, 7:40:24 PM, you wrote:
> >
> > DF> These are user/MUT times, at the moment, my machine is busy, so that
> > elapsed DF> time is about double that, otherwise these times are ra
Oh, like this (by Stefan Wehr):
http://www.cse.unsw.edu.au/~dons/code/icfp05/tests/unit-tests/VariableExpansion.hs
$ ghci -fth VariableExpansion.hs
*VariableExpansion> let x = 7 in $( expand "${x}" )
"7"
*VariableExpansion> let url = "http://www.google.com";
*VariableExpansion> $( expand
:D
Haskell now ranked 2nd overall, only a point or so behind C:
http://shootout.alioth.debian.org/gp4/benchmark.php?test=all&lang=all
And still a bit more we can squeeze out...
-- Don
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://w
sebastian.sylvan:
> On 1/15/06, Isaac Gouy <[EMAIL PROTECTED]> wrote:
> > > Haskell now ranked 2nd overall, only a point or so
> > > behind C:
> >
> > It was always obvious that the "Write the program
> > as-if lines of code were not being measured" clause
> > relied too heavily on contributors wil
sebastian.sylvan:
> On 1/15/06, Donald Bruce Stewart <[EMAIL PROTECTED]> wrote:
> > sebastian.sylvan:
> > > On 1/15/06, Isaac Gouy <[EMAIL PROTECTED]> wrote:
> > > > > Haskell now ranked 2nd overall, only a point or so
> > > > > behind
jupdike:
> > > Maybe we finally have enough motivation to move to
> > > some other measurement of program volume :-)
>
> > I'm not sure how you could do this better, though... Maybe counting
> > the number of "tokens" (not sure how you'd define that though)
>
> I was thinking the same thing for t
haskell:
> There is a new combined benchmark, "partial sums" that subsumes several
> earlier
> benchmarks and runs 9 different numerical calculations:
>
> http://haskell.org/hawiki/PartialSumsEntry
Ah! I had an entry too. I've posted it on the wiki. I was careful to
watch that all loops are com
haskell:
> Donald Bruce Stewart wrote:
> > haskell:
> >> There is a new combined benchmark, "partial sums" that subsumes several
> >> earlier
> >> benchmarks and runs 9 different numerical calculations:
> >>
> >> http://haskell.o
john:
> I have often wanted a shorthand syntax for testing if a value matches a
> given pattern. I want to implement such an extension for jhc but can't
> decide an appropriate syntax so I thought I'd ask the group. basically I
> want something like
>
> /Left (Just _)/ expands to
>
> \x -> cas
joelkoerwer:
>
>Thanks Chris. I was actually asking about analyzing Core
>output in general. I'm well aware of the problems we're
>having with the nbody entry.
>I'm convinced my list based version can go faster than it is
>now. That's why I was asking if Don could put together
Haskell is now ranked number 1 on the Great Language Shootout!
http://shootout.alioth.debian.org/gp4/benchmark.php?test=all&lang=all
Hooray :)
-- Don
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo
briqueabraque:
> Hi,
>
> I would like to know what options I have in Haskell to do something
> similar to this C++ code:
>
> double a = 1000;
> while (a>1) a/=2;
>
> I'm able to do that with lists, but I would like to know how to do
> that with monads and variables with state.
You'll ge
Ben.Lippmeier:
> Sebastian Sylvan wrote:
> >>Haskell is now ranked number 1 on the Great Language Shootout!
> >>
> >That is neat. Mostly for dispelling the "pure lazy fp is inherently
> >slow" argument.
>
> Ha! I don't think "pure lazy fp" would be the phrase I would choose to
> describe this co
Ben.Lippmeier:
> Donald Bruce Stewart wrote:
>
> >>Ha! I don't think "pure lazy fp" would be the phrase I would choose to
> >>describe this code.
> >>
> >>An example (from fannkuch):
> >>
> >>t <- IO $ \s ->
>
haskell:
> Joel Koerwer wrote:
> > Don, that's a great little mini tutorial, exactly what I was hoping for.
> > I'm looking forward to learning more tricks.
> >
> > On an unrelated note, I have an STUArray nbody. I haven't really looked
> > closely at the chris+dons version, but I suspect they amo
Just so we can feel that we're doing the right things :)
On the great language shootout, as of last night, we're:
* Ranked overall number 1, by a good margin:
* Ranked number 1 on lines of code
* Ranked number 2 on speed.
http://shootout.alioth.debian.org/gp4/benchmark.php?test=all&lang=
hiperfume:
>
>Hello all,
>Now I am trying on a simple translator module. This module
>needs to translate an input string( this string represent a
>formula) as follows:
>(x^2 - 5x + 4=0) /\ (x^3 - 5>0) -> x>3
>And I want the output string represent a formula like:
>(x^2
jamie.edwards:
>
> I have 3 integers, a b c that I want to pass to a function, and I want the
> function to return the 3 integers sorted, from largest to smallest - any
> idea how to do this?
Prelude> let sort3 x y z = List.sort [x,y,z]
Prelude> sort3 8 2 0
[0,2,8]
Cheers,
Don
___
sebastian.sylvan:
> On 2/13/06, Sebastian Sylvan <[EMAIL PROTECTED]> wrote:
> > On 2/13/06, JimpsEd <[EMAIL PROTECTED]> wrote:
> > >
> > > I have 3 integers, a b c that I want to pass to a function, and I want the
> > > function to return the 3 integers sorted, from largest to smallest - any
> > >
jupdike:
> For scenario (a) you can use hs-plugins and ghc
> http://www.cse.unsw.edu.au/~dons/hs-plugins/
> With hs-plugins you can get an "eval" command, or you can dynamically
> load Haskell modules (from source or pre-compiled .o files).
>
> GHC (>= 6.5) has an API that you can access from Ha
maeder:
> Hi,
>
> haskell admits many programming styles and I find it important that
> several developers of a prject agree on a certain style to ease code review.
>
> I've set up guidelines (still as plain text) for our (hets) project in
Perhas you'd like to put up a Style page on thew new Ha
sean.seefried:
> >>
> >I still don't see clearly. So you've implemented the type inference
> >algorithm from Jones' paper, good. But is there any significance or
> >gain, apart from it being a nice and interesting exercise?
>
> No. Nor did I state that there was. There's a reason I posted this
Suggested by a question from sethk on #haskell irc channel.
Solves an FAQ where people have often resorted to cpp or m4:
a `trace' that prints line numbers.
> module Location (trace, assert) where
>
> import qualified Control.Exception as C (catch)
> import System.IO.Unsafe (unsafePerformIO
instinctive:
> I've been coming up to speed on afrp, and I see the code base is
> almost two years old. Is this the state of the art? Thanks.
Also, a practical application appeared this year with Frag -- Mun Hon
Cheong's implementation of a Quake-like game in Haske
shae:
> Nils Anders Danielsson <[EMAIL PROTECTED]> writes:
>
> > I had the same thought yesterday, after an Emacs-Lisp session in which
> > I was trying to get Gnus to do exactly what I wanted it to...
>
> Yeah, same here. I use Gnus and it's nice, but occasionally I want to erase it
> from the t
> 5) Ideally the scripting language would be Haskell..
> ... I can't find anything which would allow you
> to compile and load functions into a running program.
>From haskell.org:
"hs-plugins"
A library for compiling and loading plugins into a running Haskell
program.
Have a look at
1:
> I've got another n00b question, thanks for all the help you have been
> giving me!
>
> I want to read a text file. As an example, let's use
> /usr/share/dict/words and try to print out the last line of the file.
> First of all I came up with this program:
>
> import System.IO
> main = re
dons:
> 1:
> > I've got another n00b question, thanks for all the help you have been
> > giving me!
> >
> > I want to read a text file. As an example, let's use
> > /usr/share/dict/words and try to print out the last line of the file.
> > First of all I came up with this program:
> >
> > impo
> Donald Bruce Stewart wrote:
>
> >a) Compile your code with GHC instead of interpreting it. GHC is blazing
> >fast.
>
> That's one answer I suppose! I quite liked using Hugs for that
> particular program because it's a script that I didn't want to s
dominic.steinitz:
> Robert Dockins fastmail.fm> writes:
>
> > FYI, putStrLn will automatically insert a newline for you, and the
> > final 'return ()' is unnecessary. My favorite idiom for this kind of
> > thing is:
> >
> > mainMenu = putStr $ unlines
> >[ "line 1"
> >, "line 2"
> >
per.gustafsson:
>
> Haskell gurus,
>
> We have made a proposal to extend the Erlang `binary' data type from
> being a sequence of bytes (a byte stream) to being a sequence of bits (a
> bitstream) with the ability to do pattern matching at the bit level.
>
> Our experience in writing efficient (a
miketerrance:
> What is a good technique for breaking up long lines of code (for easier
> readability)?
>
> I have been inserting {- -} comments but there must be a better way.
> Something like \ in Python?
Can you give an example?
Usually breaking long lines is just a matter of cutting on wh
bulat.ziganshin:
> Hello
>
> it seems that sudoku solver may be a good candidate for nofib suite /
> language comparison shootout
It would also be nice to see some example sudoku solvers posted
on an `Idioms' page on haskell.org:
http://www.haskell.org/haskellwiki/Category:Idioms
someone co
patc:
>
> Is there an equivalent of an "indent" program for haskell? I have a
> bit of code I want to clean up ...
You could run your code through ghc, with -ddump-parsed turned on.
Then with a little bit of sed magic, you could recover the original code
Before:
$ cat B.hs
main = do {
With a recent snapshot of Cabal you can build a profiled version
of any library as follows (including for FPS):
$ ./Setup.hs configure -p
You'll then see ./Setup.hs build build the lib twice, once with and
once without profiling.
/usr/bin/ar: creating dist/build/libHSfps-0.1.a
/usr/
akamaus:
> Hello, Bulat
>
> I'm currently working on some kind of program for analysing FAT partitions.
> Don't ask why did I chose to implement it in Haskell :) Just for fun.
> My program needs to read scattered chunks of binary data from a huge file and
> to
> do a good amount of deserialisati
Question:
Can I manipulate 1G strings in Haskell?
Short answer:
Yes! Mostly.
Doing some stress testing of FPS, here are some results for 1G strings.
3.2Ghz box, 2G physical mem.
Size of input string: 1G
N.B. 2G of physical ram is not enough when trying to benchmark functions
that copy 1
dagit:
> On 4/19/06, Donald Bruce Stewart <[EMAIL PROTECTED]> wrote:
> > Question:
> > Can I manipulate 1G strings in Haskell?
> >
> >
> > Failed due to memory exhaustion.
> > Almost made it though, just need a tad more ram than I had.
joelr1:
> Howdy folks!
>
> Does anyone have sample code for independent component analysis
> (ICA), singular value decomposition (SVD) aka spectral graph
> partitioning, or semidiscrete decomposition (SDD)?
>
> I'm trying to learn this rocket science and apply it to RDF graph
> analysis.
H
401 - 500 of 661 matches
Mail list logo