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: MonadThrow, MonadReader and shake (PICCA Frederic-Emmanuel) 2. Re: MonadThrow, MonadReader and shake (PICCA Frederic-Emmanuel) 3. Re: MonadThrow, MonadReader and shake (Francesco Ariis) 4. Re: MonadThrow, MonadReader and shake (Sylvain Henry) 5. Re: MonadThrow, MonadReader and shake (PICCA Frederic-Emmanuel) ---------------------------------------------------------------------- Message: 1 Date: Fri, 14 Dec 2018 12:58:29 +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="Windows-1252" ________________________________________ De : Beginners [beginners-boun...@haskell.org] de la part de Francesco Ariis [fa...@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 ------------------------------ Message: 2 Date: Fri, 14 Dec 2018 13:04:14 +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" 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. :)) ------------------------------ Message: 3 Date: Fri, 14 Dec 2018 16:07:45 +0100 From: Francesco Ariis <fa...@ariis.it> To: beginners@haskell.org Subject: Re: [Haskell-beginners] MonadThrow, MonadReader and shake Message-ID: <20181214150745.rfc63yjeh4pty...@x60s.casa> Content-Type: text/plain; charset=us-ascii On Fri, Dec 14, 2018 at 12:58:29PM +0000, PICCA Frederic-Emmanuel wrote: > Yes exactly > ... > With All these extensions. > ... > sorry I do not have a public branch with the current modifications. Far too much for me to chew! Maybe post in haskell-cafe@ and see what they say -F ------------------------------ Message: 4 Date: Sat, 15 Dec 2018 10:06:43 +0100 From: Sylvain Henry <sylv...@haskus.fr> To: beginners@haskell.org Subject: Re: [Haskell-beginners] MonadThrow, MonadReader and shake Message-ID: <3f2fc567-501f-e026-fcdc-3789bd4af...@haskus.fr> Content-Type: text/plain; charset=utf-8; format=flowed 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 ------------------------------ Message: 5 Date: Sat, 15 Dec 2018 11:29:52 +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, 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 ------------------------------ 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 12 ******************************************