Re: [Haskell-cafe] Re: sendfile leaking descriptors on Linux?

2010-02-18 Thread Taru Karttunen
Excerpts from Bardur Arantsson's message of Wed Feb 17 21:27:07 +0200 2010:
> For sendfile, a timeout of 1 second would probably be fine. The *ONLY* 
> purpose of threadWaitWrite in the sendfile code is to avoid busy-waiting 
> on EAGAIN from the native sendfile.

Of course this will kill connections for all clients that may have a
two second network hickup.

> How so? As a user I expect sendfile to work and not semi-randomly block 
> threads indefinitely.

If you want sending something to terminate you will add a timeout to
it. A nasty client may e.g. take one byte each minute and sending your
file may take a few years.

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


Re: [Haskell-cafe] Re: sendfile leaking descriptors on Linux?

2010-02-17 Thread Taru Karttunen
Excerpts from Bardur Arantsson's message of Tue Feb 16 23:48:14 +0200 2010:
> > This cannot be fixed in the sendfile library, it is a 
> > feature of TCP that connections may linger for a long
> > time unless explicit timeouts are used.
> 
> The problem is that the sendfile library *doesn't* wake
> up when the connection is terminated (because of threadWaitWrite)
> -- it doesn't matter what the timeout is.

Even server code without sendfile has the same issue since
all writing to sockets ends up using threadWaitWrite.

System.Timeout.timeout terminates a threadWaitWrite using
asynchronous exceptions.

If you want to detect dead sockets somewhat reliably 
without a timeout then there is SO_KEEPALIVE combined
with polling SO_ERROR every few minutes.

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


Re: [Haskell-cafe] Re: sendfile leaking descriptors on Linux?

2010-02-16 Thread Taru Karttunen
Excerpts from Bardur Arantsson's message of Tue Feb 16 22:57:23 +0200 2010:
> As far as I can tell, all nonblocking networking code is vulnerable to 
> this issue (unless it actually does use threadWaitRead, obviously :)).

There are a few easy fixes:

1) socket timeouts with Network.Socket.setSocketOption
2) just make your server code have timeouts in Haskell

This cannot be fixed in the sendfile library, it is a 
feature of TCP that connections may linger for a long
time unless explicit timeouts are used.

So just document it and in your code using sendfile
wrap it in an application specific timeout.

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


Re: [Haskell-cafe] setNonBlockingFD?

2010-02-04 Thread Taru Karttunen
Excerpts from Magnus Therning's message of Wed Feb 03 21:51:34 +0200 2010:
> Thanks.  That pointed me in the right direction.  I've posted the
> attached patch as a suggested fix to the developer.  Hopefully
> there'll be a compilable version on Hackage soon.

There is now 0.1.5 on Hackage with GHC 6.12 support.

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


Re: [Haskell-cafe] Is Haskell capable of matching C in string processing performance?

2010-01-23 Thread Taru Karttunen
Excerpts from John Millikin's message of Fri Jan 22 19:40:58 +0200 2010:
> Correct me if I'm wrong, but ByteStrings can't contain non-ASCII
> values, right? I'm looking for something like this pseudo-C:
> 
> typedef void (*Callback)(const uint32_t *chars, size_t n_chars, void *);
> WriterState *new_state (Callback, void *);
> 
> I tried using the Text type, but its conversions to Ptr Word16 are all
> O(n) -- not much better than String.

Are you using unicode on the C side with wchar_t?

You can have utf-8 inside ByteStrings.

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


Re: [Haskell-cafe] Re: AlternativePrelude extension

2010-01-17 Thread Taru Karttunen
Excerpts from Roel van Dijk's message of Sun Jan 17 13:50:22 +0200 2010:
> The "extensions" field in a cabal package description is a bit tricky.
> The documentation states "A list of Haskell extensions used by every
> module". This might give the impression that it documents the various
> extensions used in a package. What it actually does is enable those
> extensions for every module.
> 
> Duncan's comments on this ticket are enlightening:
> http://hackage.haskell.org/trac/hackage/ticket/370
> 
> I think the idea of adding a new field "used-extensions" warrants a
> separate ticket.

Why not have Cabal autogenerate that information?

Hackage already displays generated info like "Built on" and thus
it should be doable. i.e.

1) Scan all the source files used for extension pragmas
2) Generate a list of those
3) Include that on Hackage

The functionality needed for this is also needed for validating
the proposed used-extensions field is correct, and thus not harder to
implement.

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


Re: [Haskell-cafe] From records to a type class

2010-01-16 Thread Taru Karttunen
Excerpts from Stephen Tetley's message of Sat Jan 16 10:27:33 +0200 2010:
> If you haven't obviously got dispatch on type then records are certainly fine.

Yes, no dispatch on type.

I got a class based implementation compiling, but it seems overly
complex. Maybe the record approach is better after all.

This is a bit more complex than Parsec unfortunately. (an analogue
would be adding encodings to the types of Parsec parsers)


import Data.Word

data IsDir
data IsFile

type Ino  = Word32
data Attr = Attr {}
 
data Proxy t
type family FT (fht :: ((* -> *) -> *)) (fd :: *)
class FH (t :: (* -> *) -> *) where
fhFre  :: Proxy t -> Word64 -> IO ()
fhAllo :: forall any. FT t any -> IO Word64
fhRe   :: forall any. Word64 -> IO (FT t any)

data UseRaw :: ((* -> *) -> *)
type instance FT UseRaw any = Word64
instance FH UseRaw where
   fhFre _ _ = return ()
   fhAllo= return
   fhRe  = return

data UseStablePtr :: (* -> *) -> (* -> *) -> *
type instance FT (UseStablePtr ty) fh = ty fh
instance FH (UseStablePtr ty) where -- omitted

class FH (FhImpl ty) => Fuse' ty where
  type FhImpl ty :: (* -> *) -> *
  open'  :: ty -> Ino -> IO (FT (FhImpl ty) IsFile)
  read'  :: ty -> Ino -> FT (FhImpl ty) IsFile -> Word64  -> Word32 
-> IO [Word8]
  opendir'   :: ty -> Ino -> IO (FT (FhImpl ty) IsDir)
  getattr'   :: forall fileOrDir. ty -> Ino -> FT (FhImpl ty) fileOrDir 
-> IO Attr

data MyUserType = MyUserType
instance Fuse' MyUserType where
  type FhImpl MyUserType = UseRaw
  open' = \_ _ -> return 22


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


[Haskell-cafe] From records to a type class

2010-01-15 Thread Taru Karttunen
Hello

I am wrapping Fuse in a pure Haskell binding and have some issues
with the interface. Currently I am using a record for managing 
the callback functions, but I think there may be a more elegant 
formulation.

Any ideas how to formulate the Fuse record as a typeclass elegantly?

Some notes:
+ TFs not FDs.
+ Separate fh* implementations (raw/stableptr/custom implemented by user)
  easily selected by the library user.
+ Readable type errors.
+ One large typeclass + overlapping instances works, but seems hacky.
+ MPTCs will probably work but is it good form to use them with TFs?
+ Or is using a record better currently?

ps. Note that the interface is very much simplified for the sake
of the discussion. (e.g. [Word8] instead of ByteString).

> import Data.Word
> 
> data IsDir
> data IsFile
> 
> type Ino  = Word32
> data Attr = Attr {}
> 
> data Fuse (fh :: * -> *) = Fuse {
>   open  :: Ino -> IO (fh IsFile)
> , read  :: Ino -> fh IsFile -> Word64 -> Word32 -> IO [Word8]
> , opendir   :: Ino -> IO (fh IsDir)
> , getattr   :: forall fileOrDir. Ino -> fh fileOrDir -> IO Attr
> -- ...
> 
> -- File handle management
> , fhFree  :: Word64 -> IO ()
> , fhAlloc :: forall any. fh any -> IO Word64
> , fhRef   :: forall any. Word64 -> IO (fh any)
> }
> 
> -- Optimally get rid of this wrapping...
> newtype RawFH t = R { r :: Word64 }
> noFhEmpty :: Fuse RawFH
> noFhEmpty = Fuse { fhFree= \_ -> return ()
>  , fhAlloc   = return . r
>  , fhRef = return . R
>  }
> 
> stablePtrEmpty :: Fuse anyfh
> stablePtrEmpty = Fuse {} -- implement fh* with StablePtrs (omitted)
> 
> -- User file handle type might be like this:
> 
> data Obj t where
> Dir  :: {} -> Obj IsDir
> File :: {} -> Obj IsFile


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


Re: [Haskell-cafe] Re: Cleaner networking API - network-fancy

2009-08-13 Thread Taru Karttunen
Excerpts from Johan Tibell's message of Thu Aug 13 21:41:51 +0300 2009:
> My best advice would be to form an special interest group (SIG) and
> iron out the details. This doesn't have to be anything terribly
> formal. Just a bunch of people who are interested in improving things.
> 
> The SIG could keep a wiki with the current design. This makes it
> easier for both the members and other interested developer to review
> the design and find flaws.

+1 

I would be interested in participating in this.

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


Re: [Haskell-cafe] Re: Cleaner networking API - network-fancy

2009-08-13 Thread Taru Karttunen
Excerpts from Thomas DuBuisson's message of Thu Aug 13 21:09:38 +0300 2009:
> Right now the thought has came to me that the cleanest, most uniform
> method might be to have a Config data type with all these ideas as
> options and use a single 'connect', 'listen' or 'receive' function for
> all the different protocols and their various options.  I'll think on
> it.

UDP does not play nicely with Handles. TCP wants Handles. Thus
using an unified API does not make much sense. The semantics are just
too different. 

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


[Haskell-cafe] Cleaner networking API - network-fancy

2009-08-13 Thread Taru Karttunen
Hello

network-fancy offers a cleaner API to networking facilities in
Haskell. It supports high-level operations on tcp, udp and unix
sockets. 

I would like some feedback on the API
http://hackage.haskell.org/packages/archive/network-fancy/0.1.4/doc/html/Network-Fancy.html

In particular:
* Does the type of the server function in dgramServer make sense?
  or would (packet -> Address -> (packet -> IO ()) -> IO ()) be
  better?
* Does the StringLike class make sense?
* Any other suggestions?

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


Re: [Haskell-cafe] Typeclass for functions taking different kinds of strings

2009-08-05 Thread Taru Karttunen
Excerpts from Neil Mitchell's message of Wed Aug 05 16:36:06 +0300 2009:
> I currently use this library:
> 
> http://community.haskell.org/~ndm/darcs/tagsoup/Text/StringLike.hs
> 

It looks nice but is not really a solution for passing large amounts
of data efficiently. Converting everything to String creates too much
overhead for large chunks of data.

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


[Haskell-cafe] Typeclass for functions taking different kinds of strings

2009-08-05 Thread Taru Karttunen
Hello

It seems like a very common issue to have an API like:

foo   :: String -> Foo
fooBS :: ByteString -> Foo
fooLBS:: L.ByteString -> Foo

is there currently a library that makes unifying them easy?

Below is attached one try at this, does it make sense? I'm thinking of
uploading it to Hackage but would like comments first.

With the library the above code is transformed into:

foo :: StringLike string => string -> Foo


- Taru Karttunen


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


[Haskell-cafe] Records and associated types

2008-12-11 Thread Taru Karttunen
Hello

What is the correct way to transform code that uses record selection
with TypeEq (like HList) to associated types? I keep running into
problems with overlapping type families which is not allowed unless
they match.

The fundep code:

class Select rec label val | rec label -> val
instance TypeEq label label True => Select (Label label val :+: rest) label val
instance (Select tail field val) => Select (any :+: tail) field val

And a conversion attempt:

class SelectT rec label where
type S rec label
instance TypeEq label label True => SelectT (Label label val :+: rest) label 
where
type S (Label label val :+: rest) label = val
instance (SelectT tail field) => SelectT (any :+: tail) field where
type S (any :+: tail) field = S tail field

which fails with:

Conflicting family instance declarations:
  type instance S (Label label val :+: rest) label
-- Defined at t.hs:19:9
  type instance S (any :+: tail) field -- Defined at t.hs:23:9


How is it possible to get the TypeEq constraint into the type family?


Attached is a complete example that illustrates the problem.


- Taru Karttunen
{-# LANGUAGE 
  UndecidableInstances, OverlappingInstances, FunctionalDependencies, 
  TypeFamilies, TypeOperators, EmptyDataDecls, GADTs, MultiParamTypeClasses,
  FlexibleInstances
  #-}

-- Fundeps - this works

class Select rec label val | rec label -> val
instance TypeEq label label True => Select (Label label val :+: rest) label val
instance (Select tail field val) => Select (any :+: tail) field val


-- Associated types

class SelectT rec label where
type S rec label
instance TypeEq label label True => SelectT (Label label val :+: rest) label where
type S (Label label val :+: rest) label = val

-- THIS FAILS (comment to get this to compile):
instance (SelectT tail field) => SelectT (any :+: tail) field where
type S (any :+: tail) field = S tail field

{-
ERROR:
Conflicting family instance declarations:
  type instance S (Label label val :+: rest) label
-- Defined at t.hs:19:9
  type instance S (any :+: tail) field -- Defined at t.hs:23:9
-}


-- Support code, to get it compile

data True
data False

type family TypeEqR a b
type instance TypeEqR a a = True

class TypeEq a b result
instance (TypeEqR a b ~ isEq, Proxy2 isEq result) => TypeEq a b result

class Proxy2 inp out
instance (result ~ True) => Proxy2 True result
instance (result ~ False) => Proxy2 notTrue result

data End
data (:+:) a b

infixr :+:

newtype Rec wrap rtype = Rec (OuterWrap wrap (R wrap rtype))

type family InnerWrap wrap t :: *
type family OuterWrap wrap t :: *

data R wrap rtype where
End   :: R wrap End
(:+:) :: InnerWrap wrap x -> R wrap xs -> R wrap (x :+: xs)

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