On Tue, 6 Jan 2009, Daniel Fischer wrote:
Could you elaborate? I couldn't find an inconsistency using your previous
code, it behaved as it should (until I ^C-ed it).
In several versions of the code, now unfortunately lost because of a crash
on a power failure (which is extremely rare whe
You can use "undefined" or "error ..." :
{-# LANGUAGE RecursiveDo #-}
import Control.Concurrent.STM
import Control.Monad.Fix
-- Transactional loop. A loop is a circular link list.
data Loop a
= ItemLink
{ item :: a
, prev :: TVar (Loop a)
, next :: TVar (Loop a)
}
-
Jeff Heard schrieb:
> Alright... I *think* I'm nearly there, but I can't figure out how to
> derive a class instance using record accessors and updaters...
Has this something to do with
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/data-accessor-template
?
__
Manlio Perillo ha scritto:
[...]
How is this handled in GHC?
- exit(1)?
- abort()?
- IO exception?
Ok, found it by myself:
http://hackage.haskell.org/trac/ghc/ticket/1791
It is also explicitly documented in:
http://haskell.org/ghc/docs/latest/html/libraries/base/Control-Exception.html
and i
manlio_perillo:
> Hi.
>
> Here:
> http://damienkatz.net/2008/03/what_sucks_abou.html
>
> I found how Erlang (or at least old versions of Erlang) handles out of
> memory failure: it just calls exit(1).
>
>
> How is this handled in GHC?
> - exit(1)?
> - abort()?
> - IO exception?
>
>
GHC:
On 6 jan 2009, at 18:08, Jeff Heard wrote:
Alright... I *think* I'm nearly there, but I can't figure out how to
derive a class instance using record accessors and updaters... Can
anyone help? There are [| XXXf |] instances at the end of the module
and they all need replaced, but I can't figure
Hi.
Here:
http://damienkatz.net/2008/03/what_sucks_abou.html
I found how Erlang (or at least old versions of Erlang) handles out of
memory failure: it just calls exit(1).
How is this handled in GHC?
- exit(1)?
- abort()?
- IO exception?
Thanks Manlio Perillo
__
Hi,
I've written a circularly linked list, but there is some code in it I feel
is redundant, but don't know how to get rid of:
-- Transactional loop. A loop is a circular link list.
data Loop a
= ItemLink
{ item :: a
, prev :: TVar (Loop a)
, next :: TVar (Loop a)
}
Apfelmus,
Thanks for the reply.
>>From your description (without reading the code ;))
I hope the code is better than my description! :) The structure is more like
Nothing(RK 0 _)
Nothing(RK 1 _)
A(RK 2 4)
B(RK 3 6)
C(RK 2 0)
> The root of the tree is the center and you can des
Thanks; I'm using GHC 6.10.1 and the latest binary now, and things get
inlined perfectly well.
Anyways, the main bottleneck turned out to be the performance of
zip-archive , which is now (since 1-2 days ago) ~25x better, and now
the Haskell version is about just 2.5x slower than the Java one, and
On Sat, Jan 3, 2009 at 4:06 PM, Massimiliano Gubinelli
wrote:
> I've tried to undestand the paper, in particular the relation between
> the combinators written in cps style and combinators written using a
> Maybe type (i.e pattern matching functions returning Maybe to signal
> success or failure)
Am Dienstag, 6. Januar 2009 18:32 schrieb Murray Gross:
> My last note had an error in it, and the code originally sent to the list
> should be ignored. I have attached the current version of the code, and
> here is some further information (the behavior is different, by the way,
> but still appare
ekirpichov:
> Hi,
>
> I'm parsing Java classfiles with Data.Binary, the code is here:
> http://paste.org/index.php?id=4625
>
> The problem is that the resulting code parses rt.jar from JDK6 (about
> 15K classes, 47Mb zipped) in 15 seconds (run the program with main
> -mclose rt.jar, for instance)
Thanks for helping!
* alpheccar [2009-01-06 19:47:21+0100]
> Roman,
>
> Here is the source code to do what you want:
>
> import Graphics.PDF
> import Complex
>
> main = runPdf "bug.pdf" standardDocInfo (PDFRect 0 0 100 100) pdf
> where
> pdf = do
> p <- addPage Nothing
> d
If you believe this is a compiler bug, please report it:
http://hackage.haskell.org/trac/ghc/newticket?type=bug
mgross21:
>
>
> My last note had an error in it, and the code originally sent to the list
> should be ignored. I have attached the current version of the code, and
> here is som
Roman,
The text monad is very low level and its functions are mapping
directly to the PDF text environment commands.
"text" function is generating two PDF commands : Td and Tj. In Adobe
PDF spec :
Td : Move to the start of the next line, offset from the start of the
current line by (tx
Here is a program which illustrates an unexpected behaviour:
import Graphics.PDF
main = runPdf "bug.pdf" standardDocInfo (PDFRect 0 0 100 100) pdf
where
pdf = do
p <- addPage Nothing
drawWithPage p $ drawText $
sequence $ replicate 10 $
Hi,
has anybody here successfully tried to "attach" another database to an
Sqlite database with HDBC-Sqlite3?
I keep failing, so I'd be grateful for a hint how to do it.
Günther
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.has
Alright... I *think* I'm nearly there, but I can't figure out how to
derive a class instance using record accessors and updaters... Can
anyone help? There are [| XXXf |] instances at the end of the module
and they all need replaced, but I can't figure out what to replace
them with. The basic id
My last note had an error in it, and the code originally sent to the list
should be ignored. I have attached the current version of the code, and
here is some further information (the behavior is different, by the way,
but still apparently wrong).
I have attached the current version of the
Duncan Coutts wrote:
On Tue, 2008-12-23 at 03:56 +0100, wman wrote:
Thanks to you all for inspiration.
My web app (which otherwise ran ok) was getting stuck while getting
harassed by ab (apache-benchmark) after receiving some 800+ requests
in short succession (not less, never gotten to 900, wha
John Goerzen wrote:
Duncan Coutts wrote:
On Mon, 2008-12-22 at 10:30 +, Malcolm Wallace wrote:
The terminology seems counter-intuitive, but in other other words, a
"safe" call is slower but more flexible, an "unsafe" call is fast and
dangerous. Therefore it is always OK to convert an "uns
Bulat Ziganshin wrote:
Hello Günther,
Monday, December 22, 2008, 1:57:22 AM, you wrote:
try -threaded, +RTS -N2, and forkOS simultaneously. it may work - i
don't see reasons why other threads should be freezd why one does
unsafe call
Please don't suggest using forkOS - it will probably harm p
Hi Murray,
> The issue here is not whether or not the code is pretty or elegant, but
> whether or not I get correct execution of what I have, which is a correct
> statement of what I want (even if not the prettiest or most lint free), and
> I don't.
Sorry, I was merely responding to someone else
Exactly. The best you can do is try to reduce your code to a tiny
fragment that still exposes the problem, and report it as a bug.
On Tue, Jan 6, 2009 at 4:52 PM, Murray Gross wrote:
>
> The issue here is not whether or not the code is pretty or elegant, but
> whether or not I get correct executi
The issue here is not whether or not the code is pretty or elegant, but
whether or not I get correct execution of what I have, which is a correct
statement of what I want (even if not the prettiest or most lint free),
and I don't. There are lots of ways to work around the problem, but that
do
Daniil Elovkov wrote:
Ok, enough talking to myself :)
If anybody ever wants to build hsql-mysql on windows and has the same
problems as I had, here's how it should be done.
The problem I had seemed to be that libmysql.dll uses stdcall, but
names its functions without @ decoration. Thus, when li
Hi
> gTst3 right left = if (lr > ll) then False else True
> where lr = length (right ! 2)
> ll = length (left ! 2)
Running this code over HLint (http://www.cs.york.ac.uk/~ndm/hlint) says:
Example.hs:8:1: Error: Redundant if
Found:
if (lr > ll
Specifically for this code:
gTst3 right left = if (lr > ll) then False else True
where lr = length (right ! 2)
ll = length (left ! 2)
why don't you just negate the condition, like:
gTst3 right left = (lr <= ll)
wher
Dan Weston wrote:
>> For the 2D grid zipper above, moving around is O(1) but update is O(log
>> n). This is acceptable; also because I'm quite confident that a zipper
>> for a 2D grid with everything O(1) does not exist. I can prove that for
>> a special case and should probably write it down at so
> Nice. Good solution. ``imperative style'' is not a bad idea when I'm
> not used to the ``pure functional style''
>
> E.g.
>
> filename <- return $ combine filename "Makefile"
>
> Similar to the other imperative language
>
> filename = joinPath(filename,"Makefile")
I wouldn't consider it
Hi Evan,
> You can also reuse the name exactly by using bind+return instead of
let:
> test filename = do
> is_dir <- doesDirectoryExist filename
> filename <- return $ if not is_dir then filename else filename
> I'm not a huge fan of the prime thing because it's tiny and easy to
miss and if y
2009/1/6 Luke Palmer :
> 2009/1/6 Wang, Chunye (NSN - CN/Beijing)
> Dear haskeller,
>>
>>
>> Can I destructive rebind a local variable like this
>>
>> import System.Directory
>> test filename = do
>> is_dir <- doesDirectoryExist filename
>> let filename = if not is_dir then filename else f
33 matches
Mail list logo