Re: [Haskell-cafe] Maybe a compiler bug?

2009-01-06 Thread Murray Gross



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 where I live), I did not get 
any "goOn" despite the value of gTst3 indicating I should, or where, 
according to your analysis, I should have gotten a single "fail," I 
didn't.  If I can prod myself into recreating now lost code (unfortunate, 
sending out the wrong version of the code and losing the right one, only 
to replace it with one that seems to work now [yes, I'm careful about 
deleting .o and .hi files]), I'll do so, and report it as a bug according 
to the instructions in another post. Since I have workarounds and I am 
using a back-dated version of GHC, it probably isn't worth too much more 
attention, although I'll keep a wary eye open.


Thanks to all for attention.

Best,

Murray Gross

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


[Haskell-cafe] Re: Tying a simple circularly STM linked list

2009-01-06 Thread ChrisK

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)
  }

-- Create a new empty transactional loop.
newLoop :: a -> STM (TVar (Loop a))
newLoop item = do
   tLoop <- newTVar undefined
   writeTVar tLoop (ItemLink item tLoop tLoop)
   return tLoop


Hmmm.. STM does not have a MonadFix instance.  But IO does:



-- Use MonadFix instance of newLoopIO
newLoopIO :: a -> IO (TVar (Loop a))
newLoopIO item = mfix (\ tLoop -> newTVarIO (ItemLink item tLoop tLoop))


But mfix (like fix) is difficult to read in large amounts, so there is "mdo":


-- Use RecursiveDo notation
newLoopMDO :: a -> IO (TVar (Loop a))
newLoopMDO item = mdo
   tLoop <- newTVarIO (ItemLink item tLoop tLoop)
   return tLoop




Cheers,
  Chris




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


Re: [Haskell-cafe] Template Haskell question

2009-01-06 Thread Henning Thielemann
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
?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] how out of memory is handled in Haskell

2009-01-06 Thread Manlio Perillo

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 it's very strange that I have not seen it, sorry.



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


Re: [Haskell-cafe] how out of memory is handled in Haskell

2009-01-06 Thread Don Stewart
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:

$ ./A +RTS -M2M
Heap exhausted;
Current maximum heap size is 1998848 bytes (1 MB);
use `+RTS -M' to increase it

Which is invoked via the OutOfHeapHook function:

#include "Rts.h"
#include 

void
OutOfHeapHook (lnat request_size, lnat heap_size) /* both sizes in bytes */
{
  /*fprintf(stderr, "Heap exhausted;\nwhile trying to allocate %lu 
bytes in a %lu-byte heap;\nuse `+RTS -H' to increase the total heap 
size.\n", */

  (void)request_size;   /* keep gcc -Wall happy */
  fprintf(stderr, "Heap exhausted;\nCurrent maximum heap size is %lu bytes 
(%lu MB);\nuse `+RTS -M' to increase it.\n",
  heap_size, heap_size / (1024*1024));
}

Which you can modify yourself at link time.

It is invoked as:

void
heapOverflow(void)
{
  OutOfHeapHook(0/*unknown request size*/, 
RtsFlags.GcFlags.maxHeapSize * BLOCK_SIZE);
  
  stg_exit(EXIT_HEAPOVERFLOW);
}

That is, your OutOfHeapHook is called, and then stg_exit is called to shut down 
the runtime with:

void  
stg_exit(int n)
{ 
#ifdef PAR
  if (exit_started) 
return;
  exit_started=rtsTrue;

  shutdownParallelSystem(n);
#endif

  if (exitFn)
(*exitFn)(n);
  exit(n);
}

Where you can also set your own exitFn, before, if all else fails, exit() is 
called.

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


Re: [Haskell-cafe] Template Haskell question

2009-01-06 Thread Eelco Lempsink

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 out what to replace
them with.


...

-- usage: $(deriveUIState ''MyTypeWithUIState)
{-
- Derive an instance of UIState from some type that has had UIState
fields added to it.
-}
deriveUIState tp = do
   return [InstanceD []
 (appUIState $ appType tp [])
 [FunD 'mousePosition  [|  
mousePositionf |]

...
,FunD 'setMousePosition[| \b a ->  
a{ mousePositionf=b } |]

...

Quick guess: this doesn't typecheck?

FunD :: Name -> [Clause] -> Dec

while [| ... |] will return something of type ExpQ (which is the same  
as Q Exp).


You're indeed nearly there, but if you use the quotation brackets you  
need to write monadic code (for the Q monad) and use functions like  
clause and funD.  The tutorials on the wiki (you've probably seen  
them, http://www.haskell.org/haskellwiki/Template_Haskell) or pretty  
good and you could also look at packages at hackage for inspiration/ 
examples, e.g. http://hackage.haskell.org/packages/archive/haxr-th/3000.0.0/doc/html/src/Network-XmlRpc-THDeriveXmlRpcType.html


--
Regards,

Eelco Lempsink



PGP.sig
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] how out of memory is handled in Haskell

2009-01-06 Thread 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?


Thanks   Manlio Perillo

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


[Haskell-cafe] Tying a simple circularly STM linked list

2009-01-06 Thread John Ky
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)
  }
   | InitLink

-- Create a new empty transactional loop.
newLoop :: a -> STM (TVar (Loop a))
newLoop item = do
   tLoop <- newTVar InitLink
   writeTVar tLoop (ItemLink item tLoop tLoop)
   return tLoop

In the above, the InitLink value is only ever used in the newLoop function
to create a single one element circular linked list.  Is there a way to
write newLoop to avoid using this value?

Thanks

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


Re: [Haskell-cafe] Re: Updating doubly linked lists

2009-01-06 Thread Dan Weston

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 descend on the right.
> But with this structure, walking from A to B is O(d) = O(n)
> (where d is the distance from the origin,
> n the side length of the grid) instead of O(1).

No. The tree is [[Node]], where the outer list has one element for each 
radius that has an occupied node and each inner list has the number of 
nodes at the given radius.


You descend the spine of the outer list radially in O(deltaR) time, 
which for incremental moves is O(1).


Then you search for an existing inner list element in O(nk(r)), which 
stays fairly constant for reasonable paths (basically, the width of a 
path swath).


> I mean, O(d) may be fine for you, but it's not O(1) for everything as
> advertised. :)

d is not the distance from the origin, it is nk(r), the number of nodes 
at a given radius: d(2) = 2, d(3) = 1.


An outward radial path will only expand the tree linearly, not 
quadratically, in size.


> Put differently, using  Data.Tree.Zipper.parent  on B will move you to
> C, not to A.

The parent of C is either A or B, depending on the path that created it, 
but parent teleports you in O(1).


Walking from A to B only involves:

(bX,bY) = (-3,0)
(aX,aY) = (-2,0)
(bR,bK) = (|bX| + |bY|, bR - bX) = (3,6) -- left halfplane
(aR,aK) = (|aX| + |aY|, aR - aX) = (2,4) -- left halfplane
deltaR  = bR - aR = 1
maybe (insertDownFirst (newNode rk) z) (moveAround rk) $ firstChild z

When firstChild fails, insertDownFirst and we're done! All operations 
are O(1).


When firstChild succeeds, moveAround queries each of the defined nodes 
-- but not any of the undefined nodes! -- at that radius. There is at 
most one defined node with Nothing value to ensure a path from the 
origin to every node (where path is not contiguous in X,Y, or K, only in R!)


The diagram you describe can be created with:

Prelude> :l GridZipper
*GridZipper> let f &&& g  = \x -> (f x, g x)
*GridZipper> let f >>> g  = g . f
*GridZipper> const (newGrid :: Grid String) >>> fromTree
 >>> west >>> west >>> setValue (Just "A: X=-2,Y=0,R=2,K=4")
 >>> west  >>> setValue (Just "B: X=-3,Y=0,R=3,K=6")
 >>> east >>> east >>> east
 >>> east >>> east >>> setValue (Just "C: X= 2,Y=0,R=2,K=0")
 >>> assocList >>> show >>> putStrLn $ ()

-- The tree is this:

[(XY (-2) 0,"A: X=-2,Y=0,R=2,K=4"),
 (XY (-3) 0,"B: X=-3,Y=0,R=3,K=6"),
 (XY   2  0,"C: X= 2,Y=0,R=2,K=0")]

-- Zipper starts at origin:

Loc
 {tree = Node {rootLabel = GridLabel (RK 0 0) Nothing,
  subForest = []}, lefts = [], rights = [], parents = []}


-- Zipper after walking to A and setting value:

Loc
 {tree = Node {rootLabel = GridLabel (RK 2 4)
 (Just "A: X=-2,Y=0,R=2,K=4"),
  subForest = []},
 lefts   = [],
 rights  = [],
 parents = [([],GridLabel (RK 1 2) Nothing,[])
   ,([],GridLabel (RK 0 0) Nothing,[])]}

-- Zipper after walking to B and setting value:

Loc
 {tree = Node {rootLabel = GridLabel (RK 3 6)
   (Just "B: X=-3,Y=0,R=3,K=6"),
  subForest = []},
 lefts   = [],
 rights  = [],
 parents = [([],GridLabel (RK 2 4)
   (Just "A: X=-2,Y=0,R=2,K=4"),
[]),([],GridLabel (RK 1 2) Nothing,[])
   ,([],GridLabel (RK 0 0) Nothing,[])]}




-- Zipper where it left off at C:
(Loc
 {tree = Node {rootLabel = GridLabel (RK 2 0)
  (Just "C: X=2,Y=0,R=2,K=0"),
  subForest = []},
  lefts   = [],
  rights  = [],
  parents = [([Node {rootLabel = GridLabel (RK 1 2) Nothing,
  subForest = [Node {rootLabel = GridLabel (RK 2 4)
(Just "A: X=-2,Y=0,R=2,K=4"),
  subForest = [Node {rootLabel = GridLabel (RK 3 6)
(Just "B: X=-3,Y=0,R=3,K=6"),
  subForest = []}]}]}],  GridLabel (RK 1 0) Nothing,[]),
 ([],GridLabel (RK 0 0) Nothing,[])]},

-- Zipper at origin

Loc
 {tree  =  Node {rootLabel = GridLabel (RK 0 0) Nothing,
  subForest = [Node {rootLabel = GridLabel (RK 1 2) Nothing,
  subForest = [Node {rootLabel = GridLabel (RK 2 4)
   (Just "A: X=-2,Y=0,R=2,K=4"),
  subForest = [Node {rootLabel = GridLabel (RK 3 6)
   (Just "B: X=-3,Y=0,R=3,K=6"),
  subForest = [] } ]} ]},
   Node {rootLabel = GridLabel (RK 1 0) Nothing,
  subForest = [Node {rootLabel = GridLabel (RK 2 0)
(Just "C: X=2,Y=0,R=2,K=0"),
  subForest = [] }] }]},
  lefts   = [],
  rights  = [],
  parents = []})



Apfelmus, Heinrich wrote:

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 

Re: [Haskell-cafe] Lack of inlining -> slow parsing with Data.Binary

2009-01-06 Thread Eugene Kirpichov
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
I'm quite satisfied with this result and with the process that led to
it.
(Surprisingly, the bottleneck is now in a conversion from a linked
list to an STArray)

In case anyone is interested, here are the results of my hacking:
 - http://hackage.haskell.org/cgi-bin/hackage-scripts/package/digest -
bindings to crc32 and adler32 from zlib
 - http://hackage.haskell.org/cgi-bin/hackage-scripts/package/zip-archive
- updated version of zip-archive that uses digest and doesn't suffer
from a crc32 bottleneck
 - http://hackage.haskell.org/cgi-bin/hackage-scripts/package/jarfind
- the very utility in question (the classfile searcher)

All in all, Haskell rocks :)

2009/1/6 Don Stewart :
> 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), which is 10 times slower than my Java
>> version of the same code.
>>
>> I compile the program with -O2 ; I tried -ddump-inlinings and it turns
>> out that my readByte/readWord16/readWord32 functions don't get
>> inlined, despite being simply aliases for 'get::Get WordXX'; so, in
>> places where my Java version does a pointer access (after being
>> JIT-compiled), the Haskell version does two function calls.
>>
>> What can be the reason of this lack of inlining? Or how do I
>> understand the output of -ddump-inlinings?
>>
>
>
> Which version of GHC and Data.Binary are you using?
> If using 6.8.x, use the previous Data.Binary release. If using 6.10.x,
> use the latest.
>
> -- Don
>



-- 
Евгений Кирпичев
Разработчик Яндекс.Маркета
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Pattern combinators

2009-01-06 Thread David Menendez
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).

In your implementation, they are (almost) equivalent.

> newtype PatA a b = PatA {
>  unPatA :: forall ans. (b -> ans) -> ans -> a -> ans
>  }

> newtype PatB a b = PatB { unPatB :: a -> Maybe b }

Specifically, "PatA a b" is isomorphic to "a -> (forall ans. (b ->
ans) -> ans -> ans)" and "forall ans. (b -> ans) -> ans -> ans" is
(mostly) isomorphic to "Maybe b".

maybe :: Maybe b -> (b -> ans) -> ans -> ans
maybe (Just x) f z = f x
maybe Nothing f z = z

unMaybe :: (forall ans. (b -> ans) -> ans -> ans) -> Maybe b
unMaybe f = f Just Nothing

(As usual, seq prevents this from being a true isomorphism, because
maybe (unMaybe _|_) = const (const _|_), and seq allows us to
distinguish _|_ from const _|_.)

I'm not sure which form is preferable. I suspect the continuation
version will do less allocation, but with enough in-lining, GHC can
effectively convert the Maybe version into the continuation version on
its own.

-- 
Dave Menendez 

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


Re: [Haskell-cafe] Maybe a compiler bug?

2009-01-06 Thread Daniel Fischer
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 apparently wrong).
>
> I have attached the current version of the program, which behaves
> slightly differently from the version originally sent.
>
> I am running ghc 6.6, gcc 4.1.2, g++ 4.1.1, on Debian Linux. The compile
> lines are ghc -threaded solve.hs or ghc -threaded -O2 solve.hs. The
> execution line is ./a.out, which should give me single-threaded execution.
>
> Ignore the output on stdout; it is the same for both versions.
>
> On stderr, the unoptimized version of the attached code gives me both
> "fail" and "goOn" (see lines #150 and #153). The optimized version gives
> me only "goOn." I think that both should give me both "fail" and "goOn."

I get one "fail" and many "goOn" with optimisation using both, ghc-6.6 and 
ghc-6.8.3. That should indeed be so, because with optimisation, the branch

else trace "fail" []

is only evaluated once, the result ([]) being reused. Without optimisation, 
that branch is re-evaluated every time it is hit, so many "fail" are printed.

>
> Were circumstances different, I might suspect that laziness and
> optimization had something to do with this. However, earlier tests showed
> inconsistency between the result of the test in gTst3 and the code where
> the value of gTst3 is used.

Could you elaborate? I couldn't find an inconsistency using your previous 
code, it behaved as it should (until I ^C-ed it).

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


Re: [Haskell-cafe] Lack of inlining -> slow parsing with Data.Binary

2009-01-06 Thread Don Stewart
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), which is 10 times slower than my Java
> version of the same code.
> 
> I compile the program with -O2 ; I tried -ddump-inlinings and it turns
> out that my readByte/readWord16/readWord32 functions don't get
> inlined, despite being simply aliases for 'get::Get WordXX'; so, in
> places where my Java version does a pointer access (after being
> JIT-compiled), the Haskell version does two function calls.
> 
> What can be the reason of this lack of inlining? Or how do I
> understand the output of -ddump-inlinings?
> 


Which version of GHC and Data.Binary are you using? 
If using 6.8.x, use the previous Data.Binary release. If using 6.10.x,
use the latest.

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


[Haskell-cafe] Re: bug in HPDF?

2009-01-06 Thread Roman Cheplyaka
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
> drawWithPage p $ do
> moveto $ 10 :+ 10
> sequence $ replicate 10 $ drawText $ text (PDFFont Helvetica 
> 10) 0 0 (toPDFString "ABC")
>
>
> It is the Text monad that needs to be replicated. Each copy will start  
> drawing the text lines at (10,10) as specified by the moveto.
> But, inside the text monad, each "text" will create a new line.
>
> Thanks,
> Christophe.
>
>
>> 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 $
>>text (PDFFont Helvetica 10) 10 10 (toPDFString "ABC")
>>
>> What I expect here is "ABC" printed 10 times on the same place  
>> (starting
>> at (10,10)). What I see (in Okular) is ABC printed each time in the new
>> place like this:
>>
>>   ABC
>>  ABC
>> ABC
>> ABC
>>
>> What's happening here? I'm using HPDF-1.4.1 from Hackage.
>>
>> -- 
>> Roman I. Cheplyaka :: http://ro-che.info/
>> "Don't let school get in the way of your education." - Mark Twain
>

-- 
Roman I. Cheplyaka :: http://ro-che.info/
"Don't let school get in the way of your education." - Mark Twain
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Maybe a compiler bug?

2009-01-06 Thread Don Stewart
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 some further information (the behavior is different, by the way, 
> but still apparently wrong).
> 
> I have attached the current version of the program, which behaves 
> slightly differently from the version originally sent.
> 
> I am running ghc 6.6, gcc 4.1.2, g++ 4.1.1, on Debian Linux. The compile 
> lines are ghc -threaded solve.hs or ghc -threaded -O2 solve.hs. The 
> execution line is ./a.out, which should give me single-threaded execution.
> 
> Ignore the output on stdout; it is the same for both versions.
> 
> On stderr, the unoptimized version of the attached code gives me both 
> "fail" and "goOn" (see lines #150 and #153). The optimized version gives 
> me only "goOn." I think that both should give me both "fail" and "goOn."
> 
> Were circumstances different, I might suspect that laziness and 
> optimization had something to do with this. However, earlier tests showed 
> inconsistency between the result of the test in gTst3 and the code where 
> the value of gTst3 is used.
> 
> A copy of the current version of solve.hs is attached.
> 
> Best,
> 
> Murray Gross
> 
> P.S.: For anyone who has actually looked at the logic, I am aware that the 
> test in gTst3 can be sharpened. That will come later. The current version 
> is adequate for the time being.

Content-Description: Current version of solve.hs
> -- *
> -- *   *
> -- *  Eternity II puzzle. Each puzzle piece is represented by a  *
> -- *5-tuple, in which the first 4 entries represent the four   *
> -- *edge colors in the order left, top, right, bottom, and the *
> -- *fifth member is the (numerical) identifier for the piece.  *
> -- *   *
> -- *
> 
> -- module Solve where
> 
> 
> import Data.Array.IArray
> import Control.Parallel
> import Control.Parallel.Strategies
> import List
> import Debug.Trace
> 
> 
> 
> main = putStrLn (show corns) >>
> putStrLn (corpic) >>
> putStrLn "Left sides\n">>
> 
> putStrLn (pArrayPic (pArray pSides)) >>
>   putStrLn "Right sides\n">>
> putStrLn (pArrayPic (rightArray ))>>
> putStrLn (show (length (perims (pArray pSides) corTemp))) >>  
> putStrLn (show (perims (pArray pSides) corTemp))>>
> putStrLn "done"
> 
> 
> 
> 
> -- *
> -- *   *
> -- *Make a list of all possible perimeters. Run the operation in   *
> -- *parallel over the list of possible corner configurations.  *
> -- *   *
> -- *
> 
> 
> perims:: Array (Int) [Int]->
>  [(Int,Int,Int,Int)]->[[Int]]
> perims pArray corTemp = concat $ parMap rwhnf (\oneCor->makPerim
>oneCor pArray
>)
>corTemp
> 
> 
> -- *
> -- *   *
> -- *  We build a list of perimeters by constructing each backward*
> -- *  from position 59. However, position 59 needs special handling  *
> -- *  because it must match position 0 as well as 58. Each of the*
> -- *  other corners will also need special handling, which is done   *
> -- *  by a case statement.   *
> -- *   *
> -- *Note that pArray is organized by the left sides of the pieces, *
> -- *while in makePerim we need to check the right side of a*
> -- *against the bottom of the first corner. This results in the*
> -- *need for rightArray, and some tricky indexing. *
> -- *   *
> -- *
> 
> makPerim :: (Int,Int,Int,Int) -> Array (Int) [Int] -> [[Int]]
> makPerim oneCor
>  pArray = [a:b | a <- ((rightArray) ! startCol), b <- 
>  (restPerim a 
> (pArray // [(left(refPerim!a),
>   (pArray!(left(refPerim!a)))\\[a])]) 
> 
> (rightArray /

[Haskell-cafe] Re: bug in HPDF?

2009-01-06 Thread alpheccar

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 , ty ). tx and ty are numbers expressed in  
unscaled text space units.


Tj : Show a text string.

So, the behavior is correct and HPDF really needs a documentation :-)  
and some cleaning of the API.


Thanks,
Christophe.


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 $
   text (PDFFont Helvetica 10) 10 10 (toPDFString "ABC")

What I expect here is "ABC" printed 10 times on the same place  
(starting
at (10,10)). What I see (in Okular) is ABC printed each time in the  
new

place like this:

  ABC
 ABC
ABC
ABC

What's happening here? I'm using HPDF-1.4.1 from Hackage.

--
Roman I. Cheplyaka :: http://ro-che.info/
"Don't let school get in the way of your education." - Mark Twain


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


[Haskell-cafe] bug in HPDF?

2009-01-06 Thread Roman Cheplyaka
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 $
text (PDFFont Helvetica 10) 10 10 (toPDFString "ABC")

What I expect here is "ABC" printed 10 times on the same place (starting
at (10,10)). What I see (in Okular) is ABC printed each time in the new
place like this:

   ABC
  ABC
 ABC
ABC

What's happening here? I'm using HPDF-1.4.1 from Hackage.

-- 
Roman I. Cheplyaka :: http://ro-che.info/
"Don't let school get in the way of your education." - Mark Twain
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] HDBC-Sqlite3 "attaching databases"

2009-01-06 Thread Günther Schmidt

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.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Template Haskell question

2009-01-06 Thread Jeff Heard
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 idea of the module is that you define your
record type, Q, and that record type contains all the state you're
interested in.  The Hieroglyph system has other basic state, and the
idea is that you use

$(additions "QWithState" ''Q)
$(deriveUIState ''QWithState)

to create your final UIState instance.

-- -

{-# LANGUAGE TemplateHaskell #-}
module Graphics.Rendering.Hieroglyph.TH where

import Language.Haskell.TH
import Language.Haskell.TH.Syntax
import Graphics.Rendering.Hieroglyph.UIState
import Graphics.Rendering.Hieroglyph.Primitives
import Graphics.UI.Gtk.Types (Widget)
import Control.Monad

{- output of $( fmap (LitE . StringL . show) [| reify ''BasicUIState |] )
TyConI
(DataD []
   Graphics.Rendering.Hieroglyph.BasicUIState.BasicUIState
   []
   [RecC Graphics.Rendering.Hieroglyph.BasicUIState.BasicUIState

[(Graphics.Rendering.Hieroglyph.BasicUIState.mousePosition,NotStrict,ConT
Graphics.Rendering.Hieroglyph.Primitives.Point)

,(Graphics.Rendering.Hieroglyph.BasicUIState.mouseLeftButtonDown,NotStrict,ConT
GHC.Base.Bool)

,(Graphics.Rendering.Hieroglyph.BasicUIState.mouseRightButtonDown,NotStrict,ConT
GHC.Base.Bool)

,(Graphics.Rendering.Hieroglyph.BasicUIState.mouseMiddleButtonDown,NotStrict,ConT
GHC.Base.Bool)

,(Graphics.Rendering.Hieroglyph.BasicUIState.mouseWheel,NotStrict,ConT
GHC.Base.Int)

,(Graphics.Rendering.Hieroglyph.BasicUIState.keyCtrl,NotStrict,ConT
GHC.Base.Bool)

,(Graphics.Rendering.Hieroglyph.BasicUIState.keyShift,NotStrict,ConT
GHC.Base.Bool)

,(Graphics.Rendering.Hieroglyph.BasicUIState.keyAlt,NotStrict,ConT
GHC.Base.Bool)

,(Graphics.Rendering.Hieroglyph.BasicUIState.key,NotStrict,ConT
Graphics.Rendering.Hieroglyph.UIState.Key)

,(Graphics.Rendering.Hieroglyph.BasicUIState.drawing,NotStrict,AppT
(ConT Data.Maybe.Maybe) (ConT Graphics.UI.Gtk.Types.Widget))

,(Graphics.Rendering.Hieroglyph.BasicUIState.sizeX,NotStrict,ConT
GHC.Float.Double)

,(Graphics.Rendering.Hieroglyph.BasicUIState.sizeY,NotStrict,ConT
GHC.Float.Double)

,(Graphics.Rendering.Hieroglyph.BasicUIState.imageCache,NotStrict,AppT
(ConT Data.Maybe.Maybe) (ConT
Graphics.Rendering.Hieroglyph.UIState.ImageCache))]] [])
-}

-- usage: $(additions "MyTypeName" OldTypeName)
{-
 - Add fields to a record type for handling basic UI state for
Hieroglyph.  Gives you mouse buttons, etcetera
-}
additions newtypenamestr nm = do
TyConI (DataD _ _ _ [RecC _ fielddefs]) <- reify nm
let newtypename = mkName newtypenamestr
return $
(DataD []
   newtypename
   []
   [RecC newtypename
 [(mkName "mousePositionf",NotStrict,ConT ''Point)
 ,(mkName "mouseLeftButtonDownf",NotStrict,ConT ''Bool)
 ,(mkName "mouseRightButtonDownf",NotStrict,ConT ''Bool)
 ,(mkName "mouseMiddleButtonDownf",NotStrict,ConT ''Bool)
 ,(mkName "mouseWheelf",NotStrict,ConT ''Int)
 ,(mkName "keyCtrlf",NotStrict,ConT ''Bool)
 ,(mkName "keyShiftf",NotStrict,ConT ''Bool)
 ,(mkName "keyAltf",NotStrict,ConT ''Bool)
 ,(mkName "keyf",NotStrict,ConT ''Key)
 ,(mkName "drawingf",NotStrict,AppT (ConT ''Maybe)
(ConT ''Widget))
 ,(mkName "sizeXf",NotStrict,ConT ''Double)
 ,(mkName "sizeYf",NotStrict,ConT ''Double)
 ,(mkName "imageCachef",NotStrict,AppT (ConT ''Maybe)
(ConT ''ImageCache))] ++ fielddefs] [])

-- | Apply a Binary type constructor to given type: "t" -> "Binary t"
appUIState :: Type -> Type
appUIState t  =  AppT (ConT ''UIState) t

-- | Generate from list of type names result of types application:
-- appType T [a,b] -> "T a b"
appType :: Name -> [Name] -> Type
--appType t []  = ConT t -- T
--appType t [t1]= AppT (ConT t) (VarT t1)-- T a
--appType t [t1,t2] = AppT (AppT (ConT t) (VarT t1)) (VarT t2)   -- T
a b == (T a) b
appType t ts  =  foldl (\a e -> AppT a (VarT e)) (ConT t) ts --
general definition

-- | Generate `n` unique variables and return them in form of patterns
and expressions
genNames :: Int -> Q ([PatQ],[ExpQ])
genNames n = do
  ids <- replicateM n (newName "x")
  return (map varP ids, map varE ids)

-- usage: $(deriveUIState ''MyTypeWithUIState)
{-
 - Derive an instance of UIState from some type that has had UIState
fields added to it.
 -}
deriveUIState tp = do
return [InstanceD []
  (appUIState $ appType tp [])
  [FunD 'mousePosition  [| mousePositionf |]
  ,FunD 'mouseLeftButtonDown[|
mouseLeftButtonDownf |]
   

Re: [Haskell-cafe] Maybe a compiler bug?

2009-01-06 Thread 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 apparently wrong).


I have attached the current version of the program, which behaves 
slightly differently from the version originally sent.


I am running ghc 6.6, gcc 4.1.2, g++ 4.1.1, on Debian Linux. The compile 
lines are ghc -threaded solve.hs or ghc -threaded -O2 solve.hs. The 
execution line is ./a.out, which should give me single-threaded execution.


Ignore the output on stdout; it is the same for both versions.

On stderr, the unoptimized version of the attached code gives me both 
"fail" and "goOn" (see lines #150 and #153). The optimized version gives 
me only "goOn." I think that both should give me both "fail" and "goOn."


Were circumstances different, I might suspect that laziness and 
optimization had something to do with this. However, earlier tests showed 
inconsistency between the result of the test in gTst3 and the code where 
the value of gTst3 is used.


A copy of the current version of solve.hs is attached.

Best,

Murray Gross

P.S.: For anyone who has actually looked at the logic, I am aware that the 
test in gTst3 can be sharpened. That will come later. The current version 
is adequate for the time being.-- *
-- *   *
-- *Eternity II puzzle. Each puzzle piece is represented by a  *
-- *5-tuple, in which the first 4 entries represent the four   *
-- *edge colors in the order left, top, right, bottom, and the *
-- *fifth member is the (numerical) identifier for the piece.  *
-- *   *
-- *

-- module Solve where


import Data.Array.IArray
import Control.Parallel
import Control.Parallel.Strategies
import List
import Debug.Trace



main = putStrLn (show corns) >>
putStrLn (corpic) >>
putStrLn "Left sides\n">>

putStrLn (pArrayPic (pArray pSides)) >>
putStrLn "Right sides\n">>
putStrLn (pArrayPic (rightArray ))>>
putStrLn (show (length (perims (pArray pSides) corTemp))) >>
putStrLn (show (perims (pArray pSides) corTemp))>>
putStrLn "done"




-- *
-- *   *
-- *Make a list of all possible perimeters. Run the operation in   *
-- *parallel over the list of possible corner configurations.  *
-- *   *
-- *


perims:: Array (Int) [Int]->
 [(Int,Int,Int,Int)]->[[Int]]
perims pArray corTemp = concat $ parMap rwhnf (\oneCor->makPerim
   oneCor pArray
   )
   corTemp


-- *
-- *   *
-- *We build a list of perimeters by constructing each backward*
-- *from position 59. However, position 59 needs special handling  *
-- *because it must match position 0 as well as 58. Each of the*
-- *other corners will also need special handling, which is done   *
-- *by a case statement.   *
-- *   *
-- *Note that pArray is organized by the left sides of the pieces, *
-- *while in makePerim we need to check the right side of a*
-- *against the bottom of the first corner. This results in the*
-- *need for rightArray, and some tricky indexing. *
-- *   *
-- *

makPerim :: (Int,Int,Int,Int) -> Array (Int) [Int] -> [[Int]]
makPerim oneCor
 pArray = [a:b | a <- ((rightArray) ! startCol), b <- 
   (restPerim a 
  (pArray // [(left(refPerim!a),
(pArray!(left(refPerim!a)))\\[a])]) 
  
  (rightArray //[(startCol,
   (rightArray ! startCol) \\ [a])])
  oneCor 
  58),
   trace (show b) 
  b /=[]
  ]  
  where startCol = bot  (corns !! (fst4 oneCor))
   

[Haskell-cafe] Re: Threads with high CPU usage

2009-01-06 Thread Simon Marlow

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, what was weird
that running like 500 reqs - pause - 500 reqs ... went ok).

After compiling with -threaded and running with +RTS -N2 it handles
10k+ requests (with 10 concurrent request running at once) without
missing a beat.


How about compiled with -threaded and running with just +RTS -N1 ?

I would expect the crucial thing is the -threaded not the number of cpus
running Haskell code concurrently (-threaded uses a pool of OS threads
to make blocking foreign calls effectively non-blocking).


Exactly - adding another virtual CPU with +RTS -N2 should never turn a 
deadlocked program into a responsive one (unless there are threads busy not 
allocating anything, that is).


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


[Haskell-cafe] Re: Threads with high CPU usage

2009-01-06 Thread Simon Marlow

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 "unsafe" declaration
into a "safe" one, but never OK to convert from "safe" to "unsafe"
without looking at what the foreign side actually does.

And in general we would not even bother with considering using "unsafe"
for calls that are already expensive. It's only worth considering when
the length of the call is always very short.

For example in a database library it might make sense to use 'unsafe' on
the data-access functions that extract data from a local query result
but we should always use 'safe' on any DB function that might want to
talk to the network (eg to get more query results).


It's difficult to anticipate the needs here.  For instance, some people
may be using a few very-long-running queries measured in minutes, such
as the original poster.  Other people, such as web app developers, may
be issuing literally millions of queries, right after another, where the
difference matters.


I'd be really interested to know whether you can actually measure a 
difference between safe and unsafe foreign calls for something complicated 
like a database query.  Do you have any figures?  If it turns out that 
"safe" calls are a bottleneck, then there might be room for optimisation there.



I had initially used "unsafe" because of the documented performance
benefit, plus I certainly am not expecting Sqlite to call back into the
Haskell runtime.

It seems to me strange that using "unsafe" instead of "safe" would have
negative implications for threading.  After all, as Malcolm said above,
"it is always OK to convert an unsafe declaration into a safe one".  So
could the compiler be made to be smart enough to do so when it is
advantageous for threading purposes?


It's not possible to make the choice at runtime without compromising the 
efficiency of "unsafe" calls.  An "unsafe" call is just an inline call to 
the C function, whereas a "safe" call is wrapped in a couple of calls into 
the RTS to save/restore the Haskell state.


Cheers,
Simon

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


[Haskell-cafe] Re: Threads with high CPU usage

2009-01-06 Thread Simon Marlow

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 performance and 
do nothing else, unless you actually need it (i.e. you're using OpenGL).


Cheers,
Simon

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


Re: [Haskell-cafe] Maybe a compiler bug?

2009-01-06 Thread Neil Mitchell
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 suggesting ways to
improve your code. Of course you are right - if the code goes wrong
when written in an inelegant way that is the fault of the compiler,
not the fault or the author!

Trying your code I get 69 of output on stdout, then the message "fail"
repeatedly on stderr. This happens whether I compile the code with
-fasm or -fvia-c, using GHC 6.10. What are you expecting the code to
output in each case, what command lines do you use, and which do you
believe is correct? Please make sure you clean all the .hi and .o
files between each build, so they don't have any confusing effects.

As soon as someone else can reproduce the problem, they will probably
be able to snip it down to a more manageable example.

Thanks

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


Re: [Haskell-cafe] Maybe a compiler bug?

2009-01-06 Thread Peter Verswyvelen
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 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
> doesn't, unfortunately, make the problem go away, and it is sure to appear
> elsewhere as the program is extended, which it will be.
>
> It would appear that the real issue here is that someone with resources I
> don't have needs to dig into the compilers--it should not be necessary to
> use trial and error to find an alternate writing of code that is legal and
> correct (regardless of the aesthetics) but is incorrectly compiled. For the
> time being, I will use native compilation and hope that someone can find and
> fix the error so that I can use the speed advantage of optimization.
>
> Best,
>
> Murray Gross
>
>
>
> On Tue, 6 Jan 2009, Neil Mitchell wrote:
>
>> 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) then False else True
>> Why not:
>>  not (lr > ll)
>>
>> Making that change and running it again gives:
>>
>> Example.hs:8:1: Error: Use <=
>> Found:
>>  not (lr > ll)
>> Why not:
>>  lr <= ll
>>
>> Which ends up with something similar to what you came up with.
>> However, if we take your final answer:
>>
>>> gTst3 right left = (lr <= ll)
>>>where lr = length (right ! 2)
>>>  ll = length (left ! 2)
>>
>> We get:
>>
>> Example.hs:8:1: Warning: Redundant brackets
>> Found:
>>  (lr <= ll)
>> Why not:
>>  lr <= ll
>>
>> Leaving us with the HLint 1.0 compliant (TM) :
>>
>> gTst3 right left = lr <= ll
>>where lr = length (right ! 2)
>>  ll = length (left ! 2)
>>
>> 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
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Maybe a compiler bug?

2009-01-06 Thread Murray Gross


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 
doesn't, unfortunately, make the problem go away, and it is sure to appear 
elsewhere as the program is extended, which it will be.


It would appear that the real issue here is that someone with resources I 
don't have needs to dig into the compilers--it should not be necessary to 
use trial and error to find an alternate writing of code that is legal and 
correct (regardless of the aesthetics) but is incorrectly compiled. For 
the time being, I will use native compilation and hope that someone can 
find and fix the error so that I can use the speed advantage of 
optimization.


Best,

Murray Gross



On Tue, 6 Jan 2009, Neil Mitchell wrote:


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) then False else True
Why not:
 not (lr > ll)

Making that change and running it again gives:

Example.hs:8:1: Error: Use <=
Found:
 not (lr > ll)
Why not:
 lr <= ll

Which ends up with something similar to what you came up with.
However, if we take your final answer:


gTst3 right left = (lr <= ll)
where lr = length (right ! 2)
  ll = length (left ! 2)


We get:

Example.hs:8:1: Warning: Redundant brackets
Found:
 (lr <= ll)
Why not:
 lr <= ll

Leaving us with the HLint 1.0 compliant (TM) :

gTst3 right left = lr <= ll
where lr = length (right ! 2)
  ll = length (left ! 2)

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


[Haskell-cafe] Re: building HSQL MySQL on windows (Was: FFI imported function names)

2009-01-06 Thread Simon Marlow

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 linking a
Haskell program against it, names with @ cannot be resolved.

The solution is pretty much a hack. Somebody from the Ruby community
used to run into the same problem, from the same situation -- namely
building ruby mysql bindings.

Here is the procedure one person suggests
http://rubydotnetproxy.rubyforge.org/mysql_win.html

It worked perfectly for me. Of course, with some cabal specifics,
which is obviously not described in the above page.

The solution was to create a def file listing the names which could
not be resolved and creating a .a file based on the dll and this def
file.


GHC adds the @N suffix to any foreign function declared with the stdcall 
calling convention, which I think matches what gcc does.  I wonder how it 
works for C.


Cheers,
Simon




2008/12/24 Daniil Elovkov :

Mm, actually I didn't change the calling convention ffi imports when I
thought I did. I tried to do it through defines...

Well, by explicitly saying ccall I get the names without @
decoration. And it all links well. But I get segault when I run the
code, which should mean that calling conventions didn't match.

Actually I found some ramblings on the internet that there's something
wrong with libmysql.dll and libmysql.lib in this respect, but they
were from 2004.

Thus the question: how do I link against a lib file in ghc? When I say
-lmysql on command line it strictly searches for dll and complains if
it's not found. Adding lib exlpicitly on the cmd line doesn't seem to
have any effect.

Thanks


2008/12/24 Daniil Elovkov :

Hello

How is decided whether the name of imported function gets the ending
of the form @4 in ghc?

I'm having this problem on Windows trying to use HSQL MySQL on windows.

I compile HSQL Oracle backend and I get names without that. It's ok.
With HSQL MySQL I get names with that stuff. It prevents me from
further linking to dll. Supplying in the ghc command-line the "lib"
file where names have those marks doesn't have any effect.

The linker says that fn...@nn cannot be resolved.

Can I control that?

The ffi calling convention doesn't (and shouldn't as I understand)
affect this. The only difference is that in the case of mysql the
header file itself where functions are described marks it STDCALL. Is
that the reason?

Also I changed ffi import line from "hsmysql.h func" to just "func",
to no avail.

ghc 6.8.2

I'm lost. Please help.

--
Daniil Elovkov




--
Daniil Elovkov







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


Re: [Haskell-cafe] Maybe a compiler bug?

2009-01-06 Thread Neil Mitchell
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) then False else True
Why not:
  not (lr > ll)

Making that change and running it again gives:

Example.hs:8:1: Error: Use <=
Found:
  not (lr > ll)
Why not:
  lr <= ll

Which ends up with something similar to what you came up with.
However, if we take your final answer:

> gTst3 right left = (lr <= ll)
>   where lr = length (right ! 2)
> ll = length (left ! 2)

We get:

Example.hs:8:1: Warning: Redundant brackets
Found:
  (lr <= ll)
Why not:
  lr <= ll

Leaving us with the HLint 1.0 compliant (TM) :

gTst3 right left = lr <= ll
where lr = length (right ! 2)
  ll = length (left ! 2)

Thanks

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


Re: [Haskell-cafe] Maybe a compiler bug?

2009-01-06 Thread Rafael Gustavo da Cunha Pereira Pinto
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)
where lr = length (right ! 2)
  ll = length (left ! 2)




2009/1/5 Murray Gross 

>
>
> No unsafe perform (except what may be hidden in trace), nothing, fancy, no
> gimmicks (very pedestrian, even heavy-handed) code. Complete code is
> attached (I don't have smaller snippets, because I just discovered the
> problem).
>
>
>
> Best,
>
> Murray Gross
>
>
>
>
> On Mon, 5 Jan 2009, Luke Palmer wrote:
>
>  On Mon, Jan 5, 2009 at 4:34 PM, Murray Gross 
>> wrote:
>>
>>
>>> When using any of -O, -O1, -O2 with the Debian binary build of GHC 6.6,
>>> trace shows that the expression
>>>
>>>  if (lr > ll)  then  False else True
>>>
>>> is (at least partially) evaluated, but the value returned is always True,
>>> even though trace reports that (lr > ll) is True. When I use only the
>>> native
>>> code generator (without optimization), the correct value (False) is
>>> returned.
>>>
>>> Further detail and complete code on request.
>>>
>>
>>
>> Of course!  This is obviously incorrect behavior.  Are you doing any
>> unsafePerformIO?  Please, complete code (minimal test case if possible,
>> but
>> don't let that stop you).
>>
>> Luke
>>
>>
>>
>>
>>
>>>
>>> Best,
>>>
>>> Murray Gross
>>> ___
>>> 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
>
>


-- 
Rafael Gustavo da Cunha Pereira Pinto
Electronic Engineer, MSc.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Updating doubly linked lists

2009-01-06 Thread Apfelmus, Heinrich
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 some point.
> 
> Really? My solution (rose tree zipper where tree depth is manhattan
> distance from origin and forest width is nodes around concentric
> diamonds, see
> http://permalink.gmane.org/gmane.comp.lang.haskell.cafe/49948) was
> designed specifically to be amortized constant for everything for paths
> that do not specifically move helically around the origin. The
> complexity of lookup is O(d) where d is the number of defined nodes at a
> given radius. Until the grid gets pretty dense, d grows very slowly for
> most sane paths.
> 
> Have I missed something?

>From your description (without reading the code ;)), I gather that your
tree looks something like this?

 -+-
/   \
  -+ -+- +-
 /  /   \  \
   -+ -+ -+- +- +-
  /  /  /   \  \  \
-+ -+ -+ -+- +- +- +-
   /  /  /  /   \  \  \  \
  +  B  A  +  +--+--C--+--+-- ...
   \  \  \  \   /  /  /  /
-+ -+ -+ -+- +- +- +-
  \  \  \   /  /  /
   -+ -+ -+- +- +-
 \  \   /  /
  -+ -+- +-
\   /
 -+-

The root of the tree is the center and you can descend on the right. But
with this structure, walking from A to B is O(d) = O(n) (where d is the
distance from the origin, n the side length of the grid) instead of O(1).

Put differently, using  Data.Tree.Zipper.parent  on B will move you to
C, not to A.


I mean, O(d) may be fine for you, but it's not O(1) for everything as
advertised. :)


Regards,
H. Apfelmus

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


Re: [Haskell-cafe] Can I destructive rebind a local variable in haskell?

2009-01-06 Thread Evan Laforge
>   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 particularly imperative, it's just variable
shadowing.  It desugars to calling a function with a parameter that
shadows the old variable.

Of course, you could say a more functional way would be to use
pointfree style or just nested calls to avoid naming the intermediate
values.  Then you can't intersperse IO actions... but it's good to
avoid doing that anyway.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Can I destructive rebind a local variable in haskell?

2009-01-06 Thread Wang, Chunye (NSN - CN/Beijing)
 
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 you forget it you probably won't get a type error, you'll
just get a bug, possibly a subtle one.  Besides, what's the next step?
>  filename''?  filename'''?

   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")

 and I often write similar code in EmacsLisp also.
 It is not so buggy, because we live in "imperitive programming" for
long time

Best Regards
Chunye Wang 


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


Re: [Haskell-cafe] Can I destructive rebind a local variable in haskell?

2009-01-06 Thread Evan Laforge
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 filename
>
> Nope.  The "filename" on the right side of the = is the same as the
> "filename" on the left, so you're making an infinite loop, the same way:
>let x = x in x
> is an infinite loop.  However you can make a new name as you are trying, you
> just can't reference the old one.  e.g.:
>let filename = 42

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 you forget it you probably won't get a type error, you'll
just get a bug, possibly a subtle one.  Besides, what's the next step?
 filename''?  filename'''?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe