
I've posted this question to stackoverflow:
https://stackoverflow.com/questions/24650813/find-all-text-inputs-on-webpage...
On Tue, Jul 8, 2014 at 6:16 PM, Cody Goodman
That gave a syntax error, however this was valid:
let textElems = filter ((==) "text" . (`attr` "type")) inputs
It then gave me some ambiguous type errors:
{-# LANGUAGE OverloadedStrings #-}
import Control.Monad import Control.Monad.IO.Class import qualified Data.Text as T 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" let textElems = filter ((==) ("text") . (`attr` "type")) inputs :: [Element] -- wait 20 seconds waitUntil 20 (getText <=< findElem $ ByCSS ".doesnotexist") `onTimeout` return "" liftIO $ putStrLn "done" where capabilities = allCaps { browser=firefox }
-- Prelude Control.Monad Control.Monad.IO.Class Control.Monad.Trans.Class> :r -- [1 of 1] Compiling Main ( src/Main.hs, interpreted )
-- src/Main.hs:15:31: -- No instance for (Eq (wd0 (Maybe T.Text))) -- arising from a use of ‘==’ -- The type variable ‘wd0’ is ambiguous -- Note: there are several potential instances: -- instance Eq a => Eq (GHC.Real.Ratio a) -- Defined in ‘GHC.Real’ -- instance Eq (Test.WebDriver.Common.Profile.PreparedProfile b) -- -- Defined in ‘Test.WebDriver.Common.Profile’ -- instance Eq (Test.WebDriver.Common.Profile.Profile b) -- -- Defined in ‘Test.WebDriver.Common.Profile’ -- ...plus 27 others -- In the first argument of ‘(.)’, namely ‘(==) ("text")’ -- In the first argument of ‘filter’, namely -- ‘((==) ("text") . (`attr` "type"))’ -- In the expression: -- filter ((==) ("text") . (`attr` "type")) inputs :: [Element]
-- src/Main.hs:15:37: -- No instance for (Data.String.IsString (wd0 (Maybe T.Text))) -- arising from the literal ‘"text"’ -- The type variable ‘wd0’ is ambiguous -- Note: there is a potential instance available: -- instance a ~ Data.ByteString.Internal.ByteString => -- Data.String.IsString -- (attoparsec-0.12.1.0:Data.Attoparsec.ByteString.Internal.Parser a) -- -- Defined in ‘attoparsec-0.12.1.0:Data.Attoparsec.ByteString.Char8’ -- In the first argument of ‘(==)’, namely ‘("text")’ -- In the first argument of ‘(.)’, namely ‘(==) ("text")’ -- In the first argument of ‘filter’, namely -- ‘((==) ("text") . (`attr` "type"))’
I then remembered that the type of attr is WebDriver wd => Element -> Text -> wd (Maybe Text) and made this change:
- let textElems = filter ((==) ("text") . (`attr` "type")) inputs :: [Element] + let textElems = filter ((==) (Just "text" :: Maybe T.Text) . (`attr` "type")) inputs :: [Element]
and got what I believe to be a monadic error:
Prelude Control.Monad Control.Monad.IO.Class Control.Monad.Trans.Class> :r [1 of 1] Compiling Main ( src/Main.hs, interpreted )
src/Main.hs:15:69: Couldn't match type ‘Maybe T.Text’ with ‘T.Text’ Expected type: Element -> Maybe T.Text Actual type: Element -> Maybe (Maybe T.Text) In the second argument of ‘(.)’, namely ‘(`attr` "type")’ In the first argument of ‘filter’, namely ‘((==) (Just "text" :: Maybe T.Text) . (`attr` "type"))’ In the expression: filter ((==) (Just "text" :: Maybe T.Text) . (`attr` "type")) inputs :: [Element] Failed, modules loaded: none.
This led me to make this change:
-let textElems = filter ((==) (Just "text" :: Maybe T.Text) . (`attr` "type")) inputs :: [Element] +let textElems = filter ((==) (return $ Just "text" :: Maybe T.Text) . (`attr` "type")) inputs :: [Element]
and I got the following error:
src/Main.hs:15:78: Couldn't match type ‘Maybe T.Text’ with ‘T.Text’ Expected type: Element -> Maybe T.Text Actual type: Element -> Maybe (Maybe T.Text) In the second argument of ‘(.)’, namely ‘(`attr` "type")’ In the first argument of ‘filter’, namely ‘((==) (return $ Just "text" :: Maybe T.Text) . (`attr` "type"))’ In the expression: filter ((==) (return $ Just "text" :: Maybe T.Text) . (`attr` "type")) inputs :: [Element] Failed, modules loaded: none.
On Tue, Jul 8, 2014 at 6:02 PM, Brandon Allbery
wrote: On Tue, Jul 8, 2014 at 6:52 PM, Cody Goodman
wrote: textElems <- filterM (liftM $ ((==) "text" . (`attr` "type"))) inputs
Are you sure this shouldn't be:
let textElems = filter ((==) "text" . `attr` "type") inputs
? The type in the error suggests this is more appropriate.
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net