
Hello, I have some code like this data Hdf5Path sh e = H5RootPath (Hdf5Path sh e) | H5GroupPath ByteString (Hdf5Path sh e) | H5GroupAtPath Int (Hdf5Path sh e) | H5DatasetPath ByteString | H5DatasetPathAttr (ByteString, ByteString) | H5Or (Hdf5Path sh e) (Hdf5Path sh e) deriving (Show) Then I implement this kind of method withHdf5PathP :: (MonadSafe m, Location l) => l -> Hdf5Path sh e -> (Dataset -> m r) -> m r withHdf5PathP loc (H5RootPath subpath) f = withHdf5PathP loc subpath f withHdf5PathP loc (H5GroupPath n subpath) f = withGroupP (openGroup loc n Nothing) $ \g -> withHdf5PathP g subpath f withHdf5PathP loc (H5GroupAtPath i subpath) f = withGroupAtP loc i $ \g -> withHdf5PathP g subpath f withHdf5PathP loc (H5DatasetPath n) f = withDatasetP (openDataset' loc n Nothing) f withHdf5PathP loc (H5DatasetPathAttr (a, c)) f = withDatasetP (openDatasetWithAttr loc a c) f withHdf5PathP loc (H5Or l r) f = withHdf5PathP loc l f `catchAll` const (withHdf5PathP loc r f) I decided to switch to the ContT transfomer and try to implement this like this withHdf5PathP :: (MonadSafe m, Location l) => l -> Hdf5Path sh e -> ContT r m Dataset withHdf5PathP loc (H5RootPath subpath) = withHdf5PathP loc subpath withHdf5PathP loc (H5GroupPath n subpath) = do g <- withGroupP (openGroup loc n Nothing) withHdf5PathP g subpath withHdf5PathP loc (H5GroupAtPath i subpath) = do g <- withGroupAtP loc i withHdf5PathP g subpath withHdf5PathP loc (H5DatasetPath n) = withDatasetP (openDataset' loc n Nothing) withHdf5PathP loc (H5DatasetPathAttr (a, c)) = withDatasetP (openDatasetWithAttr loc a c) withHdf5PathP loc (H5Or l r) = ??? during the process, I also changed all the withXXX method to use Continuation. -bracket' :: MonadSafe m => (a -> IO ()) -> IO a -> (a -> m r) -> m r -bracket' r a = bracket (liftIO a) (liftIO . r) +bracket' :: MonadSafe m => (a -> IO ()) -> IO a -> ContT r m a +bracket' r a = ContT (bracket (liftIO a) (liftIO . r)) -withBytes :: MonadSafe m => Int -> (ForeignPtr a -> m r) -> m r +withBytes :: MonadSafe m => Int -> ContT r m (ForeignPtr a) withBytes n = bracket' touchForeignPtr (mallocForeignPtrBytes n) -withFileP :: MonadSafe m => IO File -> (File -> m r) -> m r +withFileP :: MonadSafe m => IO File -> ContT r m File withFileP = bracket' closeFile -withGroupP :: MonadSafe m => IO Group -> (Group -> m r) -> m r +withGroupP :: MonadSafe m => IO Group -> ContT r m Group withGroupP = bracket' closeGroup -withGroupAtP :: (Location l, MonadSafe m) => l -> Int -> (Group -> m r) -> m r -withGroupAtP l i f = do +withGroupAtP :: (Location l, MonadSafe m) => l -> Int -> ContT r m Group +withGroupAtP l i = do es <- liftIO $ nxEntries' l - withGroupP (openGroup l (es !! i) Nothing) f + withGroupP (openGroup l (es !! i) Nothing) -withDatasetP :: MonadSafe m => IO Dataset -> (Dataset -> m r) -> m r +withDatasetP :: MonadSafe m => IO Dataset -> ContT r m Dataset withDatasetP = bracket' closeDataset -withDataspaceP :: MonadSafe m => IO Dataspace -> (Dataspace -> m r) -> m r +withDataspaceP :: MonadSafe m => IO Dataspace -> ContT r m Dataspace withDataspaceP = bracket' closeDataspace The H5Or is a sort of Alternative which try to extract the info from l and if any exception is triggered switch to the right part r. Would you be so kind to help me write the H5Or part with the continuation. I am not sure that I understand all the ContT arcanes. thanks for your help Frederic

I end up with this but I do not know if this is the best solution. withHdf5PathP loc (H5Or l r) = ContT $ \cont -> (runContT (withHdf5PathP loc l) cont) `catchAll` const (runContT (withHdf5PathP loc r) cont)

I would suggest that continuations don't even belong to the "structured programming" camp, while exceptions are well structured in this regard, so I doubt they can mix well. But continuation is powerful enough to implement exception throwing/catching, so maybe it's just the existing synchronous, `IO` based exceptions don't cooperate well, you may be able to get well with your own implementation of try/catch/bracket with continuations there.
On 2021-11-16, at 22:45, PICCA Frederic-Emmanuel
wrote: I end up with this but I do not know if this is the best solution.
withHdf5PathP loc (H5Or l r) = ContT $ \cont -> (runContT (withHdf5PathP loc l) cont) `catchAll` const (runContT (withHdf5PathP loc r) cont) _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
participants (2)
-
Compl Yue
-
PICCA Frederic-Emmanuel