Re: [Haskell] URLs in haskell module namespace

2005-03-23 Thread Einar Karttunen
or somesuch. - Einar Karttunen ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell] Re: Existing Haskell IPv6 Code

2005-05-12 Thread Einar Karttunen
/ HTTP/1.0\r\n\r\n hFlush h hGetContents h = print hClose h - Einar Karttunen ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell] Re: Existing Haskell IPv6 Code

2005-05-12 Thread Einar Karttunen
one can use an aproach to go from URIs to sockets having a case statement for each scheme. But what URI should represent e.g. unix datagram sockets? Having an URI connection function would be nice, but having it as the primary alternative would not be very nice. - Einar Karttunen

Re: [Haskell] Mixing monadic and non-monadic functions

2005-09-15 Thread Einar Karttunen
- Einar Karttunen ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell] Paper: The essence of dataflow programming

2005-09-26 Thread Einar Karttunen
) This looks very much like monadic code written with and =. A general Functor instance is easy (but non-haskell98): instance Comonad w = Functor w where fmap f = cobind (f . counit) - Einar Karttunen ___ Haskell mailing list Haskell@haskell.org http

Re: [Haskell] A simple server (or how to do io).

2005-12-20 Thread Einar Karttunen
use the killServer call. ps. I think it may be best to continue on haskell-cafe@ rather than the main list. - Einar Karttunen ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell] Re: page names on the new Haskell wiki

2006-01-27 Thread Einar Karttunen
to have. Please consider at least leaving shorter names as alternatives with redirection if you must use long names for some reason. - Einar Karttunen ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

[Haskell] ANNOUNCE: HAppS 0.8

2006-04-13 Thread Einar Karttunen
that don't support it client side. * Sessions and much more! Where to get? http://happs.org/ darcs get http://happs.org/HAppS -- Einar Karttunen ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell] thread-local variables (was: Re: Implicit Parameters)

2006-07-30 Thread Einar Karttunen
explicit. - Einar Karttunen ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell] thread-local variables (was: Re: Implicit Parameters)

2006-07-30 Thread Einar Karttunen
that happens to use a pool of worker threads that invisible to the application. Or the same with the role of the application and library reversed. Offering it up as a separate library should be ok as it would be very easy to spot and take extra care not to cause problems. - Einar Karttunen

Re: [Haskell] thread-local variables (was: Re: Implicit Parameters)

2006-07-31 Thread Einar Karttunen
if a library uses TLS and callbacks and they end up running in threads created before the library initialization. - Einar Karttunen ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell] thread-local variables (was: Re: Implicit Parameters)

2006-07-31 Thread Einar Karttunen
immensely, and doesn't stand in the way their being useful for solving a bunch of problems. I think that them reverting to the initial value is more useful than persisting behavior. - Einar Karttunen ___ Haskell mailing list Haskell@haskell.org http

Re: [Haskell] thread-local variables

2006-08-01 Thread Einar Karttunen
On 31.07 23:53, Adrian Hey wrote: Frederik Eaton wrote: On Mon, Jul 31, 2006 at 03:09:59PM +0300, Einar Karttunen wrote: On 31.07 03:18, Frederik Eaton wrote: 4) the library runs the callback code in Tw where the TLS state is invalid. This is even worse than a global variable in this case

Re: [Haskell] thread-local variables

2006-08-04 Thread Einar Karttunen
ty = Proxy name - IO ty withTLS :: TLSVar name ty = Proxy name - ty - IO a - IO a But I don't have strong feelings about the API as I would probably not use it. - Einar Karttunen ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org

Re: [Haskell] thread-local variables

2006-08-05 Thread Einar Karttunen
at all. - Einar Karttunen ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell] thread-local variables

2006-08-06 Thread Einar Karttunen
to their parents, that is they contain the ThreadId of the parent thread. In my code this problem should not occur. - Einar Karttunen ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell] thread-local variables

2006-08-06 Thread Einar Karttunen
' monad is necessary, but I haven't read the proposal very carefully. The TL monad is necessary to make initialization order problems go away. - Einar Karttunen ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell] thread-local variables

2006-08-06 Thread Einar Karttunen
extent as 'withArgs' and 'withProgName' are. All libraries which may fork may use a preallocated thread pool. Thus they might not work with TLS. withArgs and withProgName are global and not very thread-friendly. - Einar Karttunen ___ Haskell mailing list

Re: [Haskell] thread-local variables

2006-08-08 Thread Einar Karttunen
about the number of threads and don't run to situations with 1 extra threads just because forking always is fun. The other point is to use a background thread which talks to blocking C API and executed callbacks upon receiving events from the C side. - Einar Karttunen

[Haskell] ANN: HAppS version 0.8.2

2006-09-25 Thread Einar Karttunen
--partial --tag=HAppS-0.8.2 http://happs.org/HAppS Einar Karttunen, Alex Jacobson, David Himmelstrup ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

Terminal does not reset correctly with System.Console.SimpleLineEditor

2004-11-06 Thread Einar Karttunen
This occurs with the Debian ghc package version 6.2.1 and the binary cvs snapshot of 20041017, both on i386 linux and in an xterm. - Einar Karttunen ___ Glasgow-haskell-users mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/glasgow

Re: Newbie question

2005-01-09 Thread Einar Karttunen
is print (foldl (+) 0 nums) - Einar Karttunen ___ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

schedule: re-entered unsafely - with heavy concurrent load

2005-02-18 Thread Einar Karttunen
csock `E.catch` print) acceptLoop sock handle sock = do hPutStr sock HTTP/1.0 200 OK\r\nContent-Type: text/plain\r\n\r\n hPutStr sock (This is the body for the request to\n++hope you like this.\n\nnow garbage:\n) hClose sock - Einar Karttunen

Re: schedule: re-entered unsafely - with heavy concurrent load

2005-02-19 Thread Einar Karttunen
:-) - Einar Karttunen ___ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Bug in placing _stub.o files with HEAD

2005-07-29 Thread Einar Karttunen
as it is expected as dist/build/Network/GnuTLS/IOWrap_stub.o - Einar Karttunen ___ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

ghc-6.4.1: panic - Prelude.last: empty list

2005-10-30 Thread Einar Karttunen
of the compile with -v9 is at the address below: http://cs.helsinki.fi/u/ekarttun/haskell/log.txt Is there anything else I should do to isolate the error better? - Einar Karttunen ___ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http

Preferred way of submitting patches

2005-12-17 Thread Einar Karttunen
Hello What is the preferred way of submitting patches at the moment? I tried using Trac but it seems that users without an account on haskell.org cannot attach files... Is using Trac and linking to the patch hosted externally the way to go? - Einar Karttunen

Re: storing highly shared data structures

2005-12-22 Thread Einar Karttunen
On 22.12 14:43, Christian Maeder wrote: How can I detect this sharing in order to avoid traversing the very same symbol table for every symbol? By using System.Mem.StableName SerTH (http://cs.helsinki.fi/u/ekarttun/SerTH/) implements this, so you can look at the source for pointers. I've

Re: new i/o library

2006-01-27 Thread Einar Karttunen
of window needs to be implemented - and this is easily done with read/write. - Einar Karttunen ___ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Re: GHC 6.5 error? Illegal polymorphic or qualified type

2006-04-16 Thread Einar Karttunen
) In the type signature for `foo': foo :: (Monad m) = AnyE (m t) - Einar Karttunen ___ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Re: using ghc with make

2006-04-20 Thread Einar Karttunen
, strings. m/m files support is planned but now has just preliminary implementation Having these as separate would be very nice. I think that a separately packaged AltBinary would be much easier to use for many people rather than force a dependency on the rest of Streams. - Einar Karttunen

GHC6.5 + TH + Profiling

2006-04-23 Thread Einar Karttunen
of this if needed. - Einar Karttunen ___ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Re: Building ghc-6.4 on Solaris x86

2006-04-29 Thread Einar Karttunen
this can help you further. No guarantees. http://www.cs.helsinki.fi/u/ekarttun/physrules/ghc-6.4.1-i386-unknown-solaris2.tar.bz2 - Einar Karttunen ___ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman

Re: Replacement for GMP: Update

2006-08-10 Thread Einar Karttunen
that force license related things. I think this is one reason GMP is being replaced. ps. personally I don't think the advertising clause is bad, but I think it is bad to force it on other users. - Einar Karttunen ___ Glasgow-haskell-users mailing list

Re: small errors in ghc 6.6

2006-09-20 Thread Einar Karttunen
On 19.09 21:28, Tomasz Zielonka wrote: On Tue, Sep 19, 2006 at 09:13:56PM +0200, Rene de Visser wrote: I would suggest -fforce-recomp for force recompilation. -frecompile-all - Einar Karttunen ___ Glasgow-haskell-users mailing list Glasgow-haskell

Re: ghc-6.6 candidate Win32 installer

2006-10-14 Thread Einar Karttunen
lack the space for hosting such a thing. - Einar Karttunen ___ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Pragmas for FFI imports

2006-02-16 Thread Einar Karttunen
). These changes would not break any existing code. - Einar Karttunen ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime

[Haskell-cafe] Still not dead

2006-07-21 Thread Einar Karttunen
back to hacking things when I get everything fixed. - Einar Karttunen ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Serializing Functions and Actions for Distributed Programming

2006-07-30 Thread Einar Karttunen
is quite transparent. - Einar Karttunen ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Serializing Functions and Actions for Distributed Programming

2006-07-30 Thread Einar Karttunen
functions. This is possible as lambdabot has the source code rather than an arbitrary Haskell expression at runtime. Basically how does one differentiate between: (\x - unsafePerformIO somethingNasty `seq` (x+1)) and (\x - x + 1) at runtime. - Einar Karttunen

Re: [Haskell-cafe] The difficulty of designing a sequence class

2006-08-01 Thread Einar Karttunen
) e class Foldable c where fold :: ElementType c a = (a - b - b) - b - c - b This won't work at the moment due to limitations in GHC, but seems like a cleaner solution. - Einar Karttunen ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http

Re: [Haskell-cafe] Serialising types with existential data constructors

2006-09-13 Thread Einar Karttunen
decoder-function and get the appropriate decoder from there for the type in question. - Einar Karttunen ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Traversing a graph in STM

2006-09-13 Thread Einar Karttunen
(= TVars) as visited. In addition multiple concurrent searches should be possible. Is it possible to avoid passing around an explicit Set of visited nodes? And is there a better way of getting TVar identity than StableNames? - Einar Karttunen ___ Haskell

Re: [Haskell-cafe] Traversing a graph in STM

2006-09-13 Thread Einar Karttunen
On 13.09 08:48, Chris Kuklewicz wrote: And the concurrent searches are isolated from each other? Or are you performing a single search using many threads? Isolated from each other. Mainly dreaming of the per-transaction variables attached to the nodes :-) - Einar Karttunen

[Haskell-cafe] Re: [Haskell] BitSyntax for Haskell

2006-09-25 Thread Einar Karttunen
a test part to ReadType: Test :: ReadType a - (a - Bool) - ReadType Test (or a - m ()) in the monadic case. * Add a way to limit the size of a LengthPrefixed: e.g. [Unsigned 4, LengthPrefixed] is very unsafe, the app should have a way to control the maximum length. - Einar Karttunen

Re: [Haskell-cafe] source code for haskell web server?

2006-09-28 Thread Einar Karttunen
, transactions, etc.? It would be very nice to have a common format. Historically HAppS has used ByteStrings in HTTP, while most other libraries have used Strings. The HAppS format is: http://happs.org/auto/apidoc/HAppS-Protocols-HTTP-LowLevel.html#t%3ARequest - Einar Karttunen

[Haskell-cafe] Re: [Haskell] BitSyntax for Haskell

2006-09-28 Thread Einar Karttunen
(no Haskell value produced), but check that they are valid in the data stream. - Einar Karttunen ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Eager global IO actions (per module initialization)

2006-09-28 Thread Einar Karttunen
, but additionally I want to call 'registerDecoderForType MyType decodeMyType' automatically on startup. Calling registerDecodeForType for all types in main gets very tedious and error-prone when doing things by hand. Thus an automated solution would be very nice. - Einar Karttunen

Re: [Haskell-cafe] source code for haskell web server?

2006-09-28 Thread Einar Karttunen
without unpacking first which is slow 5) One can already easily write functions that handle setting anything string-like as the body. But moving from [ByteString] into a lazy ByteString makes sense. - Einar Karttunen ___ Haskell-Cafe mailing list Haskell

Re: [Haskell-cafe] Deriving class instances using DrIFT

2006-10-30 Thread Einar Karttunen
. Another possibility is that you could replicate just the data declarations by hand, and use DrIFT -r to just spit out the derivations and put those in a file on their own. How about using Template Haskell for getting the definition and then giving that to DrIFT? - Einar Karttunen

Re: [Haskell-cafe] invalid character encoding

2005-03-19 Thread Einar Karttunen
causes the least problems. If the program wishes to display them in a graphical environment then they have to be converted to a string, but very many apps never display the filenames... - Einar Karttunen ___ Haskell-Cafe mailing list Haskell-Cafe

[Haskell-cafe] Functional dependencies and type inference

2005-07-15 Thread Einar Karttunen
a In the second argument of `foo', namely `Wrap' My guess is that GHC cannot see that the functional dependency guarantees that there are no instances which make the inferred type invalid. Any solutions to this problem? - Einar Karttunen ___ Haskell

Re: [Haskell-cafe] weired

2005-07-16 Thread Einar Karttunen
*Main 234566678786 :: Int -671099094 Which explains the result. To make the program work use Integer instead of Int. - Einar Karttunen ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] ForeignPtrs with liveness dependencies

2005-07-25 Thread Einar Karttunen
with multiple ForeignPtr A. GHC documentation tells that touchForeignPtr is not enough as it makes no guarantees about when the finalizers are run. If it helps the finalizers are C functions which neither block nor perform callbacks into Haskell. - Einar Karttunen

Re: [Haskell-cafe] ForeignPtrs with liveness dependencies

2005-07-26 Thread Einar Karttunen
a single finalizer which first calls the C-side cleanup function for Foo and then executes all the IO-actions inside the IORef. Now the association becomes associate (Foo _ ref) bar = atomicModifyIORef ref (\lst - (touchForeignPtr bar : lst, ())) - Einar Karttunen

Re: [Haskell-cafe] ForeignPtrs with liveness dependencies

2005-07-26 Thread Einar Karttunen
are not alive, then both finalizers can run, in any order. So reference counting the objects is the solution? I realise this is very subtle. By all means suggest improvements to the docs. Mentioning that references from finalizers don't count could help someone not to repeat my mistakes. - Einar

Re: [Haskell-cafe] Using unsafePerformIO

2005-08-01 Thread Einar Karttunen
You might want to use unsafeInterleaveIO :: IO a - IO a. It allows IO computation to be deferred lazily. In the particular example co' (x:xs) = do c1 - unsafeInterleaveIO (co' xs) c - f (x:xs) if (c==1) then return (1:c1) else return (0:c1) - Einar Karttunen

[Haskell-cafe] Binary parser combinators and pretty printing

2005-09-13 Thread Einar Karttunen
://erlang.se/doc/doc-5.4.8/doc/programming_examples/bit_syntax.html) and it is very nifty for some purposes. getPacket = do mid:32, sid:32, rid:32, len:32 rest:len/binary ... The list of lists gets nontrivial here too... - Einar Karttunen

Re: [Haskell-cafe] Binary parser combinators and pretty printing

2005-09-15 Thread Einar Karttunen
library released. Currently my parsers just use [FastString] (thus support lazy IO), peek and poke. - Einar Karttunen ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Binary parser combinators and pretty printing

2005-09-15 Thread Einar Karttunen
datatypes (SerTH). EK Maybe even the tuple could be eliminated by using a little of TH. it may be eliminated even without TH! :+: and :*: should work, although i don't tried this I don't know how generics work in newer versions of GHC, but it may be worth investigating. - Einar Karttunen

[Haskell-cafe] throwDyn typing fun

2005-11-11 Thread Einar Karttunen
wanted to say throwDynTo someThreadId SomeException and they both have types which unify with IO (). I think using a class Typeable = DynamicException a where ... and throwDyn :: DynamicException a = a - b could make more sense. - Einar Karttunen ___ Haskell

Re: [Haskell-cafe] Haskell GUI on top of Xlib?

2005-11-28 Thread Einar Karttunen
some nice code from that. If it works well the end result should be a pure Haskell X library. - Einar Karttunen ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] STM commit hooks

2005-11-29 Thread Einar Karttunen
. Is there a way to implement the commit that works? - Einar Karttunen ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] STM and `orElse` on a few thousand TMVars

2005-12-06 Thread Einar Karttunen
. If you want to use STM then a global TVar Int should work fine. - Einar Karttunen ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Opening the same file multiple times

2005-12-11 Thread Einar Karttunen
no simpler solution? - Einar Karttunen ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Opening the same file multiple times

2005-12-11 Thread Einar Karttunen
On 11.12 22:26, Donn Cave wrote: Quoth Einar Karttunen ekarttun@cs.helsinki.fi: | It seems that opening the same file multiple times (one writer | and multiple readers) is not supported at least on *nix with | GHC. I want to use one Handle to use append data till the | end of the file while

Re: [Haskell-cafe] Opening the same file multiple times

2005-12-12 Thread Einar Karttunen
of doing things? Most of the operations will also hit the disk, and be slow (safe) FFI calls. - Einar Karttunen ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Optimizing a high-traffic network architecture

2005-12-14 Thread Einar Karttunen
--- but the code looks kind of ugly Is there a reason you need block for checkTimers? What you certainly want to do is ignore exceptions from the timer actions. - Einar Karttunen ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org

Re: [Haskell-cafe] Optimizing a high-traffic network architecture

2005-12-15 Thread Einar Karttunen
scenario. An additional problem is that these mechanisms depend on the version of the kernel running on the machine... Thus e.g. not all linux machines will have epoll. - Einar Karttunen ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http

Re: [Haskell-cafe] Optimizing a high-traffic network architecture

2005-12-16 Thread Einar Karttunen
On 16.12 07:03, Tomasz Zielonka wrote: On 12/16/05, Einar Karttunen ekarttun@cs.helsinki.fi wrote: To matters nontrivial all the *nix variants use a different more efficient replacement for poll. So we should find a library that offers a unified interface for all of them, or implement one

[Haskell-cafe] Re: [Haskell] A simple server (or how to do io).

2005-12-21 Thread Einar Karttunen
killServer s1 killServer s2 For simple testing you might want to just use getLine to wait for the right time to exit. - Einar Karttunen ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] binary IO

2005-12-28 Thread Einar Karttunen
FastPackedStrings. http://www.uncurry.com/repos/TzDNS Nice, here is my shot at DNS - http://cs.helsinki.fi/u/ekarttun/haskell/hdnsd-20051227.tar.bz2 feel free to take bits if you are interested. The serialization/deserialization uses Ptrs. - Einar Karttunen

Re: [Haskell-cafe] In for a penny, in for a pound.

2006-01-09 Thread Einar Karttunen
the impure one at least. I took the liberty of submitting some of these. Please keep in future the comment lines in the entries, because Shootout wants the names of the contributers. - Einar Karttunen ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

[Haskell-cafe] Re: Shootout favoring imperative code

2006-01-11 Thread Einar Karttunen
become combineTo a i (+) b i. - Einar Karttunen ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] I/O and utf8

2006-01-11 Thread Einar Karttunen
? The BOM is used to mark the encoding (http://en.wikipedia.org/wiki/Byte_Order_Mark), but most UTF-8 streams lack it. I have not seen it used in UTF-8 files either. Do you plan on supporting things like HTTP where the character set is only known in the middle of the parsing? - Einar Karttunen

Re: [Haskell-cafe] standard poll/select interface

2006-02-09 Thread Einar Karttunen
If you want I can look at getting network-alt to implement the interface. - Einar Karttunen ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] getChar + System.Cmd.system + threads causes hangups

2006-02-20 Thread Einar Karttunen
= do putStrLn hello: start system echo hello world! putStrLn hello: done - Einar Karttunen ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] getChar + System.Cmd.system + threads causes hangups

2006-02-20 Thread Einar Karttunen
Here is a version that works fine: myRawSystem cmd args = do (inP, outP, errP, pid) - runInteractiveProcess cmd args Nothing Nothing hClose inP os - pGetContents outP es - pGetContents errP ec - waitForProcess pid case ec of ExitSuccess - return ()

[Haskell-cafe] Looking for an efficient tree in STM

2006-03-08 Thread Einar Karttunen
Hello Does anyone have an efficient tree implemented in STM that supports concurrent updates in an efficient fashion? This seems suprisingly hard to implement - a normal binary tree with links as TVar is very slow and does not scale very well. - Einar Karttunen

[Haskell-cafe] Re: request for code review

2006-03-12 Thread Einar Karttunen
a ParseContext. consolidateOutput :: ParseContext - String consolidateOutput ctx = ctx | output | reverse | concat consolidateOutput = output reverse concat and so on. - Einar Karttunen ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http

Re: [Haskell-cafe] More STUArray questions

2006-03-12 Thread Einar Karttunen
On 12.03 18:44, Martin Percossi wrote: However, just out of curiosity, I'm still curious at how I could do the runSTMatrix, which would really be the icing on the cake in terms of client usability. You might want to look at the definition of Data.Array.ST (at

Re: [Haskell-cafe] GetOpt

2006-04-26 Thread Einar Karttunen
Config Help __- help message - Einar Karttunen ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] GetOpt

2006-04-27 Thread Einar Karttunen
and for an example instance see: http://test.happs.org/HAppS/src/HAppS/Protocols/SimpleHTTP.hs - Einar Karttunen ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Existentially-quantified constructors: Hugs is fine, GHC is not?

2006-05-10 Thread Einar Karttunen
-quantified constructors. You can rewrite the code in a way that GHC accepts it. Just avoid pattern binding your variables. I had the same problem in HAppS code and needed to lift some code to the top level to solve it. - Einar Karttunen ___ Haskell-Cafe

[Haskell-cafe] Implementing tryReadMVar

2004-09-01 Thread Einar Karttunen
?): tryReadMVarzh_fast { W_ mvar, info; /* args: R1 = MVar closure */ mvar = R1; info = GET_INFO(mvar); if (info == stg_EMPTY_MVAR_info) RET_NP(0, stg_NO_FINALIZER_closure); RET_NP(1, vStgMVar_value(mvar); } What is the best way to do this? - Einar Karttunen

Re: [Haskell-cafe] Implementing tryReadMVar

2004-09-01 Thread Einar Karttunen
On 01.09 09:27, Jan-Willem Maessen - Sun Labs East wrote: Einar Karttunen wrote: Hello Is it possible to implement an operation like tryReadMVar :: MVar a - IO (Maybe a) in a good fashion? The semantics should be Read the value of the MVar without taking it if it is filled, otherwise

Re: [Haskell-cafe] Implementing tryReadMVar

2004-09-02 Thread Einar Karttunen
it with tryTakeMVar, as that would break dupChan. Rather we need a tryReadMVar or a different channel abstraction. - Einar Karttunen ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Implementing tryReadMVar

2004-09-02 Thread Einar Karttunen
is starvation of the debug thread---which you may or may not actually care about. I was trying to implement safe tryReadChan, which seems to be very simple with tryReadMVar, without it it seems to suffer from various concurrency problems. - Einar Karttunen

[Haskell-cafe] Strings - why [Char] is not nice

2004-09-20 Thread Einar Karttunen
instance is used at compile time. - Einar Karttunen ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Strings - why [Char] is not nice

2004-09-20 Thread Einar Karttunen
of String doesn't output ['b','l','a'] but bla. This is because Show has a special case for lists: class Show showsPrec :: Int - a - ShowS show :: a - String showList :: [a] - Shows This is not very elegant and does not help when using a boilerplate style traversal. - Einar

Re: [Haskell-cafe] Strings - why [Char] is not nice

2004-09-20 Thread Einar Karttunen
(map unpackPS pss)) And most important they need a conversion (unpackPS), before using them with external libraries which expect Strings. - Einar Karttunen ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Seeking reference(s) relating to FP performance

2004-09-29 Thread Einar Karttunen
with minor corrections (not reflected on the website yet). - Einar Karttunen ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] ArrowLoop examples?

2004-10-23 Thread Einar Karttunen
Hello Are there any examples of using ArrowLoop outside the signal functions? Instances are declared for ordinary functions and Kleisli arrows, but how should they be actually used? - Einar Karttunen ___ Haskell-Cafe mailing list [EMAIL PROTECTED

[Haskell-cafe] Implementing computations with timeout

2005-01-07 Thread Einar Karttunen
= tryPutMVar mv . Just return ()) forkIO (threadDelay time killThread tid tryPutMVar mv Nothing return ()) takeMVar mv btw How would I do the same with the new STM abstraction? - Einar Karttunen ___ Haskell-Cafe mailing list Haskell-Cafe

Re: [Haskell-cafe] Implementing computations with timeout

2005-01-07 Thread Einar Karttunen
then using the TMVar has few advantages over using an MVar. - Einar Karttunen ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe