[Haskell-beginners] how to skip pattern match error when applying a mapM_
PICCA Frederic-Emmanuel
frederic-emmanuel.picca at synchrotron-soleil.fr
Tue Jan 17 14:49:11 UTC 2017
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 at haskell.org] de la part de Francesco Ariis [fa-ml at 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 at haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
More information about the Beginners
mailing list