Re: [Haskell-cafe] Unexpected behaviour with send and send-buffer setting

2013-09-03 Thread Joey Adams
On Tue, Sep 3, 2013 at 6:56 PM, Simon Yarde simonya...@me.com wrote:

 I'm new to Haskell and have reached an impasse in understanding the
 behaviour of sockets.

 The crux of my line of enquiry is this;  how can my application know when
 to pause in generating its chunked output if send doesn't block and the
 current non-blocking send behaviour apparently succeeds when the send
 buffer should be full?


'send' will eventually block after enough 'send's without matching
'recv's.  As Brandon explains, there is more buffering going on than the
send buffer.  In particular, the receiving host will accept segments until
its buffer fills up.  TCP implements flow control (i.e. keeps the sender
from flooding the receiver) by having the receiver tell the sender how many
more bytes it is currently willing to accept.  This is done with the
window size value in the TCP segment header [1].

 [1]:
http://en.wikipedia.org/wiki/Transmission_Control_Protocol#TCP_segment_structure
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] PPC binaries for GHC 7.x?

2013-08-21 Thread Joey Adams
On Wed, Aug 21, 2013 at 4:55 AM, Rogan Creswick cresw...@gmail.com wrote:

 Does anyone have PPC binaries for GHC 7.x?

 I've been trying to help a PPC user compile a large haskell application,
 and it (and it's dependencies) require a newer ghc; the latest ppc binaries
 we've found are for 6.10, and we have been unable to compile a never ghc
 from source (6.12 /almost/ worked, but eventually failed with a linker
 error that appears to be unsolvable in the near-term).


What operating system?

Debian Wheezy (stable) supports PowerPC, and has a working GHC 7.4.1.  You
can also try unstable (sid).  Don't install sid packages on stable (I ran
into linker errors with direct-sqlite when I tried that).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] deriving Data.HashTable - stack overflow

2013-08-08 Thread Joey Adams
On Thu, Aug 8, 2013 at 12:22 PM, Lyle Kopnicky li...@qseep.net wrote:

 ...

 So I went to the Data.Hashable page and looked up examples on how to
 derive a Hashable instance for my datatype:

 http://hackage.haskell.org/packages/archive/hashable/latest/doc/html/Data-Hashable.html

 The problem occurs even when using the sample code on the page:


 {-# LANGUAGE DeriveGeneric #-}

  import GHC.Generics (Generic)
  import Data.Hashable

  data Colour = Red | Green | Blue
deriving Generic

  instance Hashable Colour

 If I then type `hash Red` I get a stack overflow.

 I am using the Haskell Platform, so I have hashable-1.1.2.5, but I notice
 the docs are for hashable-1.2.0.10. If I install 1.2.0.10 though, other
 code in my project breaks - seems like one part doesn't recognize the
 instances from another part. So I'll stick with the platform version.

 ...


Generic support was added in hashable-1.2.  Before then, the default
implementations for `hash` and `hashWithSalt` were written in terms of each
other:

hash = hashWithSalt defaultSalt
hashWithSalt salt x = salt `combine` hash x

Because you did not give an implementation for either of these, both
default implementations were used, leading to a loop.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ordNub

2013-07-14 Thread Joey Adams
On Sun, Jul 14, 2013 at 7:31 AM, Clark Gaebel cgae...@uwaterloo.ca wrote:

 Similarly, I've always used:

 import qualified Data.HashSet as S

 nub :: Hashable a = [a] - [a]
 nub = S.toList . S.fromList

 And i can't think of any type which i can't write a Hashable instance, so
 this is extremely practical.

This won't yield results lazily (e.g. nub (repeat 'x') = _|_ instead of 'x'
: _|_), but Niklas' ordNub will.  His ordNub can be translated directly to
HashSet and still have the stability and laziness properties.

A difficulty with putting ordNub in Data.List is that it depends on
containers, which is outside of the base package.  Some options:

 * Move the implementation of Set to base.

 * Implement a lean version of Set in base that only provides 'insert' and
'member'.

 * Define ordNub in Data.Set instead.

Adding a Hashable-based nub to base would be even more problematic, since
you'd need Hashable in base.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [database-devel] Announcing postgresql-libpq-0.8.2.3

2013-07-08 Thread Joey Adams
On Mon, Jul 8, 2013 at 9:03 PM, Leon Smith leon.p.sm...@gmail.com wrote:

 I just fixed a fairly serious performance problem with postgresql-libpq's
 binding to PQescapeStringConn;   in was exhibiting a non-linear slowdown
 when more strings are escaped and retained.


 I'd like to point out a somewhat related bottleneck in postgresql-simple
(but not postgresql-libpq).  Every PQescapeStringConn or PQescapeByteaConn
call involves a withMVar, which is about 100ns on the threaded RTS on my
system.  Taking the Connection lock once for the whole buildQuery call
might be much faster, especially for multi-row inserts and updates.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to design an network client with user program.

2013-04-15 Thread Joey Adams
I've been struggling with a similar situation: a client and server that
communicate with binary-encoded messages, sending heartbeats (dummy
messages) every 30 seconds, and timing out the connection if no response is
received in 3 minutes.  The client sends data to the server, while also
listening for configuration changes from the server.  The connection needs
to interact with multiple threads on both sides.

See http://ofps.oreilly.com/titles/9781449335946/sec_conc-server.html (Parallel
and Concurrent Programming in Haskell, Chapter 9) for a thorough example of
using STM to write a simple networked application.  You may want to read
some of the previous chapters if you have trouble understanding this one.

If your program becomes an overwhelming tangle of threads, tackle it like
any other complexity: break your program into modules with simple
interfaces.  In particular, build your connection module in layers.  For
example, you could have a module that serializes messages:

data Config = Config { host :: HostName, port :: PortNumber }

data Connection = Connection
{ connBase :: Handle
, connRecvState :: IORef ByteString
  -- ^ Leftover bytes from last 'recv'
}

connect :: Config - IO Connection
close :: Connection - IO ()

send :: Connection - Request - IO ()
recv :: Connection - IO (Maybe Response)

On top of that, timed messages:

data Connection = Connection
{ connBase :: Base.Connection
, connSendLock :: MVar SendState
}

data SendState = SendOpen | SendError SomeException

Here, both 'send' and a timer thread take the send lock.  If either fails,
it places 'SendError' in the MVar to prevent subsequent accesses.

MVar locking is pretty cheap: about 100 nanoseconds per withMVar, versus
several microseconds per network I/O operation.  Don't be afraid to stack
MVar locks if it makes your code easier to maintain.

@Michael Snoyman: The Connection example above is one case where resumable
conduits might be useful.  For Connection to use conduits, 'recv' and
'send' would have to feed conduits incrementally.  Otherwise, it'd need a
different interface (e.g. return Source and Sink).

I wrote a conduit-resumable package [1], but did not release it because of
a semantic issue regarding leftovers: if a conduit has leftovers, should
they go back to the source, or stay with the conduit?  conduit-resumable
does the former, but we'd want the latter here.

 [1]: https://github.com/joeyadams/hs-conduit-resumable
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simple way to do something like ArrowChoice.right on a Conduit? (version 1.0.0)

2013-03-08 Thread Joey Adams
On Wed, Mar 6, 2013 at 1:42 AM, Michael Snoyman mich...@snoyman.com wrote:


 I'm still not sure I follow this. In the example I linked to, the go
 function within breaker could arbitrarily modify the data before it gets
 passed on to the inner Conduit. So it seems like it should be possible to
 achieve your goals this way. But I may just not fully understand your use
 case.


I would have to put my entire message handler in a Sink monad.  Also, I'm
not sure this approach would work if I wanted to use multiple conduits to
process different types of messages, since everything has to go through the
zlib conduit.

In any case, my existing code is a StateT computation.  It'd be convenient
if I could just make the ResumableConduit part of my state, rather than
turning all that code into a Sink.

I pushed a resumable branch [1] with a (stub) Data.Conduit.Resumable
module.  It has ResumableSource, ResumableSink, and ResumableConduit.
Data.Conduit re-exports ResumableSource operations.

 [1]: https://github.com/joeyadams/conduit/tree/resumable
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Library API design: functional objects VS type classes

2013-03-05 Thread Joey Adams
On Mon, Mar 4, 2013 at 5:50 PM, Rob Stewart robstewar...@gmail.com wrote:

 ...
 -
 import Control.Concurrent

 -- API approach 1: Using type classes
 class FooC a where
   mkFooC :: IO a
   readFooC :: a - IO Int
   incrFooC :: a - IO ()


I recommend taking 'mkFooC' out of the typeclass.  It keeps you from being
able to (easily) construct a 'FooC' from dynamic data, e.g.:

mkFoo :: Host - Port - IO MyFoo

After this change, the typeclass approach and the data constructor approach
are nearly equivalent, except:

 * With the typeclass approach, the compiler passes the dictionary
implicitly, which can be more convenient to use (e.g. `readFooC a` instead
of `readFooC (getFoo a)`).

 * With the typeclass approach, you have to define a Foo type to contain
the environment needed for Foo methods.  With the record approach, you can
just construct and use a FooT record directly.

Either way, don't forget about simple encapsulation:

data LineDevice -- abstract

-- Some LineDevice constructors for common tasks
stdio :: LineDevice
openFile :: FilePath - IO LineDevice
connectTo :: HostName - PortId - IO LineDevice

getLine :: LineDevice - Int - IO ByteString
putLine :: LineDevice - ByteString - IO ()

This interface is very easy to understand.  If you want to let users make
their own LineDevice objects, you can still provide an internal module
with something like this:

data Driver = Driver
{ getLine :: Int - IO ByteString
, putLine :: ByteString - IO ()
}

newLineDevice :: Driver - IO LineDevice

Hope this helps,
-Joey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simple way to do something like ArrowChoice.right on a Conduit? (version 1.0.0)

2013-03-05 Thread Joey Adams
On Tue, Mar 5, 2013 at 9:24 AM, Michael Snoyman mich...@snoyman.com wrote:

 ...
 I'm not sure if I entirely understand your use case, but in general it
 should be possible to have multiple Conduits running one after the other.
 Here's an example of restarting an accumulator after every multiple of 5:


 https://www.fpcomplete.com/user/snoyberg/random-code-snippets/multiple-conduits


Neat.  I didn't think to do that with plain Conduits.  I did realize I
could use a resumable conduit as a temporary filter (basically what your
example does).  This suggests that a resumable conduit can be used in any
consumer (Conduit or Sink), not just a sink.  Perhaps it can even be used
in a producer, though different operators would be needed (+$= instead of
=$+).

In my compression example, the incoming message sink needs to feed chunks
of compressed data to a zlib conduit.  It can't just hand full control of
the input to zlib; it has to decode messages, and only send CompressedData
messages through zlib.  I need a resumable conduit for that.

Here's my current implementation of resumable conduits [1].  I don't know
much about conduit finalizers; I mostly followed 'connectResume' and
'pipeL'.

The main wrinkle is that when the ResumableConduit receives an upstream
terminator, it forwards it to the sink, rather than telling the conduit
that the stream ended.  This allows the conduit to be reused.  Only when we
finish the ResumableConduit () do we send it the stream terminator.

I'll continue toying with this.  It might be possible to factor out
terminator forwarding, and generalize connectResume to support resumable
sources, conduits, and sinks.

Thanks for the help,
-Joey

 [1]:
https://github.com/joeyadams/hs-resumable-conduit/blob/master/ResumableConduit.hs
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simple way to do something like ArrowChoice.right on a Conduit? (version 1.0.0)

2013-03-04 Thread Joey Adams
On Sun, Mar 3, 2013 at 10:24 PM, Joey Adams joeyadams3.14...@gmail.comwrote:

 ...
 Here's a possible API for a resumable Conduit:

 newtype ResumableConduit i m o = -- hidden --

 newResumableConduit :: Monad m = Conduit i m o - ResumableConduit i
 m o

 -- | Feed the 'Source' through the conduit, and send any output from
 the
 -- conduit to the 'Sink'.  When the 'Sink' returns, close the
 'Source', but
 -- leave the 'ResumableConduit' open so more data can be passed
 through it.
 runResumableConduit
 :: Monad m
 = ResumableConduit i m o
 - Source m i
 - Sink o m r
 - m (ResumableConduit i m o, r)
 ...


While trying to implement this, I found a more elegant interface for
resuming the ResumableConduit:

-- | Fuse a 'ResumableConduit' to a 'Sink'.  When the 'Sink' returns,
-- it returns the 'ResumableConduit' so the caller can reuse it.
(=$++) :: Monad m
   = ResumableConduit i m o
   - Sink o m r
   - Sink i m (ResumableConduit i m o, r)

This takes advantage of Sink's return value to forward the
ResumableConduit.  I don't think a ($=++) can be implemented.

Advantages:

 * (=$++) is easier to implement than 'runResumableConduit' since it only
has to fuse two pipes together instead of three.

 * Pretty syntax: (resumable', a) - source $$ resumable =$++ sink
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simple way to do something like ArrowChoice.right on a Conduit? (version 1.0.0)

2013-03-03 Thread Joey Adams
Thanks for the response.  I spent some time thinking about leftovers and
understand the Category issue now.  Thanks for clearing that up.

While trying to work conduits into a program I'm working on, I find myself
wanting something more powerful: a resumable Conduit.

For example, consider receiving a stream of messages over a network:

data Message = Data ByteString | CompressedData ByteString |
RestartCompressor

When CompressedData is received, feed the bytes to a decompressor conduit.
When RestartCompressor is received, close the first decompressor conduit
and fire up a new one.

Supporting restarts needs more than just Conduit i m o - Conduit (Either x
i) m (Either x o).  It involves opening and closing a conduit within
another conduit's operations.

Here's a possible API for a resumable Conduit:

newtype ResumableConduit i m o = -- hidden --

newResumableConduit :: Monad m = Conduit i m o - ResumableConduit i m
o

-- | Feed the 'Source' through the conduit, and send any output from the
-- conduit to the 'Sink'.  When the 'Sink' returns, close the 'Source',
but
-- leave the 'ResumableConduit' open so more data can be passed through
it.
runResumableConduit
:: Monad m
= ResumableConduit i m o
- Source m i
- Sink o m r
- m (ResumableConduit i m o, r)

-- | Tell the conduit there is no more input available, and send the
remaining
-- output (if any) to the 'Sink'.
closeResumableConduit
:: Monad m
= ResumableConduit i m o
- Sink o m r
- m r

Does anyone want to comment on this interface?

Perhaps conduit could have a module called Data.Conduit.Resumable that
contains ResumableSource, ResumableConduit, and ResumableSink.  The
conduit-resumablesink package by Andrew Miller [1] implements
ResumableSink; it just needs to be updated for conduit 1.0.

 [1]: http://hackage.haskell.org/package/conduit-resumablesink
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simple way to do something like ArrowChoice.right on a Conduit? (version 1.0.0)

2013-03-01 Thread Joey Adams
On Thu, Feb 28, 2013 at 9:18 PM, Joey Adams joeyadams3.14...@gmail.comwrote:

 Can I transform a conduit so some values are passed through unchanged, but
 others go through the conduit?  For example:

 right :: Conduit i m o - Conduit (Either x i) m (Either x o)


Actually, I didn't need this after all.  I'm using Automaton from the
arrows package for the first part of my pipeline.  Only the zlib
compression step is a Conduit, so I can just use arrow functions to lift
Flush to the rest.

Nonetheless, someone else might want to do this.  Now that I think of it,
not all of the arrow operations make sense (in particular, (***)), but
splitting data between conduits (like ArrowChoice (+++)) does make sense, I
think.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Help: Main: thread blocked in MVar operation

2012-10-23 Thread Joey Adams
On Tue, Oct 23, 2012 at 5:03 PM, José A. Lopes jose.lo...@ist.utl.pt wrote:
 Hey everyone,

 I changed my code I now I get the following error message
 Main: thread blocked indefinitely in an MVar operation

 Before the change, I was using the State monad with runState.
 Then, I changed the code to use the StateT monad transformer wrapped around
 IO monad and runStateT.
 And this change introduced the error message.

 BTW I am using DoRec extension, maybe it is the source of the problem, but I
 don't know.

See if you can reproduce the problem using a small code sample.  The
problem is likely that your program is trying to use a state value
that hasn't been produced yet.

DoRec uses fixIO for the IO monad.  fixIO passes a callback its own
return value.  It's not magic; it only works if the thunk is not
forced within the callback.

Take a look at how fixIO is implemented:


http://hackage.haskell.org/packages/archive/base/latest/doc/html/src/System-IO.html#fixIO

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


Re: [Haskell-cafe] One of the new buzz phrases is Event-Sourcing; is Haskell suitable for this?

2012-09-30 Thread Joey Adams
On Sat, Sep 29, 2012 at 8:46 PM, KC kc1...@gmail.com wrote:
 http://martinfowler.com/eaaDev/EventSourcing.html

 http://martinfowler.com/articles/lmax.html

This notion of Capture all changes to an application state as a
sequence of events sounds a lot like what John Carmack did in Quake 3
[1]:

 I settled on combining all forms of input into a single system event queue, 
 similar to the windows message queue. My original intention was to just 
 rigorously define where certain functions were called and cut down the number 
 of required system entry points, but it turned out to have much stronger 
 benefits.

 [1]: http://www.team5150.com/~andrew/carmack/johnc_plan_1998.html#d19981014

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


Re: [Haskell-cafe] Platform Versioning Policy: upper bounds are not our friends

2012-08-16 Thread Joey Adams
On Wed, Aug 15, 2012 at 3:38 PM, Bryan O'Sullivan b...@serpentine.com wrote:
 I propose that the sense of the recommendation around upper bounds in the
 PVP be reversed: upper bounds should be specified only when there is a known
 problem with a new version of a depended-upon package.

I, too, agree.  Here is my assortment of thoughts on the matter.

Here's some bad news: with cabal 1.14 (released with Haskell Platform
2012.2), cabal init defaults to bounds like these:

  build-depends:   base ==4.5.*, bytestring ==0.9.*, http-types ==0.6.*

Also, one problem with upper bounds is that they often backfire.  If
version 0.2 of your package does not have upper bounds, but 0.2.1 does
(because you found out about a breaking upstream change), users who
try to install your package may get 0.2 instead of the latest, and
still get the problem you were trying to shield against.

A neat feature would be a cabal option to ignore upper bounds.  With
--ignore-upper-bounds, cabal would select the latest version of
everything, and print a list of packages with violated upper bounds.

-Joey

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


Re: [Haskell-cafe] Data structure containing elements which are instances of the same type class

2012-08-07 Thread Joey Adams
On Tue, Aug 7, 2012 at 2:03 PM, Daniel Trstenjak
daniel.trsten...@gmail.com wrote:
 Data structure containing elements which are instances of the same type class

Are you looking for existential quantification [1]?

data SomeFoo = forall a. Foo a = a

 [1]: 
http://www.haskell.org/ghc/docs/latest/html/users_guide/data-type-extensions.html#existential-quantification

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


[Haskell-cafe] ANNOUNCE: system-time-monotonic-0.1

2012-08-06 Thread Joey Adams
system-time-monotonic [1] provides access to the system's monotonic
clock.  Usage looks like this:

 * Use 'newClock' to create a new monotonic clock

 * Use 'clockGetTime' to see how much time has elapsed since the clock
was created.

This package currently supports Linux and Windows.  It might also work
on BSD, but I haven't tested it there.

Mac OS X support is currently not implemented, but patches are
welcome.  GHC uses mach_absolute_time and mach_timebase_info; see
ticket #5865 [2].

I also added a handy utility function 'delay', a variant of
threadDelay taking a DiffTime instead of Int microseconds.  Thus:

delay 1.5

Waits 1.5 seconds.  Note that since 'delay' simply calls 'threadDelay'
in a loop, it is disrupted by system clock changes (again, see ticket
#5865).

 [1]: http://hackage.haskell.org/package/system-time-monotonic
 [2]: http://hackage.haskell.org/trac/ghc/ticket/5865

---

The rest of this email describes various hurdles involved in
implementing this package, and how they were addressed.

## GetTickCount

The most obvious one is that GetTickCount has a short wraparound (49.7
days).  Two ways to address this:

 * Don't use GetTickCount; use QueryPerformanceCounter (or similar)
instead.  This is currently how it's done in GHC HEAD.

 * Use GetTickCount, but avoid comparing times that are far apart by
tracking the total difference each time we look at the clock.

I took the second approach, because I found out that
QueryPerformanceCounter is actually less accurate in the long run than
GetTickCount.  In particular, QueryPerformanceCounter stops ticking
(or maybe ticks slower, I forget) when the computer is asleep.

Here's the trick I use to work around GetTickCount's wraparound (pseudocode):

st1 :: Word32
t1  :: DiffTime

newClock:
st1 := GetTickCount()
t1  := 0

clockGetTime:
st2 := GetTickCount()
t2  := t1 + (Int32)(st2 - st1 modulo 2^32)

st1 := st2
t1  := t2

return t2

This workaround only works if clockGetTime is called at least once
every 24.8 days.

It's important that st2 - st1 be done modulo 2^32, to compensate for
wraparound.  However, the result should be converted to a signed
32-bit integer, in case st2 was recorded earlier than st1 (which can
easily happen in a concurrent context).

In particular, here's what you should *not* do (which GHC currently
does, when QueryPerformanceCounter is not available):

st1 = (bigger_type) GetTickCount();
...
st2 = (bigger_type) GetTickCount();
return (st2 - st1)

This will return a bogus value if a wraparound occurred between st1 and st2.

system-time-monotonic tests, at runtime, if GetTickCount64 is
available.  If so, it uses it.  Otherwise, it falls back to
GetTickCount.  Here's the code I used to do the run-time system call
lookup:

/* cbits/dll.c */
typedef ULONGLONG (WINAPI *GetTickCount64_t)(void);

GetTickCount64_t system_time_monotonic_load_GetTickCount64(void)
{
return (GetTickCount64_t)
GetProcAddress(GetModuleHandle(TEXT(kernel32.dll)),
   GetTickCount64);
}


-- System/Time/Monotonic/Direct.hsc
type C_GetTickCount64 = IO #{type ULONGLONG}

foreign import ccall
system_time_monotonic_load_GetTickCount64 :: IO (FunPtr
C_GetTickCount64)

foreign import stdcall dynamic
mkGetTickCount64 :: FunPtr C_GetTickCount64 - C_GetTickCount64

Did I do this right?  In particular:

 * Can I assume the kernel32.dll HMODULE won't be pulled out from under me?

 * Is `foreign import stdcall dynamic` the right incantation for
using a pointer to a WINAPI function?

## CLOCK_MONOTONIC is not actually monotonic on Linux

CLOCK_MONOTONIC is subject to NTP adjustments.  Worse, CLOCK_MONOTONIC
stops when the computer is put to sleep (unlike GetTickCount, which
does the right thing).

Two clocks were introduced very recently in Linux:

 * CLOCK_MONOTONIC_RAW

 * CLOCK_BOOTTIME

I'd like to support CLOCK_BOOTTIME at some point.  I'm not sure if
it's subject to NTP adjustments or not, since the announcement [3]
says:

CLOCK_BOOTTIME is identical to CLOCK_MONOTONIC, except it also
includes any time spent in suspend (as currently measured by
read_persistent_clock()). This allows applications to get a
suspend aware monotonic clock.

One idea would be to hard-code the clockid_t of CLOCK_BOOTTIME and
CLOCK_MONOTONIC_RAW, and try calling clock_gettime with each of these.
 If one of these succeeds, use it.  Otherwise, fall back to
CLOCK_MONOTONIC.  Thus, the compiled binary can test, at runtime, if a
new enough kernel is available.

For now, system-time-monotonic simply uses CLOCK_MONOTONIC.

 [3]: http://lwn.net/Articles/428176/

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


[Haskell-cafe] ANN: stm-sbchan-0.1 - STM channel with maximum total size of items

2012-07-31 Thread Joey Adams
This package provides a bounded channel type for STM.  TBChan (in
stm-chans) and TBQueue (introduced in stm 2.4) are bounded channels
that limit the number of items in the channel.  SBChan, on the other
hand, limits the total size of items in the channel, where size is
defined by providing an instance of the ItemSize class:

data Entry = Entry Int64 ByteString Time

-- | Estimated amount of memory an 'Entry' requires,
-- including channel overhead
instance ItemSize Entry where
itemSize (Entry _ s _) = B.length s + 200

Then, SBChan Entry is a channel that limits (approximately) the
amount of memory the entries take up.

SBChan can also be used as a regular count-bounded channel by using
the SBCItem newtype wrapper, where itemSize is always 1.

http://hackage.haskell.org/package/stm-sbchan

Enjoy!
-Joey

--- Implementation details ---

itemSize returns an Int.  I originally considered using an associated
type, so users could pick their own number type to use.  However, this
would have made the implementation harder to reason about, if we had
to worry about the user picking an ill-behaved number type like Float.
 Besides, Int is usually adequate for representing in-memory sizes.

This library takes a lot of ideas from TChan and TBChan.  I decided to
use the linked list of TVars approach that TChan uses, rather than the
pair of lists approach T(B)Queue uses, to avoid a potential problem
with code like this:

msg - readTBQueue
case msg of
Foo - ...
Bar - ...

If the transaction is repeated a lot due to retries or invalidation,
and readTBQueue needs to turn around the list at this point, then
we'll end up repeating O(n) work a bunch of times.

SBChan uses stm-tlist, a library I wrote that is based on TChan's
internal representation.  Also, SBChan uses the usual trick for
reducing reader-writer contention by having two counters for capacity,
one for readers and one for writers.

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


Re: [Haskell-cafe] Logging pure code

2012-07-29 Thread Joey Adams
On Fri, Jul 27, 2012 at 9:52 AM, Marco Túlio Gontijo e Silva
marcotmar...@gmail.com wrote:
 I thought that the only thing I needed to take care while using
 unsafePerformIO was knowing that the time of execution is undetermined
 and that it could even run more than once.  This is not a problem for
 my logging.  Is there something else I should be aware while using
 unsafePerformIO?

Another thing to be aware of is that unsafePerformIO and STM don't
interact well.  In particular, STM will abort doomed transactions.  If
the transaction is IO that has exception handlers set up, those
handlers won't be run.  This is the case for unsafeIOToSTM, but I'm
not sure if it's the case for unsafePerformIO as well.

Are you using STM in your program?  Also, what version of GHC are you using?

-Joey

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


[Haskell-cafe] A useful function for forking a thread, but letting the parent do setup first

2012-07-18 Thread Joey Adams
Here's a useful little function:

-- | Fork a thread, but wait for the main thread to perform a setup action
-- using the child's 'ThreadID' before beginning work in the child thread.
forkSetup :: (ThreadId - IO (Maybe a, r))
 -- ^ Setup action to be called before the thread begins working
  - (a - IO b)
 -- ^ What to do in the worker thread
  - IO r
forkSetup setup inner =
mask $ \restore - do
mv - newEmptyMVar
tid - forkIO $ join $ takeMVar mv
(ma, r) - setup tid `onException` putMVar mv (return ())
case ma of
Nothing - putMVar mv $ return ()
Just a  - putMVar mv $ restore $ inner a  return ()
return r

A question about 'mask': is it safe to use the 'restore' callback in a
forked thread?  Or might this be invalid in a future version of GHC?
I'm aware that if forkSetup itself is called with exceptions masked,
the child thread will also have exceptions masked.  This seems
reasonable, given that forkIO behaves the same way.

Is a function like this available in some existing library?  If not,
where would be a good home for it?

Thanks for the input!

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


Re: [Haskell-cafe] strange hangs with -threaded runtime

2012-07-13 Thread Joey Adams
On Fri, Jul 13, 2012 at 2:26 PM, Joey Hess j...@kitenet.net wrote:
 Are there any common gotchas with converting to the threaded runtime
 that might provide a hint to what's wrong? My code does not currently
 use Control.Concurrent or threads, although it does use some libraries
 like MissingH that use forkIO or forkOS.

Off the top of my head, I'm not aware of any (non-Windows-related)
gotchas with using -threaded.  However, some functions in MissingH
(e.g. in System.Cmd.Utils) call forkProcess.  To quote the
documentation of forkProcess [1]:

---
forkProcess comes with a giant warning: since any other running
threads are not copied into the child process, it's easy to go wrong:
e.g. by accessing some shared resource that was held by another thread
in the parent.
---

Perhaps the forked process is inheriting an interleaved computation
that tries to use resources in the parent process.

 [1]: 
http://hackage.haskell.org/packages/archive/unix/latest/doc/html/System-Posix-Process.html#v:forkProcess

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


Re: [Haskell-cafe] [Haskell] ANNOUNCE: control-monad-loop 0.1

2012-07-09 Thread Joey Adams
On Mon, Jul 9, 2012 at 8:28 AM, Roman Cheplyaka r...@ro-che.info wrote:
 Very nice!

 Here's a patch to generalize foreach to any Foldable:
 https://github.com/joeyadams/haskell-control-monad-loop/pull/1

Thanks for the patch!  I merged it, but I plan to wait a little while
before uploading another release to Hackage.  This changes the
signature of an existing function, so I'll have to bump the major
version number.

 Also, it's not obvious how your tests work. Please consider using HUnit
 and test-framework (or similar) to organize them.

The tests currently aren't automated.  It's hard to write an automated
test to make sure a program doesn't leak.  Not impossible (thanks to
GHC.Stats), but hard.

Thanks for pointing out test-framework, though.

-Joey

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


Re: [Haskell-cafe] Linking against Sqlite3 on Windows problem

2012-07-09 Thread Joey Adams
On Mon, Jul 9, 2012 at 3:56 AM, Eugene Dzhurinsky jdeve...@gmail.com wrote:
 Hi all!

 I created simple application, which uses sqlite3 as it's datastore back-end. I
 faced no problems when building and running it on Linux, but after I tried to
 build it on Windows, I see weird linking error:

You could use the bundled sqlite3.c instead:

cabal install --flags=builtin-sqlite3

Unfortunately, the sqlite3 package currently ships with a very old
version of sqlite3.c (version 3.5.9).  I submitted a bug report:

https://github.com/GaloisInc/sqlite/issues/1

Until a fix is pushed, you can try downloading the latest sqlite3.c
yourself, and placing it at sqlite3.6/sqlite3.c .  I don't know if you
will encounter any compatibility issues or not.

Hope this helps,
-Joey

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


[Haskell-cafe] ANNOUNCE: control-monad-loop 0.1

2012-07-08 Thread Joey Adams
This package provides imperative-style loops supporting continue and
break.  For example:

import Control.Monad
import Control.Monad.IO.Class
import Control.Monad.Trans.Loop
import Control.Monad.Trans.Class

main :: IO ()
main =
foreach [0..] $ \i -
foreach [0..] $ \j - do
when (j == 0) $
continue-- skip to next iteration
when (j = 5) $
exit-- exit the loop
when (i = 5) $
lift exit   -- exit the outer loop by calling 'exit'
in the parent monad
liftIO $ print (i, j)

It works by having the loop body run under the LoopT monad
transformer, which provides early exit functions 'continue' and
'exit'.  Functions like 'foreach' and 'while' run a LoopT callback,
passing it continuations defining 'continue' and 'exit'.

http://hackage.haskell.org/package/control-monad-loop

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


Re: [Haskell-cafe] Threads and hGetLine

2012-04-28 Thread Joey Adams
On Sat, Apr 28, 2012 at 2:23 PM, H. M. h._h._...@hotmail.com wrote:
 There are two threads, one which is waits on input via
 hGetLine
 and another, which should terminate this thread or close this handle.

 hClose
 as well as
 killThread
 doesn't seem to work, caused by the fact, that the thread is blocked until 
 input
 is availiable.

What OS?  GHC currently doesn't have proper IO manager support for
Windows.  On Windows, IO is performed through FFI calls.  An FFI call
masks asynchronous exceptions (C code generally doesn't expect to be
interrupted at arbitrary points in time).  If another thread tries to
`killThread` the thread waiting for input, the exception will not be
received until the FFI call completes.  This means both threads will
hang.

-Joey

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


Re: [Haskell-cafe] Looking for an heap-like data structure allowing efficient update

2012-03-04 Thread Joey Adams
On Sun, Mar 4, 2012 at 1:27 PM, Arnaud Bailly arnaud.oq...@gmail.com wrote:
 Hello Cafe,
 I am looking for a data structure that would have the following
 informal properties:
  - allow efficient retrieval of minimum element for some ordering
 relation on a computed property of the elements
  - allow efficient update of any element wrt to this property

I think what you're looking for is called a priority search queue.
It supports the operations of both a priority queue and a search tree.
 Two implementations on Hackage are:

 * http://hackage.haskell.org/package/fingertree-psqueue

 * http://hackage.haskell.org/package/PSQueue

Both libraries appear to have the same API.  I'm not sure which of
these is better.  The priority search queue used by GHC's event
manager is based on PSQueue.  On the other hand, fingertree-psqueue is
newer.

In any case, a PSQ is just like a Map in that it binds keys to values.
 The difference is that values are called priorities, as you can
efficiently look up or extract the minimum value.  Note that keys must
be unique (just like with Map), but priorities do not need to be.

It appears that if you want to attach a value in addition to the
priority, you'll need to define a data type.  E.g.:

import Data.PSQueue (PSQ)
import Data.Unique (Unique)

type Time = ... some efficient representation of time values ...

data Event
= Event
{ eventTimeout :: Time
, eventAction  :: IO ()
}

instance Eq Event where
a == b = eventTimeout a == eventTimeout b

instance Ord Event where
compare a b = compare (eventTimeout a) (eventTimeout b)

type EventQueue = PSQ Unique Event

In this case, the PSQ will be able to remove the Event whose
expiration is soonest.  It will also be able to remove an Event by its
Unique key, useful for canceling Events.

Hope this helps,
-Joey

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


Re: [Haskell-cafe] Question about concurrency, threads and GC

2012-03-02 Thread Joey Adams
On Fri, Mar 2, 2012 at 3:04 PM, Alexander V Vershilov
alexander.vershi...@gmail.com wrote:
 Hello, Paul.

 It seems you should not use 3 threads, but run in a data-driven behaviour with
 one thread per client.

I don't think this will work for Paul's situation.  He needs to be
able to send notifications to clients.  This means sending to the
client even when the client has nothing to say at the moment.

I've been grappling with the same problem.  See:

http://www.haskell.org/pipermail/haskell-cafe/2012-January/098495.html

The discussion was recently summed up in Parallel Haskell Digest 8
(scroll down to How to make asynchronous I/O composable and safe?):

http://www.well-typed.com/blog/64

To try to address this problem, I wrote a module called stm-channelize:

http://hackage.haskell.org/package/stm-channelize

However, I did not end up using it.  I would point you to the source
of my channelize function, but I think it's more complicated than it
needs to be.

I, for one, would recommend a three-thread approach.  That is, for
each client, you basically have:

 * A thread for receiving

 * A thread for sending

 * A main thread that waits for the other two threads, and kills them
when one of them finishes or dies.

I'll try to put together a simple chat server example, like the one I
wrote for stm-channelize.

-Joey

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


Re: [Haskell-cafe] Question about concurrency, threads and GC

2012-03-02 Thread Joey Adams
On Fri, Mar 2, 2012 at 7:34 PM, Joey Adams joeyadams3.14...@gmail.com wrote:
 I'll try to put together a simple chat server example, like the one I
 wrote for stm-channelize.

Here it is:

https://github.com/joeyadams/haskell-chat-server-example

See, in particular, the serveLoop function.  When a message is
received from the client, it is written to the send channel of every
other client.  When a message is written on the client's own send
channel, it is transmitted to the client.  The primary thread for the
client waits until one of the worker threads signals completion, then
kills both of the worker threads.

I hope this example gives you some ideas.

-Joey

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


Re: [Haskell-cafe] ANN: network-socket-options 0.1

2012-02-23 Thread Joey Adams
On Wed, Feb 22, 2012 at 10:23 PM, Johan Tibell johan.tib...@gmail.com wrote:
 But the network package doesn't try to let you work with raw file
 descriptors elsewhere (e.g. send and recv.) I'm not saying that
 functions on Fds aren't useful, they are, just that the network
 package is the wrong place for them. I'd put them in the unix package.

Putting them in the unix package means they won't be available for
Windows (where I needed them the most).

 I use Int64 for Microseconds, to avoid truncation when Int is 32 bits.
  2^31-1 microseconds is only 35 minutes and 47.483647 seconds.
 Perhaps I should just use Int and Int64, and be sure to document what
 units are used.

 We should use whatever the underlying OS uses. If that's a 32-bit int,
 using a 64-bit int on the Haskell side doesn't help us. The goal here
 is to faithfully match the underlying APIs.

For SO_RCVTIMEO and SO_SNDTIMEO, Windows and Unix use different
representations.  Windows uses DWORD (unsigned 32-bit) milliseconds,
while Unix uses struct timeval, which has microsecond precision.

-Joey

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


Re: [Haskell-cafe] ANN: network-socket-options 0.1

2012-02-22 Thread Joey Adams
On Wed, Feb 22, 2012 at 5:56 AM, L Corbijn aspergesoe...@gmail.com wrote:
 On Wed, Feb 22, 2012 at 5:58 AM, Joey Adams joeyadams3.14...@gmail.com 
 wrote:
 I released network-socket-options 0.2, adding setSocketTimeouts and
 setHandleTimeouts.  I'll post an announcement in a separate thread
 once the Haddock documentation is generated.

 -Joey

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

 Hi Joey,

 Seeing the large number of getters and setters in this package I was
 wondering if it might be improved by using 'StateVar's from the
 StateVar package.
 http://hackage.haskell.org/package/StateVar

 Lars

 P.S. It does mention OpenGL (where it's actively used), but replacing
 that with 'socket' makes the description seem to fit rather well.

Copying to the mailing list.

Thanks for pointing out StateVar.  However, setSocketOption and
getSocketOption (or variants taking raw Fds or GHC FDs) will not have
a class for socket options to abstract over.  It'd be nicer to see a
list of settable options under the SetSockOpt class, and a list of
gettable options under the GetSockOpt class.

-Joey

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


Re: [Haskell-cafe] ANN: network-socket-options 0.1

2012-02-22 Thread Joey Adams
Thanks for the review!

On Wed, Feb 22, 2012 at 11:15 AM, Johan Tibell johan.tib...@gmail.com wrote:
 The API looks fine except:

 HasSocket - I don't think we want to abstract over sockets here, as we
 don't do so in the rest of the module.

I know it's a bit ugly, but not having it makes it hard to work with
unmanaged sockets (e.g. those buried under Handles).  If the functions
take a managed Socket, you'd have to say something like:

setRecvTimeout (MkSocket fd undefined undefined undefined undefined)
   12000

If they take CInt instead, users of the higher-level API would have to say:

setRecvTimeout (fdSocket sock) 12000

Perhaps representing options with ADTs isn't such a bad idea after
all.  That way, we could have something like:

setSocketOption :: SetSockOpt opt = Socket - opt - IO ()
setRawSocketOption :: SetSockOpt opt = CInt - opt - IO ()

Usage might look like:

setSocketOption sock $ RecvTimeout 12000
Type t - getSocketOption sock

 Seconds and Microseconds - These seem a bit misplaced here. I'd say so with 
 Int.

I use Int64 for Microseconds, to avoid truncation when Int is 32 bits.
 2^31-1 microseconds is only 35 minutes and 47.483647 seconds.
Perhaps I should just use Int and Int64, and be sure to document what
units are used.

It'd be nice to use a strongly-typed time package like time-units, but:

 * It involves conversion to and from Integer

 * It doesn't tell the whole story.  Most quantity values in socket
options are truncated and even modified for OS-specific reasons.

 setHandleTimeout - If we want to keep it at all it should go in
 Network and not be conditionally exported.

I agree.  setHandleTimeouts should simply be a no-op on non-GHC.

 timeouts - we need to think about how this interacts with the I/O
 manager and provide a consistent API across platforms. I suggest we
 leave them out until we have done so.

The ideal solution would be to not even need these.  GHC ought to have
proper IO manager support for Windows, or at least use socket timeouts
or similar to prevent OS threads from hanging indefinitely on IO
operations.  setHandleTimeouts is a workaround, and will be deprecated
as soon as it is no longer necessary.

 I've thought about doing this change before, but I didn't have time to
 fully explore the design space. I'm happy to accept these patches if
 someone does that for me. :)

 In particular:

  * Should we use an algebraic data type to represent options? I don't
 think so, for the reason pointed out in one of the source code
 comments in Joey's library.

We can separate getters and setters using typeclasses GetSockOpt and
SetSockOpt, and having newtype wrappers for each socket option.  See
my setSocketOption example above.

I would do this, but I have other things I need to work on.

  * Are we covering all possible options? Can there be custom options
 that can no longer be set by the user since we're enumerating a fixed
 set of options?
  * Are there any other design trade-offs? Someone needs to read the
 getsockopt and setsockopt man pages thoroughly and make sure we cover
 all the cases.
  * Are we covering all major OSes in the API?

network-socket-options isn't comprehensive.  It currently should have
all of the SOL_SOCKET and IPPROTO_TCP options present in both Linux
and Windows.  It compiles on both.  I haven't tested on Mac OS X or
FreeBSD.

I think it'd be better to start with at least some options, and add
more as users ask for them.  One problem with adding every option we
possibly can right now is that none of the options will get
documented.  If a user asks for a specific option and provides a
reason for needing it, we can include this information in the
documentation.

-Joey

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


Re: [Haskell-cafe] ANN: network-socket-options 0.1

2012-02-21 Thread Joey Adams
On Tue, Feb 21, 2012 at 7:36 PM, Conrad Parker con...@metadecks.org wrote:
 awesome! I've prepared some patches for network to add this module and
 its tests, in this branch:

 https://github.com/kfish/network/tree/options

Cool, thanks!

 I didn't modify any other modules, perhaps Network.Socket.Options
 should be re-exported from Network.Socket, and perhaps
 {get,set}SocketOption should be deprecated?

I agree with deprecating getSocketOption and setSocketOption.  Don't
remove them, just deprecate them.  Network.Socket.Options doesn't
implement all of the options {get,set}SocketOption has, yet (e.g.
RecvLowWater).

I'm not sure about re-exporting Network.Socket.Options, though.
That's a lot to dump into the namespace.  Particularly worrisome names
include:

* getError

* getType

Note the following:

 * I'm going to release network-socket-options 0.1.1 pretty soon.  It
will add higher-level functions for setting socket timeouts, to work
around the lack of a proper IO manager for Windows:

http://trac.haskell.org/network/ticket/2
http://trac.haskell.org/network/ticket/31#comment:1

 * Network.Socket has a getPeerCred function, which gets the
SO_PEERCRED socket option.  Perhaps it should be moved to
Network.Socket.Options (re-exported in Network.Socket for backward
compatibility) and generalized with HasSocket like the other options.

 * A couple of the tests in my test suite require root access.
Consider them optional, as they cover ground already pretty
well-covered by the other tests.

Thanks for the integration work.

-Joey

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


Re: [Haskell-cafe] ANN: network-socket-options 0.1

2012-02-21 Thread Joey Adams
I released network-socket-options 0.2, adding setSocketTimeouts and
setHandleTimeouts.  I'll post an announcement in a separate thread
once the Haddock documentation is generated.

-Joey

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


[Haskell-cafe] ANN: network-socket-options 0.1

2012-02-20 Thread Joey Adams
I added a new package containing wrappers for getsockopt and setsockopt:

http://hackage.haskell.org/package/network-socket-options

The network package already has getSocketOption and setSocketOption.
The problem is, these don't work for socket options that aren't
represented by integers, such as SO_LINGER:

http://trac.haskell.org/network/ticket/23

Another, less serious problem is that getSocketOption and
setSocketOption don't leverage the type system as well as they could.
Many options are boolean values; it'd be better to get and set them
with 'Bool's instead of 'Int's.

network-socket-options implements options using getter and setter
functions, e.g.:

getLinger :: HasSocket sock = sock - IO (Maybe Seconds)

setLinger :: HasSocket sock = sock - Maybe Seconds - IO ()

type Seconds = Int

The HasSocket type class is defined to overload the getters and
setters to work on raw file descriptors, not just Socket objects.

This functionality should probably go in the network package itself.
However, I decided to release it as a separate package so I could
start using it sooner.  If people like it enough, perhaps the network
package can absorb it, as was done with network-bytestring.

-Joey Adams

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


Re: [Haskell-cafe] How to make asynchronous I/O composable and safe?

2012-01-17 Thread Joey Adams
On Tue, Jan 17, 2012 at 3:20 PM, David Barbour dmbarb...@gmail.com wrote:
 I'd say use of asynchronous exceptions should be a last resort. ...

I agree.  However, network libraries in Haskell (e.g. Handle,
Network.TLS) generally don't provide the primitives needed to do that
on the receiving end.  For example, if a thread is blocked on hGetBuf,
it cannot also wait on a signal telling it to stop.  Since hClose on
the same handle will block until the hGetBuf is done, the only way to
stop reading from the handle is to throw an asynchronous exception at
the hGetBuf thread.

Worse, since there is no threadWaitReadHandle :: Handle - IO (),
there's no way to guarantee that hGetBuf will not be interrupted in
the middle of receiving a packet.  From an application perspective,
this invalidates subsequent retrievals unless the protocol is
self-synchronizing.

-Joey

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


Re: [Haskell-cafe] How to make asynchronous I/O composable and safe?

2012-01-17 Thread Joey Adams
I uploaded a package that creates an STM layer over a network connection:

http://hackage.haskell.org/package/stm-channelize

I haven't used it in anger yet, but I hope it's a step in the right
direction.  I included a sample chat client and server.  The client is
pretty cute:

main =
let connect = connectTo localhost (PortNumber 1234) = connectHandle
 in channelize connect  $ \conn -
channelize connectStdio $ \stdio -
forever $ atomically $
(recv conn = send stdio) `orElse`
(recv stdio = send conn)

I use channelize on both the network connection, and on stdin/stdout.

The server is much longer, but shouldn't be terribly confusing.  It
demonstrates kicking out a client without a dangerous asynchronous
exception, something we can't do easily without waiting on
alternatives (i.e. orElse).

-Joey

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


Re: [Haskell-cafe] How to make asynchronous I/O composable and safe?

2012-01-14 Thread Joey Adams
On Sat, Jan 14, 2012 at 1:29 AM, Bardur Arantsson s...@scientician.net wrote:
 So, the API becomes something like:

   runSocketServer :: ((Chan a, Chan b) - IO ()) - ... - IO ()

 where the first parameter contains the client logic and A is the type of
 the messages from the client and B is the type of the messages which are
 sent back to the client.

Thanks, that's a good idea.  Even if I only plan to receive in one
thread, placing the messages in a Chan or TChan helps separate my
application thread from the complexities of connection management.

Is there something on Hackage that will do this for me?  Or will I
need to roll my own?  Namely, convert a network connection to a pair
of channels, and close the connection automatically.  Something like
this:

-- | Spawn two threads, one which populates the first channel with messages
-- from the other host, and another which reads the second channel and sends
-- its messages to the other host.
--
-- Run the given computation, passing it these channels.  When the
computation
-- completes (or throws an exception), sending and receiving will
stop, and the
-- connection will be closed.
--
-- If either the receiving thread or sending thread encounter an exception,
-- sending and receiving will stop, and an asynchronous exception will be
-- thrown to your thread.
channelize :: IO msg_in -- ^ Receive callback
   - (msg_out - IO () -- ^ Send callback
   - IO () -- ^ Close callback
   - (TChan msg_in - TChan msg_out - IO a)
-- ^ Inner computation
   - IO a

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


[Haskell-cafe] How to make asynchronous I/O composable and safe?

2012-01-13 Thread Joey Adams
I'm not happy with asynchronous I/O in Haskell.  It's hard to reason
about, and doesn't compose well.  At least in my code.

I'm currently trying to build a networking layer for my application
using Network.TLS.  Here is a rather minimalist API:

   newtype Connection = Connection (TLSCtx Handle)

   connectClient :: Handle         -- ^ Connection handle, as returned
by 'connectTo'
                 - X509           -- ^ TLS certificate (i.e. public key)
                 - IO Connection

   connectServer :: Handle         -- ^ Connection handle, as returned
by 'accept'
                 - X509           -- ^ TLS certificate (i.e. public key)
                 - TLS.PrivateKey -- ^ TLS private key
                 - IO Connection

   close :: Connection - IO ()

   sendMessage :: Connection - Message - IO ()

   recvMessage :: Connection - ByteString - IO (Message, ByteString)

The module provides little more than connection initialization and
message serialization.  I don't try to use locks or STM to multiplex
the connection or, in the case of recvMessage, hide connection state.
I just be sure to only use sendMessage in one thread at a time, only
use recvMessage in one thread at a time, and marshal the extra bytes
parameter of recvMessage from call to call (with the help of StateT).

I wrote a simple chat server to test it.  The client turned out okay:

   main :: IO ()
   main = do
       cert - getCertificate
       handle - connectTo localhost (PortNumber 1337)
       conn - connectClient handle cert
       _ - forkIO $ forever $ do
           s - getLine
           sendMessage conn $ TestMessage s
       forever $ flip runStateT B.empty $ do
           msg - StateT $ recvMessage conn
           case msg of
               TestMessage s -
                   liftIO $ putStrLn s
               _ -
                   liftIO $ hPrintf stderr
                       Warning: unrecognized message from server: %s\n
                       (messageTypeName msg)

The only glaring problem is that, if the user presses Ctrl+D, the
forked (sending) thread dies, but the main (receiving) thread lingers.
 I'd have to add exception handlers to ensure that when one thread
dies, the other thread dies too.

However, the server is an abomination (see attachment).

Unfortunately, it's not as simple as spawn one thread per client.
We need at least two threads, one to listen for messages from the
client, and another to send messages to the client.  GHC won't let us
simultaneously, in the same thread, wait for input from a connection
and wait for an STM transaction to succeed.

Another source of complexity is: what if we throw an exception at a
thread while it is in the middle of sending a packet?  Then we can't
shut down the connection properly (i.e. Network.TLS.bye), because the
receiver might think the close_notify packet is part of the
interrupted packet.

Having a thread for each client is good, as it:

 * Lets us think about each client separately.  No need to turn our
code inside out or write one big loop that juggles all the clients.

 * Isolates exceptions.  If sendMessage or recvMessage throws an
exception, it doesn't bring the whole server down.

On the other hand, having multiple threads interact with a single
client is hard to think about:

 * We have to synchronize the threads (e.g. when one dies, kill the other one)

 * Multiple places where an exception can arise

 * Can multiple threads interact with the connection handle simultaneously?

So why don't I make my connection API handle some of this?  Well, I
tried.  There are so many ways to do it, and I couldn't find a way
that simplified usage much.  The approach used by Handle and by
Network.TLS is to use MVars and IORefs to ensure that, if two threads
access the same connection, the connection doesn't become totally
corrupt.  If I do the same, then I'll have *three* layers of locking
under the hood.

Worse, the locking done by Handle and Network.TLS doesn't guarantee
much.  I don't know if it's safe to have one thread sending and
another thread receiving.  Especially in the case of Network.TLS,
where 'recvData' automatically handshakes in some cases, which sends
packets.  Since I don't know how much thread safety to expect, I can't
write networking code and know for sure that it is safe.

I'm certainly not protected from interleaved data if multiple threads
send on the same handle.  For example:

import Control.Concurrent
import System.IO

main :: IO ()
main = do
hSetBuffering stdout NoBuffering
_ - forkIO $ putStrLn One sentence.
putStrLn Another sentence.

produces:

AnOonteh esre nsteenntceen.c
e.

That is, I can't rely on putStrLn being atomic.  To produce
intelligible output (without changing the buffering mode), I have to
lock the output each time I write something.  putStrLn doesn't do it
for me.

=== Summary ===

In Haskell, sound logic and a great type system lead to elegant,
composable code in a variety of 

Re: [Haskell-cafe] STM: nested atomically error

2012-01-12 Thread Joey Adams
On Thu, Jan 12, 2012 at 7:48 AM, Johan Brinch brin...@gmail.com wrote:
 Hi all,

 I'm seeing the Control.Concurrent.STM.atomically was nested error,
 but I just can't figure out what's happening. I'm not using any unsafe
 IO (only for debug printing), and the test program is only running one
 thread. Where is a transaction being nested?

 What are the scenarios where this error is reported?

I might as well state the obvious.

The type system prevents this from happening under normal
circumstances.  However, it is possible to circumvent the type system
using, for example, unsafePerformIO or unsafeInterleaveIO:

nest1 :: IO ()
nest1 =
let x = unsafePerformIO $ atomically $ return ()
 in atomically (x `seq` return ())

nest2 :: IO ()
nest2 = do
x - unsafeInterleaveIO $ atomically $ return ()
atomically (x `seq` return ())

In both nest1 and nest2, x is a thunk whose evaluation performs an STM
transaction.  In both cases, this produces an atomically was nested
error.

On GHC, the Debug.Trace functions internally call a C function called
debugBelch (defined in RtsMessages.c).  These don't appear to use
'atomically' at all.  Thus, I doubt using trace will produce an
atomically was nested error.

- Joey

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


Re: [Haskell-cafe] ANN: Monad.Reader Issue 19

2011-10-31 Thread Joey Adams
On Wed, Oct 26, 2011 at 4:24 PM, Bas van Dijk v.dijk@gmail.com wrote:
 I have one question regarding your use of atomicModifyIORef:

  x - atomicModifyIORef ref (\_ - (tmstr, ()))
  x `seq` return ()

 Can't you write that as just: writeIORef ref tmstr? If you're not
 using the previous value of the IORef there's no chance of
 inconsistency.

From the documentation at
http://hackage.haskell.org/packages/archive/base/latest/doc/html/Data-IORef.html
:

IORef operations may appear out-of-order to another thread, ...

...

atomicModifyIORef acts as a barrier to reordering. Multiple
atomicModifyIORef operations occur in strict program order.

Based on this description, it seems that atomicModifyIORef is safer
for writing to an IORef than writeIORef when there are multiple
threads reading and writing it.  If my assessment is correct, I think
Data.IORef should have an atomicWriteIORef :: IORef a - a - IO ()
function to clarify this.  I'm not completely sure about this myself.
Could someone confirm this?

Moreover, it'd be nice if there were writeIORef' and
atomicModifyIORef' functions that force the value.  Doing so would
help people avoid making the mistake described by the author.  It's a
really common mistake.

- Joey

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