Re: [Haskell] Re: ANN: HDBC (Haskell Database Connectivity)

2006-01-07 Thread Chris Kuklewicz
Benjamin Franksen wrote:
> On Wednesday 04 January 2006 20:13, John Goerzen wrote:
> 
>>Well, yes and no.  It would be impossible to garbage collect (and
>>thus finalize) any object for which references to it still exist. 
>>Statement handles in HDBC maintain references to the database handle
>>pointers, either directly or indirectly, so I can't see how it is
>>possible for a database handle to be finalized before the statement
>>handle in this situation.
> 
> 
> Hi John,
> 
> I fear it /is/ possible. This is a very unfortunate situation and one I 
> had quite some difficulties to understand, when Simon Marlow explained 
> it to me.
> 
> The problem is that finalization of the statement handle might be 
> delayed indefinitely. The data dependencies between statement and 
> connection handle only ensures that whenever the statement handle is 
> alive, then too is the connection handle. But it does not say anything 
> about what happens in which order after /both/ are dead (garbage). As 
> soon as the connection handle to garbage, too, bothe handles can be 
> finalized in /any/ order.
> 
> As I pointed out before, this is a very bad thing, because it makes 
> finalizers a whole lot less useful than they could be if an order 
> between finalizations could be specified (directly or indirectly). The 
> arguments against such a solution are mostly: (1) it is difficult to 
> implement efficienty and (2) the programmer could accidentally cause 
> finalizer deadlocks by specifying circular dependencies.
> 
> Ben

This is also mentioned in the documentation:

http://www.haskell.org/ghc/docs/6.4.1/html/libraries/base/Foreign-ForeignPtr.html#v%3AtouchForeignPtr

> touchForeignPtr :: ForeignPtr a -> IO ()
> 
> This function ensures that the foreign object in question is alive at the 
> given place in the sequence of IO actions. In particular withForeignPtr does 
> a touchForeignPtr after it executes the user action.
> 
> Note that this function should not be used to express liveness dependencies 
> between ForeignPtrs. For example, if the finalizer for a ForeignPtr F1 calls 
> touchForeignPtr on a second ForeignPtr F2, then the only guarantee is that 
> the finalizer for F2 is never started before the finalizer for F1. They might 
> be started together if for example both F1 and F2 are otherwise unreachable, 
> and in that case the scheduler might end up running the finalizer for F2 
> first.
> 
> In general, it is not recommended to use finalizers on separate objects with 
> ordering constraints between them. To express the ordering robustly requires 
> explicit synchronisation using MVars between the finalizers, but even then 
> the runtime sometimes runs multiple finalizers sequentially in a single 
> thread (for performance reasons), so synchronisation between finalizers could 
> result in artificial deadlock. 


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


Re: [Haskell] License for haskell.org content

2006-01-09 Thread Chris Kuklewicz
I have appended the relevant conclusion

Ian Lynagh wrote:
> On Sun, Jan 08, 2006 at 09:31:16PM -0500, John Peterson wrote:
> 
>>I believe the scenario that the FDL addresses is that someone
>>(probably Paul Hudak!) "borrows" massive amounts of stuff from the wiki,
>>adds his own good stuff, and then publishes a nice book or something
>>without having to share his additional contribution.  Some people
>>would like to be sure that their contributions can't be exploited in
>>this manner.
> 
> 
> Why not use the GPL, then?
> 
> FWIW, the GFDL is considered non-free by Debian[1], so that would mean
> any documentation or anything derived from the wiki couldn't be packaged
> for Debian.
> 
> Apart from the issue of code itself on the wiki, that other people have
> already mentioned, presumably you'd also have licence fun if you try to
> take surrounding explanatory text to use as haddock docs etc.
> 
> 
> Thanks
> Ian
> 
> [1] http://people.debian.org/~srivasta/Position_Statement.xhtml
> http://home.twcny.rr.com/nerode/neroden/fdl.html
> 


==
Conclusion

It is not possible to borrow text from a GFDL'd manual and incorporate
it in any free software program whatsoever.  This is not a mere
license incompatibility.  It's not just that the GFDL is incompatible
with this or that free software license: it's that it is fundamentally
incompatible with any free software license whatsoever.  So if you
write a new program, and you have no commitments at all about what
license you want to use, saving only that it be a free license, you
cannot include GFDL'd text.

The GNU FDL, as it stands today, does not meet the Debian Free
Software Guidelines.  There are significant problems with the license,
as detailed above; and, as such, we cannot accept works licensed unde
the GNU FDL into our distribution.
==

Thus defaulting the FDL for all wiki content, including code, is a very bad 
idea.

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


Re: [Haskell] Simple IO Regions

2006-01-19 Thread Chris Kuklewicz
I tweaked the IORegions code using some other ideas from the thread.

The "IOM marks a" monad which wrapped (IO a) is now "IOQ marks m a"
which wraps "m a".  So it is a MonadTrans and if m is MonadIO then so is
"IOQ marks m".

qGetChar was just a demo, and has been replaced by liftH, liftH2, and
liftH3 which should cover all the System.IO hFoo functions.

But bracket does not know what MonadIO is, so the withFile* functions
are no as general as possible.

Eventually these could be stuck on the wiki.

-- 
Chris

> {-# OPTIONS -fglasgow-exts #-}

This is a tweaked version from oleg.  I think all the "should not
compile" tests still correctly create error messages when compiled.

>
> module IORegionsTest where
>
> import IORegions3 -- see below
> import System.IO
>
> test0 = withFile "/etc/motd" (const $ return True)

With IORegions3, liftH,liftH2,liftH3 are exported, and withFile*
functions.  This lets us promote every h* functions ourselves. A
fseparate sub-module, perhaps IORegions.IO, could have all these
trivial lifting already written and named:

> qGetChar q = liftH hGetChar q
>
>
> reader q = do
>c1 <- qGetChar q
>c2 <- qGetChar q
>return [c1,c2]
>
> test1 = withFile "/etc/motd" reader
> test1r = runIOQ test1 >>= print

Instead of handles, we have Qs -- marked handles. The are created by
the function withFile and used similar to regular handles. A special
IOQ monad is a newtype away from the regular IO. The phantom type
parameter of the IOQ monad maintains the marks of the regions.

*IORegionsTest> :t reader
reader :: (Monad (IOQ marks), IORegions.IN mark marks) =>
  Q mark -> IOQ marks [Char]

the type of the reader shows that it takes a marked handle and yields
a marked IO computation. The constraint IN assures that the
computation must be marked with the mark of the handle.

If we attempt to leak the handle:
*> test2 = withFile "/tmp/i.hs" (\q -> return q)

we get
Inferred type is less polymorphic than expected
  Quantified type variable `mark' escapes
In the second argument of `withFile', namely `(\ q -> return q)'

The following is OK: we perform the computation and return its result:

> test3 = withFile "/etc/motd" (\q ->  (qGetChar q))
>
> test3r = runIOQ test3 >>= print

If we attempt to return the unperformed computation itself:
*> test4 = withFile "/tmp/i.hs" (\q ->  return (qGetChar q))

we get
Could not deduce (IORegions.IN mark marks1)
  from the context (IORegions.IN mark marks)
  arising from use of `qGetChar' at IORegionsTest.h...

As we said earlier, more than one handle can be at play at the same
time:

> reader2 q1 q2 = do
>  c1 <- qGetChar q1
>  c2 <- qGetChar q2
>  return [c1,c2]
> test5 = withFile "/etc/motd" (\q1 -> 
>   withFile "/etc/motd" (\q2 -> reader2 q1 q2))
>
> test5r = runIOQ test5 >>= print

Incidentally, the inferred type of reader2 is

*IORegionsTest> :t reader2
reader2 :: (Monad (IOQ marks),
IORegions.IN mark1 marks,
IORegions.IN mark marks) =>
   Q mark -> Q mark1 -> IOQ marks [Char]

Obviously, the resulting computation is marked with the marks of both
argument handles.

With two handles, we can actually return a handle -- provided we
return an outermost handle from the innermost region (but not the
other way around). For example, the following is wrong

*> test6 = withFile "/etc/motd" 
*>  (\q2 -> 
*>   do
*>   q' <- withFile "/etc/motd" (\q -> return q)
*>   qGetChar q')


but the following is OK:

> test7 = withFile "/etc/motd" 
>  (\q2 -> 
>   do
>   q' <- withFile "/etc/motd" (\q -> return q2)
>   qGetChar q')
>
> test7r = runIOQ test7 >>= print

Ditto for the computation:

The following is the improper leakage and leads to a type error:

*> test8 = withFile "/etc/motd" 
*>  (\q2 -> 
*>   do
*>   a <- withFile "/etc/motd" (\q -> return (qGetChar q))
*>   a)

But the following is fine:

> test9 = withFile "/etc/motd" 
>  (\q2 -> 
>   do
>   a <- withFile "/etc/motd" (\q -> return (qGetChar q2))
>   a)
>
> test9r = runIOQ test9 >>= print

All the test runners:

> tests = [test1r,test3r,test5r,test7r,test9r]
>
> runTests = sequence tests
{-# OPTIONS -fglasgow-exts #-}
{- 
  Version 2006-01-19 by Chri

Re: [Haskell] Discrete event simulation

2006-01-26 Thread Chris Kuklewicz
I don't have an answer.  But I do have questions which may help.

Paul Johnson wrote:
> Hi, I'm going slowly nuts here.  Maybe someone can help me out.

You could also try the IRC channel #haskell on freenode.irc.net

> 
> I want to do some fairly straightforward discrete event simulation. 

But I do not know your terms, so I will ask you about them.

> Tasks do side effects, probably in the ST monad.  Every so often the
> current task calls "delay n" where n is a number of seconds. This puts
> the task back on a list of schedulable processes that is ordered by
> time, and then takes the head of the list and starts executing it.

So side effects means setting STRef's or ST(U)Arrays.

"delay n" means simulated seconds or wall clock seconds?

Also tasks are sounding like threads...Could you define event and task and
scheduler for us? How many events or tasks are there?

How does the scheduler interact with the events or tasks?

> Part of this will be some kind of synchronisation primitive.  I don't
> much care what it is, but somewhere I need a way to make a process wait
> until something happens rather than just a constant time.

Is a task is polling: calling "delay n" over and over again, checking for
something interesting each time?

If you are not in ST, then you can be in STM or IO and have a task in a thread
that will block waiting for a TMVar or an MVar (or a QSem), which represents
something interesting happening.  The forkIO threads are really cheap, and STM
is very cool if the optimistic assumption is valid.

> I think I want to use something like
> 
>   type Task r s a =  ContT r (ST s) a
> 
> But I can't see how to actually do it.  I've read All About Monads. 
> I've googled for anything to do with continuations and coroutines.  I'm
> stuck.  Can someone show me how to do it.

Now continuations and a scheduler sounds like the Zipper-base file server/OS:

http://lambda-the-ultimate.org/node/1036

That code uses partial continuations to manage tasks that talk to a scheduler.
The code is quite short and it knows more than I do.

> 
> Thanks,
> 
> Paul.
> 

Good Luck,

  Chris

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


Re: [Haskell] Re: compares :: Ord a => a -> a -> Ordering -> Ordering

2006-02-15 Thread Chris Kuklewicz
Christian Maeder wrote:
> Ben Rudiak-Gould wrote:
>> I just realized that the class Ord should have an additional method:
>>
>>   class Eq a => Ord a where
>> compares :: a -> a -> Ordering -> Ordering
>> compares x y d = case compare x y of { EQ -> d ; o -> o }
>> ...
> 
> How about:
> 
> instance (Ord a, Ord b, Ord c, Ord d) => Ord (a,b,c,d) where
> compare (a1,b1,c1,d1) (a2,b2,c2,d2) =
> compare ((a1,b1,c1),d1) ((a2,b2,c2),d2)
> 
> or another tuple nesting)
> 
> Christian

That works, but...

Constructing the new tuples is usually more heap allocation, and these short
lived data items can make the garbage collection load higher.

The `mappend` method avoids this pitfall.
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Compilation of big, computed tables

2006-02-22 Thread Chris Kuklewicz
Stefan Karrmann wrote:
> Dear all,
> 
> can ghc compile huge tables into efficient code if they are constant at
> compile time?
> 
> Two examples may clearify the question:
> 
> big1 :: UArray Int Char
> big1 = array (0,1000) $! map (\i -> (i,toEnum i)) [0..1000]
> 
> big2 = sum [0..1]::Int -- == 50005000 == n*(n+1)/2 where n = 1
> 

GHC does not compute such values are compile time because
*) The computation may not finish in reasonable time (infinite/not halting)
*) The computation may generate a run-time error and crash the compilation
(divide by zero, pattern march failure, etc.)
*) Haskell is supposed to be lazy, things are computed when needed, not before

The big1 UArray is unboxed which prevents laziness, so big1 will be fully
computed the first time any of the values are referenced.

There is a way around this:

I have not needed to use it, but template haskell can compute things at compile
time. ( http://haskell.org/hawiki/TemplateHaskell and
http://haskell.org/hawiki/TemplateHaskellTutorial are good links)

[ Template haskell could even be abused to interactively allow you to
interactively type in a URL from which to download code to insert into the 
file. ]
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] how to write an interactive program ? gui library to use ?

2006-02-25 Thread Chris Kuklewicz
Dean Herington wrote:
> At 7:31 PM +0100 2/24/06, minh thu wrote:
>> Hi all,
>>
>> 1/
>> I'd like to know how can I implement an interactive program (an
>> editor) in haskell where some "things" have to be updated.
>> The "things" can be text in a word processor, or a pixel array in a 2d
>> graphics editor, and so on.
>> Have I to pass the state (the "things") explicitely in the arguments
>> of the main loop (a recursive function) ?
>> Sorry if it's stupid...
> 
> No, it's not a stupid question at all...
> 
> Essentially, the answer is "yes", the state needs to be passed around
> (neglecting hackery to simulate global variables that is better
> avoided).  However, this can be made convenient by using a monad. You
> define a monad which is based on IO and carries your state (something
> like StateT YourState IO a; see
> http://www.haskell.org/ghc/docs/latest/html/libraries/mtl/Control-Monad-State.html).
> 

If the things need to be more explicitly mutable you can
*) Create a bunch of IORefs (or MVar for thread safety)
*) Put them into some data structure (your own or perhaps tuples)
*) Use a ReaderT from Control.Monad.Reader, ReaderT YourData IO a

Then you can
*) lookup the IORef you need with using "asks"
*) read/write/update that mutable data
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] debuggers

2006-03-11 Thread Chris Kuklewicz
Bulat Ziganshin wrote:
> Hello Ernesto,
> 
> Saturday, March 11, 2006, 7:36:21 PM, you wrote:
> 
> EDS> Some body know another debugger?
> 
> printf :)
> 

Debug.Trace, such as (trace (show foo) a)
and
System.IO.Unsafe, such as (unsafePerformIO ( print foo >> return a))

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


Re: [Haskell] Understanding the LGPL

2006-05-30 Thread Chris Kuklewicz
Brian Hulley wrote:
> Malcolm Wallace wrote:
>> "Brian Hulley" <[EMAIL PROTECTED]> wrote:

>> If what you really mean by "open source" is the ability to take code
>> and into make non-open modifications to it (as BSD permits), then
>> that is far more demanding than what most people mean by the term.
> 
> Well the problem with LGPL afaiu is that if you statically link your
> code to it your are required to make your own source code available.
> 

That is untrue.  You never have to reveal your source code when your code uses
an LGPL libary.  If you modify the LGPL library source then you do have to
release the modified library source under the LGPL -- but this does not mean you
need to release the code that uses your modified library.

http://www.gnu.org/licenses/lgpl.html

"When a program is linked with a library, whether statically or using a shared
library, the combination of the two is legally speaking a combined work, a
derivative of the original library. The ordinary General Public License
therefore permits such linking only if the entire combination fits its criteria
of freedom. The Lesser General Public License permits more lax criteria for
linking other code with the library."

If you dynamically link then there is little to do, as the users can easily
switch to a modified library.  If you statically link you must supply object
code (not source code):

"If you link other code with the library, you must provide complete object files
to the recipients, so that they can relink them with the library after making
changes to the library and recompiling it. And you must show them these terms so
they know their rights."

So there is a difference in static vs dynamic linking -- with static linking you
have to make (at least) your object code available.

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


Re: [Haskell] GADTs are not nice to me ;-)

2006-07-03 Thread Chris Kuklewicz

Wolfgang Jeltsch wrote:

Hello everybody,

I wanted to do something like that:

data Pair :: (* -> *) -> * where
Pair :: a b -> b -> Pair a

data Sel :: * -> * where
A :: Sel Bool
B :: Sel Integer

showSnd :: Pair Sel -> String
showSnd (Pair A bool)
= show bool
showSnd (Pair B integer)
= show integer

However, GHC 6.4.1 with -fglasgow-exts complains in the second last and last 
line that there is no instance for (Show b).  I don't really understand this 
since in my opinion it is clear that bool :: Bool and integer :: Integer and 
that therefore bool and integer are showable.  What's the problem with my 
code?


Best wishes,
Wolfgang


I cut and pasted your code into ghci-6.4.2 with -fglasgow-exts and there was no 
error.  And I can (print (showSnd (Pair A True)) and (print (showSnd (Pair B 
8))) but when I try to compile it with ghc-6.4.2 it complains about the Show 
instance.  I find this deeply wierd, and it seems like a bug.


Changing the definition of Pair made it compile and run with ghc:

> data Pair :: (* -> *) -> * where
>   Pair :: (Show b) => a b -> b -> Pair a

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


Re: [Haskell] GADTs are not nice to me ;-)

2006-07-04 Thread Chris Kuklewicz

Wolfgang Jeltsch wrote:
> Am Montag, 3. Juli 2006 18:46 schrieb Simon Peyton-Jones:
>> Thanks.  Can you confirm that it's fixed in 6.4.2?  And if so, can you
>> record that too?  No point in us haring after fixed bugs!
>>
>> S
>
> As Chris Kuklewicz pointed out, this bug doesn't seem to be completely fixed
> in 6.4.2.  Currently, I neither can confirm this nor can I disprove it since
> at the moment there seem to be no Debian packages for 6.4.2 which I could
> install and I don't have the time to install GHC from source.
>
> Best wishes,
> Wolfgang

I am using ghc-6.4.2 from darwinports on OS X 10.4.7

Can I help confirm / test this with something test cases?

The older messages were:

> Wolfgang Jeltsch wrote:
>> Hello everybody,
>>
>> I wanted to do something like that:
>>
>> data Pair :: (* -> *) -> * where
>> Pair :: a b -> b -> Pair a
>>
>> data Sel :: * -> * where
>> A :: Sel Bool
>> B :: Sel Integer
>>
>> showSnd :: Pair Sel -> String
>> showSnd (Pair A bool)
>> = show bool
>> showSnd (Pair B integer)
>> = show integer
>>
>> However, GHC 6.4.1 with -fglasgow-exts complains in the second last and last 
line that there is no instance for (Show b).  I don't really understand this 
since in my opinion it is clear that bool :: Bool and integer :: Integer and 
that therefore bool and integer are showable.  What's the problem with my code?

>>
>> Best wishes,
>> Wolfgang
>
> I cut and pasted your code into ghci-6.4.2 with -fglasgow-exts and there was 
no error.  And I can (print (showSnd (Pair A True)) and (print (showSnd (Pair B 
8))) but when I try to compile it with ghc-6.4.2 it complains about the Show 
instance.  I find this deeply wierd, and it seems like a bug.

>
> Changing the definition of Pair made it compile and run with ghc:
>
>> data Pair :: (* -> *) -> * where
>>   Pair :: (Show b) => a b -> b -> Pair a

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


Re: [Haskell] Can someone provide a summary of best Sudoku solver times?

2006-07-09 Thread Chris Kuklewicz

Murray Gross wrote:
> I'd greatly appreciate it if someone could provide a summary of the best
> times recently posted for Haskell Sudoku solvers so I can compare them
> with some experimental code I have.
>
> Since the Sudoku puzzle is incidental to the purpose of my code, I'd just
> like to find out whether or not my current code is working in the
> neighborhood of "the good stuff." Right now, easy puzzles go under in 4 or
> 5 seconds, evil puzzles range from about 12 seconds to just under 2
> minutes on a 650 MHz Duron.
>
> Thanks,
>
> Murray Gross
>
>

I improved the speed and strength of my solver and it finishes the 36638 puzzles 
of http://www.csse.uwa.edu.au/~gordon/sudoku17 in 3885 seconds.  It can solve 
all but 164 without guessing, and averages greater 9 puzzles per second on a 
1.33 GHz PPC Mac OS X laptop using ghc-6.4.2


Most of those puzzles (about 91.5%) are particularly simple and go especially 
quickly.  The next 8.1% of the puzzles use more expensive deductive methods, and 
the remaining 0.4% do depth first guessing.


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


Re: [Haskell] Can someone provide a summary of best Sudoku solver times?

2006-07-10 Thread Chris Kuklewicz

Taral wrote:

On 7/9/06, Chris Kuklewicz <[EMAIL PROTECTED]> wrote:
I improved the speed and strength of my solver and it finishes the 
36638 puzzles
of http://www.csse.uwa.edu.au/~gordon/sudoku17 in 3885 seconds.  It 
can solve
all but 164 without guessing, and averages greater 9 puzzles per 
second on a

1.33 GHz PPC Mac OS X laptop using ghc-6.4.2


Is this the DLX solver on the wiki?

Not quite.  This is an optimized, bug-fixed, and more powerful solver.  
I will update the wiki version soon.


--
Chris


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


Re: [Haskell] Can someone provide a summary of best Sudoku solver times?

2006-07-11 Thread Chris Kuklewicz

Murray Gross wrote:

I'd greatly appreciate it if someone could provide a summary of the best
times recently posted for Haskell Sudoku solvers so I can compare them
with some experimental code I have. 


Since the Sudoku puzzle is incidental to the purpose of my code, I'd just
like to find out whether or not my current code is working in the
neighborhood of "the good stuff." Right now, easy puzzles go under in 4 or
5 seconds, evil puzzles range from about 12 seconds to just under 2
minutes on a 650 MHz Duron. 

Thanks, 


Murray Gross



I have put my deductive solver on the wiki:

http://haskell.org/haskellwiki/Sudoku#Very_Smart.2C_with_only_a_little_guessing

source code:

http://evenmere.org/~chrisk/chris-sudoku-deduce.tar.gz

--
Chris

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


[Haskell] ANN: TextRegexLazy 0.44

2006-07-12 Thread Chris Kuklewicz

TextRegexLazy: The Text.Regex.Lazy replacement and enhancement for Text.Regex

New Version: 0.44
Where: http://sourceforge.net/projects/lazy-regex

Changes from 0.33 to 0.44

* Cabal
* Compile with -Wall -Werror
* Change DFAEngineFPS from Data.FastPackedString to Data.ByteString
  (still fairly untested)

This was my first time packaging with cabal, and I am hoping it works for you.
The tests have been cleaned up and now Cabal can run them.
The change from FPS to ByteString was trivial.

Question 1: What more would people want from a Regex engine for Data.ByteString?

Question 2: Is there interest in getting this into an official release of the 
base libraries?  The Compat module could at least replace or sit alongside the 
performance sink of the current Text.Regex code.


--
Chris

"I define UNIX as 30 definitions of regular expressions living under one roof."
   * Donald Knuth: Chapter 33 of the book Digital Typography, p. 649.
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


[Haskell] Re: ANN: TextRegexLazy 0.44

2006-07-13 Thread Chris Kuklewicz

Bulat Ziganshin wrote:

Hello Chris,

Thursday, July 13, 2006, 1:03:19 AM, you wrote:


This was my first time packaging with cabal, and I am hoping it works for you.


are you included Makefile? this makes building & installation somewhat
simpler for a user


Yes, but the makefile is used just to compile Setup.hs to ./setup and tell the 
user to run that instead.



Question 2: Is there interest in getting this into an official release of the
base libraries?  The Compat module could at least replace or sit alongside the
performance sink of the current Text.Regex code.


i'm 120% want to see ByteString, regular expressions matching for
String and ByteString, and JRegex (=~ operator implementation) to be
included in GHC 6.6


That typeclass interface is very handy, BUT it expects the thing being matched 
against is a list of something.  This prevents making ByteString an instance of 
RegexLike.


The answer will be to alter the type class to not make such an assumption. 
Luckily John Meacham put JRegex under the 3 clause BSD, so I will

  * Make a modified version of the type classes
  * Make Text.Regex.Lazy an instance of these type classes
  * Port JRegex to be instances of these type classes (links to PCRE!)
Then I or someone else can
  * Implement an efficient instance of Bytestring being handled by PCRE.

I expect step zero will be "Make a darcs repository" and step (-1) will be 
"Learn how to make a remotely accessible darcs repository"


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


[Haskell] Re: ANN: TextRegexLazy 0.44

2006-07-14 Thread Chris Kuklewicz

Bulat Ziganshin wrote:

Hello Chris,

Thursday, July 13, 2006, 12:17:30 PM, you wrote:


Question 2: Is there interest in getting this into an official release of the
base libraries?  The Compat module could at least replace or sit alongside the
performance sink of the current Text.Regex code.

i'm 120% want to see ByteString, regular expressions matching for
String and ByteString, and JRegex (=~ operator implementation) to be
included in GHC 6.6



That typeclass interface is very handy, BUT it expects the thing being matched
against is a list of something.  This prevents making ByteString an instance of
RegexLike.



The answer will be to alter the type class to not make such an assumption.
Luckily John Meacham put JRegex under the 3 clause BSD, so I will
   * Make a modified version of the type classes
   * Make Text.Regex.Lazy an instance of these type classes
   * Port JRegex to be instances of these type classes (links to PCRE!)
Then I or someone else can
   * Implement an efficient instance of Bytestring being handled by PCRE.


regexps support for ByteStrings already exists:



btw, what will be really useful now, imho, is the interface to
Text.Regex. how about working on it as next stage?


This is already done actually, here:
http://www.cse.unsw.edu.au/~dons/code/lambdabot/Lib/Regex.hsc
http://www.cse.unsw.edu.au/~dons/code/hmp3/Regex.hsc



Thanks, I'll go take a look at that.  I have pcre + JRegex installed now. And I 
have a remote darcs repository with my current version imported. (URL coming 
after I am sure it won't get re-organized).




well, i'm just dumb user telling what i want to see in GHC 6.6:

* regexp matching for Strings and ByteStrings
* perl-like syntax for doing it
* ability to select regexp engine for each matching operation and
using of most efficient ones (Lazy for String, posix or pcre (?) for
ByteString) by default

i also know that Simon Marlow want to see JRegex(-like) engine
included in 6.6 (see http://hackage.haskell.org/trac/ghc/ticket/710 )

what you mentioned is just implementation details for me, the dumb user :)


As a user, the JRegex API can also only support a single Regex type and a single 
backend.  But it would be really handy to be able to use different types of 
regular expressions.  Mainly there are going to be different regex syntax 
possibilities:


  * Old Text.Regex syntax, also emulated by Text.Regex.Lazy.Compat
  * The "Full" syntax of Text.Regex.Lazy (close to Extended regex)
  * regex.h syntax (perhaps Basic as well as Extended)
  * pcre.h syntax

All of these might conceivably come in [Word8] and [Char] sources.

The backend will vary: at least because we will want both a Lazy version and a 
hand-off to pcre library version (if installed) or regex library (more likely to 
be installed).


And the plan is to generalize the target to be either [Char] or ByteString.

New Question: What do people think is the best way to use data/newtype/class to 
allow for

  1) Different regex syntax as different types
  2) Different target [Char] or ByteString
  3) Different engine in the back end.

My first thought is that the type of the regex encodes both which syntax is in 
use and which back-end will be used.  Something like


 "Hello" =~ (pcre "el+")

would use PCRE syntax and pcre library backend against the [Char]. And

 (pack "Hello") =~ (compatRE "el+")

Would use the old Text.Regex syntax and my lazy backend against the ByteString 
produced by pack.


Other answers?

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


Re: [Haskell] Re: ANN: TextRegexLazy 0.44

2006-07-24 Thread Chris Kuklewicz

John Meacham wrote:
> On Fri, Jul 14, 2006 at 05:05:50PM +0100, Chris Kuklewicz wrote:
>> As a user, the JRegex API can also only support a single Regex type and a
>> single backend.  But it would be really handy to be able to use different
>> types of regular expressions.  Mainly there are going to be different regex
>> syntax possibilities:
>
> This isn't true, the API is a class, you can create as many instances as
> you like for it. In fact, it comes with at least 2 back ends, and at
> least a couple different instances for the regex syntax. It was
> specifically designed as a framework for many regular expression
> backends to be used via a common and useful interface.
>
> John
>

JRegex does require the source too be a list [x]:

> class RegexContext x a where
> (=~) :: RegexLike r x => [x] -> r -> a
> (=~~) :: (Monad m, RegexLike r x) => [x] -> r -> m a
>
> class RegexLike r a | r -> a where
> matchTest :: r -> [a] -> Bool
> matchCount :: r -> [a] -> Int
> matchAll  :: r -> [a] -> [(Array Int (Int,Int))]
> matchOnce :: r -> [a] -> Bool -> Maybe (Array Int (Int,Int))

The List requirement precludes a ByteString instance.  The functional dependency 
"r->a" also prevents mixing different backends with different data source types.


The Bool parameter to matchOnce is there so matchAll can be implemented in terms 
of matchOnce, exploiting the fact that the source data type is a list.  (Though 
this is not very optimal compared to a specialized matchAll).


I am done rewriting the Posix regex and PCRE code with both String and 
ByteString as instances.  The latest type classes (from today) look like:


> type MatchArray = Array Int (Int,Int) -- (starting index,length)
>
> class (RegexOptions regex compOpt execOpt) => RegexMaker regex source where
>   makeRegex :: source -> regex
>   makeRegexOpts :: compOpt -> execOpt -> source -> regex
>
> class RegexLike regex source where
>   matchAll :: regex -> source -> [MatchArray]
>   matchCount :: regex -> source -> Int
>   matchOnce :: regex -> source -> Maybe MatchArray
>   matchTest :: regex -> source -> Bool
>   matchTest regex source = isJust (matchOnce r s)
>   matchCount regex source = length (matchAll r s)

I have omitted the RegexOptions class for space (  The job of the "Bool" to 
matchOnce is subsumed by the more general execOpt handling ).  Clearly I have 
taken the names and most of the types from JRegex.  I don't have the cool 
polymorphic RegexContext yet, but that is the next step.


Once the code stabilizes at all, I will post a link to the development darcs 
address.


The flexibility of source data type and backend is provided by making 
WrapPosix.hsc and WrapPRCE.hsc modules that expect a source type of 
CString/CStringLen and are comprehensive enough so that the four files 
(Byte)?String(Posix|PCRE) are just .hs files (no -cpp needed) instead of a .hsc 
files.  And these four use optimized routines for match(All|Count|Once|Test) 
instead of using either of the defaults.


The next backend to make instances for will be my "Text.Regex.Lazy" one based on 
Parsec.  Then I will have 3 backends and two data source types, making 6 
combinations.  For example: I can compile a String regex as a PCRE and match 
that against a ByteString and against a String.  The type of the regex source 
and the type of the data are separate.  And I can make a new Regex from an old 
one with different execution options.


--
Chris

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


[Haskell] ANN: TextRegexLazy-0.56, (=~) and (=~~) are here

2006-08-02 Thread Chris Kuklewicz

Announcing: TextRegexLazy version 0.56
Where: Tarball from http://sourceforge.net/projects/lazy-regex
   darcs get --partial [--tag=0.56] http://evenmere.org/~chrisk/trl/stable/
License : BSD, except for DFAEngine.hs which is LGPL (derived from CTK light)

Development/unstable version is at:
   darcs get [--partial] http://evenmere.org/~chrisk/trl/devel/

This is the version that has eaten John Meacham's JRegex library and survived to 
become strong.  Thanks John!


It now compiles against the posix regexp provided by the c library and the pcre 
library, in addition to the "full lazy" and the "DFA" backends.


All 4 backends can accept regular expressions given as String and as ByteString.

All 4 backends can run regular expressions against String and ByteString.

In particular, the PosixRE and PCRE can run very efficiently against ByteString. 
(Though the input for the PosixRE needs to end in a \NUL character for efficiency).


So there are 4*2*2 = 16 ways to use to provide input to this library.  And the 
RegexContext class has at least 11 instances that both (=~) and (=~~) can 
target.  So that is 4*2*2*11*2 = 352 things you can do with this library!  Get 
your copy today!


To run with cabal before 1.1.4 you will need to comment out the 
"Extra-Source-Files:" line in the TextRegexLazy.cabal file.


The Example.hs file:


{-# OPTIONS_GHC -fglasgow-exts #-}
import Text.Regex.Lazy
import Text.Regex.Full((=~),(=~~)) -- or DFA or PCRE or PosixRE

main = let b :: Bool
   b = ("abaca" =~ "(.)a")
   c :: [MatchArray]
   c = ("abaca" =~ "(.)a")
   d :: Maybe (String,String,String,[String])
   d = ("abaca" =~~ "(.)a")
   in do print b
 print c
 print d


This produces:


True
[array (0,1) [(0,(1,2)),(1,(1,1))],array (0,1) [(0,(3,2)),(1,(3,1))]]
Just ("a","ba","ca",["b"])


You can also use makeRegex and makeRegexOpts to compile and save a regular 
expression which will be used multiple times.  Each of the 4 backends has a 
separate "Regex" data type with its own option types.


For low level access, the WrapPCRE and WrapPosix modules expose a typesafe layer 
around the c libraries.  You can query the "getVersion :: Maybe String" to see 
if the have been compiled into the library.


It may be possible to use WrapPCRE and the UTF8 option flags to do unicode regex 
matching with PCRE. ( The Full and DFA backends use the Haskell unicode Char 
already ).


Adding new types to String/ByteString is a matter of adding instances to the 
existing classes.


Feedback and comments of any length is welcome.

--
Chris Kuklewicz
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


[Haskell] Re: [Haskell-cafe] ANN: TextRegexLazy-0.56, (=~) and (=~~) are here

2006-08-02 Thread Chris Kuklewicz

Ooops.

I just patched the efficiency of ByteStringPCRE to agree with the original 
announcement.


Use
darcs get --partial http://evenmere.org/~chrisk/trl/stable/
to get the fixed version.

A new 0.57 tarball will go to sourceforge soon.

Chris Kuklewicz wrote:

Announcing: TextRegexLazy version 0.56
Where: Tarball from http://sourceforge.net/projects/lazy-regex
   darcs get --partial [--tag=0.56] 
http://evenmere.org/~chrisk/trl/stable/
License : BSD, except for DFAEngine.hs which is LGPL (derived from CTK 
light)


Development/unstable version is at:
   darcs get [--partial] http://evenmere.org/~chrisk/trl/devel/

This is the version that has eaten John Meacham's JRegex library and 
survived to become strong.  Thanks John!


It now compiles against the posix regexp provided by the c library and 
the pcre library, in addition to the "full lazy" and the "DFA" backends.


All 4 backends can accept regular expressions given as String and as 
ByteString.


All 4 backends can run regular expressions against String and ByteString.

In particular, the PosixRE and PCRE can run very efficiently against 
ByteString. (Though the input for the PosixRE needs to end in a \NUL 
character for efficiency).


So there are 4*2*2 = 16 ways to use to provide input to this library.  
And the RegexContext class has at least 11 instances that both (=~) and 
(=~~) can target.  So that is 4*2*2*11*2 = 352 things you can do with 
this library!  Get your copy today!


To run with cabal before 1.1.4 you will need to comment out the 
"Extra-Source-Files:" line in the TextRegexLazy.cabal file.


The Example.hs file:


{-# OPTIONS_GHC -fglasgow-exts #-}
import Text.Regex.Lazy
import Text.Regex.Full((=~),(=~~)) -- or DFA or PCRE or PosixRE

main = let b :: Bool
   b = ("abaca" =~ "(.)a")
   c :: [MatchArray]
   c = ("abaca" =~ "(.)a")
   d :: Maybe (String,String,String,[String])
   d = ("abaca" =~~ "(.)a")
   in do print b
 print c
 print d


This produces:


True
[array (0,1) [(0,(1,2)),(1,(1,1))],array (0,1) [(0,(3,2)),(1,(3,1))]]
Just ("a","ba","ca",["b"])


You can also use makeRegex and makeRegexOpts to compile and save a 
regular expression which will be used multiple times.  Each of the 4 
backends has a separate "Regex" data type with its own option types.


For low level access, the WrapPCRE and WrapPosix modules expose a 
typesafe layer around the c libraries.  You can query the "getVersion :: 
Maybe String" to see if the have been compiled into the library.


It may be possible to use WrapPCRE and the UTF8 option flags to do 
unicode regex matching with PCRE. ( The Full and DFA backends use the 
Haskell unicode Char already ).


Adding new types to String/ByteString is a matter of adding instances to 
the existing classes.


Feedback and comments of any length is welcome.



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


[Haskell] Re: [Haskell-cafe] ANN: TextRegexLazy-0.56, (=~) and (=~~) are here

2006-08-02 Thread Chris Kuklewicz

Brian Hulley wrote:

Chris Kuklewicz wrote:

Announcing: TextRegexLazy version 0.56
Where: Tarball from http://sourceforge.net/projects/lazy-regex
   darcs get --partial http://evenmere.org/~chrisk/trl/stable/
License : BSD, except for


Great! - Thanks for all your hard work in making this available to 
everyone!



DFAEngine.hs which is LGPL (derived from CTK light)


I sense some possible problems coming...


I wrote that ominous line, so I would have to agree.



[in another post]

Bulat Ziganshin wrote:

Hello Chris,

Wednesday, August 2, 2006, 3:16:58 PM, you wrote:


Announcing: TextRegexLazy version 0.56


your feature list is really strong! it will be great now to make it
a part of GHC standard distribution


Does the LGPL license for DFAEngine.hs use the static linking exception 
or not?

  [... snip ...]


I am fine because I have only released my derivative modules as source.

If we want to include it in GHC, then the simplest thing to do is ask the 
original author, Manuel M T Chakravarty, to allow us to re-license this derived 
work as BSD3 compatible. ( http://www.cse.unsw.edu.au/~chak/ctk/ )  It is only 
derived from part of the Lexer of CTKLight, and has been streamlined to be less 
flexible than it used to be in order to be more suitable as a regex engine.  And 
if he does not want use to use it in GHC, then we live with 3 engines instead of 4.


On a more positive note, I note that the European Parliament voted (last 
year iirc) that software patents are just a lot of rubbish and are null 
and void in Europe so at least that's one tender bud of common sense 
that's managed to burst through the asphalt.


Regards, Brian.



Yes, the European Parliament finally beat back the corrupt bureaucrats that were 
trying to change the patent rules.  But the forces of plutocracy will never give 
up; it will be the same fight every year or two.


--
Chris

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


[Haskell] Foreign.Marshal.Alloc questions

2006-08-09 Thread Chris Kuklewicz
For the allocation functions in Foreign.Marshall.Alloc, are the function 
contracts that return new pointers such that the pointers are never nullPtr, or 
is it prudent to always check the new ptr?


I can see on GHC than allocaBytes uses newPinnedByteArray# but I have not 
tracked down the source file for that to read it.


--
Chris Kuklewicz
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Monad transformer question

2006-10-25 Thread Chris Kuklewicz
Quick comments below

Cyril Schmidt wrote:
> Working on a Monte-Carlo simulation where I have to
> calculate the values of a certain function on the given set of inputs,
> I noticed that some of the input variables change for every iteration,
> while others do not.
> 
> To give a simple example, let's suppose I have a function
> 
> f a1 a2 p = a1*a2 + p
> 
> and I have to get its values for
> [ (a1,a2,p) | a1 <- [0.1,0.2], a2 <- [0.1,0.2], p <- [0..9] ]
> 
> For efficiency, I want to pre-calculate (a1*a2) for each pair of a1 and a2,
> and then calculate f for each p.
> 
> (The real function is far more complicated, but the idea is the same:
> pre-calculate all that depends on seldom-changing variables, and then run
> the rest of the iterations using the pre-calculated value).
> 
> I built my function f as a Reader monad because my real f has many
> input parameters, so it is handy to have them packed in the Reader's
> environment.
> There are two Readers, in fact: the first environment contains the seldom-
> -changing variables, the second contains the variable that changes often.
> 
> My code looked as follows.
> 
>> {-# OPTIONS -fno-monomorphism-restriction #-}
>> module Main where
>> import Control.Monad.Reader
> 
> The variable that changes most often:
> 
>> data Inner = Inner { p1 :: Double }
> 
> The variables that change seldom
> 
>> data Outer = Outer { a1 :: Double,
>> a2 :: Double }
> 
> Function precalc pre-calculates (a1*a2)
> 
>> precalc = do
>>a1 <- asks a1
>>a2 <- asks a2
>>let r = {-# SCC "r" #-} a1*a2
>>return r

'precalc is of type Reader Outer Double

> 
> Function f in monadic form:
> 
>> f :: Reader Outer (Reader Inner Double)

Here 'f' is a monadic computation of
instance Monad (Reader Outer) ...
that returns a value of type (Reader Inner Double)

>> f = do
>>r <- precalc

This acts as a closure to cache the 'precalc' computation value of Double

>>return $ do { p1 <- asks p1
>>; let s = {-# SCC "s" #-} r+p1
>>; return s }
> 
> Function runf runs f over all values of p:
> 
>> runf (a1,a2) = do
>>let reader  = runReader f $ Outer a1 a2

Here 'reader' is the cached result of running 'f' and is a (Reader Inner 
Double).

>>results = map (runReader reader) [ Inner { p1 = x } | x <- [0..9] ]
>>putStrLn $ "a1 = "++show a1++", a2= "++show a2++", results = "
>>   ++show results
> 
> The main function
> 
>> main = mapM_ runf [(a1,a2) | a1 <- [0.1,0.2], a2 <- [0.1,0.2]]
> 
> This all works fine; the profiler shows that the (a1*a2) calculation is
> performed
> exactly 4 times, while addition, just as expected, 40 times.
> 
> I noticed that f
> f :: Reader Outer (Reader Inner Double)
> can be implemented using monad transformer:
> f' :: ReaderT Outer (Reader Inner) Double
> 
> The only difference in the implementation is that f' uses lift instead of
> return:
> 
>> f' :: ReaderT Outer (Reader Inner) Double

f' is a ReaderT with is a Monad instance via
instance (...) =>  Monad (ReaderT Outer (Reader Inner)) Double ...
So f' is a Monad that computes a value of type Double.

>> f' = do
>>r <- precalc
>>lift   $ do { p1 <- asks p1
>>; let s = {-# SCC "s" #-} r+p1
>>; return s }
>>
>> runf' (a1,a2) = do
>>let reader  = runReaderT f' $ Outer a1 a2

This forms the same (Reader Inner Double) type for 'reader' as before, but not
by computing any part of f'.  It just packages f' and (Outer a1 a2).  It turns
f' into a different Monad that computes a value of type Double and calls it
'reader'.

>>results = map (runReader reader) [ Inner { p1 = x } | x <- [0..9] ]
>>putStrLn $ "a1 = "++show a1++", a2= "++show a2++", results = "
>>   ++show results
> 
> 
> However similar they look, f and f' have very different behaviour (their
> results are the same, of course).
> 
> When I use runf' instead of runf, the profiler shows that precalc is
> invoked 40 times,
> which means that all the benefits of pre-calculating (a1*a2) are gone. (In
> the real application, I pre-calculate a much more complicated and
> expensive expression, that's why it matters).
> 
> I am curious why this happens. As far as I can see, the lift function of
> ReaderT is the same as return of Reader, and the >>= in Reader and ReaderT
> are pretty similar to each other, so why is the behaviour different?
> 
> This is a question of a purely theoretical significance for me; it does
> not hinder my work in any way. Still, I would greatly appreciate any
> ideas.
> By the way, I am using GHC 6.4.2 on Windows.
> 
> Kind regards,
> 
> Cyril
> 
> ___
> Haskell mailing list
> Haskell@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell

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


Re: [Haskell] base libraries

2006-11-23 Thread Chris Kuklewicz
This is a small reply to clarify the regular expression situation:

Bulat Ziganshin wrote:
> Hello libraries,
> 
> after analyzing the situation, i concluded that source of problem, at
> least partially, is GHC HQ's policy of packaging libraries with GHC.
> The list of such libraries is *closed* and odd at first look. why, for
> example, it includes 2 of 4 regexp libs? at last end, we can learn
> that this is the list of libs required to build ghc itself!

Some of the other regex-* libraries are interfaces to c-library backends (pcre
and tre) and it is not GHC's place to come with copies of those libraries.  But
GHC used regex internally, so it must come with at least a single backend.

> [...snip...]
> 
> and while we are here - splitting of Base library should be very easy
> task. its ghc version specific part is in GHC.* modules. these modules
> should be moved into the new Core library. plus a few modules from
> Data.* or System.* hierarchy they imports. plus a few modules imported
> by Hugs/NHC Prelude. the rest of Base library should be pretty portable, at
> least between various GHC versions.
> 
> and independent on this work, we can always look into moving pieces of
> Base into independent libs. as a rule of thumb, everything not used in
> Base lib may be moved outside of it. of course, these new libs should
> be included in base libs set

The regex-* modules that are installed with GHC are not in the "base" package.
They are in "regex-base" and "regex-posix" and "regex-compat" because I took
excellent design advice and finely split the modules.  I see no reason one could
not by able to upgrade these on top of the GHC versions.

> in particular, my hottest hope is that ghc 6.6.1 will be shipped with
> fps 0.8 as separate library that will provide both backward
> compatibility with 6.6 and will allow to upgrade fps without recompiling
> ghc itself :D

By separate library you really mean using a separate package name instead of
"base".  The Text.XHtml is already separate into the "xhtml" package.

You are correct: as far as I can see the only module that is in "base" which
might need to be split out is Data.ByteString.  The same may or may not apply to
Data.Sequence.

Cheers,
  Chris
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Help needed interrupting accepting a network connection

2006-12-02 Thread Chris Kuklewicz
Hi, I have taken a crack at this.  The best thing would be not to use the
asynchronous exceptions to signal the thread that calls accept.  And use STM
more, since the exception semantics are much easier to get right.

But a few minor changes gets closer to what you want.  First, the main problem
you claim to run into is

> Except that, whoops, the "takeMVar" in the accept thread code which updates 
> the
> childrenDone" MVar is also interruptible.  So now I'm getting an
> interruption right where I don't want it, when I'm updating my data
> structure. 

Short version: There is no problem because it will not become interruptible.
Long version:  The takeMVar unblocks exceptions only if it must
stop and wait for the MVar.  The MVar is only taken by this command/thread and
during graceful shutdown after this thread is dead.  So this MVar should never
be in contention (and in theory does not *need* to be a locked MVar, and an
IORef would do).  See http://citeseer.ist.psu.edu/415348.html for why I think
takeMVar only allow exceptions if the MVar is unavailable.

The biggest change is ensuring the accepting thread puts to acceptLoopDone by
using finally.  Many things might kill that thread; it is best to ensure it lets
the main thread know that it is dead.

More subtlety, I added "unblock (return ())" before accept.  This makes it look
for the asynchronous exception even when an incoming connection would be
immediately available. Otherwise a busy server would never notice the exception!

As a style point: there is an ugly moment between takeMVar and putMVar in which
you state is  inconsistent (being inside block makes it safe though).  So I
changed this to modifyMVar_ which is better practice.

> import Control.Concurrent
> import Control.Concurrent.MVar
> import Control.Exception as Exception
> import Network.Socket
> import Data.Typeable
> import System.IO
>
> -- A ConnectionHandler is a function which handles an incoming
> -- client connection.  The handler is run in its own thread, and is
> -- passed a handle to the client socket.  The handler does whatever
> -- communication it wants to do with the client, and when it returns,
> -- the client socket handle is closed and the thread terminates.
> -- A list of active handlers is kept, and the client connection is
> -- also marked as finished when the handler returns.
>
> type ConnectionHandler = Handle -> IO ()
>
> example_connection_handler :: ConnectionHandler
>
> example_connection_handler handle = do
>   hPutStrLn handle "Hello."
>   hPutStrLn handle "Goodbye."
>
>
> type ChildrenDone = MVar [MVar ()]
>
> data ExitGracefully = ExitGracefully deriving Typeable
>
>
> waitForChildren :: ChildrenDone -> IO ()
>
> waitForChildren childrenDone = do
>   cs <- takeMVar childrenDone
>   mapM_ takeMVar cs
>
> shutdownServer :: MVar () -> ChildrenDone -> ThreadId -> IO ()
>
> shutdownServer acceptLoopDone childrenDone acceptThreadId = do
>   throwDynTo acceptThreadId ExitGracefully
>   takeMVar acceptLoopDone
>   -- There can be no more changes to childrenDone
>   waitForChildren childrenDone
>   return ()
>
> acceptConnections :: MVar () -> ChildrenDone -> ConnectionHandler -> Socket 
> -> IO ()
>
> acceptConnections acceptLoopDone childrenDone connectionHandler sock =
>   finially (acceptConnections' acceptLoopDone childrenDone connectionHandler 
> sock)
>(putStrLn "accept loop exiting" >> putMVar acceptLoopDone () ) -- 
> run last
>
> -- This only looks for exceptions when "accept sock" is executed
> acceptConnections' acceptLoopDone childrenDone connectionHandler sock = block 
> loop
>   where loop = do
>   unblock (return ()) -- safe point to be interrupted, so unblock
>   (clientSocket, addr) <- accept sock  -- may or may not unblock and 
> wait
>   clientHandle <- socketToHandle clientSocket ReadWriteMode
>   childDone <- newEmptyMVar
>   forkIO $ handleConnection childDone connectionHandler clientHandle
>   modifyMVar_ childrenDone (return . (childDone:))  -- non-blocking 
> atomic change to MVar
>   loop
>
> handleConnection childDone connectionHandler clientHandle = do
>   Exception.catch
> (finially (connectionHandler clientHandle)
>   (hClose clientHandle >> putMVar childDone () )
>
> -- TODO we'll want to do something better when
> -- connectionHandler throws an exception, but
> -- for now we'll at least display the exception.
> (\e -> do { putStrLn $ show e; return () })

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


Re: [Haskell] Help needed interrupting accepting a network connection

2006-12-02 Thread Chris Kuklewicz
Cat Dancer wrote:
> On 12/2/06, Chris Kuklewicz <[EMAIL PROTECTED]> wrote:
>> Hi, I have taken a crack at this.  The best thing would be not to use the
>> asynchronous exceptions to signal the thread that calls accept.
> 
> I'd certainly be most happy not to use asynchronous exceptions as the
> signalling mechanism, but how would you break out of the accept,
> except by receiving an asynchronous exception?
> 

Short Version: You trigger a graceful exit using a TVar...
...and then you use killThread to break out of accept.

Long Version:

{-

The main accepting thread spawns this a slave thread to run accept and
stuffs the result into a TMVar.  The main loop then atomically checks
the TVar used for graceful shutdown and the TMVar.  These two checks
are combined by `orElse` which gives the semantics one wants: on each
loop either the TVar has been set to True or the the slave thread has
accepted a client into the TMVar.

There is still the possibility that a busy server could accept a
connection from the last client and put it in the TMVar where the main
loop will miss it when it exits.  This is handled by the finally
action which waits for the slave thread to be well and truly dead and
then looks for that last client in the TMVar.

No uses of block or unblock are required.

-}

-- Example using STM and orElse to compose a solution
import Control.Concurrent
import Control.Exception
import Control.Concurrent.STM
import Network
import System.IO

runExampleFor socket seconds = do
  tv <- newTVarIO False   -- Set to True to indicate graceful exit 
requested
  sInfo <- startServer socket tv
  threadDelay (1000*1000*seconds)
  shutdownServer tv sInfo

startServer socket tv = do
  childrenList <- newMVar []
  tInfo <- fork (acceptUntil socket exampleReceiver childrenList 
(retry'until'true tv))
  return (tInfo,childrenList)

-- Capture idiom of notifying a new MVar when a thread is finished
fork todo = do
  doneMVar <- newEmptyMVar
  tid <- forkIO $ finally todo (putMVar doneMVar ())
  return (doneMVar,tid)

acceptUntil socket receiver childrenList checker = do
  chan <- newEmptyTMVarIO
  (mv,tid) <- fork (forever (accept socket >>= syncTMVar chan))
  let loop = do
result <- atomically (fmap Left checker `orElse` fmap Right (takeTMVar 
chan))
case result of
  Left _ -> return ()
  Right client -> spawn client >> loop
  spawn client@(handle,_,_) = do
cInfo <- fork (finally (receiver client) (hClose handle))
modifyMVar_ childrenList (return . (cInfo:))
  end = do
killThread tid
takeMVar mv
maybeClient <- atomically (tryTakeTMVar chan)
maybe (return ()) spawn maybeClient
  finally (handle (\e -> throwTo tid e >> throw e) loop) end

forever x = x >> forever x

-- Pass item to another thread and wait for pickup
syncTMVar tmv item = do
  atomically (putTMVar tmv item)
  atomically (do empty <- isEmptyTMVar tmv
 if empty then return () else retry)

retry'until'true tv = do
  val <- readTVar tv
  if val then return ()
 else retry

exampleReceiver (handle,_,_) = do
  hPutStrLn handle "Hello."
  hPutStrLn handle "Goodbye."

shutdownServer tv ((acceptLoopDone,_),childrenList) = do
  atomically (writeTVar tv True)
  readMVar acceptLoopDone
  withMVar childrenList (mapM_ (readMVar . fst))
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Help needed interrupting accepting a network connection

2006-12-03 Thread Chris Kuklewicz
Cat Dancer wrote:
>> > I'd certainly be most happy not to use asynchronous exceptions as the
>> > signalling mechanism, but how would you break out of the accept,
>> > except by receiving an asynchronous exception?
>>
>> Short Version: You trigger a graceful exit using a TVar...
>> ...and then you use killThread to break out of accept.
> 
> Oh, OK, you're still using an asynchronous exception to break out of
> the accept (killThread throws a ThreadKilled asynchronous exception to
> the thread), but you're using STM to *signal* the graceful exit
> instead of using the asynchronous exception as the signalling
> mechanism.  Nice.
> 
> Thanks.  My ghc 6.6 (needed for newTVarIO) installation is broken for
> some reason, so I'll need to fix that tomorrow and then I'll be able
> to try your code.

Since newTVarIO is not in unsafePerformIO, you can replace it with
"atomically (newTVar)"

> 
>>  (mv,tid) <- fork (forever (accept socket >>= syncTMVar chan))
> 
> It looks like to me you could get a connection from "accept" but then
> get a ThreadKilled exception before the "syncTMVar chan" executes, and
> then the connection would be left open and hanging until it was
> eventually garbage collected?

Sigh.  I missed that one.  Not bad to fix, just use block and
split syncTMVar, putting the unblocked empty check before the accept.
I also switched to using "cond", a kind of flipped "if".  The new code:

cond true false test = if test then true else false

acceptUntil socket receiver childrenList checker = do
  chan <- newEmptyTMVarIO
  (mv,tid) <- fork . block . forever $ do
unblock . atomically $
  isEmptyTMVar chan >>= cond (return ()) retry
client <- accept socket
atomically (putTMVar chan client)
  let loop = do
result <- atomically (fmap Left checker `orElse` fmap Right (takeTMVar 
chan))
case result of
  Left _ -> return ()
  Right client -> spawn client >> loop
  spawn client@(handle,_,_) = do
cInfo <- fork (finally (receiver client) (hClose handle))
modifyMVar_ childrenList (return . (cInfo:))
  end = do
killThread tid
readMVar mv
maybeClient <- atomically (tryTakeTMVar chan)
maybe (return ()) spawn maybeClient
  finally (handle (\e -> throwTo tid e >> throw e) loop) end

The new code makes sure chan is empty, and so we are sure the putTMVar chan 
will never
have to wait so it will never unblock (I just wrote and ran short test to 
confirm this).
I think this is fixed now.
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Help needed interrupting accepting a network connection

2006-12-03 Thread Chris Kuklewicz
I realized there is another problem, since my code holds onto the ThreadId's 
the thread
data structures may or may not be getting garbage collected and for a long 
running
server the list of children grows without bound.

So I changed it to periodically clean out the finished child threads from the 
list
of children.  A simple counter IORef is used to avoid doing the cleanup on each
new child.

There are also a couple of other small style changes.

> {-
> 
> The main accepting thread spawns this a slave thread to run accept and
> stuffs the result into a TMVar.  The main loop then atomically checks
> the TVar used for graceful shutdown and the TMVar.  These two checks
> are combined by `orElse` which gives the semantics one wants: on each
> loop either the TVar has been set to True or the the slave thread has
> accepted a client into the TMVar.
> 
> There is still the possibility that a busy server could accept a
> connection from the last client and put it in the TMVar where the main
> loop will miss it when it exits.  This is handled by the finally
> action which waits for the slave thread to be well and truly dead and
> then looks for that last client in the TMVar.
> 
> The list of child threads is cleaned periodically (currently every
> 10th child), which allows the garbage collected to remove the dead
> threads' structures.
> 
> -}
> 
> -- Example using STM and orElse to compose a solution
> import Control.Monad
> import Control.Concurrent
> import Control.Exception
> import Control.Concurrent.STM
> import Data.IORef
> import Network
> import System.IO
> 
> forever x = x >> forever x
> 
> runExampleFor socket seconds = do
>   tv <- newTVarIO False   -- Set to True to indicate graceful exit 
> requested
>   sInfo <- startServer socket tv
>   threadDelay (1000*1000*seconds)
>   shutdownServer tv sInfo
> 
> startServer socket tv = do
>   childrenList <- newMVar []
>   tInfo <- fork (acceptUntil socket exampleReceiver childrenList 
> (retry'until'true tv))
>   return (tInfo,childrenList)
> 
> shutdownServer tv ((acceptLoopDone,_),childrenList) = do
>   atomically (writeTVar tv True)
>   readMVar acceptLoopDone
>   withMVar childrenList (mapM_ (readMVar . fst))
> 
> -- Capture idiom of notifying a new MVar when a thread is finished
> fork todo = do
>   doneMVar <- newEmptyMVar
>   tid <- forkIO $ finally todo (putMVar doneMVar ())
>   return (doneMVar,tid)
> 
> cond true false test = if test then true else false
> 
> -- This is an asychronous exception safe way to use accept to get one
> -- client at a time and pass them to the parent thread via a TMVar.
> acceptInto socket chan =  block . forever $ do
>   unblock . atomically $
> isEmptyTMVar chan >>= cond (return ()) retry
>   client <- accept socket
>   atomically (putTMVar chan client)
> 
> -- This demonstrates how to use acceptInto to spawn client thread
> -- running "receiver".  It ends when checker commits instead of using
> -- retry.
> acceptUntil socket receiver childrenList checker = do
>   counter <- newIORef (0::Int) -- who cares if it rolls over?
>   chan <- atomically (newEmptyTMVar)
>   (mv,tid) <- fork (acceptInto socket chan)
>   let loop = atomically (fmap Left checker `orElse` fmap Right (takeTMVar 
> chan))
>  >>= either (const (return ()))(\client -> spawn client >> 
> loop)
>   spawn client@(handle,_,_) = do
> cInfo <- fork (finally (receiver client) (hClose handle))
> count <- readIORef counter
> writeIORef counter $! (succ count)
> modifyMVar_ childrenList $ \kids -> fmap (cInfo:) $
>   if count `mod` 10 == 0  -- 10 is arbitrary frequency for cleaning 
> list
> then return kids
> else filterM (isEmptyMVar . fst) kids
>   end = do
> killThread tid
> readMVar mv
> atomically (tryTakeTMVar chan) >>= maybe (return ()) spawn
>   finally (handle (\e -> throwTo tid e >> throw e) loop) end
> 
> exampleReceiver (handle,_,_) = do
>   hPutStrLn handle "Hello."
>   hPutStrLn handle "Goodbye."
> 
> retry'until'true tv = (readTVar tv >>= cond (return ()) retry)

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


[Haskell] Safe forking question

2006-12-03 Thread Chris Kuklewicz
In response to question by Cat Dancer <[EMAIL PROTECTED]> I wrote a few tests of
sending asynchronous signal to a thread using GHC 6.6

The goal was to run a child thread via forkIO and use handle or finally to 
respond
to the thread's demise.

Unfortunately, it seems that there is an irreducible window where this fails.  
The
forkIO returns but any exception handlers such as block/handle/catch/finally are
not in place yet.

So this fails:

> module Main where
> 
> import Control.Exception
> import Control.Concurrent
> import Control.Concurrent.STM
> 
> forever x = x >> forever x
> 
> count tv = do
>   val <- takeTMVar tv
>   putTMVar tv $! (succ val)
>   return val
> 
> -- Capture idiom of notifying a new MVar when a thread is finished
> fork todo = do
>   doneMVar <- newEmptyMVar
>   tid <- block $ forkIO $ block $ handle (\e -> print ("Exception",e) >> 
> throw e)
>  (finally (unblock todo) 
>   (print "dying!" >> putMVar 
> doneMVar ()))
>   return (doneMVar,tid)
> 
> spawn = do
>   tv <- atomically (newTMVar 0)
>   fork . forever $ atomically (count tv) >>= print
> 
> kill (mv,tid) = do
>   -- yield
>   print "killing.."
>   killThread tid
>   print "..checking corpse.."
>   readMVar mv
>   print "..confirmed dead"
> 
> main = spawn >>= kill

On my system, the above sends the killThread and destroys the thread before the
handle or finally are setup, so the child thread never prints anything and never
runs the "putMVar doneMVar ()".

If I uncomment the yield statement then the child thread does start executing 
and
the handle and finally work as desired.

This makes it impossible to reliably do anything with the child thread.  I 
cannot
discern between a living and dead child thread at all, as there is way to know 
if
it is waiting to be scheduled or if it has been killed waiting to be scheduled.

The get/setUncaughtExceptionHandler does not seem to be inherited by the child 
thread,
so this was not a useful guard.

The best thing I can come up with is the ugly code:

> fork todo = block $ do
>   doneVar <- atomically (newEmptyTMVar)
>   let putStarted = atomically (putTMVar doneVar False)
>   putStopped = atomically (tryTakeTMVar doneVar >> putTMVar doneVar True)
>   tid <- forkIO $ block $ (finally (putStarted >> unblock todo) putStopped)
>   yield
>   atomically $ do
> value <- takeTMVar doneVar
> when value (putTMVar doneVar True)
>   return (doneVar,tid)

This does not return the ThreadId until the finally clause has started running. 
 But if
the thread is killed by any external force before getting that far then the 
main thread
will hang on the "takeTMVar doneVar".

Is there any remotely better way of forking a child with an exception handler?

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


Re: [Haskell] Help needed interrupting accepting a network connection

2006-12-03 Thread Chris Kuklewicz
After more testing I found an ugly problem that a child could be killed before
the finally installed the handler that calls (putMVar doneMVar ())

Thus I have added slightly more paranoid code to ensure that the child is 
running
before exposing the (T)MVar/ThreadId to the rest of the application.

That this was needed is is really really annoying, and does not *really* fix the
problem but just minimize it.

Change fork to:

> fork todo = block $ do
>   doneVar <- atomically (newEmptyTMVar)
>   let putStarted = atomically (putTMVar doneVar False)
>   putStopped = atomically (tryTakeTMVar doneVar >> putTMVar doneVar True)
>   tid <- forkIO $ block $ (finally (putStarted >> unblock todo) putStopped)
>   yield
>   atomically $ do
> value <- takeTMVar doneVar
> when value (putTMVar doneVar True)
>   return (doneVar,tid)

and in the rest of the code change a few readMVar to readTMVar and add 
atomically.

The doneVar is in 3 states:
 empty meaning child has not started yet
 False meaning child has definitely started
 empty meaning meaning child is still running
 True meaning child has definitely stopped

The first two of those states should only be seen inside the fork function.
When the fork function is finished only the second two states should be seen.

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


[Haskell] Re: Safe forking question

2006-12-04 Thread Chris Kuklewicz
Hi,

  Thanks for the reply.  I have my own proposal below:

Simon Marlow wrote:
> Chris Kuklewicz wrote:
>> In response to question by Cat Dancer <[EMAIL PROTECTED]> I wrote a few
>> tests of
>> sending asynchronous signal to a thread using GHC 6.6
>>
>> The goal was to run a child thread via forkIO and use handle or
>> finally to respond
>> to the thread's demise.
>>
>> Unfortunately, it seems that there is an irreducible window where this
>> fails.  The
>> forkIO returns but any exception handlers such as
>> block/handle/catch/finally are
>> not in place yet.
> 
> We might consider it a bug that a new thread is started in "async
> exceptions unblocked" mode.  It's true that this does mean there's no
> way to reliably start a thread and guarantee to know if it is killed.
> 
> Starting threads in 'blocked' mode isn't the answer.  That would force
> everyone to add an 'unblock' to their forkIO's after setting up an
> exception handler, and that's too easy to forget (and not backwards
> compatible).

Starting in 'blocked' mode is more primitive, since you can always safely
define the unblocked version from it but never the other way around.

>  So instead we could introduce a new abstraction:
> 
>   forkCatchIO :: (Exception -> IO ()) -> IO () -> IO ThreadId
> 
> which combines forkIO with catch in an atomic way, such that the handler
> is guaranteed to execute if the thread receives an exception.

If I run "forkCatchIO handler (block io)" then it looks like there is still a
vulnerable gap for throwTo to trigger the handler before the "block" goes
into effect.  Is this correct?  If so then I need an MVar again.

> You can
> implement this using an MVar and not returning the ThreadId until the
> child thread is inside the exception handler (as in your example):

I take great consolation in having found the right workaround.  Note that my
solution has been changed to remove the "unblock" to create "forkBlocked":

> forkBlocked todo = block $ do
>   doneVar <- atomically (newEmptyTMVar)
>   let putStarted = atomically (putTMVar doneVar False)
>   putStopped = atomically (tryTakeTMVar doneVar >> putTMVar doneVar True)
>   tid <- forkIO $ block $ (finally (putStarted >> todo) putStopped)
>   yield
>   atomically $ do
> value <- takeTMVar doneVar
> when value (putTMVar doneVar True)
>   return (doneVar,tid)

Now I have both an exception hander and a guarantee that "todo" is running 
inside
"block" and I could recover the previous function with "fork = forkBlocked . 
unblock".

> this is ok because the only way a thread can receive an exception is by
> knowing its ThreadId.  However it's less than perfect in performance
> terms; if we had a primitive fork that created a thread in blocked mode
> we could do much better.

> If there's some agreement that this is the way to go, I'll file a task
> for GHC and try to get to it before 6.8.
> 
> Cheers,
> Simon

Being able to open a new thread in blocked mode would also be useful, as it 
gives
control over what the "safepoints" for async interruption are.  The forkCatchIO 
does
not ensure I can entered "block" mode without the kind of MVar trick I had to 
use
with forkIO.

forkInheritIO :: IO () -> IO ThreadId -- inherits parent's block or unblock 
status

forkBlockedIO :: IO () -> IO ThreadId -- starts the action in "block" mode.  
Must manually "unblock"

where forkBlockedIO could be written as "block . forkInheritIO"
and forkIO is "unblock . forkInheritIO"
but there is no way to write forkInheritIO since I can't query
the current block|unblock status dynamically.  I have no use for forkInheritIO 
but
perhaps some library code would want to play nice with the calling application.

If either of those two functions existed then one could write "forkCatchIO"
(which is unblocked) using it:

forkCatchBlockedIO hander io = forkBlockedIO (handle handler io)
forkCatchIO handler = (forkChatchBlockedIO handler) . unblock

I propose adding at least "forkInheritIO" or "forkBlockedIO" as a primitive
and perhaps "forkCatchIO" or "forkCatchBlockedIO" as a primitive if there is a 
performance gain.

Cheers,
  Chris
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] How to use STM in GUI applications?

2006-12-05 Thread Chris Kuklewicz
Lemmih wrote:
> On 12/4/06, Thorsten Seitz <[EMAIL PROTECTED]> wrote:
>> Hello,
>>
>> I'm very intrigued by the concepts of STM but I'm having difficulties
>> to see
>> how a TVar based model can be used by a GUI application (e.g. Gtk2hs):
>>
>> For example, I'd like to update the GUI (e.g. changing widget
>> sensitivity)
>> upon changes in the model.
>> But changing the sensitivity of a widget is an IO operation which
>> cannot be
>> initiated atomically by a model change which is an STM operation.
>> Therefore
>> the GUI change cannot be executed atomically together with the model
>> change.
>> This means for example that I can still press a button although the
>> model has
>> changed such that the button action is not allowed anymore. All I can
>> do is
>> check the condition of the model when the button is pressed and then
>> ignore
>> the button press which is not very satisfying for the user.
>>
>> Is it simply not appropriate to use TVar based models in a GUI
>> application?
>> Maybe STM should be more used like a service for MVar based GUI models?
> 
> How about making a list of IO actions to be executed when the
> transaction commits?
> 

That onCommit list and its execution can be done by using the slightly
modified/enhanced/wrapped AdvSTM monad.

A complex example that also can queue actions on retry is at
http://haskell.org/haskellwiki/?title=New_monads/MonadAdvSTM#Helper_Thread_Code

But for just onCommit the simpler code at
http://haskell.org/haskellwiki/New_monads/MonadAdvSTM#Just_onCommit
should work.

Cheers,
  Chris
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


[Haskell] Bug: Safepoint does not work as documented in paper

2006-12-05 Thread Chris Kuklewicz
One odd problem:  The paper on async exception defines:

safePoint = unblock (return ())

but this simply does not work in my testing.  Ever.  Even using
{-# NOINLINE safePoint #-} or "-Onot"

By comparision, this does work: safepoint = unblock (print "safe")

So how can such a safePoint be written?

-- 
Chris

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


Re: [Haskell] What guarantees (if any) do interruptible operations have in presence of asynchronous exceptions?

2006-12-05 Thread Chris Kuklewicz
Making small programs to test these properties is a good sanity check.  For
instance I just leaned that "safePoint = unblock ( return () )" does not work.

What I think happens:

Cat Dancer wrote:
>> From the discussion of "Help needed interrupting accepting a network
> connection", what we have so far is:
> 
>* To break out of an "accept" call, an asynchronous exception is needed.
> 
>* The presence of asynchronous exceptions complicates the other code
>  used to report if "accept" completed or was interrupted, whether
>  that code is written using MVar's or STM.
> 
> Thus the next question is what guarantees, if any, do interruptible
> operations possess?

During "unblock" anything can happen.
During "block":
  No async. exceptions are raised, unless...
   ...the "block" is lifted by an "interruptible operation"
   The will only happen when that operation must block.


> 
> For example, suppose that inside of a "block", a putMVar operation was
> guaranteed to either interrupt and allow an asynchronous exception to
> be raised, or to complete the putMVar operation, but not both.

A putMVar will only allow interruptions insofar as it must wait for the MVar to
become empty.  So while it is waiting on the MVar it may receive an async.
exception and so will not perform the put operation.

> If this were true, then if you caught an asynchronous exception from
> the putMVar operation, you'd know that a value was not put into the
> MVar by the operation.

I think that should be a safe assumption when running under "block".

> Then it would be easy to program with MVar's in the presence of
> asynchronous exceptions.  When you caught an asynchronous exception,
> you could set a flag, and then redo the putMVar.

If you call that "easy" then sure.

> The same question can be asked of other interruptible operations.
> 
> For the "accept" call itself, is it guaranteed (inside of a "block")
> to either accept a connection, or be interrupted and allow an
> asynchronous exception to be raised, but not both?

That should be true, for the same reason as putMVar.

> For STM, is "atomically" an interruptible operation?  If it is, what
> guarantees does it offer in the presence of asynchronous exceptions?

"block (atomically stm)" is interruptible when the operation "stm" uses retry
and perhaps when it has to be re-attempted due to conflicting updates.  If it
runs without conflict and commits then it cannot be interrupted by an async
exception.

If (atomically stm) is interrupted then it is rolled back and will have had no
visible side effects.

-- 
Chris

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


Re: [Haskell] What guarantees (if any) do interruptible operations have in presence of asynchronous exceptions?

2006-12-05 Thread Chris Kuklewicz
Cat Dancer wrote:
> On 12/5/06, Chris Kuklewicz <[EMAIL PROTECTED]> wrote:
>> Making small programs to test these properties is a good sanity
>> check.  For
>> instance I just leaned that "safePoint = unblock ( return () )" does
>> not work.
> 
> Maybe if you do something to allocate some memory inside of the unblock?
> 
> 
>> > If this were true, then if you caught an asynchronous exception from
>> > the putMVar operation, you'd know that a value was not put into the
>> > MVar by the operation.
>>
>> I think that should be a safe assumption when running under "block".
> 
> "I think" and "should be" is nice, how do we find out if it's really
> true -- for sure?

Read the papers the have been written about the design (see the wiki for links)
and ask the developers of the compiler you are using.  nicely.


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


Re: [Haskell] Network accept loop with graceful shutdown implementation

2006-12-07 Thread Chris Kuklewicz
Cat Dancer wrote:
> I have a prospective implementation of a network accept loop with
> graceful shutdown.
> 

Could you add info about where to get your code (or the code) itself to the wiki
 at http://haskell.org/haskellwiki/Concurrency_demos/Graceful_exit ?

> To avoid the "unlock (return ())" issue that Chris discovered, this
> implementation uses an additional MVar to indicate that a shutdown is
> in process.  Thus (if the implementation is correct) the accept loop
> will shutdown either because of the MVar flag or by receiving the
> asynchronous exception inside of the 'accept'.

Small clarification: You don't need a safepoint in your code. But "unblock
yield" is the right code for a safepoint; the "unblock (return ())" suggested by
the published paper *does not work* in my small test, while "unblock yield"
worked every time in a small test.  Simon may updated the documentation
eventually to reflect this.

> To address the issue that Chris noticed of a race condition that new
> threads cannot be started in a 'block' state, yet another MVar is set
> by the accept thread to indicate that it is now inside of a 'block'
> and is ready to receive the asynchronous exception.
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Re: Converting a 'streaming' monad into a list

2006-12-30 Thread Chris Kuklewicz

> 
> 
> Oh, the Writer has much nicer properties than I thought.
> 

But WriterT is not lazy enough.  So I put a lazier version up on the wiki:

http://haskell.org/haskellwiki/New_monads/LazyWriterT

And I actually tried the same streaming generator type problem when I started
Haskell, and my results with Writer and Cont are on the old wiki:

http://haskell.org/hawiki/PythonGenerator

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


Re: [Haskell] ANNOUNCE: Data.CompactString 0.1 - my attempt at a Unicode ByteString

2007-02-05 Thread Chris Kuklewicz
Twan van Laarhoven wrote:
> Hello all,
> 
> I would like to announce my attempt at making a Unicode version of
> Data.ByteString. The library is named Data.CompactString to avoid
> conflict with other (Fast)PackedString libraries.
> 
> The library uses a variable length encoding (1 to 3 bytes) of Chars into
> Word8s, which are then stored in a ByteString.

Can I be among the first to ask that any Unicode variant of ByteString use a
recognized encoding?

You have invented a new encoding:

> -- Reading/writing chars
> --
> 
> -- Uses a custom encoding which looks like UTF8, but is slightly more 
> efficient.
> 
> -- It requires at most 3 byes, as opposed to 4 for UTF8.
> 
> --
> 
> -- Encoding looks like
> 
> --0zzz -> 0zzz
> 
> --   00yy yzzz -> 1xxx 1yyy
> 
> --  000x xxyy yzzz -> 1xxx 0yyy 1zzz
> --
> -- The reasoning behind the tag bits is that this allows the char to be read 
> both forwards
> -- and backwards.
> 
> -- | Write a character and return the size needed
> pokeCharFun :: Char -> (Int, Ptr Word8 -> IO ())
> pokeCharFun c = case ord c of
>  x | x < 0x80   -> (1, \p ->pokep   $ fromIntegral  x )
>| x < 0x4000 -> (2, \p -> do pokep   $ fromIntegral (x `shiftR`  
> 7) .|. 0x80
> pokeByteOff p 1 $ fromIntegral  x 
>  .|. 0x80 )
>| otherwise  -> (3, \p -> do pokep   $ fromIntegral (x `shiftR` 
> 14) .|. 0x80
> pokeByteOff p 1 $ fromIntegral (x `shiftR`  
> 7) .&. 0x7f
> pokeByteOff p 2 $ fromIntegral  x 
>  .|. 0x80 )
> {-# INLINE pokeCharFun #-}
> 
> -- | Write a character and return the size used
> pokeChar :: Ptr Word8 -> Char -> IO Int
> pokeChar p c = case pokeCharFun c of (l,f) -> f p >> return l
> {-# INLINE pokeChar #-}
> 
> -- | Write a character and return the size used
> pokeCharRev :: Ptr Word8 -> Char -> IO Int
> pokeCharRev p c = case pokeCharFun c of (l,f) -> f (p `plusPtr` (1-l)) >> 
> return l
> {-# INLINE pokeCharRev #-}

In reading all the poke/peek function I did not see anything that your tag bits
accomplish that the tag bits in utf-8 do not, except that you want to write only
a single routine for the poke/peek forwards and backwards operations instead of
two routines.  It is definitely more compact in the worst case, and more "Once
And Only Once", but at a very high cost of incompatibility.

One of the biggest wins with with a Unicode ByteString will be the ability to
transfer the buffer directly to and from the disk and network.  Your code will
always need the data to be rewritten both incoming and outgoing.

The most ideal case would be the ability to load different encodings via import
statements while using the same API.
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] ANNOUNCE: Data.CompactString 0.1 - my attempt at a Unicode ByteString

2007-02-05 Thread Chris Kuklewicz
shelarcy wrote:
> Hello Twan,
> 
> On Mon, 05 Feb 2007 08:46:35 +0900, Twan van Laarhoven <[EMAIL PROTECTED]> 
> wrote:
>> I would like to announce my attempt at making a Unicode version of
>> Data.ByteString. The library is named Data.CompactString to avoid
>> conflict with other (Fast)PackedString libraries.
> 
> How about add abstract layer?
> 
> Spencer Janssen tried to provied abstract layer for Unicode ByteString,
> last year's summer of code project.
> It has no Unicode support. But it supplied a good layer, Stringable class.
> 
> http://code.google.com/soc/haskell/appinfo.html?csaid=B934AEBE95120AB2
> http://darcs.haskell.org/SoC/fps-soc/
> http://darcs.haskell.org/SoC/fps-soc-aug21/
> 
> 
>> The library uses a variable length encoding (1 to 3 bytes) of Chars into
>> Word8s, which are then stored in a ByteString. The structure is very
>> much based on Data.ByteString, most of the implementation is copied from
>> there. Hopefully this means that fusion rules could be copied as well.
> 
> UTF-8 also uses 4 to 6 byte encodings now.
> CJK Unified Ideographs Extension B, Tai Xuan Jing Symbol and Music Symbol,
> etc ... use 4 byte encoding.

Looking at several sources, it seems you are incorrect.

Haskell Char go up to Unicode 1114111 (decimal) or 0x10 Hexidecimal).
These are encoded by UTF-8 in 1,2,3,or 4 bytes.

CJK Unified Ideographs Extension B starts at 131072 or 0x2
Tai Xuan Jing Symbols start at 119552 or 0x1d300

These are all within the official utf-8 encoding scheme.

> 
> Many Hasekll UTF-8 libraries doesn't support over 3 byte encodings.

UTF-8 uses 1,2,3, or 4 bytes.  Anything that does not support 4 bytes does  not
support UTF-8

> But Takusen's implementation support it correctly.

The Takusen does have unreachable dead code to serialize Char as (ord c :: Int)
up to 31 bits into as many as 6 bytes.  But it does decode up to 6 bytes to 31
bits and try to "chr" this from Int to Char.  Decoding that many bits is not
consistent with the UTF-8 standard.

> 
> http://darcs.haskell.org/takusen/Foreign/C/UTF8.hs
> http://www.haskell.org/pipermail/libraries/2007-February/006841.html
> 
> How about support 4 to 6 byte encodings?

UTF-8 is a 4 byte encoding.  There is no valid UTF-8 5 or 6 byte encoding.

> 
> 
> Best Regards,
> 

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


Re: [Haskell] Data.Hashtable operations in IO?

2007-02-20 Thread Chris Kuklewicz
ROBERT DOUGLAS HOELZ wrote:
> I was reading the docs for Data.Hashtable, and quickly noticed that 
> operations on a hashtable are of the IO monad.  Why is this?  I should think 
> that the operations would look like this:
> 
> insert :: Hashtable -> key -> val -> Hashtable
> lookup :: Hashtable -> key -> a
> 
> etc.
> 
> Thanks,
> Rob Hoelz

That would be the signature for immutable hashtables.  The old and new ones
would be distinct and could co-exist.  Building an immutable hashtable on top of
Data.Array or Data.Map would be fairly easy.

Data.Hashtable is a mutable hashtable.  After an insert the old Hashtable no
longer exists -- there is only the new one.  Thus operations needs to be
ordered.   Rightfully, there should be a Data.Hashtable.ST as well.

The standard Haskell libraries have yet to include one of the type class
approaches to immutable collections and have very little in the way of mutable
data structures.

The former is probable due to lack of standardization of MPTC / fundeps /
associated types.  The latter is due to both lack of sufficient interest and the
same lack of a standard for fancier type classes.
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] math library for Haskell

2007-07-25 Thread Chris Kuklewicz

Lloyd Allison wrote:

Am I looking in the wrong place
(http://haskell.org/ghc/docs/latest/html/libraries/ ) or
just not seeing it, but I was hoping there would be a
math library for Haskell that would include, e.g.,
a Gamma function and the like.


-L


I think the best thing would be to wrap the Gamma function form the GSL:

http://www.gnu.org/software/gsl

Or add the Gamma wrapper to the Haskell wrapping GSLHaskell at

http://dis.um.es/~alberto/GSLHaskell/

Note: Get the darcs version of GSLHaskell.
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] math library for Haskell

2007-07-25 Thread Chris Kuklewicz

Alberto Ruiz wrote:

I have included a binding to gsl_sf_gamma in the darcs repo of GSLHaskell:

http://dis.um.es/~alberto/GSLHaskell/doc/GSL-Special.html#v%3Agamma

I will try to upload to hackage a recent version of the library in a few days.

Alberto


It occurs to me that generating the binding for all the GSL "Special" functions 
by hand may be labor intensive.  Would it be reasonable to have a (perhaps 
customized) tool generate the wrapping code?


I am interested since I just ported various data processing from Mathematica to 
GSL plus C code.  (At the moment much of what I use (e.g. interpolation) is not 
in the GSL wrapper).


Cheers,
  Chris Kuklewicz
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Re: ANNOUNCE: GHC version 6.8.2

2007-12-21 Thread Chris Kuklewicz
Benjamin L. Russell wrote:
> Will a binary version of 6.8.2 be released any time
> soon for Mac OS X 10.5.x Leopard running on a PowerPC,
> as opposed to an Intel?
> 
> I have a first-generation aluminum PowerBook with a
> PowerPC currently running Mac OS X 10.2.8 Jaguar, and
> am considering upgrading to Leopard next month, but
> want to install GHC 6.8.2 on it with a binary.
> 
> Does this mean that I should not upgrade to that OS
> version?

I have a PPC laptop with OS 10.5.1 Leopard.

The ghc-6.8.1 does not work.  Though there is limited success if you only ever
use -fvia-C.  Fixing one problem (
http://hackage.haskell.org/trac/ghc/ticket/1843 ) has merely revealed another (
http://hackage.haskell.org/trac/ghc/ticket/1958 ).

The problem is being worked on.  But you will not get (PPC && Leopard &&
ghc-6.8) yet.
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] ANNOUNCE: HStringTemplate -- An Elegant, Functional, Nifty Templating Engine for Haskell

2008-01-14 Thread Chris Kuklewicz

Sterling Clover wrote:
HStringTemplate is a port of Terrence Parr’s lovely StringTemplate 
(http://www.stringtemplate.org) engine to Haskell.


Reading Terrence Parr describe StringTemplate, at 
http://www.stringtemplate.org/about.html is amusing:



The fact that StringTemplate does not allow such things as assignments (no
side-effects) should make you suspicious of engines that do allow it.


and


Another distinctive StringTemplate language feature lacking in other engines is
lazy-evaluation. StringTemplate's attributes are lazily evaluated in the sense
that referencing attribute "a" does not actually invoke the data lookup
mechanism until the template is asked to render itself to text. Lazy evaluation
is surprising useful in both the web and code generation worlds because such
order decoupling allows code to set attributes when it is convenient or
efficient not necessarily before a template that references those attributes is
create


and


Just so you know, I've never been a big fan of functional languages and I
laughed really hard when I realized (while writing the academic paper) that I
had implemented a functional language. The nature of the problem simply dictated
a particular solution. We are generating sentences in an output language so we
should use something akin to a grammar. Output grammars are inconvenient so tool
builders created template engines. Restricted template engines that enforce the
universally-agreed-upon goal of strict model-view separation also look
remarkably like output grammars as I have shown. So, the very nature of the
language generation problem dictates the solution: a template engine that is
restricted to support a mutually-recursive set of templates with
side-effect-free and order-independent attribute references.


--
Chris

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


Re: [Haskell] Simulating client server communication with recursive monads

2008-01-15 Thread Chris Kuklewicz

Jan Stranik wrote:
My question was why does the output from writer shows first all output 
from server, then followed by all output from client.


The effect of "mfix" is that the side-effects of the calculation still occur in 
the lexical order.


Since server is before client, the output of the server precedes the client.

I would like to 
see output from client and server to alternate in the order in which the 
computation occurs, namely [server, client, server, client, server, 
client, …].


Then you have to restructure the code slightly.  This works:


import Control.Monad

import Control.Monad.Writer.Lazy

client:: [Integer] -> Writer [String] [Integer]
client as = do
  dc <- doClient as
  return (0:dc)
where
  doClient (a:as) = do
  tell ["Client " ++ show a]
  as' <- doClient as
  return ((a+1):as')
  doClient [] = return []

server :: [Integer] -> Writer [String] [Integer]
server [] = return []
server (a:as) = do
  tell ["Server " ++ show a]
  rs <- server as
  return (2*a:rs)

simulation :: [(String,String)]
simulation = 
  let (clientOut,clientLog) = runWriter (client serverOut)

  (serverOut,serverLog) = runWriter (server clientOut)
  in zip serverLog clientLog

main = print (take 10 simulation)


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


Re: [Haskell] Haskell OBDD package?

2008-03-25 Thread Chris Kuklewicz

Try
http://www.informatik.uni-kiel.de/~mh/lehre/diplomarbeiten/christiansen.pdf
from
http://www.informatik.uni-kiel.de/~mh/lehre/diplomarchiv.html

Johannes Waldmann wrote:
> I'm looking for current Haskell implementations
> of (ordered) binary decision diagrams.
>
> (Yes, I tried google but this gives links from 2004 and earlier.)
>
> Thanks - Johannes Waldmann.
> ___
> Haskell mailing list
> Haskell@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell

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


Re: [Haskell] Probably a trivial thing for people knowing Haskell

2008-10-18 Thread Chris Kuklewicz

H

mm..
The totals in "sum" and "count" are not computed until printed.  This is too 
lazy.  You start with '0' and (+) things to it, but never examine or force the 
value, so man many (+) thunks are built up in memory.


If you use bang patterns then the change can be made here, to !sum !count:

check_line line !sum !count =  
let match = matchRegex regexp line

in case match of
   Just strs -> (sum + read (head strs) :: Integer, count + 1)
   Nothing -> (sum, count)



This will force evaluation before every check_line call.
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] string type class

2009-03-06 Thread Chris Kuklewicz

Matthew Pocock wrote:
It seems every time I look at hackage there is yet another stringy 
datatype. For lots of apps, the particular stringy datatype you use 
matters for performance but not algorithmic reasons. Perhaps this is a 
good time for someone to propose a stringy class?


Not likely.

I did define my own (private) class for regular expressions, to abstract over 
String, the ByteStrings, and Seq Char.  But it is used in one place and is a 
wart that should be removed.


The simple task of looping over the contents of a String (once, forward) is 
quite different from a Strict ByteString (using an index and a lookup).


This means for decent efficiency I need two copies of my code, hand specialized 
to each case.


"tail" or "(x:xs)" : very efficient for String (no allocation)
"tail" or "uncons" : not efficient for ByteString (allocation, might as well 
convert to [Char]


And indexing by Int is O(n) for String and O(1) for ByteString.

So there are few algorithm that can access both efficiently.

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