[Haskell-beginners] MonadThrow, MonadReader and shake

Sylvain Henry sylvain at haskus.fr
Sat Dec 15 09:06:43 UTC 2018


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 at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners


More information about the Beginners mailing list