thank you tom,
in fact reading doc as i saw i never used return read in monad doc i already put it in my code this gives this that compiles:
 let lstNamesBD = Prelude.map (\(Only name) ->
                                         do
                                          let strName = Text.unpack name
                                          getBD conn strName >>= (\bd ->
                                                                       return (strName,bd)))
                                 names

but sticked now for displaying it because it is now an IO tuple of 2 and i can not display it with some functions like this , it fails to compile:

--    putStr "lstNamesBD ="
--    putStrLn $ show lstNamesBD

    forM_ lstNamesBD $ \t2 ->
          do
            n <- fst t2
            b <- snd t2
            putStrLn $  (show n) ++ " " ++ maybe "NULL" show b

or with that tested first:

 forM_ lstNamesBD $ \(name,bd) ->
            putStrLn $  (show name) ++ " " ++ maybe "NULL" show bd
Prelude> :load UpdateSidonie
[1 of 1] Compiling Main             ( UpdateSidonie.hs, interpreted )

UpdateSidonie.hs:207:22: error:
    • Couldn't match expected type ‘(IO a1, b0)’
                  with actual type ‘IO (String, Maybe Float)’
    • In the first argument of ‘fst’, namely ‘t2’
      In a stmt of a 'do' block: n <- fst t2
      In the expression:
        do n <- fst t2
           b <- snd t2
           putStrLn $ (show n) ++ " " ++ maybe "NULL" show b
    |
207 |             n <- fst t2
    |                      ^^

UpdateSidonie.hs:208:22: error:
    • Couldn't match expected type ‘(a0, IO (Maybe a2))’
                  with actual type ‘IO (String, Maybe Float)’
    • In the first argument of ‘snd’, namely ‘t2’
      In a stmt of a 'do' block: b <- snd t2
      In the expression:
        do n <- fst t2
           b <- snd t2
           putStrLn $ (show n) ++ " " ++ maybe "NULL" show b
    |
208 |             b <- snd t2
    |                      ^^

UpdateSidonie.hs:211:25: error:
    • Couldn't match expected type ‘IO (String, Maybe Float)’
                  with actual type ‘(a3, Maybe a4)’
    • In the pattern: (name, bd)
      In the second argument of ‘($)’, namely
        ‘\ (name, bd)
           -> putStrLn $ (show name) ++ " " ++ maybe "NULL" show bd’
      In a stmt of a 'do' block:
        forM_ lstNamesBD
          $ \ (name, bd)
              -> putStrLn $ (show name) ++ " " ++ maybe "NULL" show bd
    |
211 |     forM_ lstNamesBD $ \(name,bd) ->
    |                         ^^^^^^^^^
Failed, no modules loaded.
Prelude>


On Sat, Dec 29, 2018 at 11:30 AM Tom Ellis <tom-lists-haskell-cafe-2017@jaguarpaw.co.uk> wrote:
I guess you want

    return (nameStr, bd)

Every statement in a do-block must be of type `IO a` for some `a`.
`(nameStr, bd)` is a pure value of type `(String, Maybe Float)`.  You turn
it into a value of type `IO (String, Maybe Float)` using `return`.

Tom

On Sat, Dec 29, 2018 at 10:08:32AM +0100, Damien Mattei wrote:
> ---------- Forwarded message ---------
> From: Damien Mattei <damien.mattei@gmail.com>
> Date: Sat, Dec 29, 2018 at 9:46 AM
> Subject: IO monad use
> To: Damien MATTEI <damien.mattei@gmail.com>
>
>
> again an annoying error with my code, i want to apply sort of MAP on  list
> resut of my database IO accessed extracting info with another query,
> queries works both but i can not MAP or if i can i do not know how to SHOW
> the result, here is the code:
>
>  lstNamesBD <- mapM (\(Only name) ->
>                                do
>                                 let nameStr = Text.unpack name
>                                 bd <- getBD conn nameStr
>                                 (nameStr,bd))
>                        names
>
> it fails to compile with this error:
>
> Prelude> :load UpdateSidonie
> [1 of 1] Compiling Main             ( UpdateSidonie.hs, interpreted )
>
> UpdateSidonie.hs:203:33: error:
>     • Couldn't match type ‘(,) String’ with ‘IO’
>       Expected type: IO (Maybe Float)
>         Actual type: (String, Maybe Float)
>     • In a stmt of a 'do' block: (nameStr, bd)
>       In the expression:
>         do let nameStr = unpack name
>            bd <- getBD conn nameStr
>            (nameStr, bd)
>       In the first argument of ‘mapM’, namely
>         ‘(\ (Only name)
>             -> do let nameStr = ...
>                   bd <- getBD conn nameStr
>                   (nameStr, bd))’
>     |
> 203 |                                 (nameStr,bd))
>     |                                 ^^^^^^^^^^^^
> Failed, no modules loaded.
>
>
> if i code like this  show does not know how to display result:
>
>  let lstNamesBD = Prelude.map (\(Only name) ->
>                                          do
>                                           let nameStr = Text.unpack name
>                                           bd <- getBD conn nameStr
>                                           res <- (nameStr,bd)
>                                           res)
>                                  names
>
>  putStr "lstNamesBD ="
>  putStrLn $ show lstNamesBD
>
> *Main> :load UpdateSidonie
> [1 of 1] Compiling Main             ( UpdateSidonie.hs, interpreted )
>
> UpdateSidonie.hs:193:16: error:
>     • No instance for (Show (IO (Maybe Float)))
>         arising from a use of ‘show’
>     • In the second argument of ‘($)’, namely ‘show lstNamesBD’
>       In a stmt of a 'do' block: putStrLn $ show lstNamesBD
>       In the expression:
>         do conn <- connect
>                      defaultConnectInfo
>                        {connectHost = "moita", connectUser = "mattei",
>                         connectPassword = "sidonie2", connectDatabase =
> "sidonie"}
>            (rows :: [(Text, Double)]) <- query_
>                                            conn
>                                            "SELECT Nom,distance FROM
> AngularDistance WHERE distance > 0.000278"
>            (names :: [Only Text]) <- query_
>                                        conn
>                                        "SELECT Nom FROM AngularDistance
> WHERE distance > 0.000278"
>            let resLstNames = Prelude.map fromOnly names
>            ....
>     |
> 193 |     putStrLn $ show lstNamesBD
>     |                ^^^^^^^^^^^^^^^
> Failed, no modules loaded.
>
> help me please

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

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