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. howto Pipe (PICCA Frederic-Emmanuel) 2. ODP: howto Pipe (Marcin Mrotek) 3. Re: ODP: howto Pipe (PICCA Frederic-Emmanuel) 4. Re: ODP: howto Pipe (Marcin Mrotek) 5. Re: ODP: howto Pipe (PICCA Frederic-Emmanuel) 6. Re: ODP: howto Pipe (Marcin Mrotek) ---------------------------------------------------------------------- Message: 1 Date: Thu, 18 Feb 2016 14:57:50 +0000 From: PICCA Frederic-Emmanuel <frederic-emmanuel.pi...@synchrotron-soleil.fr> To: "beginners@haskell.org" <beginners@haskell.org> Subject: [Haskell-beginners] howto Pipe Message-ID: <a2a20ec3b8560d408356cac2fc148e53b303a...@sun-dag3.synchrotron-soleil.fr> Content-Type: text/plain; charset="us-ascii" Hello I try to mix my C library and the Pipe module here the code I am using solveTraj :: Factory -> Geometry -> Detector -> Sample -> Pipe Engine Geometry IO () solveTraj f g d s = do e <- await let name = engineName e withSample s $ \sample -> withDetector d $ \detector -> withGeometry f g $ \geometry -> withEngineList f $ \engines -> withCString name $ \cname -> do c_hkl_engine_list_init engines geometry detector sample engine <- c_hkl_engine_list_engine_get_by_name engines cname nullPtr n <- c_hkl_engine_pseudo_axis_names_get engine >>= darrayStringLen yield $ solve' engine n e >>= getSolution0 where getSolution0 :: ForeignPtr HklGeometryList -> IO Geometry And I am using this like this runEffect $ for (each engines) >-> solveTraj factory geometry detector sample >-> P.print where [Engine] engines But When I compile the code I get this error. src/Hkl/C.hsc:83:3: Couldn't match type `IO' with `Proxy () Engine () Geometry IO' Expected type: Proxy () Engine () Geometry IO () Actual type: IO () In a stmt of a 'do' block: withSample s $ \ sample -> withDetector d $ \ detector -> withGeometry f g $ \ geometry -> ... In the expression: do { e <- await; let name = engineName e; withSample s $ \ sample -> withDetector d $ \ detector -> ... } In an equation for `solveTraj': solveTraj f g d s = do { e <- await; let name = ...; withSample s $ \ sample -> withDetector d $ ... } src/Hkl/C.hsc:91:19: Couldn't match type `Proxy x'0 x0 () (IO Geometry) m0' with `IO' Expected type: IO () Actual type: Proxy x'0 x0 () (IO Geometry) m0 () In a stmt of a 'do' block: yield $ solve' engine n e >>= getSolution0 In the expression: do { c_hkl_engine_list_init engines geometry detector sample; engine <- c_hkl_engine_list_engine_get_by_name engines cname nullPtr; n <- c_hkl_engine_pseudo_axis_names_get engine >>= darrayStringLen; yield $ solve' engine n e >>= getSolution0 } In the second argument of `($)', namely `\ cname -> do { c_hkl_engine_list_init engines geometry detector sample; engine <- c_hkl_engine_list_engine_get_by_name engines cname nullPtr; .... }' I do not understand why the yield does not produce the right type as output. I think I missed something big :), but... Thanks for your help Fred ------------------------------ Message: 2 Date: Thu, 18 Feb 2016 16:46:04 +0100 From: Marcin Mrotek <marcin.jan.mro...@gmail.com> To: The Haskell-Beginners Mailing List - Discussion of primarilybeginner-level topics related to Haskell <beginners@haskell.org> Subject: [Haskell-beginners] ODP: howto Pipe Message-ID: <56c5e758.905b190a.86e57.6...@mx.google.com> Content-Type: text/plain; charset="utf-8" Hello, I presume these `c_hkl_<something>` return `IO`? Then you need to `lift` them into `Pipe` (well, `Proxy`). Best regards, Marcin Mrotek -----Wiadomo?? oryginalna----- Od: "PICCA Frederic-Emmanuel" <frederic-emmanuel.pi...@synchrotron-soleil.fr> Wys?ano: ?2016-?02-?18 15:58 Do: "beginners@haskell.org" <beginners@haskell.org> Temat: [Haskell-beginners] howto Pipe Hello I try to mix my C library and the Pipe module here the code I am using solveTraj :: Factory -> Geometry -> Detector -> Sample -> Pipe Engine Geometry IO () solveTraj f g d s = do e <- await let name = engineName e withSample s $ \sample -> withDetector d $ \detector -> withGeometry f g $ \geometry -> withEngineList f $ \engines -> withCString name $ \cname -> do c_hkl_engine_list_init engines geometry detector sample engine <- c_hkl_engine_list_engine_get_by_name engines cname nullPtr n <- c_hkl_engine_pseudo_axis_names_get engine >>= darrayStringLen yield $ solve' engine n e >>= getSolution0 where getSolution0 :: ForeignPtr HklGeometryList -> IO Geometry And I am using this like this runEffect $ for (each engines) >-> solveTraj factory geometry detector sample >-> P.print where [Engine] engines But When I compile the code I get this error. src/Hkl/C.hsc:83:3: Couldn't match type `IO' with `Proxy () Engine () Geometry IO' Expected type: Proxy () Engine () Geometry IO () Actual type: IO () In a stmt of a 'do' block: withSample s $ \ sample -> withDetector d $ \ detector -> withGeometry f g $ \ geometry -> ... In the expression: do { e <- await; let name = engineName e; withSample s $ \ sample -> withDetector d $ \ detector -> ... } In an equation for `solveTraj': solveTraj f g d s = do { e <- await; let name = ...; withSample s $ \ sample -> withDetector d $ ... } src/Hkl/C.hsc:91:19: Couldn't match type `Proxy x'0 x0 () (IO Geometry) m0' with `IO' Expected type: IO () Actual type: Proxy x'0 x0 () (IO Geometry) m0 () In a stmt of a 'do' block: yield $ solve' engine n e >>= getSolution0 In the expression: do { c_hkl_engine_list_init engines geometry detector sample; engine <- c_hkl_engine_list_engine_get_by_name engines cname nullPtr; n <- c_hkl_engine_pseudo_axis_names_get engine >>= darrayStringLen; yield $ solve' engine n e >>= getSolution0 } In the second argument of `($)', namely `\ cname -> do { c_hkl_engine_list_init engines geometry detector sample; engine <- c_hkl_engine_list_engine_get_by_name engines cname nullPtr; .... }' I do not understand why the yield does not produce the right type as output. I think I missed something big :), but... Thanks for your help Fred _______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/beginners/attachments/20160218/d77130cd/attachment-0001.html> ------------------------------ Message: 3 Date: Thu, 18 Feb 2016 16:45:24 +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: <a2a20ec3b8560d408356cac2fc148e53b303a...@sun-dag3.synchrotron-soleil.fr> Content-Type: text/plain; charset="iso-8859-1" > I presume these `c_hkl_<something>` return `IO`? Then you need to `lift` them > into `Pipe` (well, `Proxy`). Yes the c_hkl_<omesthing> method return IO a or IO () what do you mean exactly by lift them ihto pipe ? Cheers Fr?d?ric ------------------------------ Message: 4 Date: Thu, 18 Feb 2016 18:12:07 +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==vjwcjmfar_8a1cuwhisfc_m1rmnpp7ehf1kp4ad...@mail.gmail.com> Content-Type: text/plain; charset=UTF-8 I mean literally use the function `lift`. Proxy (it's the underlying type of all pipes, Pipe is a type synonym that expands to Proxy, filling some type variables for you) implements the MonadTrans class (from http://hackage.haskell.org/package/transformers-0.5.1.0/docs/Control-Monad-Trans-Class.html): class MonadTrans t where lift :: Monad m => m a -> t m a So, if `t` is `Pipe a b` and `m` is IO, then `lift` becomes: lift :: IO r -> Pipe a b IO r Thus, for example, `lift (c_hkl_engine_list_init engines geometry detector sample)` will return `Pipe a b IO <something>` (for any `a` and `b`, this is going to be a trivial pipe that doesn't yield or await anything, and just executes the effect) rather than `IO <something>`. You don't need to import the Monad.Trans.Class module, Pipe reexports it for you. Best regards, Marcin Mrotek ------------------------------ Message: 5 Date: Thu, 18 Feb 2016 17:21:41 +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: <a2a20ec3b8560d408356cac2fc148e53b303a...@sun-dag3.synchrotron-soleil.fr> Content-Type: text/plain; charset="us-ascii" I thought that the yield method took care of this and return the right type (Pipe ...) at the end of the do statement. This is not the case ? thanks for your explanations. Fred ------------------------------ Message: 6 Date: Thu, 18 Feb 2016 18:47:49 +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=T9AFFbWV68M7KpLiExDVcTLeq5uPs1SkdydD6Mr=i...@mail.gmail.com> Content-Type: text/plain; charset=UTF-8 Yes, yield does return a Pipe. But "do" notation expands to a chain of ">>" and ">>=", and these functions only connect monadic values from the same monad. Pipes are monad transformers, so the conversion from IO to `Pipe a b IO` doesn't do anything interesting (converting back to IO would require running the pipe, which is less trivial), but it still has to be done for the types to agree. Also, now I've noticed that you may have some trouble with the `withSomething` functions. Do they take functions of type `a -> m b` and return the result wrapped again in `m` for any monad `m`, or do they only work with IO? If they are limited to IO, then you can't use them here, as you would need to convert a Pipe back to IO, and this conversion isn't a no-op and probably not what you want to do here. If this is the case, you'd need the raw functions that open and close these resources, and use Pipes.Safe to wrap them (https://hackage.haskell.org/package/pipes-safe): bracket :: MonadSafe m => Base m a -> (a -> Base m b) -> (a -> m c) -> m c This might look a bit convoluted, but for the sake of working with Pipes and IO, you can think of it as having type: bracket :: IO a -> (a -> IO b) -> (a -> Pipe x y (SafeT IO) c) -> Pipe x y (SafeT IO) c The first argument opens some resource, the senond closes it, and the third is the main working function. Instead of having a `Pipe x y IO c` you have `Pipe x y (SafeT IO) c` but this is almost the same, you'd only have to use `liftIO` instead of just `lift` to lift from IO to this monad (or use `lift` twice, once to get `SafeT IO`, and yet again to lift to `Pipe`), and after running the effect, use `runSafeT` to unwrap the value to get IO (this action ensures that the finalizer you provided to `bracket` is always executed, even if some exceptions have been raised meanwhile). But again, if the `withSomething` functions are polymorphic with respect to the monad used, then you leave them as they are and don't bother with Pipes.Safe, just wanted to warn you about a potential problem. 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 21 *****************************************