|
|
@@ -2,6 +2,7 @@ module LinkedIn.QueryRunner where
|
|
|
|
|
|
import Prelude
|
|
|
|
|
|
+import Control.Alt ((<|>))
|
|
|
import Control.Monad.Except (ExceptT(..), mapExceptT, runExceptT, throwError)
|
|
|
import Data.Array as A
|
|
|
import Data.Either (Either(..), note)
|
|
|
@@ -19,6 +20,7 @@ import Web.DOM.NodeList as NL
|
|
|
data QueryError =
|
|
|
QNodeNotFoundError String
|
|
|
| QNodeListNotFoundError String
|
|
|
+ | QNodeUnexpectedType String String
|
|
|
| QTextNotFoundError
|
|
|
| QChooseError
|
|
|
|
|
|
@@ -40,6 +42,13 @@ ignoreNotFound = mapExceptT (map ignoreNotFound')
|
|
|
(Left q) -> Left q
|
|
|
(Right n') -> Right (Just n')
|
|
|
|
|
|
+ignoreErrors ∷ ∀ a f. Functor f ⇒ ExceptT QueryError f a → ExceptT QueryError f (Maybe a)
|
|
|
+ignoreErrors = mapExceptT (map ignoreErrors')
|
|
|
+ where
|
|
|
+ ignoreErrors' = case _ of
|
|
|
+ (Left q) -> Right Nothing
|
|
|
+ (Right n') -> Right (Just n')
|
|
|
+
|
|
|
queryOne ∷ String → QueryRunner Node
|
|
|
queryOne selector node = ExceptT $ do
|
|
|
maybeNode <- U.queryOne selector node
|
|
|
@@ -66,10 +75,24 @@ subQueryOne query selector n = query =<< queryOne selector n
|
|
|
|
|
|
chooseOne ∷ ∀ a t m. Monad m ⇒ (t → ExceptT QueryError m a) → (t → ExceptT QueryError m a) → (t → ExceptT QueryError m a)
|
|
|
chooseOne q1 q2 n = do
|
|
|
- maybeN1 <- ignoreNotFound $ q1 n
|
|
|
- maybeN2 <- ignoreNotFound $ q2 n
|
|
|
+ maybeN1 <- (ignoreErrors <<< q1) n
|
|
|
+ maybeN2 <- (ignoreErrors <<< q2) n
|
|
|
+
|
|
|
+ case maybeN1 <|> maybeN2 of
|
|
|
+ Nothing -> throwError QChooseError
|
|
|
+ Just n' -> pure n'
|
|
|
+
|
|
|
+chooseOne3 ∷ ∀ a t m.
|
|
|
+ Monad m
|
|
|
+ ⇒ (t → ExceptT QueryError m a)
|
|
|
+ → (t → ExceptT QueryError m a)
|
|
|
+ → (t → ExceptT QueryError m a)
|
|
|
+ → (t → ExceptT QueryError m a)
|
|
|
+chooseOne3 q1 q2 q3 n = do
|
|
|
+ maybeN1 <- (ignoreErrors <<< q1) n
|
|
|
+ maybeN2 <- (ignoreErrors <<< q2) n
|
|
|
+ maybeN3 <- (ignoreErrors <<< q3) n
|
|
|
|
|
|
- case maybeN1, maybeN2 of
|
|
|
- Nothing, Nothing -> throwError QChooseError
|
|
|
- Just n1, _ -> pure n1
|
|
|
- _, Just n2 -> pure n2
|
|
|
+ case maybeN1 <|> maybeN2 <|> maybeN3 of
|
|
|
+ Nothing -> throwError QChooseError
|
|
|
+ Just n' -> pure n'
|