Skip to content
This repository was archived by the owner on Oct 4, 2020. It is now read-only.

Add missing Element-Attr API functions, add Attr type. #15

Open
wants to merge 1 commit into
base: master
Choose a base branch
from
Open
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
64 changes: 64 additions & 0 deletions src/DOM/Node/Attr.purs
Original file line number Diff line number Diff line change
@@ -0,0 +1,64 @@
module DOM.Node.Attr where

import Prelude

import Data.Nullable
import Data.Maybe (Maybe(..))
import Control.Monad.Eff (Eff())

import DOM
import DOM.Node.Types
import qualified DOM.Node.Element as E

attr :: String -> String -> Attr
attr x y = { localName: x, value: y }

attrNS :: String -> String -> Maybe String -> Maybe String -> AttrNS
attrNS ln v ns pr = { localName : ln
, value : v
, namespaceURI : toNullable ns
, prefix : toNullable pr
, legacyName : ln
, legacySpecified : true }

setAttribute :: forall eff. Attr -> Element -> Eff (dom :: DOM | eff) Attr
setAttribute x y = E.setAttribute x.localName x.value y >> return x

setAttributeNS :: forall eff. AttrNS -> Element -> Eff (dom :: DOM | eff) AttrNS
setAttributeNS x y = E.setAttributeNS x.namespaceURI x.localName x.value y >> return x

getAttribute :: forall eff. Attr -> Element -> Eff (dom :: DOM | eff) (Nullable Attr)
getAttribute x y = E.getAttribute x.localName y >>=
\v -> return $
fmapNull (\v1 -> { localName: x.localName, value: v1 }) v

getAttributeNS :: forall eff. AttrNS -> Element -> Eff (dom :: DOM | eff) (Nullable AttrNS)
getAttributeNS x y = E.getAttributeNS x.namespaceURI x.localName y >>=
\v -> return $
fmapNull (\v1 -> { localName : x.localName
, value : v1
, legacyName : x.legacyName
, namespaceURI : x.namespaceURI
, prefix : x.prefix
, legacySpecified : x.legacySpecified }) v

hasAttribute :: forall eff. Attr -> Element -> Eff (dom :: DOM | eff) Boolean
hasAttribute x y = E.hasAttribute x.localName y

hasAttributeNS :: forall eff. AttrNS -> Element -> Eff (dom :: DOM | eff) Boolean
hasAttributeNS x y = E.hasAttributeNS x.namespaceURI x.localName y

removeAttribute :: forall eff. Attr -> Element -> Eff (dom :: DOM | eff) Attr
removeAttribute x y = E.removeAttribute x.localName y >> return x

removeAttributeNS :: forall eff. AttrNS -> Element -> Eff (dom :: DOM | eff) AttrNS
removeAttributeNS x y = E.removeAttributeNS x.namespaceURI x.localName y >> return x

fmapNull :: forall a b. (a -> b) -> (Nullable a) -> (Nullable b)
fmapNull f x = g f $ toMaybe x
where
g f Nothing = toNullable Nothing
g f (Just v) = toNullable $ Just (f v)

(>>) :: forall a b m. (Monad m) => m a -> m b -> m b
(>>) x y = x >>= \_ -> y
Copy link
Member

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

This is defined as (*>) in Control.Applicative - no need for (>>) in PureScript as Applicative is a superclass of Monad.

Copy link
Contributor Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Old habits die hard.

61 changes: 61 additions & 0 deletions src/DOM/Node/Element.js
Original file line number Diff line number Diff line change
Expand Up @@ -81,10 +81,71 @@ exports.setAttribute = function (name) {
};
};

exports.setAttributeNS = function (ns) {
return function (localName) {
return function (value) {
return function (element) {
return function () {
element.setAttribute(localName, value);
return {};
};
};
};
};
};

exports.getAttribute = function (name) {
return function (element) {
return function () {
return element.getAttribute(name);
};
};
};

exports.getAttributeNS = function (ns) {
return function (localName) {
return function (element) {
return function () {
return element.getAttribute(localName);
};
};
};
};

exports.hasAttribute = function (name) {
return function (element) {
return function () {
return element.hasAttribute(name);
};
};
};

exports.hasAttributeNS = function (ns) {
return function (localName) {
return function (element) {
return function () {
return element.hasAttribute(localName);
};
};
};
};

exports.removeAttribute = function (name) {
return function (element) {
return function () {
element.removeAttribute(name);
return {};
};
};
};

exports.removeAttributeNS = function (ns) {
return function (name) {
return function (element) {
return function () {
element.removeAttribute(name);
return {};
};
};
};
};
6 changes: 6 additions & 0 deletions src/DOM/Node/Element.purs
Original file line number Diff line number Diff line change
Expand Up @@ -22,4 +22,10 @@ foreign import getElementsByTagNameNS :: forall eff. Nullable String -> String -
foreign import getElementsByClassName :: forall eff. String -> Element -> Eff (dom :: DOM | eff) HTMLCollection

foreign import setAttribute :: forall eff. String -> String -> Element -> Eff (dom :: DOM | eff) String
foreign import setAttributeNS :: forall eff. (Nullable String) -> String -> String -> Element -> Eff (dom :: DOM | eff) String
foreign import getAttribute :: forall eff. String -> Element -> Eff (dom :: DOM | eff) (Nullable String)
foreign import getAttributeNS :: forall eff. (Nullable String) -> String -> Element -> Eff (dom :: DOM | eff) (Nullable String)
foreign import hasAttribute :: forall eff. String -> Element -> Eff (dom :: DOM | eff) Boolean
foreign import hasAttributeNS :: forall eff. (Nullable String) -> String -> Element -> Eff (dom :: DOM | eff) Boolean
foreign import removeAttribute :: forall eff. String -> Element -> Eff (dom :: DOM | eff) String
foreign import removeAttributeNS :: forall eff. (Nullable String) -> String -> Element -> Eff (dom :: DOM | eff) String
10 changes: 10 additions & 0 deletions src/DOM/Node/Types.purs
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,7 @@ module DOM.Node.Types where

import Prelude

import Data.Nullable (Nullable())
import qualified Unsafe.Coerce as U

foreign import data Node :: *
Expand Down Expand Up @@ -73,3 +74,12 @@ foreign import data DocumentType :: *

documentTypeToNode :: DocumentType -> Node
documentTypeToNode = U.unsafeCoerce

type Attr = { localName :: String
, value :: String }
type AttrNS = { localName :: String
, value :: String
, legacyName :: String
, namespaceURI :: Nullable String
, prefix :: Nullable String
, legacySpecified :: Boolean }