[Haskell-cafe] Webdriver: Couldn't match type `Element' with `WD Element'

Cody Goodman codygman.consulting at gmail.com
Tue Jul 8 22:52:44 UTC 2014


I received some help/guidance in #haskell, but I still can't get this
to work. I'm basically trying to find all the text elemnts in a
webpage with the webdriver package. Here is my code and errors:


{-# LANGUAGE OverloadedStrings #-}

import           Control.Monad
import           Control.Monad.IO.Class
import           Test.WebDriver
import           Test.WebDriver.Classes       (WebDriver (..))
import           Test.WebDriver.Commands
import           Test.WebDriver.Commands.Wait

main = do
  runSession defaultSession capabilities $ do
      openPage "http://www.appnitro.com/demo/view.php?id=1"
      inputs <- findElems $ ByTag "input"
      textElems <- filterM (liftM $ ((==) "text" . (`attr` "type"))) inputs
      -- wait 20 seconds
      waitUntil 20 (getText <=< findElem $ ByCSS ".doesnotexist")
        `onTimeout` return ""
  liftIO $ putStrLn "done"
    where
      capabilities = allCaps { browser=firefox }

-- [1 of 1] Compiling Main             ( src/Main.hs, interpreted )

-- src/Main.hs:168:70:
--     Couldn't match type `Element' with `WD Element'
--     Expected type: [WD Element]
--       Actual type: [Element]
--     In the second argument of `filterM', namely `inputs'
--     In a stmt of a 'do' block:
--       textElems <- filterM
--                      (liftM $ ((==) "text" . (`attr` "type"))) inputs
--     In the second argument of `($)', namely
--       `do { openPage "http://www.appnitro.com/demo/view.php?id=1";
--             inputs <- findElems $ ByTag "input";
--             textElems <- filterM
--                            (liftM $ ((==) "text" . (`attr` "type"))) inputs;
--             waitUntil 20 (getText <=< findElem $ ByCSS ".doesnotexist")
--             `onTimeout` return "" }'
-- Failed, modules loaded: none.


More information about the Haskell-Cafe mailing list