Skip to content
Projects
Groups
Snippets
Help
Loading...
Help
Submit feedback
Contribute to GitLab
Sign in
Toggle navigation
P
purescript-reactix
Project
Project
Details
Activity
Releases
Cycle Analytics
Repository
Repository
Files
Commits
Branches
Tags
Contributors
Graph
Compare
Charts
Issues
0
Issues
0
List
Board
Labels
Milestones
Merge Requests
0
Merge Requests
0
CI / CD
CI / CD
Pipelines
Jobs
Schedules
Charts
Wiki
Wiki
Snippets
Snippets
Members
Members
Collapse sidebar
Close sidebar
Activity
Graph
Charts
Create a new issue
Jobs
Commits
Issue Boards
Open sidebar
gargantext
purescript-reactix
Commits
28e65139
Commit
28e65139
authored
Jun 30, 2019
by
James Laver
Browse files
Options
Browse Files
Download
Email Patches
Plain Diff
v0.4.0
parent
8df9707e
Changes
4
Hide whitespace changes
Inline
Side-by-side
Showing
4 changed files
with
202 additions
and
114 deletions
+202
-114
README.md
README.md
+24
-0
HTML.purs
src/Reactix/DOM/HTML.purs
+134
-101
Utils.purs
src/Reactix/Utils.purs
+6
-0
Spec.purs
test/Reactix/React/Spec.purs
+38
-13
No files found.
README.md
View file @
28e65139
...
...
@@ -100,6 +100,30 @@ Breaking:
*
`useEffect`
,
`useLayoutEffect`
and their numbered variants no longer
take a redundant dummy unit value to delay computation.
New:
*
'Magic' DOM Props. Each takes a record of props which will be transformed
*
`aria`
- prop names will be prefixed with
`aria-`
*
`data`
- prop names will be prefixed with
`data-`
*
`on`
- prop names will be prefixed with
`on`
, values will be
`mkEffectFn1`
'd
Example:
```
purescript
import Reactix as R
import Reactix.DOM.HTML (div, text)
import DOM.Simple.Console (log)
ex :: R.Element
ex =
div
{ aria: {label: "example"}
, data: {thing: Just 1}
, on: {click: \_ -> log "Hello World"}
}
[ text "Hello World" ]
```
### 0.3.1
Bug Fixes:
...
...
src/Reactix/DOM/HTML.purs
View file @
28e65139
module Reactix.DOM.HTML where
import Prelude ((<<<), ($), (<>), map, identity)
import Data.Maybe (maybe)
import Data.Foldable (foldl)
import Data.String (toUpper)
import Effect.Uncurried (mkEffectFn1)
import FFI.Simple.Objects ((.?), (.=), (!-), (..), keys)
import Reactix.React (Element, createDOMElement)
import Reactix.Utils (ucFirst)
import Unsafe.Coerce (unsafeCoerce)
createLeafElement :: forall props. String -> Record props -> Element
createLeafElement e p = createDOMElement e p []
createDOM :: forall props. String -> Record props -> Array Element -> Element
createDOM e p = createDOMElement e (magicProps p)
magicProps :: forall props. props -> props
magicProps = xformAriaProps <<< xformDataProps <<< xformEventProps
where
xformAriaProps = magicPrefixProp "aria" "aria-"
xformDataProps = magicPrefixProp "data" "data-"
magicPrefixProp :: forall props. String -> String -> props -> props
magicPrefixProp prop pre props = maybe props help (props .? prop)
where help val = prefixCopyAll pre props val !- prop
xformEventProps :: forall props. props -> props
xformEventProps props = maybe props help (props .? "on")
where
help = mapCopyAll eventPropName mkEffectFn1 props
eventPropName other = "on" <> ucFirst other
prefixCopyAll :: forall p q. String -> p -> q -> p
prefixCopyAll pre = mapCopyAll (pre <> _) identity
mapCopyAll :: forall a b p q. (String -> String) -> (a -> b) -> p -> q -> p
mapCopyAll xf yf dest src = foldl f dest (keys src)
where f dest k = (dest .= xf k) (yf $ src .. k)
createLeafDOM :: forall props. String -> Record props -> Element
createLeafDOM e p = createDOM e p []
-- A factory function for a DOM element with no children
type LeafFactory = forall props. Record props -> Element
...
...
@@ -32,298 +65,298 @@ text :: String -> Element
text = unsafeCoerce
a :: ElemFactory
a = createDOM
Element
"a"
a = createDOM "a"
abbr :: ElemFactory
abbr = createDOM
Element
"abbr"
abbr = createDOM "abbr"
address :: ElemFactory
address = createDOM
Element
"address"
address = createDOM "address"
article :: ElemFactory
article = createDOM
Element
"article"
article = createDOM "article"
aside :: ElemFactory
aside = createDOM
Element
"aside"
aside = createDOM "aside"
audio :: ElemFactory
audio = createDOM
Element
"audio"
audio = createDOM "audio"
b :: ElemFactory
b = createDOM
Element
"b"
b = createDOM "b"
bdi :: ElemFactory
bdi = createDOM
Element
"bdi"
bdi = createDOM "bdi"
bdo :: ElemFactory
bdo = createDOM
Element
"bdo"
bdo = createDOM "bdo"
blockquote :: ElemFactory
blockquote = createDOM
Element
"blockquote"
blockquote = createDOM "blockquote"
br :: LeafFactory
br = createLeaf
Element
"br"
br = createLeaf
DOM
"br"
button :: ElemFactory
button = createDOM
Element
"button"
button = createDOM "button"
canvas :: ElemFactory
canvas = createDOM
Element
"canvas"
canvas = createDOM "canvas"
caption :: ElemFactory
caption = createDOM
Element
"caption"
caption = createDOM "caption"
cite :: ElemFactory
cite = createDOM
Element
"cite"
cite = createDOM "cite"
code :: ElemFactory
code = createDOM
Element
"code"
code = createDOM "code"
col :: LeafFactory
col = createLeaf
Element
"col"
col = createLeaf
DOM
"col"
colgroup :: ElemFactory
colgroup = createDOM
Element
"colgroup"
colgroup = createDOM "colgroup"
data' :: ElemFactory
data' = createDOM
Element
"data"
data' = createDOM "data"
datalist :: ElemFactory
datalist = createDOM
Element
"datalist"
datalist = createDOM "datalist"
dd :: ElemFactory
dd = createDOM
Element
"dd"
dd = createDOM "dd"
del :: ElemFactory
del = createDOM
Element
"del"
del = createDOM "del"
details :: ElemFactory
details = createDOM
Element
"details"
details = createDOM "details"
dfn :: ElemFactory
dfn = createDOM
Element
"dfn"
dfn = createDOM "dfn"
dialog :: ElemFactory
dialog = createDOM
Element
"dialog"
dialog = createDOM "dialog"
div :: ElemFactory
div = createDOM
Element
"div"
div = createDOM "div"
dl :: ElemFactory
dl = createDOM
Element
"dl"
dl = createDOM "dl"
dt :: ElemFactory
dt = createDOM
Element
"dt"
dt = createDOM "dt"
em :: ElemFactory
em = createDOM
Element
"em"
em = createDOM "em"
embed :: LeafFactory
embed = createLeaf
Element
"embed"
embed = createLeaf
DOM
"embed"
fieldset :: ElemFactory
fieldset = createDOM
Element
"fieldset"
fieldset = createDOM "fieldset"
figcaption :: ElemFactory
figcaption = createDOM
Element
"figcaption"
figcaption = createDOM "figcaption"
figure :: ElemFactory
figure = createDOM
Element
"figure"
figure = createDOM "figure"
footer :: ElemFactory
footer = createDOM
Element
"footer"
footer = createDOM "footer"
form :: ElemFactory
form = createDOM
Element
"form"
form = createDOM "form"
h1 :: ElemFactory
h1 = createDOM
Element
"h1"
h1 = createDOM "h1"
h2 :: ElemFactory
h2 = createDOM
Element
"h2"
h2 = createDOM "h2"
h3 :: ElemFactory
h3 = createDOM
Element
"h3"
h3 = createDOM "h3"
h4 :: ElemFactory
h4 = createDOM
Element
"h4"
h4 = createDOM "h4"
h5 :: ElemFactory
h5 = createDOM
Element
"h5"
h5 = createDOM "h5"
h6 :: ElemFactory
h6 = createDOM
Element
"h6"
h6 = createDOM "h6"
header :: ElemFactory
header = createDOM
Element
"header"
header = createDOM "header"
hr :: LeafFactory
hr = createLeaf
Element
"hr"
hr = createLeaf
DOM
"hr"
i :: ElemFactory
i = createDOM
Element
"i"
i = createDOM "i"
iframe :: ElemFactory
iframe = createDOM
Element
"iframe"
iframe = createDOM "iframe"
img :: LeafFactory
img = createLeaf
Element
"img"
img = createLeaf
DOM
"img"
input :: LeafFactory
input = createLeaf
Element
"input"
input = createLeaf
DOM
"input"
ins :: ElemFactory
ins = createDOM
Element
"ins"
ins = createDOM "ins"
kbd :: ElemFactory
kbd = createDOM
Element
"kbd"
kbd = createDOM "kbd"
label :: ElemFactory
label = createDOM
Element
"label"
label = createDOM "label"
legend :: ElemFactory
legend = createDOM
Element
"legend"
legend = createDOM "legend"
li :: ElemFactory
li = createDOM
Element
"li"
li = createDOM "li"
link :: LeafFactory
link = createLeaf
Element
"link"
link = createLeaf
DOM
"link"
main :: ElemFactory
main = createDOM
Element
"main"
main = createDOM "main"
mark :: ElemFactory
mark = createDOM
Element
"mark"
mark = createDOM "mark"
meter :: ElemFactory
meter = createDOM
Element
"meter"
meter = createDOM "meter"
nav :: ElemFactory
nav = createDOM
Element
"nav"
nav = createDOM "nav"
object :: ElemFactory
object = createDOM
Element
"object"
object = createDOM "object"
ol :: ElemFactory
ol = createDOM
Element
"ol"
ol = createDOM "ol"
optgroup :: ElemFactory
optgroup = createDOM
Element
"optgroup"
optgroup = createDOM "optgroup"
option :: ElemFactory
option = createDOM
Element
"option"
option = createDOM "option"
output :: ElemFactory
output = createDOM
Element
"output"
output = createDOM "output"
p :: ElemFactory
p = createDOM
Element
"p"
p = createDOM "p"
param :: LeafFactory
param = createLeaf
Element
"param"
param = createLeaf
DOM
"param"
picture :: ElemFactory
picture = createDOM
Element
"picture"
picture = createDOM "picture"
pre :: ElemFactory
pre = createDOM
Element
"pre"
pre = createDOM "pre"
progress :: ElemFactory
progress = createDOM
Element
"progress"
progress = createDOM "progress"
q :: ElemFactory
q = createDOM
Element
"q"
q = createDOM "q"
rp :: ElemFactory
rp = createDOM
Element
"rp"
rp = createDOM "rp"
rt :: ElemFactory
rt = createDOM
Element
"rt"
rt = createDOM "rt"
ruby :: ElemFactory
ruby = createDOM
Element
"ruby"
ruby = createDOM "ruby"
s :: ElemFactory
s = createDOM
Element
"s"
s = createDOM "s"
samp :: ElemFactory
samp = createDOM
Element
"samp"
samp = createDOM "samp"
section :: ElemFactory
section = createDOM
Element
"section"
section = createDOM "section"
source :: LeafFactory
source = createLeaf
Element
"source"
source = createLeaf
DOM
"source"
span :: ElemFactory
span = createDOM
Element
"span"
span = createDOM "span"
strong :: ElemFactory
strong = createDOM
Element
"strong"
strong = createDOM "strong"
style :: ElemFactory
style = createDOM
Element
"style"
style = createDOM "style"
sub :: ElemFactory
sub = createDOM
Element
"sub"
sub = createDOM "sub"
sup :: ElemFactory
sup = createDOM
Element
"sup"
sup = createDOM "sup"
summary :: ElemFactory
summary = createDOM
Element
"summary"
summary = createDOM "summary"
svg :: ElemFactory
svg = createDOM
Element
"svg"
svg = createDOM "svg"
table :: ElemFactory
table = createDOM
Element
"table"
table = createDOM "table"
tbody :: ElemFactory
tbody = createDOM
Element
"tbody"
tbody = createDOM "tbody"
td :: ElemFactory
td = createDOM
Element
"td"
td = createDOM "td"
template :: ElemFactory
template = createDOM
Element
"template"
template = createDOM "template"
textarea :: ElemFactory
textarea = createDOM
Element
"textarea"
textarea = createDOM "textarea"
tfoot :: ElemFactory
tfoot = createDOM
Element
"tfoot"
tfoot = createDOM "tfoot"
th :: ElemFactory
th = createDOM
Element
"th"
th = createDOM "th"
thead :: ElemFactory
thead = createDOM
Element
"thead"
thead = createDOM "thead"
time :: ElemFactory
time = createDOM
Element
"time"
time = createDOM "time"
title :: ElemFactory
title = createDOM
Element
"title"
title = createDOM "title"
tr :: ElemFactory
tr = createDOM
Element
"tr"
tr = createDOM "tr"
track :: LeafFactory
track = createLeaf
Element
"track"
track = createLeaf
DOM
"track"
u :: ElemFactory
u = createDOM
Element
"u"
u = createDOM "u"
ul :: ElemFactory
ul = createDOM
Element
"ul"
ul = createDOM "ul"
var :: ElemFactory
var = createDOM
Element
"var"
var = createDOM "var"
video :: ElemFactory
video = createDOM
Element
"video"
video = createDOM "video"
wbr :: LeafFactory
wbr = createLeaf
Element
"wbr"
wbr = createLeaf
DOM
"wbr"
src/Reactix/Utils.purs
View file @
28e65139
module Reactix.Utils where
import Prelude ((<<<), (<>))
import Data.Unit (Unit, unit)
import Data.Tuple (Tuple(..))
import Data.Function.Uncurried (Fn2, runFn2)
import Data.String (splitAt, toUpper)
import Effect (Effect)
import Effect.Uncurried (EffectFn1, runEffectFn1)
import FFI.Simple (delay)
...
...
@@ -18,3 +20,7 @@ currySecond (Tuple a b) = Tuple a (runEffectFn1 b)
hook :: forall v. (Unit -> Effect v) -> Hooks v
hook f = unsafeHooksEffect (delay unit f)
ucFirst :: String -> String
ucFirst = help <<< splitAt 1
where help {before, after} = toUpper before <> after
test/Reactix/React/Spec.purs
View file @
28e65139
...
...
@@ -5,11 +5,13 @@ import Data.Array as A
import Data.Array ( (!!) )
import Data.EuclideanRing (mod)
import Data.Maybe ( Maybe(..) )
import Data.Nullable (null)
import Data.Traversable ( traverse, traverse_, sequence_ )
import Data.Tuple ( Tuple(..) )
import Data.Tuple.Nested ( (/\) )
import Data.Unfoldable (fromMaybe)
import Effect ( Effect )
import Effect.Aff ( Aff )
import Effect.Aff ( Aff
, launchAff
)
import Effect.Class ( liftEffect )
import Effect.Ref as Ref
import Effect.Uncurried ( EffectFn1, mkEffectFn1, runEffectFn1 )
...
...
@@ -20,7 +22,9 @@ import Test.Spec.Assertions ( shouldEqual )
import DOM.Simple as DOM
import DOM.Simple.Document as Document
import DOM.Simple.Element as Element
import DOM.Simple.Node as Node
import DOM.Simple.Event as Event
import DOM.Simple.Types (Element)
import FFI.Simple (delay)
import Reactix as R
import Reactix.Test as RT
...
...
@@ -31,10 +35,22 @@ staticTest :: Spec Unit
staticTest =
describe "Basic DOM rendering" $ do
it "Simple elements" $ do
root <- liftEffect $ RT.render
elem
root <- liftEffect $ RT.render
simple
let children = Element.children root.container
(Element.name <$> children) `shouldEqual` ["I"]
(Element.innerHTML <$> children) `shouldEqual` ["hello world"]
it "Magic props" $ do
root <- liftEffect $ RT.render magic
let children = Element.children root.container
A.length children `shouldEqual` 1
let children2 = children >>= Element.children
let attrNames = A.sort (children >>= Element.attrNames)
let attrVals =
do name <- attrNames
child <- children
fromMaybe $ Element.attr child name
["aria-label", "data-sample"] `shouldEqual` attrNames
["example", "example"] `shouldEqual` attrVals
it "Fragments" $ do
root <- liftEffect $ RT.render $ frag
Element.childCount root.container `shouldEqual` 2
...
...
@@ -42,8 +58,13 @@ staticTest =
A.length children `shouldEqual` 2
(Element.name <$> children) `shouldEqual` ["I", "I"]
(Element.innerHTML <$> children) `shouldEqual` ["hello","world"]
where elem = i {} [ text "hello world" ]
frag = i {} [ text "hello" ] <> i {} [ text "world" ]
where
simple = i {} [ text "hello world" ]
magic = div {aria: {label: "example"}, "data": {sample: "example"}} []
frag = i {} [ text "hello" ] <> i {} [ text "world" ]
getAttr :: String -> Element -> Maybe String
getAttr = flip Element.attr
type CounterProps = ( count :: Int )
...
...
@@ -53,9 +74,8 @@ counterCpt = R.hooksComponent "Counter" cpt
cpt {count} _ = do
y /\ setY <- R.useState' count
pure $ div { className: "counter" }
[ button { type: "button",
onClick: onclick setY (_ + 1)
} [ text "++" ]
[ button { type: "button",
on: { click: \_ -> setY (_ + 1) }
} [ text "++" ]
, div {} [ text (show y) ] ]
onclick set to = mkEffectFn1 $ \e -> set to
counterTest :: Spec Unit
counterTest =
...
...
@@ -95,10 +115,9 @@ bicounterCpt = R.hooksComponent "Bicounter" cpt
cpt {count} _ = do
y /\ reduceY <- R.useReducer' reduce count
pure $ div { className: "counter" }
[ button { type: "button", on
Click: onclick reduceY Inc
} [ text "++" ]
, button { type: "button", on
Click: onclick reduceY Dec
} [ text "--" ]
[ button { type: "button", on
: { click: \_ -> reduceY Inc }
} [ text "++" ]
, button { type: "button", on
: { click: \_ -> reduceY Dec }
} [ text "--" ]
, div {} [ text (show y) ] ]
onclick reducer with = mkEffectFn1 $ \_ -> reducer with
reduce count Inc = count + 1
reduce count Dec = count - 1
...
...
@@ -228,11 +247,17 @@ themeChooserCpt = R.hooksComponent "ThemeChooser" cpt
let context = R.readRef ref
pure $
div {}
[ button { type: "button", onClick: onclick setTheme (const Nothing) } [ text "None" ]
, button { type: "button", onClick: onclick setTheme (const $ Just Dark) } [ text "Dark" ]
, button { type: "button", onClick: onclick setTheme (const $ Just Light) } [ text "Light" ]
[ button
{ type: "button", on: {click: \_ -> setTheme (const Nothing) } }
[ text "None" ]
, button
{ type: "button", on: {click: \_ -> setTheme (const $ Just Dark) } }
[ text "Dark" ]
, button
{ type: "button", on: {click: \_ -> setTheme (const $ Just Light) } }
[ text "Light" ]
, R.provideContext context theme [ R.createElement themedCpt { theme: context } [] ] ]
onclick setTheme theme = mkEffectFn1 $ \_ -> setTheme theme
themeChooserTest :: Spec Unit
themeChooserTest =
describe "ThemeChooser" do
...
...
Write
Preview
Markdown
is supported
0%
Try again
or
attach a new file
Attach a file
Cancel
You are about to add
0
people
to the discussion. Proceed with caution.
Finish editing this message first!
Cancel
Please
register
or
sign in
to comment