Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1. Re:  ODP: howto Pipe (PICCA Frederic-Emmanuel)
   2. Re:  ODP: howto Pipe (PICCA Frederic-Emmanuel)
   3. Re:  ODP: howto Pipe (Marcin Mrotek)


----------------------------------------------------------------------

Message: 1
Date: Sat, 20 Feb 2016 10:12:26 +0000
From: PICCA Frederic-Emmanuel
        <frederic-emmanuel.pi...@synchrotron-soleil.fr>
To: "The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell" <beginners@haskell.org>
Subject: Re: [Haskell-beginners] ODP: howto Pipe
Message-ID:
        
<a2a20ec3b8560d408356cac2fc148e53b303b...@sun-dag3.synchrotron-soleil.fr>
        
Content-Type: text/plain; charset="us-ascii"

Hello

first a big thanks your for all your comment :)


I end-up with this solution


data Diffractometer = Diffractometer { difEngineList :: (ForeignPtr 
HklEngineList)
                                     , difGeometry :: (ForeignPtr HklGeometry)
                                     , difDetector :: (ForeignPtr HklDetector)
                                     , difSample :: (ForeignPtr HklSample)
                                     }
                      deriving (Show)

newDiffractometer :: Factory ->  Geometry -> Detector -> Sample -> IO 
Diffractometer
newDiffractometer f g d s = do
  f_engines <- newEngineList f
  f_geometry <- newGeometry f g
  f_detector <- newDetector d
  f_sample <- newSample s
  withForeignPtr f_sample $ \sample ->
      withForeignPtr f_detector $ \detector ->
          withForeignPtr f_geometry $ \geometry ->
              withForeignPtr f_engines $ \engines -> do
                  c_hkl_engine_list_init engines geometry detector sample
                  return $ Diffractometer f_engines f_geometry f_detector 
f_sample

solve' :: Ptr HklEngine -> CSize -> Engine -> IO (ForeignPtr HklGeometryList)
solve' engine n (Engine _ ps _) = do
  let positions = [v | (Parameter _ v _) <- ps]
  withArray positions $ \values ->
      c_hkl_engine_pseudo_axis_values_set engine values n unit nullPtr
      >>= newForeignPtr c_hkl_geometry_list_free

solveTrajPipe' :: Diffractometer -> Pipe Engine Geometry IO ()
solveTrajPipe' dif = forever $ do
    -- Inside here we are using `StateT Int (Consumer a IO) r`
    e <- await
    let name = engineName e
    solutions <- lift $ withForeignPtr (difEngineList dif) $ \engines ->
     withCString name $ \cname -> do
       engine <- c_hkl_engine_list_engine_get_by_name engines cname nullPtr
       n <- c_hkl_engine_pseudo_axis_names_get engine >>= darrayStringLen
       solutions <- solve' engine n e >>= getSolution0
       return solutions
    yield solutions

solveTrajPipe :: Factory -> Geometry -> Detector -> Sample -> Pipe Engine 
Geometry IO ()
solveTrajPipe f g d s = do
  dif <- lift $ newDiffractometer f g d s
  solveTrajPipe' dif


so, I created a data type with contain all my foreignPtr.
instanciate them at the begining. this newDiffractometer function also 
initialise the C library objects
c_hkl_engine_list_init engines geometry detector sample

then I just need to do a forever loop and use this type data to keep the C 
internal state.

what's worring me is that I have a sort of internal state but this is not 
expressed anywhere in the type system...

Cheers

Frederic

------------------------------

Message: 2
Date: Sat, 20 Feb 2016 10:57:38 +0000
From: PICCA Frederic-Emmanuel
        <frederic-emmanuel.pi...@synchrotron-soleil.fr>
To: "The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell" <beginners@haskell.org>
Subject: Re: [Haskell-beginners] ODP: howto Pipe
Message-ID:
        
<a2a20ec3b8560d408356cac2fc148e53b303b...@sun-dag3.synchrotron-soleil.fr>
        
Content-Type: text/plain; charset="us-ascii"

except that if I use this 

    runEffect $ each engines >-> solveTrajPipe factory geometry detector sample 
>-> P.drain

instead of 
    -- >-> P.print

I get a segfault when I do a big number of coputation ???

It seems to me that the dif object is released as I am still using the 
underlying foreign ptr...


------------------------------

Message: 3
Date: Sat, 20 Feb 2016 12:15:08 +0100
From: Marcin Mrotek <marcin.jan.mro...@gmail.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] ODP: howto Pipe
Message-ID:
        <CAJcfPz=O0nHbVTKL3+jEXh-wpU93ZPMYOwC18TLNkGvo6w6R=w...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

> then I just need to do a forever loop and use this type data to keep the C 
> internal state.
>
> what's worring me is that I have a sort of internal state but this is not 
> expressed anywhere in the type system...

You can use (StateT <your_type> IO) instead of plain IO in the pipe to
pass that data around. There are functions for working with StateT
(and other transformer) pipes in Pipes.Lift module:
https://hackage.haskell.org/package/pipes-4.1.8/docs/Pipes-Lift.html#g:5

Other than that, having to worry about state kept in the C part of a
Haskell program is often a pain in general, unfortunately. Perhaps you
could take some hints from https://hackage.haskell.org/package/GPipe
for example, but I have no idea if that's going to be of any help.

> I get a segfault when I do a big number of coputation ???

The only change is from Pipes.print to Pipes.drain? This is weird,
maybe you'd have better luck asking on Pipes mailing list:
https://groups.google.com/forum/?fromgroups#!forum/haskell-pipes (
mailto:haskell-pi...@googlegroups.com )

Best regards,
Marcin Mrotek


------------------------------

Subject: Digest Footer

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners


------------------------------

End of Beginners Digest, Vol 92, Issue 23
*****************************************

Reply via email to