Re: [Haskell] ANN: Updates in the monadic regions family

2011-03-10 Thread Bas van Dijk
In regions-0.9 I removed support for forking threads because it
allowed you to use a closed handle in a forked thread. Unfortunately I
just realized that it's still possible to fork threads in a region.
The reason is that I've derived a MonadControlIO instance for RegionT
which enables you to use forkIO as demonstrated by the following
program:

-
{-# LANGUAGE UnicodeSyntax, NoImplicitPrelude, KindSignatures #-}

module Main where

-- from base:
import Data.Function  ( ($) )
import Control.Concurrent ( ThreadId, forkIO, threadDelay )
import Control.Monad  ( (>>=), liftM, void )
import System.IO  ( IO )

-- from transformers:
import Control.Monad.IO.Class ( liftIO )

-- from regions:
import Control.Monad.Trans.Region ( RegionT, runRegionT )

-- from safer-file-handles:
import System.IO.SaferFileHandles ( openFile
  , IOMode(ReadMode)
  , hGetContents
  , putStrLn
  )

-- from pathtype:
import System.Path.Posix ( asAbsFile )

-- from monad-control:
import Control.Exception.Control ( mask_ )
import Control.Monad.IO.Control  ( MonadControlIO, liftControlIO )

main ∷ IO ()
main = do runRegionT region
  threadDelay 150

region ∷ MonadControlIO pr ⇒ RegionT s pr ()
region = do
  putStrLn "Running region"

  h ← openFile (asAbsFile "/etc/passwd") ReadMode

  _ ← liftForkIO $ do
   putStrLn "Forked region"
   liftIO $ threadDelay 100
   hGetContents h >>= putStrLn

  liftIO $ threadDelay 50
  putStrLn "Exiting region"

liftForkIO ∷ MonadControlIO m ⇒ m α → m ThreadId
liftForkIO m = liftControlIO $ \runInIO →
 forkIO $ void $ runInIO m
-

Executing main yields the following error:

> main
Running region
Forked region
Exiting region
: /etc/passwd: hGetContents: illegal operation (handle is closed)

I think the only solution is to drop the derived MonadControlIO and
MonadTransControl instances. Unfortunately the packages that use
regions require this instance because they need to use mask_ when
opening resources. Here an example from safer-file-handles:

openFile ∷ (MonadControlIO pr, AbsRelClass ar)
 ⇒ FilePath ar
 → IOMode ioMode
 → RegionT s pr
 (RegionalFileHandle ioMode (RegionT s pr))
openFile = openNormal E.openFile

openNormal open = \filePath ioMode → mask_ $ do
  h ← liftIO $ open (getPathString filePath) ioMode
  ch ← onExit $ sanitizeIOError $ hClose h
  return $ RegionalFileHandle h ch

I guess I have to solve this by providing a custom mask_ function or
using MonadCatchIO-transformers as I did before.

I'm going to think about the best solution. In the mean time just
don't use something like liftForkIO.

Regards,

Bas

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


[Haskell] A opportunity to lern (parsing huge binary file)

2011-03-10 Thread Skeptic .


Hi,
I finally have an opportunity to learn Haskell (I'm a day-to-day Java 
programmer, but I'm also at ease with Scheme), parsing a huge (i.e. up to 50 
go) binary file. The encoding is very stable, but it's not a flat struct array 
(i.e. it uses flags). 
Different outputs (i.e. text files) will be needed, some unknown at this time. 
Sounds to me a perfect "real-world" task to see what Haskell can offer.

Any suggestions at how to structure the code or on which packages to look at is 
welcome.

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


Re: [Haskell] A opportunity to lern (parsing huge binary file)

2011-03-10 Thread Piyush P Kurur
On Thu, Mar 10, 2011 at 10:36:27AM -0500, Skeptic . wrote:
> 
> 
> Hi,

> I finally have an opportunity to learn Haskell (I'm a day-to-day
> Java programmer, but I'm also at ease with Scheme), parsing a huge
> (i.e. up to 50 go) binary file. The encoding is very stable, but
> it's not a flat struct array (i.e. it uses flags).   Different
> outputs (i.e. text files) will be needed, some unknown at this
> time.   Sounds to me a perfect "real-world" task to see what Haskell
> can offer.
> 

  Maybe you can try attoparsec. I have not tired it but will like to
hear your experience

Regards

ppk

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


Re: [Haskell] A opportunity to lern (parsing huge binary file)

2011-03-10 Thread Don Stewart
ppk:
> On Thu, Mar 10, 2011 at 10:36:27AM -0500, Skeptic . wrote:
> > 
> > 
> > Hi,
> 
> > I finally have an opportunity to learn Haskell (I'm a day-to-day
> > Java programmer, but I'm also at ease with Scheme), parsing a huge
> > (i.e. up to 50 go) binary file. The encoding is very stable, but
> > it's not a flat struct array (i.e. it uses flags).   Different
> > outputs (i.e. text files) will be needed, some unknown at this
> > time.   Sounds to me a perfect "real-world" task to see what Haskell
> > can offer.
> > 
> 
>   Maybe you can try attoparsec. I have not tired it but will like to
> hear your experience
> 

attoparsec or Data.Binary 

-- Don

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