
Hello, I try to write this sort of code xdsme' :: SomeDataCollection -> Maybe Cell -> Maybe SpaceGroup -> GZiped -> [Path Abs File] -> ReaderT Beamline IO () xdsme' c@(SomeDataCollection SCollect SHdf5 _) cell sg z is = do -- xdsme compute the output path by himself. cwd' <- toProcessDataPath c rdir <- resultsPrefixFile xdsMePrefix c dir <- resultsPrefixDir ("xdsme_" ++ xdsMePrefix) c dir' <- resultsPrefixFile "" c xmlPath <- parseRelFile $ toFilePath dir' ++ "_xdsme.xml" xml <- parseAbsFile $ toFilePath cwd' > toFilePath dir > toFilePath xmlPath uploadedPath <- parseRelFile $ toFilePath dir' ++ "_xdsme.uploaded" uploaded <- parseAbsFile $ toFilePath cwd' > toFilePath dir > toFilePath uploadedPath let shakeFiles' = toFilePath cwd' > toFilePath dir > ".shake/" let images = getImages c z liftIO $ shake shakeOptions{ shakeFiles=shakeFiles' , shakeReport=["/tmp/shake.html"] , shakeVerbosity=Diagnostic} $ do want [toFilePath uploaded] -- execute xdsme and deal with input dependencies toFilePath xml %> \_out -> do need (map toFilePath is) processXdsMe cwd' cell sg rdir images toFilePath uploaded %> \_out -> do need [toFilePath xml] container <- liftIO . fromFile . toFilePath $ xml -- post processing let attachment = _autoProcProgramAttachment . _autoProcProgramContainer $ container attachment' <- toRuchePath attachment <- HERE PROBLEM _ <- copyAttachment' attachment attachment' let container' = (autoProcProgramContainer . autoProcProgramAttachment .~ attachment') container -- replace attachement -- upload into ISPYB liftIO $ storeAutoProcIntoISPyB c NoAnomalous container' cmd_ ("touch" :: String) (toFilePath uploaded) where toRuchePath :: (MonadReader Beamline m, MonadThrow m) => [AutoProcProgramAttachment WithPrefix] -> m [AutoProcProgramAttachment ISPyB] toRuchePath = mapM go where go :: (MonadReader Beamline m, MonadThrow m) => AutoProcProgramAttachment WithPrefix -> m (AutoProcProgramAttachment ISPyB) go a = do (d, _) <- toPath a b <- ask newd <- mkText255 . pack . toRuchePath' b . fromAbsDir $ d return a {filePath = newd} but when I try to compile this I get this error. How can I teach ghc how to solve this issue ? thanks for your help Frederic src/XdsMe.hs:211:22-43: error: • Could not deduce (MonadThrow Action) arising from a use of ‘toRuchePath’ from the context: t ~ 'Collect bound by a pattern with constructor: SCollect :: SCollectType 'Collect, in an equation for ‘xdsme'’ at src/XdsMe.hs:180:30-37 or from: f ~ 'ISPyB.DataCollection.Hdf5 bound by a pattern with constructor: SHdf5 :: SCollectSourceFormat 'ISPyB.DataCollection.Hdf5, in an equation for ‘xdsme'’ at src/XdsMe.hs:180:39-43 • In a stmt of a 'do' block: attachment' <- toRuchePath attachment In the expression: do { need [toFilePath xml]; container <- liftIO . fromFile . toFilePath $ xml; let attachment = _autoProcProgramAttachment . _autoProcProgramContainer $ container; attachment' <- toRuchePath attachment; .... } In the second argument of ‘(%>)’, namely ‘\ _out -> do { need [...]; container <- liftIO . fromFile . toFilePath $ xml; .... }’

Hello Frédéric, On Thu, Dec 13, 2018 at 09:15:41AM +0000, PICCA Frederic-Emmanuel wrote:
Hello,
I try to write this sort of code
[...] . but when I try to compile this I get this error. How can I teach ghc how to solve this issue ?
This
src/XdsMe.hs:211:22-43: error: • Could not deduce (MonadThrow Action) arising from a use of ‘toRuchePath’
Must has to mean that *inside* the do block starting with toFilePath uploaded %> \_out -> do `MonadThrow` does not work. I stress inside vs. outside because the outermost `do` block is of type `ReaderT Beamline IO ()` (which *is* an instance of `MonadThrow`), while `Action` apparently is not. I can think of two solutions: - Make `Action` an instance of `MonadThrow` - Let the throw happen outside that `do` block Let us know if that helped -F

Hello
- Make `Action` an instance of `MonadThrow`
If I read the documentationof Action, I have this. So you are right Action has no Instance for MonadThrow. BUT it seems that there is a LiftIO available. Do you think that it can be usefull or must I create a dedicated instance of Action https://hackage.haskell.org/package/shake-0.17.3/docs/Development-Shake.html...
- Let the throw happen outside that `do` block
I can not move this out of the o`block because I need a computation done in the block. Maybe there is a way but I do not know how... Cheers Frederic

On Thu, Dec 13, 2018 at 10:56:17AM +0000, PICCA Frederic-Emmanuel wrote:
If I read the documentationof Action, I have this. So you are right Action has no Instance for MonadThrow.
BUT it seems that there is a LiftIO available. Do you think that it can be usefull or must I create a dedicated instance of Action
Using LiftIO should work fine!

Using LiftIO should work fine!
I endup with this error src/XdsMe.hs:214:31-52: error: • Could not deduce (Control.Monad.Reader.Class.MonadReader Beamline IO) arising from a use of ‘toRuchePath’ from the context: t ~ 'Collect bound by a pattern with constructor: SCollect :: SCollectType 'Collect, in an equation for ‘xdsme'’ at src/XdsMe.hs:183:30-37 or from: f ~ 'ISPyB.DataCollection.Hdf5 bound by a pattern with constructor: SHdf5 :: SCollectSourceFormat 'ISPyB.DataCollection.Hdf5, in an equation for ‘xdsme'’ at src/XdsMe.hs:183:39-43 • In the second argument of ‘($)’, namely ‘toRuchePath attachment’ In a stmt of a 'do' block: attachment' <- liftIO $ toRuchePath attachment In the expression: do { need [toFilePath xml]; container <- liftIO . fromFile . toFilePath $ xml; let attachment = _autoProcProgramAttachment . _autoProcProgramContainer $ container; attachment' <- liftIO $ toRuchePath attachment; .... } Here the signature of the function xdsme' :: SomeDataCollection -> Maybe Cell -> Maybe SpaceGroup -> GZiped -> [Path Abs File] -> ReaderT Beamline IO () xdsme' c@(SomeDataCollection SCollect SHdf5 _) cell sg z is = do

Hello, In fact I do not understand this error message, and thus I do not understand how to fix this ? How Can I give hint to ghc in order to fix this compilation error. thanks for your help. Frederic src/XdsMe.hs:214:31-52: error: • Could not deduce (Control.Monad.Reader.Class.MonadReader Beamline IO) arising from a use of ‘toRuchePath’ from the context: t ~ 'Collect bound by a pattern with constructor: SCollect :: SCollectType 'Collect, in an equation for ‘xdsme'’ at src/XdsMe.hs:183:30-37 or from: f ~ 'ISPyB.DataCollection.Hdf5 bound by a pattern with constructor: SHdf5 :: SCollectSourceFormat 'ISPyB.DataCollection.Hdf5, in an equation for ‘xdsme'’ at src/XdsMe.hs:183:39-43 • In the second argument of ‘($)’, namely ‘toRuchePath attachment’ In a stmt of a 'do' block: attachment' <- liftIO $ toRuchePath attachment In the expression: do { need [toFilePath xml]; container <- liftIO . fromFile . toFilePath $ xml; let attachment = _autoProcProgramAttachment . _autoProcProgramContainer $ container; attachment' <- liftIO $ toRuchePath attachment; .... } Here the signature of the function xdsme' :: SomeDataCollection -> Maybe Cell -> Maybe SpaceGroup -> GZiped -> [Path Abs File] -> ReaderT Beamline IO () xdsme' c@(SomeDataCollection SCollect SHdf5 _) cell sg z is = do

On Fri, Dec 14, 2018 at 11:29:20AM +0000, PICCA Frederic-Emmanuel wrote:
src/XdsMe.hs:214:31-52: error: • Could not deduce (Control.Monad.Reader.Class.MonadReader Beamline IO) arising from a use of ‘toRuchePath’ from the context: t ~ 'Collect
Are you by chance using existential quantification or gadts? I might need a self contained example to load on ghci.

________________________________________ De : Beginners [beginners-bounces@haskell.org] de la part de Francesco Ariis [fa-ml@ariis.it] Envoyé : vendredi 14 décembre 2018 13:00 À : beginners@haskell.org Objet : Re: [Haskell-beginners] MonadThrow, MonadReader and shake On Fri, Dec 14, 2018 at 11:29:20AM +0000, PICCA Frederic-Emmanuel wrote:
src/XdsMe.hs:214:31-52: error: • Could not deduce (Control.Monad.Reader.Class.MonadReader Beamline IO) arising from a use of ‘toRuchePath’ from the context: t ~ 'Collect
Are you by chance using existential quantification or gadts? Yes exactly data SomeDataCollection where SomeDataCollection :: SCollectType t -> SCollectSourceFormat f -> DataCollection t f -> SomeDataCollection data CollectType = Collect | Caracterization deriving Show data SCollectType a where SCollect :: SCollectType 'Collect SCaracterization :: SCollectType 'Caracterization data CollectSourceFormat = Cbf | Hdf5 | Hdf5' deriving Show data SCollectSourceFormat a where SCbf :: SCollectSourceFormat 'Cbf SHdf5 :: SCollectSourceFormat 'Hdf5 SHdf5' :: SCollectSourceFormat 'Hdf5' With All these extensions. {-# LANGUAGE DataKinds #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE UnicodeSyntax #-} sorry I do not have a public branch with the current modifications. Cheers Frederic

I forgot this on. data DataCollection (t :: CollectType) (f :: CollectSourceFormat) = DataCollection { actualCenteringPosition :: Text , axisEnd :: Double , axisRange :: Double , axisStart :: Double , beamShape :: Text , beamSizeAtSampleX :: Double , beamSizeAtSampleY :: Double , centeringMethod :: Maybe Text , dataCollectionId :: DataCollectionId , dataCollectionNumber :: Int , detector2theta :: Double , detectorDistance :: Double , endTime :: Text , exposureTime :: Double , fileTemplate :: Text , flux :: Double , fluxEnd :: Double , imageDirectory :: Path Abs Dir , imagePrefix :: Text -- (FilePath) , imageSuffix :: Maybe Text -- (FilePath) ?? Maybe , kappaStart :: Double , numberOfImages :: Int , numberOfPasses :: Int , omegaStart :: Maybe Double , overlap :: Double , phiStart :: Double , printableForReport :: Int , resolution :: Double , resolutionAtCorner :: Maybe Double , rotationAxis :: Text , runStatus :: Text , slitGapHorizontal :: Double , slitGapVertical :: Double , startImageNumber :: Int , startTime :: Text , synchrotronMode :: Text , transmission :: Double , undulatorGap1 :: Maybe Double , undulatorGap2 :: Maybe Double , wavelength :: Double , xbeam :: Double , xtalSnapshotFullPath1 :: Maybe (Path Abs File) , xtalSnapshotFullPath2 :: Maybe (Path Abs File) , xtalSnapshotFullPath3 :: Maybe (Path Abs File) , xtalSnapshotFullPath4 :: Maybe (Path Abs File) , ybeam :: Double , dataCollectionGroupId :: Int } deriving Show Where we get the t and f parameter. :))

Hello, The` toRuchePath` function has the following constraints on `m`: `MonadReader Beamline m, MonadThrow m` In your code, `m ~ Action` (from Shake) which doesn't fulfil the constraints (hence the error). If you use `liftIO` as suggested (possible because Action has a MonadIO instance), `m ~ IO` which doesn't fulfil the constraints (hence the other error). If you want `m ~ ReaderT Beamline m IO`, you can use something like: `liftIO $ runReaderT stateBeforeCallingShake $ toRuchePath attachements` (you need `stateBeforeCallingShake <- ask` before calling shake). It should fulfil the constraints because we have instances for `MonadThrow IO` and `MonadThrow m => MonadThrow (ReaderT r m)`. Hope that helps, Sylvain On 13/12/2018 10:15, PICCA Frederic-Emmanuel wrote:
Hello,
I try to write this sort of code
xdsme' :: SomeDataCollection -> Maybe Cell -> Maybe SpaceGroup -> GZiped -> [Path Abs File] -> ReaderT Beamline IO () xdsme' c@(SomeDataCollection SCollect SHdf5 _) cell sg z is = do -- xdsme compute the output path by himself. cwd' <- toProcessDataPath c rdir <- resultsPrefixFile xdsMePrefix c dir <- resultsPrefixDir ("xdsme_" ++ xdsMePrefix) c dir' <- resultsPrefixFile "" c xmlPath <- parseRelFile $ toFilePath dir' ++ "_xdsme.xml" xml <- parseAbsFile $ toFilePath cwd' > toFilePath dir > toFilePath xmlPath uploadedPath <- parseRelFile $ toFilePath dir' ++ "_xdsme.uploaded" uploaded <- parseAbsFile $ toFilePath cwd' > toFilePath dir > toFilePath uploadedPath
let shakeFiles' = toFilePath cwd' > toFilePath dir > ".shake/" let images = getImages c z
liftIO $ shake shakeOptions{ shakeFiles=shakeFiles' , shakeReport=["/tmp/shake.html"] , shakeVerbosity=Diagnostic} $ do want [toFilePath uploaded]
-- execute xdsme and deal with input dependencies toFilePath xml %> \_out -> do need (map toFilePath is) processXdsMe cwd' cell sg rdir images
toFilePath uploaded %> \_out -> do need [toFilePath xml]
container <- liftIO . fromFile . toFilePath $ xml
-- post processing let attachment = _autoProcProgramAttachment . _autoProcProgramContainer $ container
attachment' <- toRuchePath attachment <- HERE PROBLEM
_ <- copyAttachment' attachment attachment'
let container' = (autoProcProgramContainer . autoProcProgramAttachment .~ attachment') container -- replace attachement
-- upload into ISPYB liftIO $ storeAutoProcIntoISPyB c NoAnomalous container' cmd_ ("touch" :: String) (toFilePath uploaded)
where
toRuchePath :: (MonadReader Beamline m, MonadThrow m) => [AutoProcProgramAttachment WithPrefix] -> m [AutoProcProgramAttachment ISPyB] toRuchePath = mapM go where go :: (MonadReader Beamline m, MonadThrow m) => AutoProcProgramAttachment WithPrefix -> m (AutoProcProgramAttachment ISPyB) go a = do (d, _) <- toPath a b <- ask newd <- mkText255 . pack . toRuchePath' b . fromAbsDir $ d return a {filePath = newd}
but when I try to compile this I get this error. How can I teach ghc how to solve this issue ?
thanks for your help
Frederic
src/XdsMe.hs:211:22-43: error: • Could not deduce (MonadThrow Action) arising from a use of ‘toRuchePath’ from the context: t ~ 'Collect bound by a pattern with constructor: SCollect :: SCollectType 'Collect, in an equation for ‘xdsme'’ at src/XdsMe.hs:180:30-37 or from: f ~ 'ISPyB.DataCollection.Hdf5 bound by a pattern with constructor: SHdf5 :: SCollectSourceFormat 'ISPyB.DataCollection.Hdf5, in an equation for ‘xdsme'’ at src/XdsMe.hs:180:39-43 • In a stmt of a 'do' block: attachment' <- toRuchePath attachment In the expression: do { need [toFilePath xml]; container <- liftIO . fromFile . toFilePath $ xml; let attachment = _autoProcProgramAttachment . _autoProcProgramContainer $ container; attachment' <- toRuchePath attachment; .... } In the second argument of ‘(%>)’, namely ‘\ _out -> do { need [...]; container <- liftIO . fromFile . toFilePath $ xml; .... }’ _______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners

Hello,
Hello sylvain.
The` toRuchePath` function has the following constraints on `m`: `MonadReader Beamline m, MonadThrow m`
In your code, `m ~ Action` (from Shake) which doesn't fulfil the constraints (hence the error).
[...]
If you want `m ~ ReaderT Beamline m IO`, you can use something like: `liftIO $ runReaderT stateBeforeCallingShake $ toRuchePath attachements` (you need `stateBeforeCallingShake <- ask` before calling shake).
ok, I will check this :). Does it mean that if an instance of the MonadReader was writtent for shake (Action). it should work out of the box ? Fred

If you want `m ~ ReaderT Beamline m IO`, you can use something like: `liftIO $ runReaderT stateBeforeCallingShake $ toRuchePath attachements` (you need `stateBeforeCallingShake <- ask` before calling shake). ok, I will check this :). I've swapped the args above, it should be:
liftIO $ runReaderT (toRuchePath attachements) stateBeforeCallingShake
Does it mean that if an instance of the MonadReader was writtent for shake (Action). it should work out of the box ?
With additional `MonadThrow Action` and `MonadReader Beamline Action` instances it should work. But the MonadReader one is really specific to your use case. Cheers, Sylvain

I've swapped the args above, it should be:
liftIO $ runReaderT (toRuchePath attachements) stateBeforeCallingShake
Hello, I was struggling with strange errors :). Now it works. thanks a lot. I am just wondering if the best it not to add a parameter to my toRuchePath function and avoid the Reader Monad. this would simplify the code I gess.
With additional `MonadThrow Action` and `MonadReader Beamline Action` instances it should work. But the MonadReader one is really specific to your use case.
I will try also this. thansk a lot. Frederic
participants (3)
-
Francesco Ariis
-
PICCA Frederic-Emmanuel
-
Sylvain Henry