[Haskell-beginners] calling polymorphic function in Selenium question

Daniel Fischer daniel.is.fischer at web.de
Fri Apr 16 16:48:05 EDT 2010


Am Montag 05 April 2010 03:25:16 schrieb MH:
> I am running the following code that is using Selenium. If you look at
> the function "start", you will see that the return type of the
> function is polymorphic.

Actually the return type is monomorphic, but the returned value can be 
something of type

Selenium a -> IO (Either String a)

for whichever monomorphic type a the caller wants.
Explicitly,

start :: forall a. String -> IO (Selenium a -> IO (Either String a))

What you seem to want would be

start :: String -> IO (forall a. Selenium a -> IO (Either String a))

That requires {-# LANGUAGE ImpredicativeTypes #-}, which is deprecated (and 
will be removed or drastically changed in 6.14).

> Now in main function, I call start function
> to get selenium IO monad and sequentially call selenium commands
> (open, doCommand etc...). The problem that I have here is, while I can
> call all Selenium commands with signature (String  -> Selenium
> String), I can't call commands with signature (String  -> Selenium
> Bool). As I understand it, even though "start" function shall return
> IO (Selenium a -> IO (Either String a)), it actually return IO
> (Selenium String -> IO (Either String String)).
> How shall go about fixing this problem?
> I need to be able to call both types of Selenium commands
> 1. doCommand :: SCommand  -> [String] -> Selenium  String
> OR
>    selectFrame :: String  -> Selenium  String
>
> AND
> 2. isTextPresent :: String  -> Selenium  Bool
>
>
> Thanks.
> =========================================================
{-# LANGUAGE ImpredicativeTypes #-}
> module SeleniumTest where
> import Control.Monad.Error
> import Data.Maybe
> import Network.BSD
> import Network.URI
>
> import Test.Selenium.Server
> import Test.Selenium.Syntax
> infixr 0 $$
>
> -- | Starts up a session and returns a wrapper function that will run
> --   commands. Gives common defaults for browser and host.
start :: String -> IO (forall a. Selenium a -> IO (Either String a))
> start url = do
> --  host <- getHostName
>   start' Firefox "localhost" url
>
> -- | Starts up a session and returns a wrapper function that will run
> --   commands.
start' :: Browser -> HostName -> String
        -> IO (forall a. Selenium a -> IO (Either String a))
> start' browser host url = do
>   let uri = fromJust (parseURI url)
>       sel = mkSeleniumRCSession host browser uri
>   result <- runSelenium sel startSelenium
    return (runSelenium (either (\msg -> error msg) id result)
>
>
> ($$) :: Show t => (Selenium () -> r)
>      -> Selenium t -> r
> ($$) s c = s $ do r <- c; liftIO (putStrLn $ "Result: " ++ show r);
> return ()
>
> -- | Stops a session (in the wrapper returned by start)
> stop :: Selenium ()
> stop = stopSelenium
>
> --main::IO()
> main = do
>     selenium <- start "http://www.google.com"
>     selenium $ open "/"
>     selenium $ doCommand SWindowMaximize []
>     selenium $ typeText (Name "q") "stuff"
>     selenium $ clickAndWait (Name "btnG")
>     return selenium
>
> ===============================================================

compiles and might do what you want.

But I think it's meant to be used differently, more like

selenium :: Selenium String    -- or Bool, whathaveyou
selenium = do
    open "/"
    doCommand SWindowMaximize []
    typeText (Name "q") "stuff"
    clickAndWait (Name "btnG")

use url = do
    let uri = fromJust (parseURI url)
        sel = mkSeleniumRCSession host browser uri
    runSelenium sel selenium

main = use "http://www.google.com"

Compose the Selenium actions and call the composed action from main.


More information about the Beginners mailing list