how to skip pattern match error when applying a mapM_

Sorry I forgot to put a subject ________________________________________ De : Beginners [beginners-bounces@haskell.org] de la part de PICCA Frederic-Emmanuel Envoyé : mardi 17 janvier 2017 11:15 À : The Haskell-Beginners Mailing List - Discussion of primarily beginner-level topics related to Haskell Objet : [Haskell-beginners] (no subject) Hello, Here a reduction of my problem values :: IO [IO (Maybe Int)] values = do let v = [Just 1, Just 2, Just 3, Nothing, Just 5, Nothing, Just 7] :: [Maybe Int] return $ map return v main :: IO () main = do vs <- values nvs <- mapM_ go vs print nvs where go :: IO (Maybe Int) -> IO Int go v' = do Just v <- v' return v when I run this script, I get a runtime error picca@diffabs6:~/tmp$ runhaskell test.hs test.hs: user error (Pattern match failure in do expression at test.hs:13:10-15) What I want is a go method which skip silently the (IO Nothing) values. so when used in the mapM_ it return only the values which are returned by the IO (Maybe Int) (stored in the values) Thanks for your help Frédéric Indeed _______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners

On Tue, Jan 17, 2017 at 02:03:02PM +0000, PICCA Frederic-Emmanuel wrote:
Hello,
Here a reduction of my problem
values :: IO [IO (Maybe Int)] values = do let v = [Just 1, Just 2, Just 3, Nothing, Just 5, Nothing, Just 7] :: [Maybe Int] return $ map return v
main :: IO () main = do vs <- values nvs <- mapM_ go vs print nvs where go :: IO (Maybe Int) -> IO Int go v' = do Just v <- v' return v
Hello Frédéric, `Just v <- v'` doesn't silently skip Nothing values, but it's a full fledged pattern match (and one reason why I dislike `do notation` as a syntactic sugar). A way to solve the problem is to take advantage of `sequence` and `catMaybes` (from `Data.Maybe`). λ> :t sequence sequence :: (Monad m) => [m a] -> m [a] -- I cheated a bit on the signature, but the gist -- of it is: from a list of monadic actions, to -- one monadic action returning a list of results. λ> :t catMaybes catMaybes :: [Maybe a] -> [a] With that your main gets simpler: main :: IO () main = do vs <- values -- vs :: [IO (Maybe Int)] sv <- sequence vs -- sequence vs :: IO [Maybe Int] -- sv :: [Maybe Int] print (M.catMaybes sv) Does this help?

Hello In fact I realize that my real problem is during the 'values' generation of my example. I have a class like this class Frame t where len :: t -> IO (Maybe Int) row :: t -> Int -> IO (Maybe (DifTomoFrame DIM1)) And I create an instance for my dataframe comming from an hdf5 file. some time there is Nan values returned by the get_position method. I decided to return a Maybe Double and Nan -> Nothing instance Frame DataFrameH5 where len d = lenH5Dataspace (h5delta d) row d idx = do Just n <- len d let eof = n - 1 == idx let nxs' = h5nxs d let mu = 0.0 let komega = 0.0 let kappa = 0.0 let kphi = 0.0 Just gamma <- get_position' (h5gamma d) 0 Just delta <- get_position' (h5delta d) idx Just wavelength <- get_position' (h5wavelength d) 0 let source = Source (head wavelength *~ nano meter) let positions = concat [mu, komega, kappa, kphi, gamma, delta] -- print positions let geometry = Geometry K6c source positions Nothing let detector = ZeroD m <- geometryDetectorRotationGet geometry detector poniext <- ponigen d (MyMatrix HklB m) idx return $ Just DifTomoFrame { difTomoFrameNxs = nxs' , difTomoFrameIdx = idx , difTomoFrameEOF = eof , difTomoFrameGeometry = geometry , difTomoFramePoniExt = poniext } where get_position' a b = do v <- get_position a b return $ if any isNaN v then Nothing else Just v I iterate for each idx of my dataframe So I would like row to return Nothing as soon as the get_position' return Nothing but when I use this code, I get the error and it stop my program instead of skipping the point. ________________________________________ De : Beginners [beginners-bounces@haskell.org] de la part de Francesco Ariis [fa-ml@ariis.it] Envoyé : mardi 17 janvier 2017 15:19 À : The Haskell-Beginners Mailing List - Discussion of primarily beginner-level topics related to Haskell Objet : Re: [Haskell-beginners] how to skip pattern match error when applying a mapM_ On Tue, Jan 17, 2017 at 02:03:02PM +0000, PICCA Frederic-Emmanuel wrote:
Hello,
Here a reduction of my problem
values :: IO [IO (Maybe Int)] values = do let v = [Just 1, Just 2, Just 3, Nothing, Just 5, Nothing, Just 7] :: [Maybe Int] return $ map return v
main :: IO () main = do vs <- values nvs <- mapM_ go vs print nvs where go :: IO (Maybe Int) -> IO Int go v' = do Just v <- v' return v
Hello Frédéric, `Just v <- v'` doesn't silently skip Nothing values, but it's a full fledged pattern match (and one reason why I dislike `do notation` as a syntactic sugar). A way to solve the problem is to take advantage of `sequence` and `catMaybes` (from `Data.Maybe`). λ> :t sequence sequence :: (Monad m) => [m a] -> m [a] -- I cheated a bit on the signature, but the gist -- of it is: from a list of monadic actions, to -- one monadic action returning a list of results. λ> :t catMaybes catMaybes :: [Maybe a] -> [a] With that your main gets simpler: main :: IO () main = do vs <- values -- vs :: [IO (Maybe Int)] sv <- sequence vs -- sequence vs :: IO [Maybe Int] -- sv :: [Maybe Int] print (M.catMaybes sv) Does this help? _______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners

On Tue, Jan 17, 2017 at 02:49:11PM +0000, PICCA Frederic-Emmanuel wrote:
Hello
In fact I realize that my real problem is during the 'values' generation of my example.
I have a class like this
[...]
A repository would help! In any case writing: Just gamma <- get_position' (h5gamma d) 0 Just delta <- get_position' (h5delta d) idx Just wavelength <- get_position' (h5wavelength d) 0 is asking for a trouble down the road. Use a case to pattern match on nothing, (or `maybe`, or LambdaCase if you are into extensions).

Just gamma <- get_position' (h5gamma d) 0 Just delta <- get_position' (h5delta d) idx Just wavelength <- get_position' (h5wavelength d) 0
is asking for a trouble down the road. Use a case to pattern match on nothing, (or `maybe`, or LambdaCase if you are into extensions).
I tought that was the purpose of the Monad to avoid writting these boillerplate ? What I am missing ? Cheers Frederic

Hi Frederic, On Tue, Jan 17, 2017 at 05:34:05PM +0000, PICCA Frederic-Emmanuel wrote:
I tought that was the purpose of the Monad to avoid writting these boillerplate ?
What I am missing ?
You don't pattern match on 'Just' but just write: gamma <- get_position' (h5gamma d) 0 delta <- get_position' (h5delta d) idx wavelength <- get_position' (h5wavelength d) 0 If e.g. 'gamma' is 'Nothing', then the following expressions aren't evaluated and the whole "do-block" returns 'Nothing'. Greetings, Daniel

If e.g. 'gamma' is 'Nothing', then the following expressions aren't evaluated and the whole "do-block" returns 'Nothing'.
I just saw that 'row' isn't operating in the 'Maybe' monad but in the 'IO' monad, so this wont work. I don't know if 'row' contains any side effects that should also be executed if the returned 'Maybe' is 'Nothing', if this isn't the case, then you might be able to switch the return type of 'row' from 'IO (Maybe ...)' to 'Maybe (IO ...)' and then you could get the described behaviour for 'Maybe'. Greetings, Daniel

I don't know if 'row' contains any side effects that should also be executed if the returned 'Maybe' is 'Nothing', if this isn't the case, then you might be able to switch the return type of 'row' from 'IO (Maybe ...)' to 'Maybe (IO ...)' and then you could get the described behaviour for 'Maybe'.
As soon as one side effect return Nothing, it should stop the IO monad. so I should definitiely switch to Maybe IO now how can I know the behaviour in between the line of a Monad. I aimagine that this is the purpose of the bind method (>>=). Where is this defined for Maybe and IO ? Thanks Frederic

now how can I know the behaviour in between the line of a Monad. I aimagine that this is the purpose of the bind method (>>=).
Yes, that's the case.
Where is this defined for Maybe and IO ?
You just look at the Monad instance for the type. IO is a bit special, but here is the one for Maybe[1]. Greetings, Daniel [1] http://hackage.haskell.org/package/base-4.9.1.0/docs/src/GHC.Base.html#line-...

thanks and what is the purpose of
fail _ = nothing
’fail’ is called for pattern match errors, pretty much the error you’ve got from ’Just x <- ...’. The IO Monad instance raises the exception you've seen. For the Maybe Monad instance just 'Nothing' is returned. Greetings, Daniel

From [1]:
-- | Fail with a message. This operation is not part of the -- mathematical definition of a monad, but is invoked on pattern-match -- failure in a @do@ expression. -- -- As part of the MonadFail proposal (MFP), this function is moved -- to its own class 'MonadFail' (see "Control.Monad.Fail" for more -- details). The definition here will be removed in a future -- release. fail :: String -> m a fail s = errorWithoutStackTrace s Best regards, Manuel (also a newbie) [1] http://hackage.haskell.org/package/base-4.9.1.0/docs/src/GHC.Base.html#Monad
thanks and what is the purpose of
fail _ = nothing
Cheers
Fred _______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners

Hello, thanks for the informations after investigating, I could not switch the IO and the Maybe I need to process the IO in order to know if I have a Just or a Nothing So this is a IO (Maybe ...) I just would like to know if there is a better way to write this knowing len :: IO (Maybe Int) get_position' :: a -> b -> IO (Maybe Double) instance Frame DataFrameH5 where len d = lenH5Dataspace (h5delta d) row d idx = do n' <- len d case n' of (Just n) -> do let eof = n - 1 == idx let nxs' = h5nxs d let mu = 0.0 let komega = 0.0 let kappa = 0.0 let kphi = 0.0 gamma' <- get_position' (h5gamma d) 0 case gamma' of (Just gamma) -> do delta' <- get_position' (h5delta d) idx case delta' of (Just delta) -> do wavelength' <- get_position' (h5wavelength d) 0 case wavelength' of (Just wavelength) -> do let source = Source (head wavelength *~ nano meter) let positions = concat [mu, komega, kappa, kphi, gamma, delta] -- print positions let geometry = Geometry K6c source positions Nothing let detector = ZeroD m <- geometryDetectorRotationGet geometry detector poniext <- ponigen d (MyMatrix HklB m) idx return $ Just DifTomoFrame { difTomoFrameNxs = nxs' , difTomoFrameIdx = idx , difTomoFrameEOF = eof , difTomoFrameGeometry = geometry , difTomoFramePoniExt = poniext } Nothing -> return Nothing Nothing -> return Nothing Nothing -> return Nothing Nothing -> return Nothing where get_position' a b = do v <- get_position a b return $ if any isNaN v then Nothing else Just v Thanks for your help Frederic

Hi Frederic,
after investigating, I could not switch the IO and the Maybe I need to process the IO in order to know if I have a Just or a Nothing So this is a IO (Maybe ...)
I just would like to know if there is a better way to write this knowing
There's the MaybeT[1] monad transformer for this use case. Instead of having: row :: t -> Int -> IO (Maybe (DifTomoFrame DIM1)) you would have: row :: t -> Int -> MaybeT IO (DifTomoFrame DIM1) So 'row' might look like: row d idx = do n <- len d let eof = n - 1 == idx let nxs' = h5nxs d let mu = 0.0 let komega = 0.0 let kappa = 0.0 let kphi = 0.0 gamma <- get_position' (h5gamma d) 0 delta <- get_position' (h5delta d) idx wavelength <- get_position' (h5wavelength d) 0 let source = Source (head wavelength *~ nano meter) let positions = concat [mu, komega, kappa, kphi, gamma, delta] -- print positions let geometry = Geometry K6c source positions Nothing let detector = ZeroD m <- lift $ geometryDetectorRotationGet geometry detector poniext <- lift $ ponigen d (MyMatrix HklB m) idx return $ DifTomoFrame { difTomoFrameNxs = nxs' , difTomoFrameIdx = idx , difTomoFrameEOF = eof , difTomoFrameGeometry = geometry , difTomoFramePoniExt = poniext } This assumes that the functions 'len', 'get_position' also return a 'MaybeT IO (...)'. Functions in the IO monad - like 'geometryDetectorRotationGet' and 'ponigen' - have to be "lifted" into the IO monad by 'lift'. To get at the 'Maybe' result of 'row' you're using the 'runMaybeT' function in the IO monad: main :: IO () main = do ... result <- runMaybeT (row t int) ... Greetings, Daniel [1] https://hackage.haskell.org/package/transformers-0.5.2.0/docs/Control-Monad-...

fantastic I like this a lot :)) Thanks Frederic There is plenty of nice Monad transformer like that :)) I just need to learn when to use them. Cheers Frederic

Just x <- y is a construction similar to let Just x = y which is the same as x = case y of Just z -> z Nothing -> error "pattern match failed" Some matches are mapped to errors but not explicitly. Just x = y avoid some boilerplate at the cost of hiding the non exhaustive matches that may raise unexpected errors. Just x <- y is the same as z <- y let x = case z of ... On Tue, 2017-01-17 at 17:34 +0000, PICCA Frederic-Emmanuel wrote:
Just gamma <- get_position' (h5gamma d) 0 Just delta <- get_position' (h5delta d) idx Just wavelength <- get_position' (h5wavelength d) 0
is asking for a trouble down the road. Use a case to pattern match on nothing, (or `maybe`, or LambdaCase if you are into extensions).
I tought that was the purpose of the Monad to avoid writting these boillerplate ?
What I am missing ?
Cheers
Frederic _______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
participants (5)
-
Daniel Trstenjak
-
Francesco Ariis
-
jean verdier
-
Manuel Vázquez Acosta
-
PICCA Frederic-Emmanuel