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.  MonadThrow, MonadReader and shake (PICCA Frederic-Emmanuel)
   2. Re:  MonadThrow, MonadReader and shake (Francesco Ariis)
   3. Re:  MonadThrow, MonadReader and shake (PICCA Frederic-Emmanuel)
   4. Re:  MonadThrow, MonadReader and shake (Francesco Ariis)


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

Message: 1
Date: Thu, 13 Dec 2018 09:15:41 +0000
From: PICCA Frederic-Emmanuel
        <frederic-emmanuel.pi...@synchrotron-soleil.fr>
To: "beginners@haskell.org" <beginners@haskell.org>
Subject: [Haskell-beginners] MonadThrow, MonadReader and shake
Message-ID:
        
<a2a20ec3b8560d408356cac2fc148e53015b364...@sun-dag3.synchrotron-soleil.fr>
        
Content-Type: text/plain; charset="Windows-1252"

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;
                   .... }’


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

Message: 2
Date: Thu, 13 Dec 2018 11:45:40 +0100
From: Francesco Ariis <fa...@ariis.it>
To: beginners@haskell.org
Subject: Re: [Haskell-beginners] MonadThrow, MonadReader and shake
Message-ID: <20181213104540.j2lqm2rbiqb44...@x60s.casa>
Content-Type: text/plain; charset=utf-8

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


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

Message: 3
Date: Thu, 13 Dec 2018 10:56:17 +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] MonadThrow, MonadReader and shake
Message-ID:
        
<a2a20ec3b8560d408356cac2fc148e53015b364...@sun-dag3.synchrotron-soleil.fr>
        
Content-Type: text/plain; charset="us-ascii"

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#t:Action

>     - 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


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

Message: 4
Date: Thu, 13 Dec 2018 12:31:45 +0100
From: Francesco Ariis <fa...@ariis.it>
To: beginners@haskell.org
Subject: Re: [Haskell-beginners] MonadThrow, MonadReader and shake
Message-ID: <20181213113145.v22rncvjcnh74...@x60s.casa>
Content-Type: text/plain; charset=us-ascii

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!


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

Subject: Digest Footer

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


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

End of Beginners Digest, Vol 126, Issue 10
******************************************

Reply via email to