[Haskell-cafe] Re: Bi-directional Maps

2007-08-20 Thread apfelmus

Andrew Wagner wrote:

So, in writing my chess engine, I've been trying to maintain 2 Map
objects. One maps squares on the board to Ints, the other maps Ints to
actual Pieces. It occurred to me that it would be useful to explicitly
have a Bi-directional Map, which does the maintenance of keeping the
Maps synchronized behind the scenes. Thus, Bimap was born! I've taken
the API for Data.Map (which you can find at ), and cannibalized it for
Bimap. The new API is at http://hpaste.org/2344 . The idea is that if
you have a Bimap k a, and you want to treat the k's as keys, and use a
function like Data.Map.foo, it will be called Data.Map.left_foo in
Bimap. And if they want to do the same thing, but using the a's as
keys, then they simply use right_foo. The metaphor is that we can view
it as a Map in 2 directions, manipulating it from the left (on the
k's), or from the right (on the a's).

Is this useful? Is there a better way? Is the API too big, and if so,
how can it be pared down?


IMHO, the API is too big and not beautiful enough. How about a function

  flip :: Bimap a b - Bimap b a

that interchanges the role of keys and values? Or maybe keep every 
functions symmetric in  a  and  b , like in


  update :: ((a,b) - Maybe (a,b))
 - Either a b - Bimap a b - Bimap a b

The changer functions take pairs and the search key to look for is 
Either a b .


But most of the map functions (including  update  above) probably won't 
work anyway, what should


  left_insertWith (\new old - new) 'a' 1 (fromList [('a',2),('b',1)])

do? I can't yield

  fromList [('a',1),('b',1)]

since 1 has two keys now.

Regards,
apfelmus

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


[Haskell-cafe] Tying the knot with unknown keys

2007-08-20 Thread David Ritchie MacIver
I was playing with some code for compiling regular expressions to finite 
state machines and I ran into the following problem. I've solved it, but 
I'm not terribly happy with my solution and was wondering if someone 
could come up with a better one. :-)


Essentially I have

data FSM = State { transitions :: (Map Char FSM) }

and

transitions' :: Regexp - Map Char Regexp

I want to lift this so that the Regexps become states of the finite 
state machine (while making sure I set up a loop in the data structure). 
Tying the knot is the traditional way of doing such things, but we 
couldn't figure out a way to make it work without the set of keys known 
in advance because of the strictness of Map in its keys (an association 
list was suggested, and that would probably work, but it seemed a bit 
ugly and would be fairly inefficient).


In the end what I did was just work out the set of reachable regexps in 
advance and use a standard tying the knot trick, but it felt vaguely 
unsatisfactory (and does some repeat work which I felt should be 
unneccessary). Anyone have a more elegant suggestion?


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


[Haskell-cafe] Re: Using Collections: ElemsView and KeysView

2007-08-20 Thread Jean-Philippe Bernardy

foldr on ElemsView is defined as such:

 foldr f i (ElemsView c) = foldr (f . snd) i c 

so, for example:

 getElementList = toList . ElemViews


When I designed this code (some years ago), I didn't like the fold of Map to
have the type:

 fold :: (a - b - b) - b - Map k a - b

This just doesn't make sense if we see maps as a collection of (key, value)
pairs.  (Indeed, toList :: Map k a - [(k, a)])

In order to be consistent, but to provide an easy way to migrate to the new
collection classes I was designing, I provided the ElemViews/KeyViews to
switch to the former behaviour on a case by case basis.

This also allows for definining optimized versions of foldr, etc. for each types
that supports Views, but this was tedious, so I never did it. GHC RULE
pragma is probably better suited to the purpose anyway.

As for the lack of documentation, everyone is very welcome to contribute ;)

Cheers,
JP.




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


[Haskell-cafe] How can I pass IOUArrays to FFI functions?

2007-08-20 Thread Ryan Ingram
I have a C function of type
   void f ( HsWord32* p0, HsWord32* p1, HsWord32 size );

along with the FFI declaration:
   foreign import ccall unsafe f :: Ptr Word32 - Ptr Word32 - Word32 - IO
()

In my Haskell code I have an unboxed IO array of Word32; IOUArray Int
Word32.
I want to pass the pointer to this array to f().  How can I get the pointer
out of the array?  Or, is there a better way to declare f() to do this?

I'm open to using GHC hackery; using v6.6.1 right now.

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


Re: [Haskell-cafe] How can I pass IOUArrays to FFI functions?

2007-08-20 Thread Spencer Janssen
On Monday 20 August 2007 07:27:04 Ryan Ingram wrote:
 I have a C function of type
void f ( HsWord32* p0, HsWord32* p1, HsWord32 size );

 along with the FFI declaration:
foreign import ccall unsafe f :: Ptr Word32 - Ptr Word32 - Word32 -
 IO ()

 In my Haskell code I have an unboxed IO array of Word32; IOUArray Int
 Word32.
 I want to pass the pointer to this array to f().  How can I get the pointer
 out of the array?  Or, is there a better way to declare f() to do this?

 I'm open to using GHC hackery; using v6.6.1 right now.

   -- ryan

Perhaps you'd like to use Data.Array.Storable?  It supports the MArray
interface, and has the additional operation:

withStorableArray :: StorableArray i e - (Ptr e - IO a) - IO a


Cheers,
Spencer Janssen

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


Re: [Haskell-cafe] Diagnosing stack overflow

2007-08-20 Thread Justin Bailey
On 8/18/07, Matthew Brecknell [EMAIL PROTECTED] wrote:
 Justin Bailey:
  Would retainer profiling help me see what was building up
  this large thunk/closure?

 I'm not really familiar enough with GHC's profiling to answer that, but
 I'll take a guess.

You're experimental programs have given me an idea  - I can use them
to test if the profiling tools can show me where a stack overflow
might be occurring.

Thanks for the clear explanation of the difference. I also found the
wiki page http://www.haskell.org/haskellwiki/Stack_overflow to be
helpful.

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


Re: [Haskell-cafe] Newbie question: Where is StackOverflow on the Wiki?

2007-08-20 Thread Lanny Ripple
Not really more efficient but plays to the language 
implementation's strengths.


Imagine

  take 10 $ foo (10^9)

and

  take 10 $ bar (10^9)

bar wouldn't evaluate until the 10^9 was done.  (And I just 
ground my laptop to a halt checking that.  :)  foo on the other 
hand would run out to 10^6 and then conveniently finish the rest 
of your program waiting for the need of the other 10^9-10 values. 
 If you *always* needed the result of the 10^9 calculations then 
tail-recursion should be better since you won't be holding onto 
the evaluation frames.


  -ljr

Peter Verswyvelen wrote:


Now if I understand this correctly, this just means that when writing
something like:

foo n = if n0 then [] else n : foo (n-1)

bar n = aux 0 [] where
  aux i xs = if in then xs else aux (i+1) (i:xs)

that foo is more efficient than bar because lazy evaluation of foo just puts
the delayed computation in the cdr of the list, while lazy evaluation of
bar has to keep track of all aux calls (the closures) which gives much
more overhead, maybe even stack overflow? Something like that? 


Thanks,
Peter




--
Lanny Ripple [EMAIL PROTECTED]
ScmDB / Cisco Systems, Inc.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Newbie question: Where is StackOverflow on the Wiki?

2007-08-20 Thread Lanny Ripple



Lanny Ripple wrote:
Not really more efficient but plays to the language implementation's 
strengths.


Imagine

  take 10 $ foo (10^9)

and

  take 10 $ bar (10^9)

bar wouldn't evaluate until the 10^9 was done.  (And I just ground my 
laptop to a halt checking that.  :)  foo on the other hand would run out 
to 10^6 and then conveniently finish the rest of your program waiting 


   s/10^6/10/

That's what I get for not proof-reading after making a change 
after the first proof-read.


for the need of the other 10^9-10 values.  If you *always* needed the 
result of the 10^9 calculations then tail-recursion should be better 
since you won't be holding onto the evaluation frames.


  -ljr

Peter Verswyvelen wrote:


Now if I understand this correctly, this just means that when writing
something like:

foo n = if n0 then [] else n : foo (n-1)


bar n = aux 0 [] where
  aux i xs = if in then xs else aux (i+1) (i:xs)

that foo is more efficient than bar because lazy evaluation of foo 
just puts
the delayed computation in the cdr of the list, while lazy 
evaluation of

bar has to keep track of all aux calls (the closures) which gives much
more overhead, maybe even stack overflow? Something like that?
Thanks,
Peter






--
Lanny Ripple [EMAIL PROTECTED]
ScmDB / Cisco Systems, Inc.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Tying the knot with unknown keys

2007-08-20 Thread Bertram Felgenhauer
David Ritchie MacIver wrote:
 I was playing with some code for compiling regular expressions to finite 
 state machines and I ran into the following problem. I've solved it, but 
 I'm not terribly happy with my solution and was wondering if someone could 
 come up with a better one. :-)

 Essentially I have

 data FSM = State { transitions :: (Map Char FSM) }

 and

 transitions' :: Regexp - Map Char Regexp

 I want to lift this so that the Regexps become states of the finite state 
 machine (while making sure I set up a loop in the data structure). Tying 
 the knot is the traditional way of doing such things, but we couldn't 
 figure out a way to make it work without the set of keys known in advance 
 because of the strictness of Map in its keys (an association list was 
 suggested, and that would probably work, but it seemed a bit ugly and would 
 be fairly inefficient).

 In the end what I did was just work out the set of reachable regexps in 
 advance and use a standard tying the knot trick, but it felt vaguely 
 unsatisfactory (and does some repeat work which I felt should be 
 unneccessary). Anyone have a more elegant suggestion?

Hmm. I tried and came up with this:

 import Data.Maybe
 import Data.Map (Map)

 data Graph b = Graph (Map b (Graph b))

 buildTransitionGraph :: (Ord a, Ord b) = (a - Map b a) - a - Graph b
 buildTransitionGraph f i = fromJust $ i `M.lookup` build M.empty [i] where
 -- build :: Map a (Graph b) - [a] - Map a (Graph b)
 build g [] = g
 build g (a:as) = g'' where
 -- g'' :: Map a (Graph b)
 g'' = build g' as'
 (as', g') = foldr step (as, g) (M.toList (f a))
 step (l, n) (as, g)
  | M.member n g = (as, g)
  | otherwise= (n:as, M.insert n (f' n) g)
 -- f' :: a - Graph b
 f' = Graph . M.map (fromJust . (`M.lookup` g'')) . f

which couples the knot tying with finding the reachable states.

'build' takes a map of states seen so far to their corresponding
'Graph' node, and a working stack of states not processed yet
and processes a single state.

'step' processes a single transition. If it leads to an unknown
state, the state is added to the seen state map. The knot is tied
between the final result of the calculation, g'', and the map
that is being built - this happens in f'.

Test:

 t :: Int - Map Int Int
 t 1 = M.fromList [(1,2),(2,1)]
 t 2 = M.fromList [(1,2),(3,1),(4,3)]
 t _ = M.empty

 traces :: Ord b = Int - Graph b - [[b]]
 traces 0 g = [[]]
 traces d (Graph g) = concat
 [map (n:) (trace (d-1) g') | (n, g') - M.toList g]

*Main trace 1 $ buildTransitionGraph t 1
[[1],[2]]
*Main trace 1 $ buildTransitionGraph t 2
[[1],[3],[4]]
*Main trace 2 $ buildTransitionGraph t 1
[[1,1],[1,3],[1,4],[2,1],[2,2]]

It's still not lazy though. The potential lookups of states that
haven't been seen yet makes this hard to accomplish, although it
should be possible with an unbalanced search tree and some clever
use of irrefutable patterns.

enjoy,

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


[Haskell-cafe] is there a way to patch the build-depends line of a cabal file without breaking backwards compatibility?

2007-08-20 Thread Thomas Hartman
cafe, is there a way to patch the build-depends line of a cabal file 
without breaking backwards compatibility? 

I just patched HDBC head to compile under ghc 6.7. Unfortunately it now 
won't compile in 6.6.1. 

is there a way for build-depends to detect which version of ghc you're on?

also I seem to recall that -fglasgow-exts was deprecated under 6.7. is 
there a better way to beat back the error message below than this?

thanks,

thomas.

{
hunk ./Database/HDBC/Statement.hs 1
+{-# LANGUAGE TypeSynonymInstances #-}
hunk ./Database/HDBC/Types.hs 1
+{-# OPTIONS_GHC -fglasgow-exts #-}
+{-
+-- without -fglasgow-exts you get: [_$_]
+Database/HDBC/Types.hs:202:0:
+Illegal polymorphic or qualified type: forall conn.
+  (IConnection conn) =
+  conn - b
+In the type signature for `withWConn':
+  withWConn :: forall b.
+  ConnWrapper - (forall conn. (IConnection conn) = conn 
- b) - b
+-}
hunk ./HDBC.cabal 13
-Build-Depends: base, mtl
+
+Build-Depends: base, mtl, old-time, bytestring, containers
+-- breaks backwards compability with ghc 6.6.1
+
}


---

This e-mail may contain confidential and/or privileged information. If you 
are not the intended recipient (or have received this e-mail in error) 
please notify the sender immediately and destroy this e-mail. Any 
unauthorized copying, disclosure or distribution of the material in this 
e-mail is strictly forbidden.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] cabal install of HDBC-odbc fails on ghc 6.7, -I flag causes problems

2007-08-20 Thread Thomas Hartman
problemw with the -I flag to ghc are causing cabal install to fail for 
hdbc-odbc (darcs head).

man ghc still reports that -I is a valid flag after installing ghc 6.7 
from darcs head a couple days ago.

I think the problem might be the space after the -I flag (which is bad for 
both 6.6.1 and 6.7)

[EMAIL 
PROTECTED]:~/installs/HDBC-odbc-head/hdbc-odbc/usr/local/bin/ghc-6.7.20070816 
  -I. -e '' Setup.hs
[EMAIL 
PROTECTED]:~/installs/HDBC-odbc-head/hdbc-odbc/usr/local/bin/ghc-6.7.20070816 
  -I/ -e '' Setup.hs
[EMAIL 
PROTECTED]:~/installs/HDBC-odbc-head/hdbc-odbc/usr/local/bin/ghc-6.7.20070816 
  -I / -e '' Setup.hs
ghc-6.7.20070816: unrecognised flags: -I

just a guess... 

anothing thing is it seems like there's a new INCLUDE pragma in 6.7. 
perhaps this should be used in one of the source files to get it to 
compile. but which one? I couldn't figure out what was causing 

  ghc -c -I dist/build/Database/HDBC/ODBC/Connection_hsc_make.c -o 
dist/build/Database/HDBC/ODBC/Connection_hsc_make.o

to be run. (I did try grepping on ghc but no luck, below.)

Any tips on debugging this cabal install would be appreciated.

thanks,

thomas

*

$ runghc Setup.hs configure; runghc Setup.hs build

.

configure: Using tar found on system at: /bin/tar
Reading parameters from 
/home/hartthoma/installs/HDBC-odbc-head/hdbc-odbc/HDBC-odbc.buildinfo
Preprocessing library 
[EMAIL PROTECTED]:~/installs/HDBC-odbc-head/hdbc-odbcdarcs 
whatsnew.0...
ghc-6.7.20070816: unrecognised flags: -I
Usage: For basic information, try the `--help' option.
compiling dist/build/Database/HDBC/ODBC/Connection_hsc_make.c failed
command was: ghc -c -I dist/build/Database/HDBC/ODBC/Connection_hsc_make.c 
-o dist/build/Database/HDBC/ODBC/Connection_hsc_make.o




[EMAIL PROTECTED]:~/installs/HDBC-odbc-head/hdbc-odbcdarcs whatsnew
{
hunk ./Setup.hs 8
-main = defaultMainWithHooks defaultUserHooks{preConf = conf, postConf = 
ok}
-   where ok _ _ _ _ = return ExitSuccess
+--main = defaultMainWithHooks defaultUserHooks{preConf = conf, postConf = 
ok}
+--   where ok _ _ _ _ = return ExitSuccess
+main = do
+  let ok _ _ _ _ = do return ExitSuccess
+  return ()
+in defaultMainWithHooks defaultUserHooks{preConf = conf, postConf = 
ok}
+  return ()
+
}

.

[EMAIL PROTECTED]:~/installs/HDBC-odbc-head/hdbc-odbcgrep -i ghc *
HDBC-odbc.buildinfo:ghc-prof-options:
HDBC-odbc.buildinfo:ghc-options:
HDBC-odbc.cabal:GHC-Options: -O2
Makefile:GHCPARMS := -fglasgow-exts
Makefile:all: setup # GHC build
Makefile:   ghc -package Cabal Setup.hs -o setup
Makefile:   cd testsrc  ghc --make -package mtl -package HUnit 
-package MissingH -package HDBC -lodbc $(GHCPARMS) -o runtests 
-i../dist/build:.. ../d\
ist/build/hdbc-odbc-helper.o runtests.hs
Makefile:test-ghc6: testsrc/runtests
Makefile:interact-ghci: all
Makefile:   ghci -idist/build -Ldist/build $(GHCPARMS)
Makefile:test: test-ghc6 test-hugs
README.txt:You'll need either GHC 6.4.1 or above, or Hugs 2005xx or above. 
 If
README.txt:2) ghc --make -o setup Setup.lhs
README.txt:To use with GHC, you'll want to use:


---

This e-mail may contain confidential and/or privileged information. If you 
are not the intended recipient (or have received this e-mail in error) 
please notify the sender immediately and destroy this e-mail. Any 
unauthorized copying, disclosure or distribution of the material in this 
e-mail is strictly forbidden.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] GHC optimisations

2007-08-20 Thread Andrew Coppin

Stefan O'Rear wrote:

On Sun, Aug 19, 2007 at 12:53:07PM +0100, Andrew Coppin wrote:
  
Does GHC do stuff like converting (2*) into (shift 1) or converting x + x 
into 2*x?



For a good time, compile some code which uses even or odd :: Int - Bool
using -O2 -fasm -ddump-asm...  The compiler *really* shouldn't be using 'idivl'.

(If you use -fvia-C -optc-O2, the C compiler will notice the operations
and optimize it itself.  This is one of the very few areas where -fvia-C
is still better.)
  


The way I heard it is that compilation via C is always better, though 
they plan to change that some day. I don't know how true that is...



If I do x * sin 12, is GHC likely to compute sin 12 at compile-time?



Also try -ddump-simpl-stats and -ddump-simpl-iterations if you want to
know *why*.  (The extremely obscure 'full laziness' transformation
performed by GHC has a fundamental effect on the compilation of x * sin
12...)
  


Hmm, OK.

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


Re: [Haskell-cafe] is there a way to patch the build-depends line of a cabal file without breaking backwards compatibility?

2007-08-20 Thread Thomas Schilling


On 20 aug 2007, at 18.37, Thomas Hartman wrote:



cafe, is there a way to patch the build-depends line of a cabal  
file without breaking backwards compatibility?


I just patched HDBC head to compile under ghc 6.7. Unfortunately it  
now won't compile in 6.6.1.


is there a way for build-depends to detect which version of ghc  
you're on?


also I seem to recall that -fglasgow-exts was deprecated under 6.7.  
is there a better way to beat back the error message below than this?




The next release of Cabal (and the current HEAD) supports  
conditionals to test for flags, os/arch, and implementation  
(+version).  Note that the problem isn't the GHC version, but the new  
base version, in which the old base was split up into smaller  
packages, so we have something roughly like:  base-1.0 = base-2.0 +  
bytestring + old-time + mtl.  Take a look at the Cabal.cabal file,  
how this is solved, atm.  Please also note that this might not be the  
best way to use the new features;  as I suggested in another thread,  
simulating base-1.0 on systems with base-2.0 is probably best handled  
with a base.cabal file that imports base-2.0, old-time, etc. and re- 
exports all imported modules to get a virtual base-1.0.


/ Thomas

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


Re: [Haskell-cafe] can't build haxml under ghc 6.7, says HughesPJ is hidden... but ghc-pkg doesn't say it's hidden...

2007-08-20 Thread Thomas Hartman
so you get

$ runghc Setup.hs configure
Setup.hs: Multiple description files found.  Please use only one of : 
[HaXml.cabal,HaXml-darcs.cabal]

is there a way to specify which cabal file should be used, or do you just 
have to  move a file out out the way with eg

  mv HaXml.cabal HaXml.cabal.tmp ? 

Understanding this better is important to me because I am installing a 
number of packages on 6.7, and am reluctant to send a patch that breaks 
backwards compabitility with earlier versions.

It seems to me that if there is a way to specify the cabal file, you're a 
step closer to having something DWIM that works for either 6.6 or 6.7, as 
Claus wishlists elsewhere in this thread. 

thomas.




Malcolm Wallace [EMAIL PROTECTED] 
Sent by: [EMAIL PROTECTED]
08/10/2007 08:31 AM

To
haskell-cafe@haskell.org
cc

Subject
Re: [Haskell-cafe] can't build haxml under ghc 6.7, says HughesPJ   is 
hidden... but ghc-pkg doesn't say it's hidden...






Stefan O'Rear [EMAIL PROTECTED] wrote:

 When you build a package, Cabal passess the -hide-all-packages option
 to GHC, which prevents the package from using any installed packages
 other than the ones explicitly listed in the Build-Depends: field.
 
 For now, we just edit .cabal files when transporting code between GHC
 versions...

Just for information, the HaXml darcs repo has recently adopted the
solution of containing two .cabal files, one for ghc-6.6.x, and the
other for the split-base packages (=ghc-6.7).  The only difference is
the build-depends line, which is now as follows:

build-depends: base, haskell98, polyparse, pretty, fps

But if you have collected the earlier release HaXml-1.13.2 from hackage,
then you can omit both 'polyparse' and 'fps' dependencies.  ('fps' will
shortly be changing to 'bytestring' in any case...)

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



---

This e-mail may contain confidential and/or privileged information. If you 
are not the intended recipient (or have received this e-mail in error) 
please notify the sender immediately and destroy this e-mail. Any 
unauthorized copying, disclosure or distribution of the material in this 
e-mail is strictly forbidden.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Bi-directional Maps

2007-08-20 Thread Rich Neswold
On 8/20/07, apfelmus [EMAIL PROTECTED] wrote:

 Andrew Wagner wrote:
  It occurred to me that it would be useful to explicitly
  have a Bi-directional Map, which does the maintenance of keeping the
  Maps synchronized behind the scenes. Thus, Bimap was born!

 ... most of the map functions (including  update  above) probably won't
 work anyway, what should

left_insertWith (\new old - new) 'a' 1 (fromList [('a',2),('b',1)])

 do? I can't yield

fromList [('a',1),('b',1)]

 since 1 has two keys now.


Exactly. For this to work there needs to be the constraint that there's a
one-to-one mapping in each direction. The Bimap should have the uniqueness
promise that Set (k, v) gives. Yet you should be able to search on either
tuple value.

-- 
Rich

JID: [EMAIL PROTECTED]
AIM: rnezzy
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How can I pass IOUArrays to FFI functions?

2007-08-20 Thread Stefan O'Rear
On Mon, Aug 20, 2007 at 05:27:04AM -0700, Ryan Ingram wrote:
 I have a C function of type
void f ( HsWord32* p0, HsWord32* p1, HsWord32 size );
 
 along with the FFI declaration:
foreign import ccall unsafe f :: Ptr Word32 - Ptr Word32 - Word32 - IO
 ()
 
 In my Haskell code I have an unboxed IO array of Word32; IOUArray Int
 Word32.
 I want to pass the pointer to this array to f().  How can I get the pointer
 out of the array?  Or, is there a better way to declare f() to do this?

Short answer: You can't.

Longer: GHC uses a copying/compacting garbage collector, so most objects
don't have stable addresses.  In particular MutableByteArray# is movable
by default.  So, you need an array structure built on pinned memory.

If you want MArray operations, that leaves you with
Data.Array.Storable, as already mentioned.

Stefan


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


Re: [Haskell-cafe] Parsing binary data.

2007-08-20 Thread Adam Langley
On 8/19/07, Matthew Sackman [EMAIL PROTECTED] wrote:
 But it's vastly harder to do that for floats / non-integers. Now I know
 that the number classes in the Prelude are basically broken anyway and
 all really need rewriting, but it does seem completely arbitrary that
 Words somehow are only allowed to contain whole numbers!

Well, see the attached patch to Data.Binary to add
putFloat[32|64][be|le]. I got bored, so adding the Get functions is an
exercise for the reader :)

(And so because I think it needs unsafeSomethingIO and I'm a little
unsure about that).

If these functions would be useful for you, you should bug the binary
team to add something similar.


AGL

-- 
Adam Langley  [EMAIL PROTECTED]
http://www.imperialviolet.org   650-283-9641


data-binary-float.darcs
Description: Binary data
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] is there a way to patch the build-depends line of a cabal file without breaking backwards compatibility?

2007-08-20 Thread Thomas Hartman
 Take a look at the Cabal.cabal file, how this is solved, atm.

where is this, how can I take a look at it?

 The next release of Cabal (and the current HEAD) supports  conditionals

I couldn't install head, but since I'm running 6.7, do I already have it?

[EMAIL PROTECTED]:~/installs/cabal-head/cabalrunghc Setup.lhs configure

Distribution/Simple/InstallDirs.hs:267:36:
Not in scope: `dropDrive'

[EMAIL PROTECTED]:~/installs/cabal-head/caballs -l `which ghc`
lrwxrwxrwx 1 root root 31 2007-08-20 11:08 /usr/local/bin/ghc - 
/usr/local/bin/ghc-6.7.20070816


[EMAIL PROTECTED]:~/installs/cabal-head/cabalghc-pkg list | grep -i cabal
Cabal-1.1.7

  Please also note that this might not be the 
 best way to use the new features;  as I suggested in another thread, 
 simulating base-1.0 on systems with base-2.0 is probably best handled 
 with a base.cabal file that imports base-2.0, old-time, etc. and re- 
 exports all imported modules to get a virtual base-1.0.

I'm interested in seeing how this works, but I couldn't find that other 
thread.

Where is the documentation for the new functionality in cabal head, or do 
you just have to read the source code for now?

thanks, t




Thomas Schilling [EMAIL PROTECTED] 
08/20/2007 01:37 PM

To
Thomas Hartman/ext/[EMAIL PROTECTED]
cc
haskell-cafe haskell-cafe@haskell.org
Subject
Re: [Haskell-cafe] is there a way to patch the build-depends line of a 
cabal file without breaking backwards compatibility?







On 20 aug 2007, at 18.37, Thomas Hartman wrote:


 cafe, is there a way to patch the build-depends line of a cabal 
 file without breaking backwards compatibility?

 I just patched HDBC head to compile under ghc 6.7. Unfortunately it 
 now won't compile in 6.6.1.

 is there a way for build-depends to detect which version of ghc 
 you're on?

 also I seem to recall that -fglasgow-exts was deprecated under 6.7. 
 is there a better way to beat back the error message below than this?


The next release of Cabal (and the current HEAD) supports 
conditionals to test for flags, os/arch, and implementation 
(+version).  Note that the problem isn't the GHC version, but the new 
base version, in which the old base was split up into smaller 
packages, so we have something roughly like:  base-1.0 = base-2.0 + 
bytestring + old-time + mtl.  Take a look at the Cabal.cabal file, 
how this is solved, atm.  Please also note that this might not be the 
best way to use the new features;  as I suggested in another thread, 
simulating base-1.0 on systems with base-2.0 is probably best handled 
with a base.cabal file that imports base-2.0, old-time, etc. and re- 
exports all imported modules to get a virtual base-1.0.

/ Thomas




---

This e-mail may contain confidential and/or privileged information. If you 
are not the intended recipient (or have received this e-mail in error) 
please notify the sender immediately and destroy this e-mail. Any 
unauthorized copying, disclosure or distribution of the material in this 
e-mail is strictly forbidden.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] is there a way to patch the build-depends line of a cabal file without breaking backwards compatibility?

2007-08-20 Thread Neil Mitchell
Hi

Distribution/Simple/InstallDirs.hs:267:36:
 Not in scope: `dropDrive'

 [EMAIL PROTECTED]:~/installs/cabal-head/caballs -l `which ghc`
 lrwxrwxrwx 1 root root 31 2007-08-20 11:08 /usr/local/bin/ghc -
 /usr/local/bin/ghc-6.7.20070816


You'll need to upgrade the filepath library as well, since cabal depends on
it, and a very recent version at that.

Thanks

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


Re: [Haskell-cafe] Newbie question: Where is StackOverflow on the Wiki?

2007-08-20 Thread Stefan O'Rear
On Mon, Aug 20, 2007 at 11:21:01AM -0500, Lanny Ripple wrote:
 Not really more efficient but plays to the language implementation's 
 strengths.

 Imagine

   take 10 $ foo (10^9)

 and

   take 10 $ bar (10^9)

 bar wouldn't evaluate until the 10^9 was done.  (And I just ground my 
 laptop to a halt checking that.  :)  foo on the other hand would run out to 
 10^6 and then conveniently finish the rest of your program waiting for the 
 need of the other 10^9-10 values.  If you *always* needed the result of the 
 10^9 calculations then tail-recursion should be better since you won't be 
 holding onto the evaluation frames.

Even if you did, in the presense of laziness it's not useful to make
list producers tail recursive.  Consider:

sum = sum' 0
sum' k [] = k
sum' k (x:xs) = (sum' $! (k+x)) xs

enum x y | x = y= 0
 | otherwise = x : enum (x+1) y


sum (enum 1 10) =
sum' 0 (enum 1 10)  =
sum' 0 (1 : enum (1+1) 10)  =
(sum' $! (0+1)) (enum (1+1) 10) =
sum' 1 (enum (1+1) 10)  =

sum' 1 (2 : enum (2+1) 10)  =
(sum' $! (1+2)) (enum (2+1) 10) =
sum' 3 (enum (2+1) 10)  =

sum' 3 (3 : enum (3+1) 10)  =
(sum' $! (3+3)) (enum (3+1) 10) =
sum' 6 (enum (3+1) 10)  =

sum' 6 (4 : enum (4+1) 10)  =
(sum' $! (6+4)) (enum (4+1) 10) =
sum' 10 (enum (4+1) 10) =

...


sum' 36 (9 : enum (9+1) 10)  =
(sum' $! (36+9)) (enum (9+1) 10) =
sum' 45 (enum (9+1) 10)  =
sum' 45 []   =
45

(I need to find some way to automate making these trails :) )

It runs in constant space, despite the producer's non-tail-recursion.

Stefan


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


Re: [Haskell-cafe] GHC optimisations

2007-08-20 Thread Stefan O'Rear
On Mon, Aug 20, 2007 at 06:30:27PM +0100, Andrew Coppin wrote:
 Stefan O'Rear wrote:
 On Sun, Aug 19, 2007 at 12:53:07PM +0100, Andrew Coppin wrote:
   
 Does GHC do stuff like converting (2*) into (shift 1) or converting x + x 
 into 2*x?

 For a good time, compile some code which uses even or odd :: Int - Bool
 using -O2 -fasm -ddump-asm...  The compiler *really* shouldn't be using 
 'idivl'.

 (If you use -fvia-C -optc-O2, the C compiler will notice the operations
 and optimize it itself.  This is one of the very few areas where -fvia-C
 is still better.)

 The way I heard it is that compilation via C is always better, though 
 they plan to change that some day. I don't know how true that is...

Currently, it's never worse.  GHC's backend is about as good as GCC;
most of the optimiations it doesn't do are not possible for GCC because
of various lack-of-information problems (the stack pointer never aliases
the heap pointer, stuff like that).  It's conceivable that at some point
-fasm will be faster, because you have the possibility of much more
accurate aliasing information inside the compiler, than can be coded in
C.  In the meantime, note that the runtime difference is less than 3%
and the compile time difference is over 100%, so it's only worthwhile if
you expect *this version* of your program to be used more than 30 times,
ie releases only.

Stefan


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


RE: [Haskell-cafe] GHC optimisations

2007-08-20 Thread Simon Peyton-Jones
GHC does some constant folding, but little by way of strength reduction, or 
using shifts instead of multiplication.  It's pretty easy to add more: it's all 
done in a single module.  Look at primOpRules in the module PrelRules.

Patches welcome!  But please also supply test-suite tests that check the 
correctness of the rules.

Simon

| -Original Message-
| From: [EMAIL PROTECTED] [mailto:haskell-cafe-
| [EMAIL PROTECTED] On Behalf Of Stefan O'Rear
| Sent: 19 August 2007 20:14
| To: Andrew Coppin
| Cc: haskell-cafe@haskell.org
| Subject: Re: [Haskell-cafe] GHC optimisations
|
| On Sun, Aug 19, 2007 at 12:53:07PM +0100, Andrew Coppin wrote:
|  Does GHC do stuff like converting (2*) into (shift 1) or converting x
| + x
|  into 2*x?
|
| For a good time, compile some code which uses even or odd :: Int -
| Bool
| using -O2 -fasm -ddump-asm...  The compiler *really* shouldn't be using
| 'idivl'.
|
| (If you use -fvia-C -optc-O2, the C compiler will notice the operations
| and optimize it itself.  This is one of the very few areas where -fvia-
| C
| is still better.)
|
|  If I do x * sin 12, is GHC likely to compute sin 12 at compile-time?
|
| Also try -ddump-simpl-stats and -ddump-simpl-iterations if you want to
| know *why*.  (The extremely obscure 'full laziness' transformation
| performed by GHC has a fundamental effect on the compilation of x * sin
| 12...)
|
| Stefan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Parsing binary data.

2007-08-20 Thread Aaron Denney
On 2007-08-19, Matthew Sackman [EMAIL PROTECTED] wrote:
 Recently, Adam Langley responded so:
 On 8/18/07, Matthew Sackman [EMAIL PROTECTED] wrote:
  Also, one thing to watch out for is the fact the existing Get and Put
  instances may not do anything like what you expect. For example, for
  some reason I expected that the instances of Get and Put for Float and
  Double would send across the wire Floats and Doubles in IEEE floating
  point standard. How wrong I was...
 
 Ah, those aren't instances of Get and Put, but of Binary[1]. You use
 the Binary instances via the functions 'get' and 'put' (case is
 important).

 Gah, that'll teach me to post from memory without checking the code.
 Indeed, that is what I meant, the instances of Binary.

 Get and Put provide actions like putWord32be, for which the
 resulting bits are pretty much universally accepted. Binary has
 default instances which uses Get and Put to serialise Haskell types
 like [Int], or (Float, Float). Here the resulting bits aren't
 documented, but you can read the code and I have some C code for
 dealing with them somewhere if anyone is interrested. The
 serialisation of Float is, indeed, nothing like IEEE in either
 endianness.

 Quite. Whilst we're on the subject (and I realise I might be hijacking
 this thread a little), it does seem rather odd that it's very easy to
 take a Word8/16/32/64 and interpret it as an integer. Similarly, it's
 very easy to take an integer and convert it to a Word of some sort.

That's because there's basically only one way to interpret a given word
as an integer, and store a given integer as a word.

 But it's vastly harder to do that for floats / non-integers. Now I know
 that the number classes in the Prelude are basically broken anyway and
 all really need rewriting, but it does seem completely arbitrary that
 Words somehow are only allowed to contain whole numbers!

It's more that for floats, there are a zillion plausible ways to store
them, and many have been used.

-- 
Aaron Denney
--

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


Re: [Haskell-cafe] Tying the knot with unknown keys

2007-08-20 Thread Dan Piponi
On 8/20/07, David Ritchie MacIver [EMAIL PROTECTED] wrote:
 I was playing with some code for compiling regular expressions to finite
 state machines and I ran into the following problem.

I've met exactly the same problem myself and you got me interested in it again.

I think the tricky part isn't so much the knot-tying, but the fact
that you need a high performance Map-like datastructure that doesn't
die the way Data.Map.fromList would if you gave it an infinite list as
argument.

One approach might be to replace Map k a with something like a

data UltraLazyMap k a = ULM (Map k a) [(k,a)]

The idea is that the Map part is built only as needed and the list
part represents the elements not yet inserted into the tree. When you
come to perform a lookup you first look in the Map part. If you don't
find what you want there you start looking through the list (assuming
that when you come to do lookups, every key you need eventually
appears at least once in the list). Each time you look at a list
element you remove it from the list and insert it into the tree. That
way you never try to build an infinite tree and instead grow it as
needed. This would have a similar amortised performance as a regular
Map, but the price is that lookups change the structure and so you
need mutable state. But that's OK, you just stick all of your code in
a State monad.

I don't know if that State monad would ultimately mess up any attempt
to eventually tie your knots, and I probably won't have time to try
coding this up at lest until the weekend. So take all of this with a
pinch of salt :-)

Good luck! :-)

And if that doesn't work, I also have another approach I'm thinking about...
--
Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Tying the knot with unknown keys

2007-08-20 Thread Stefan O'Rear
On Mon, Aug 20, 2007 at 03:39:28PM -0700, Dan Piponi wrote:
 On 8/20/07, David Ritchie MacIver [EMAIL PROTECTED] wrote:
  I was playing with some code for compiling regular expressions to finite
  state machines and I ran into the following problem.
 
 I've met exactly the same problem myself and you got me interested in it 
 again.
 
 I think the tricky part isn't so much the knot-tying, but the fact
 that you need a high performance Map-like datastructure that doesn't
 die the way Data.Map.fromList would if you gave it an infinite list as
 argument.
 
 One approach might be to replace Map k a with something like a
 
 data UltraLazyMap k a = ULM (Map k a) [(k,a)]
 
 The idea is that the Map part is built only as needed and the list
 part represents the elements not yet inserted into the tree. When you
 come to perform a lookup you first look in the Map part. If you don't
 find what you want there you start looking through the list (assuming
 that when you come to do lookups, every key you need eventually
 appears at least once in the list). Each time you look at a list
 element you remove it from the list and insert it into the tree. That
 way you never try to build an infinite tree and instead grow it as
 needed. This would have a similar amortised performance as a regular
 Map, but the price is that lookups change the structure and so you
 need mutable state. But that's OK, you just stick all of your code in
 a State monad.
 
 I don't know if that State monad would ultimately mess up any attempt
 to eventually tie your knots, and I probably won't have time to try
 coding this up at lest until the weekend. So take all of this with a
 pinch of salt :-)
 
 Good luck! :-)
 
 And if that doesn't work, I also have another approach I'm thinking about...

You could also just build the map lazily.

data Map k a = Fork k a (Map k a) (Map k a) | Leaf

...

insertMany (Fork k v l r) xs = Fork k v (insertMany l $ filter (k) xs)
(insertMany r $ filter (k) xs)
insertMany Leaf   [] = Leaf
insertMany Leaf   ((k,v):xs) = insertMany (Fork k v Leaf Leaf) xs


Unfortunately it's not at all clear how to add balancing, other than
access-time mutation.

Stefan


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


Re: [Haskell-cafe] Re: I'm stuck in my thought experiment

2007-08-20 Thread Levi Stephen

Al Falloon wrote:



Maybe I am misunderstanding your requirements, but it seems to me that 
the simplest solution would be best in this case:


data Widget = BlogWidget [Article]
| TextWidget String
| MenuWiget Menu
| Rows Spacing [Widget]
| Columns Spacing [Widget]

You can also add a type parameter if you want to be able to carry around 
extra metadata about pages, or you could even parameterize the Article 
and Menu types if you want to be able to extend them separately or if 
you want to ensure your layout algorithms don't depend on widget 
contents by keeping their type abstract.




Thanks for pointing out a simple solution. Over thinking this is something
I'm worried about :)



This code seems to indicate that you want to be able to extend the 
widget types without changing this source file. This is a good goal, but 
it may not be worth the extra complexity.


Ideally, I'd like Widgets to be added through hs-plugins or similar. That
is a ideal goal though, not a necessity.



Also, this looks a lot like the Composite pattern from OO. A rule of 
thumb that I use is: if I would do this with inheritance in OO, I 
probably want a variant in FP. Since Composite depends on the 
inheritance of the composite object type, I would probably look to use a 
 single data type with multiple constructors for the different 
compisites like the Widget type above.


Interesting. I've been curious how OO concepts can map to FP, as most specs
(consider stuff like DOM) seem to be written with OO implementaitons in mind.


If I wanted to develop the widgets themselves separately from the 
layout, I would probably do something like this:


class Widget a where
render :: a - Html
bbox :: a - Size

type Layout = forall a. Widget a = Widget a
| Rows Spacing [Layout]
| Columns Spacing [Layout]
| Grid Spacing [[Layout]]

type Page = Page String Layout

renderLayout :: Layout - Html

renderPage :: Page - Html


I'm unsure this gives what I'm after. I'm trying to have layouts consist of 
Widgets (e.g., header images, common menu), and as pages also consist of Widgets 
it seems like they can be modelled using a common type/construct.






The issue becomes, given a parent page and the customized content for 
the child page,

what is the best way to insert the customized content at the right point?

Might a tree like structure be useful? But, how do you work out where 
in the tree
child content gets added? Store a traversal with each sub tree of 
child page content

that basically says 'insert here'?


This is probably a good use for a zipper (a kind of functional 
iterator). http://en.wikibooks.org/wiki/Haskell/Zippers that way you can 
pass around a value that means right here, and its clear where the 
substitution will happen.


I was wondering with zippers were appropriate, or if I just had them in mind
becuase I'd read so much about them lately :)


 So you want some sort of wildcard element that can be substituted in
 later? Maybe I am misunderstanding your requirement, but if thats the
 behavior you want, you should check out the term-level evaluators for
 lambda calculus for inspiration on substitution, but I expect your
 requirement may be simpler than that.

I'm thinking a BlankWidget or ReplacableWidget is a fairly simple option. They 
could be named for the case of multiple replacements, and have a method similar to


-- src   -   replacements- result
replaceWidgets :: Widget - [(String,Widget)] - Widget

which replaces all ReplacableWidgets in the source Widget with those specified.

Would you happen to have some links on the evaluators for lambda calculus you 
talk about? I'm not as familiar as I should be with lambda calculus




It might be simple to have a PlaceHolderWidget. Then insertions of the 
child page

content happens at each of those widgets.


This just gets trickier if I start considering multiple extension 
points for child
pages and what happens when the layout/parent page changes. This is 
why I'm

thinking I may be going along a bad path here.


Exactly. With multiple substitutions you get into issues of naming, so 
thats why looking at lambda calculus evaluators would be the right 
inspiration, but I think it may be more complicated than you need. The 
zipper approach might be easier.


I think I will try and investigate both approaches. I'm after the process here, 
rather than the end result


Thanks
Levi
lstephen.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] is there a way to patch the build-depends line of a cabal file without breaking backwards compatibility?

2007-08-20 Thread Thomas Schilling


On 20 aug 2007, at 20.58, Thomas Hartman wrote:



 Take a look at the Cabal.cabal file, how this is solved, atm.

where is this, how can I take a look at it?


http://darcs.haskell.org/cabal/Cabal.cabal

See below for a little more explaination.



 The next release of Cabal (and the current HEAD) supports   
conditionals


I couldn't install head, but since I'm running 6.7, do I already  
have it?




Yes, you already have it.  It should be in ghc/libraries/Cabal, or  
contrib/Cabal


[EMAIL PROTECTED]:~/installs/cabal-head/cabalrunghc Setup.lhs  
configure


Distribution/Simple/InstallDirs.hs:267:36:
Not in scope: `dropDrive'

[EMAIL PROTECTED]:~/installs/cabal-head/caballs -l `which ghc`
lrwxrwxrwx 1 root root 31 2007-08-20 11:08 /usr/local/bin/ghc - / 
usr/local/bin/ghc-6.7.20070816




See Neil's reply.



[EMAIL PROTECTED]:~/installs/cabal-head/cabalghc-pkg list | grep - 
i cabal

Cabal-1.1.7

  Please also note that this might not be the
 best way to use the new features;  as I suggested in another thread,
 simulating base-1.0 on systems with base-2.0 is probably best  
handled

 with a base.cabal file that imports base-2.0, old-time, etc. and re-
 exports all imported modules to get a virtual base-1.0.

I'm interested in seeing how this works, but I couldn't find that  
other thread.




There is no formal proposal, yet, and I think the note was in a  
recent thread on cabal-devel or libraries.  Therefore, I won't  
discuss it here.  I can tell you the current solution, though.


Where is the documentation for the new functionality in cabal head,  
or do you just have to read the source code for now?


Performing (in the Cabal directory) make doc should build the  
haddocks and the latest user's guide.  Performing make users-guide  
should only build the user's guide, but since that requires some  
tools which might be non-trivial to set up on some systems, I didn't  
recommend it.


So here's the relevant part of how Cabal.cabal does it:

  if flag(small_base) {
-- For ghc 6.2 you need to add 'unix' to Build-Depends:
Build-Depends: base, filepath, pretty, directory, old-time,  
process, containers

  } else {
Build-Depends: base, filepath
  }

Note, that the format changed to a sectioned format, and that it is  
quite likely that it will still change slightly before the release.   
Consult the Cabal user's guide or (probably easier) take a look at  
other .cabal files in the ghc tree.  It's quite straightforward,  
actually.


The interesting feature here is that unless overridden explicitly,  
the flag small_base will be assigned to a value appropriate for the  
system, thus, if you don't have any of the packages pretty,  
directory, etc, it will automatically be assigned to false. (I think  
it better should be base = 2.0, though.)


(Also, the comment can now be replaced by an actual test like: if impl 
(ghc =6.2) ..)


HTH
/ Thomas


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


[Haskell-cafe] #haskell irc channel reaches 400 users

2007-08-20 Thread Donald Bruce Stewart

A small announcement :)

5 1/2  years after its inception, under the guiding hand of Shae Erisson
(aka shapr), the #haskell IRC channel[1] on freenode has finally reached
400 users!

To chart the growth, we can note that the channel was founded 
in late 2001, and had slow growth till 2006, reaching 200 users in
January of that year. Since then growth in the user base has been far
more rapid, reaching 300 users in Dec 2006, and 400 users now, in August
2007.

This puts the channel at around the 13th largest community of the 5500
freenode channels. For comparision, a sample of the state of the other
language communities:

#php 485
#perl472
##c++457
##c  445
#python  430
#ruby-lang   420
 
   #haskell 411

#lisp246
##java   236
##javascript 226
#perl6   144
#scheme  139
#erlang  118
#lua 105
#ocaml58

You can see the growth of the channel over here: 
http://www.cse.unsw.edu.au/~dons/irc

If you've not dropped by the channel yet, feel free to come and chat,
and toss around some lambdas! :)

Cheers,
  Don

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


[Haskell-cafe] STM, IO and b-trees

2007-08-20 Thread Ben
for sake of argument, suppose an enterprising haskell newbie wanted to
code up concurrent b-trees (really b-link trees) in haskell.  if i am
understanding STM correctly, it will NOT help in any way with the
implementation, because of the IO-intensive nature of the algorithms?
so i will have to resort to the usual games with locks and latches?

(using

Ibrahim Jaluta, Seppo Sippu and Eljas Soisalon-Soininen. Concurrency
control and recovery for balanced B-link trees. The VLDB Journal,
Volume 14, Issue 2 (April 2005), Pages: 257 - 277, ISSN:1066-.

as a source for b-tree algorithms.)

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


Re: [Haskell-cafe] STM, IO and b-trees

2007-08-20 Thread Thomas Conway
On 8/21/07, Ben [EMAIL PROTECTED] wrote:
 for sake of argument, suppose an enterprising haskell newbie wanted to
 code up concurrent b-trees (really b-link trees) in haskell.  if i am
 understanding STM correctly, it will NOT help in any way with the
 implementation, because of the IO-intensive nature of the algorithms?
 so i will have to resort to the usual games with locks and latches?

I have produced exactly such an implementation in my day-job (so I
can't, at this stage, give you the code, I'm afraid), but I'll happily
give you some tips:

1. Investigate relaxed balance.

BTrees with relaxed balance enable you to break up operations into
much smaller transactions, which will reduce the amount of rerunning
on transactions (big transactions are more likely to contain
conflicts).

Also, getting all the edge cases right is hard with strict balance.
Especially in the presence of deletions. It is VASTLY simpler with
relaxed balance, though there are a few little tricks. If it was too
easy, it wouldn't be any fun (see 3, below). Hint: Although the
on-disk version doesn't need or want parent pointers, you might want
them for your in-memory version of pages.

2. Separate the IO from the BTree-stuff.

Conceptually keep a codeTVar (Map Address ByteString)/code. In the
transaction, use this to find pages. If the page is not there, throw
an exception containing the desired address. In a wrapper, catch the
exception, read the page, add it to the map as a separate transaction
then retry the original transaction. I say conceptually because
something like codeTArray Address (Maybe ByteString)/code, or
similar will yield much better concurrency. In general, you want to
push the TVars down as far as possible.

3. Have Fun

STM is very cool, so make sure you enjoy making it all hang together. :-)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Tying the knot with unknown keys

2007-08-20 Thread Bertram Felgenhauer
David Ritchie MacIver wrote:
 Essentially I have

 data FSM = State { transitions :: (Map Char FSM) }

 and

 transitions' :: Regexp - Map Char Regexp

 I want to lift this so that the Regexps become states of the finite state 
 machine (while making sure I set up a loop in the data structure). Tying 
 the knot is the traditional way of doing such things, but we couldn't 
 figure out a way to make it work without the set of keys known in advance 
 because of the strictness of Map in its keys (an association list was 
 suggested, and that would probably work, but it seemed a bit ugly and would 
 be fairly inefficient).

 In the end what I did was just work out the set of reachable regexps in 
 advance and use a standard tying the knot trick, but it felt vaguely 
 unsatisfactory (and does some repeat work which I felt should be 
 unneccessary). Anyone have a more elegant suggestion?

I have a solution that I like now, even though it involves quite a bit 
of code. Its core idea is very simple. The main ingredient is

 data RegexpTrie a

which is a data type that represents an infinite trie-like structure,
indexed by regular expressions. It comes with a lookup function,

 lookupRE :: RegexpTrie a - Regexp - a

with the obvious semantics. It also provides a function to populate
a trie,

 populateRE :: (Regexp - a) - RegexpTrie a

With these functions we can build a map of *all* regular expressions
to their corresponding FSM. This is where the knot-tying takes place:

 fsm :: RegexpTrie FSM
 fsm = populateRE (\re -
 State { transitions = Map.map (lookupRE fsm) (transitions' re) }

Finally, 'compile' becomes a trivial lookup,

 compile :: Regexp - FSM
 compile x = lookupRE fsm x

Detailed code can be found at http://hpaste.org/2341#a3 .

enjoy,

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