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.  (no subject) (PICCA Frederic-Emmanuel)
   2.  how to skip pattern match error when applying a  mapM_
      (PICCA Frederic-Emmanuel)
   3. Re:  how to skip pattern match error when applying a mapM_
      (Francesco Ariis)
   4. Re:  how to skip pattern match error when applying a mapM_
      (PICCA Frederic-Emmanuel)
   5. Re:  how to skip pattern match error when applying a mapM_
      (Francesco Ariis)
   6. Re:  how to skip pattern match error when applying a mapM_
      (PICCA Frederic-Emmanuel)


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

Message: 1
Date: Tue, 17 Jan 2017 10:15:24 +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: [Haskell-beginners] (no subject)
Message-ID:
        
<a2a20ec3b8560d408356cac2fc148e53bb329...@sun-dag3.synchrotron-soleil.fr>
        
Content-Type: text/plain; charset="iso-8859-1"

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

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

Message: 2
Date: Tue, 17 Jan 2017 14:03:02 +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: [Haskell-beginners] how to skip pattern match error when
        applying a      mapM_
Message-ID:
        
<a2a20ec3b8560d408356cac2fc148e53bb329...@sun-dag3.synchrotron-soleil.fr>
        
Content-Type: text/plain; charset="iso-8859-1"

Sorry I forgot to put a subject
________________________________________
De : Beginners [beginners-boun...@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


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

Message: 3
Date: Tue, 17 Jan 2017 15:19:46 +0100
From: Francesco Ariis <fa...@ariis.it>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] how to skip pattern match error when
        applying a mapM_
Message-ID: <20170117141946.ga6...@casa.casa>
Content-Type: text/plain; charset=utf-8

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?


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

Message: 4
Date: Tue, 17 Jan 2017 14:49:11 +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] how to skip pattern match error when
        applying a mapM_
Message-ID:
        
<a2a20ec3b8560d408356cac2fc148e53bb329...@sun-dag3.synchrotron-soleil.fr>
        
Content-Type: text/plain; charset="utf-8"

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-boun...@haskell.org] de la part de Francesco Ariis 
[fa...@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

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

Message: 5
Date: Tue, 17 Jan 2017 16:26:03 +0100
From: Francesco Ariis <fa...@ariis.it>
To: beginners@haskell.org
Subject: Re: [Haskell-beginners] how to skip pattern match error when
        applying a mapM_
Message-ID: <20170117152603.ga8...@casa.casa>
Content-Type: text/plain; charset=us-ascii

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



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

Message: 6
Date: Tue, 17 Jan 2017 17:34:05 +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] how to skip pattern match error when
        applying a mapM_
Message-ID:
        
<a2a20ec3b8560d408356cac2fc148e53bb329...@sun-dag3.synchrotron-soleil.fr>
        
Content-Type: text/plain; charset="us-ascii"

>     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

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

Subject: Digest Footer

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


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

End of Beginners Digest, Vol 103, Issue 14
******************************************

Reply via email to