feat: parentUntil

This commit is contained in:
orion 2023-12-28 12:45:58 -06:00
parent 03835ee89d
commit 85c95036e3
Signed by: orion
GPG Key ID: 6D4165AE4C928719
4 changed files with 6356 additions and 33 deletions

6306
spago.lock Normal file

File diff suppressed because it is too large Load Diff

View File

@ -1,16 +1,21 @@
package: package:
build:
strict: true
pedantic_packages: true
dependencies: dependencies:
- arrays - arrays
- effect - effect
- foreign
- foreign-object - foreign-object
- functions
- maybe - maybe
- nullable - nullable
- ordered-collections
- prelude - prelude
- psci-support - tailrec
- test-unit
name: cheerio name: cheerio
test:
main: Test.Main
dependencies:
- test-unit
workspace: workspace:
extra_packages: {} extra_packages: {}
package_set: package_set:

View File

@ -2,67 +2,81 @@ module Cheerio where
import Prelude import Prelude
import Control.Monad.Rec.Class (Step(..), tailRecM)
import Data.Array as Array import Data.Array as Array
import Data.Map (Map) import Data.Map (Map)
import Data.Map as Map import Data.Map as Map
import Data.Maybe (Maybe) import Data.Maybe (Maybe(..))
import Data.Nullable (Nullable) import Data.Nullable (Nullable)
import Data.Nullable as Nullable import Data.Nullable as Nullable
import Effect (Effect) import Effect (Effect)
import Foreign.Object (Object) import Foreign.Object (Object)
foreign import data CheerioNode :: Type foreign import data Node :: Type
foreign import loadImpl :: String -> Effect CheerioNode foreign import loadImpl :: String -> Effect Node
foreign import toArrayImpl :: CheerioNode -> Effect (Array CheerioNode) foreign import toArrayImpl :: Node -> Effect (Array Node)
foreign import toNullableImpl :: CheerioNode -> Effect (Nullable CheerioNode) foreign import toNullableImpl :: Node -> Effect (Nullable Node)
foreign import siblingsImpl :: CheerioNode -> Effect CheerioNode foreign import siblingsImpl :: Node -> Effect Node
foreign import childrenImpl :: CheerioNode -> Effect CheerioNode foreign import childrenImpl :: Node -> Effect Node
foreign import parentImpl :: CheerioNode -> Effect CheerioNode foreign import parentImpl :: Node -> Effect Node
foreign import attrsImpl :: CheerioNode -> Effect (Object String) foreign import attrsImpl :: Node -> Effect (Object String)
foreign import attrImpl :: String -> CheerioNode -> Effect (Nullable String) foreign import attrImpl :: String -> Node -> Effect (Nullable String)
foreign import cssImpl :: CheerioNode -> Effect (Object String) foreign import cssImpl :: Node -> Effect (Object String)
foreign import htmlImpl :: CheerioNode -> Effect String foreign import htmlImpl :: Node -> Effect String
foreign import textImpl :: CheerioNode -> Effect String foreign import textImpl :: Node -> Effect String
foreign import isImpl :: String -> CheerioNode -> Effect Boolean foreign import isImpl :: String -> Node -> Effect Boolean
foreign import findImpl :: String -> CheerioNode -> Effect CheerioNode foreign import findImpl :: String -> Node -> Effect Node
load :: String -> Effect CheerioNode load :: String -> Effect Node
load = loadImpl load = loadImpl
parent :: CheerioNode -> Effect (Maybe CheerioNode) parent :: Node -> Effect (Maybe Node)
parent = map Nullable.toMaybe <<< toNullableImpl <=< parentImpl parent = map Nullable.toMaybe <<< toNullableImpl <=< parentImpl
siblings :: CheerioNode -> Effect (Array CheerioNode) parentUntil :: (Node -> Effect Boolean) -> Node -> Effect (Maybe Node)
parentUntil f n =
let
go Nothing = pure $ Done Nothing
go (Just p) = do
mat <- f p
if mat then
pure $ Done $ Just p
else
Loop <$> parent p
in
tailRecM go =<< parent n
siblings :: Node -> Effect (Array Node)
siblings = toArrayImpl <=< siblingsImpl siblings = toArrayImpl <=< siblingsImpl
children :: CheerioNode -> Effect (Array CheerioNode) children :: Node -> Effect (Array Node)
children = toArrayImpl <=< childrenImpl children = toArrayImpl <=< childrenImpl
attrs :: CheerioNode -> Effect (Map String String) attrs :: Node -> Effect (Map String String)
attrs = map Map.fromFoldableWithIndex <<< attrsImpl attrs = map Map.fromFoldableWithIndex <<< attrsImpl
attr :: String -> CheerioNode -> Effect (Maybe String) attr :: String -> Node -> Effect (Maybe String)
attr k = map Nullable.toMaybe <<< attrImpl k attr k = map Nullable.toMaybe <<< attrImpl k
css :: CheerioNode -> Effect (Map String String) css :: Node -> Effect (Map String String)
css = map Map.fromFoldableWithIndex <<< cssImpl css = map Map.fromFoldableWithIndex <<< cssImpl
html :: CheerioNode -> Effect String html :: Node -> Effect String
html = htmlImpl html = htmlImpl
text :: CheerioNode -> Effect String text :: Node -> Effect String
text = textImpl text = textImpl
is :: String -> CheerioNode -> Effect Boolean is :: String -> Node -> Effect Boolean
is s = isImpl s is s = isImpl s
find :: String -> CheerioNode -> Effect (Array (CheerioNode)) find :: String -> Node -> Effect (Array (Node))
find s = toArrayImpl <=< findImpl s find s = toArrayImpl <=< findImpl s
findFirst :: String -> CheerioNode -> Effect (Maybe (CheerioNode)) findFirst :: String -> Node -> Effect (Maybe (Node))
findFirst s = map Array.head <<< find s findFirst s = map Array.head <<< find s

View File

@ -2,11 +2,9 @@ module Test.Cheerio where
import Prelude hiding (eq) import Prelude hiding (eq)
import Cheerio (CheerioNode)
import Cheerio as Cheerio import Cheerio as Cheerio
import Control.Monad.Error.Class (liftMaybe) import Control.Monad.Error.Class (liftMaybe)
import Data.Array as Array import Data.Array as Array
import Data.Maybe (Maybe(..))
import Effect (Effect) import Effect (Effect)
import Effect.Class (liftEffect) import Effect.Class (liftEffect)
import Effect.Exception (error) import Effect.Exception (error)