[Haskell-cafe] how to simplify ressources access and pipes steam

PICCA Frederic-Emmanuel frederic-emmanuel.picca at synchrotron-soleil.fr
Wed May 20 06:23:31 UTC 2020


Hello, I am writing a software which  do some data treatement from hdf5 files.

In order to access the data which are stored in arrays, I need to open and closes ressources.
This is the purpose of the withHdf5PathP function.

given a file f and a UhvPath I end up with this

withUhvPathP :: (MonadSafe m, Location l) => l -> UhvPath -> ((Int -> IO Geometry) -> m r) -> m r
withUhvPathP f (UhvPath m o d g w) gg =
      withHdf5PathP f m $ \m' ->
      withHdf5PathP f o $ \o' ->
      withHdf5PathP f d $ \d'->
      withHdf5PathP f g $ \g' ->
      withHdf5PathP f w $ \w' -> gg (\j -> do
                                      mu <- get_position m' j
                                      omega <- get_position o' j
                                      delta <- get_position d' j
                                      gamma' <- get_position g' j
                                      wavelength <- getValueWithUnit w' 0 angstrom
                                      let positions = Data.Vector.Storable.fromList [mu, omega, delta, gamma']
                                      let source = Source wavelength
                                      pure $ Geometry Uhv source positions Nothing)


then I use this like this

forever $ do
    (Chunk fp from to) <- await
    withFileP (openH5 fp) $ \f ->
      withHdf5PathP f imgs $ \dimgs ->
      withUhvPathP f dif $ \getDiffractometer ->
      withSamplePathP f samp $ \getSample ->
      forM_ [from..to-1] (\j -> yield =<< liftIO
                               (DataFrameHkl
                                <$> pure j
                                <*> get_image' det dimgs j
                                <*> getDiffractometer j
                                <*> getSample j))

so once I open the resources, I use the getDiffratometer ((Int -> IO Geometry) -> m r) function give the position on the stream and it return the value at the j position.
the purpose of this is to open the ressources only once at the begining and then send the values in a Pipe via the yield function of pipes package.

I hope, I was clear.

1) I find the withUhvPathP sort of ugly, and I would like to know if it could be written more elegantly, because I will need to write a lot's of these function for different types.

2) It is the right way to design a solution to my problem (open ressources and send each values into a stream).

thanks for you attention.

Frederic


More information about the Haskell-Cafe mailing list