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.  monad and variable result (Damien Mattei)
   2. Re:  monad and variable result (Francesco Ariis)


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

Message: 1
Date: Mon, 10 Dec 2018 11:32:23 +0100
From: Damien Mattei <mat...@oca.eu>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: [Haskell-beginners] monad and variable result
Message-ID: <5c0e40b7.6010...@oca.eu>
Content-Type: text/plain; charset=utf-8

have some code that works but want to put it in a simple function
without sucess:

getBD :: Connection -> String -> Float
getBD conn name = noBDfp
  where qry_head = "select `N° BD` from sidonie.Coordonnées where Nom =
?" :: Query
        bd_rows = do
          local_bd_rows <- query conn qry_head (Only (name::String))
          return local_bd_rows


i want  the variable local_bd_rows accessible in the 'where' clause

how can i do that?

note the goal is to do the same thing of my main function that works :

main :: IO ()
--main :: Int
main =

  do
    conn <- connect defaultConnectInfo
      { connectHost = "moita",
        connectUser = "mattei",
        connectPassword = "******",
        connectDatabase = "sidonie" }


-- we get all the Double Stars that have angular distance superior to a
threshold of 1 second = 0.000278 degree

    rows <- query_ conn "SELECT Nom,distance FROM AngularDistance WHERE
distance > 0.000278"

    forM_ rows $ \(name,distance) ->
      putStrLn $  Text.unpack name ++ " " ++ show (distance :: Double)


-- we will get the Durchmusterung Number BD from Sidonie and WDS and
compare them for a given name
-- Warning: there could be multiple result in WDS for a given entry name
(due to components)

-- first we get the N°BD from sidonie

    let name = "A    20"
--    let qry = "select `N° BD` from Coordonnées where Nom = " ++ name

    let qry_head = "select `N° BD` from sidonie.Coordonnées where Nom =
?" :: Query

--    bd_rows <- query_ conn "select `N° BD` from sidonie.Coordonnées
where Nom = 'A    20'"

    bd_rows <- query conn qry_head (Only (name::String))

    putStrLn $ show bd_rows
    putStrLn $ show name

    let resLst = Prelude.map fromOnly bd_rows

    let noBDtxt = fromOnly (Prelude.head bd_rows) :: Text
--    let noBD2 =  _ (Prelude.head bd_rows)

    putStrLn $ show resLst

    putStrLn $ show noBDtxt

    forM_ bd_rows $ \(Only a) ->
      putStrLn $  Text.unpack a

    let noBDstr = Text.unpack noBDtxt :: String
    let noBDfp = read $ noBDstr :: Float

    putStr "noBDfp ="
    (putStrLn (show noBDfp))

    close conn

    print "Exit."


for now i have errors in the function:

Prelude> :load UpdateSidonie
[1 of 1] Compiling Main             ( UpdateSidonie.hs, interpreted )

UpdateSidonie.hs:47:28: error:
    • Ambiguous type variable ‘r0’ arising from a use of ‘query’
      prevents the constraint ‘(QueryResults r0)’ from being solved.
      Relevant bindings include
        bd_rows :: IO [r0] (bound at UpdateSidonie.hs:46:9)
      Probable fix: use a type annotation to specify what ‘r0’ should be.
      These potential instances exist:
        instance Result a => QueryResults (Only a)
          -- Defined in ‘Database.MySQL.Simple.QueryResults’
        instance (Result a, Result b) => QueryResults (a, b)
          -- Defined in ‘Database.MySQL.Simple.QueryResults’
        instance (Result a, Result b, Result c) => QueryResults (a, b, c)
          -- Defined in ‘Database.MySQL.Simple.QueryResults’
        ...plus 21 others
        (use -fprint-potential-instances to see them all)
    • In a stmt of a 'do' block:
        local_bd_rows <- query conn qry_head (Only (name :: String))
      In the expression:
        do local_bd_rows <- query conn qry_head (Only (name :: String))
           return local_bd_rows
      In an equation for ‘bd_rows’:
          bd_rows
            = do local_bd_rows <- query conn qry_head (Only (name ::
String))
                 return local_bd_rows
   |
47 |           local_bd_rows <- query conn qry_head (Only (name::String))
   |                            ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Failed, no modules loaded.



-- 
damien.mat...@unice.fr, damien.mat...@oca.eu, UNS / OCA / CNRS


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

Message: 2
Date: Mon, 10 Dec 2018 12:19:43 +0100
From: Francesco Ariis <fa...@ariis.it>
To: beginners@haskell.org
Subject: Re: [Haskell-beginners] monad and variable result
Message-ID: <20181210111943.d3lwkltanakf3...@x60s.casa>
Content-Type: text/plain; charset=us-ascii

Hy Damien,

On Mon, Dec 10, 2018 at 11:32:23AM +0100, Damien Mattei wrote:
> i want  the variable local_bd_rows accessible in the 'where' clause

does `query` return IO ()? If so, no you can't*. Once the result
is inside IO, it stays in IO. Move what you need inside out of where
(and inside a `do`) and get ready to change the signature of
`getBD` to

    getBD :: Connection -> String -> IO Float

-F

* (you can with unsafeSomething functions, but it is really really
advisable not to do that).


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

Subject: Digest Footer

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


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

End of Beginners Digest, Vol 126, Issue 7
*****************************************

Reply via email to