Skip to content

Commit c0904fd

Browse files
Add editableTable form builder (#53)
* Make setModified recursively traverse form data * Add TableFormBuilder and editableTable form * Fix typo in comment
1 parent 2420134 commit c0904fd

File tree

5 files changed

+417
-38
lines changed

5 files changed

+417
-38
lines changed

docs/Examples/Form.example.purs

Lines changed: 113 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -3,16 +3,18 @@ module Lumi.Components.Examples.Form where
33
import Prelude
44

55
import Control.Coroutine.Aff (close, emit, produceAff)
6+
import Control.MonadZero (guard)
67
import Data.Array as Array
8+
import Data.Foldable (foldMap)
79
import Data.Int as Int
810
import Data.Lens (iso)
911
import Data.Lens.Record (prop)
1012
import Data.Maybe (Maybe(..), fromMaybe, isJust, maybe)
11-
import Data.Monoid (guard)
13+
import Data.Monoid as Monoid
1214
import Data.Newtype (class Newtype, un)
1315
import Data.Nullable as Nullable
1416
import Data.String as String
15-
import Data.String.NonEmpty (length, NonEmptyString, toString)
17+
import Data.String.NonEmpty (NonEmptyString, appendString, length, toString)
1618
import Data.Symbol (SProxy(..))
1719
import Effect (Effect)
1820
import Effect.Aff (Aff, Milliseconds(..), delay, error, throwError)
@@ -24,6 +26,7 @@ import Lumi.Components.Example (example)
2426
import Lumi.Components.Form (FormBuilder, Validated)
2527
import Lumi.Components.Form as F
2628
import Lumi.Components.Form.Defaults (formDefaults)
29+
import Lumi.Components.Form.Table as FT
2730
import Lumi.Components.Input as Input
2831
import Lumi.Components.LabeledField (labeledField, RequiredField(..))
2932
import Lumi.Components.Modal (dialog)
@@ -56,7 +59,7 @@ docs = unit # make component { initialState, render }
5659
where
5760
initialState =
5861
{ user: (formDefaults :: User)
59-
{ favoriteColor = Just "red"
62+
{ leastFavoriteColors = ["red"]
6063
}
6164
, result: Nothing :: Maybe ValidatedUser
6265
, modalOpen: false
@@ -208,6 +211,9 @@ docs = unit # make component { initialState, render }
208211
"red" -> pure { label: "Red", value: "red" }
209212
"green" -> pure { label: "Green", value: "green" }
210213
"blue" -> pure { label: "Blue", value: "blue" }
214+
"brown" -> pure { label: "Brown", value: "brown" }
215+
"black" -> pure { label: "Black", value: "black" }
216+
"white" -> pure { label: "White", value: "white" }
211217
_ -> throwError (error "No color")
212218

213219
loadColors simulatePauses search = do
@@ -217,6 +223,9 @@ docs = unit # make component { initialState, render }
217223
[ { label: "Red", value: "red" }
218224
, { label: "Green", value: "green" }
219225
, { label: "Blue", value: "blue" }
226+
, { label: "Brown", value: "brown" }
227+
, { label: "Black", value: "black" }
228+
, { label: "White", value: "white" }
220229
]
221230

222231
data Country
@@ -249,7 +258,7 @@ type User =
249258
, admin :: Boolean
250259
, height :: Validated String
251260
, addresses :: Validated (Array Address)
252-
, favoriteColor :: Maybe String
261+
, pets :: Validated (Array Pet)
253262
, leastFavoriteColors :: Array String
254263
, notes :: String
255264
, avatar :: Maybe Upload.FileId
@@ -262,11 +271,27 @@ type ValidatedUser =
262271
, admin :: Boolean
263272
, height :: Maybe Number
264273
, addresses :: Array ValidatedAddress
265-
, favoriteColor :: Maybe String
274+
, pets :: Array ValidatedPet
275+
, leastFavoriteColors :: Array String
266276
, notes :: String
267277
, avatar :: Maybe Upload.FileId
268278
}
269279

280+
type Pet =
281+
{ firstName :: Validated String
282+
, lastName :: Validated String
283+
, animal :: Validated (Maybe String)
284+
, age :: Validated String
285+
, color :: Maybe String
286+
}
287+
288+
type ValidatedPet =
289+
{ name :: NonEmptyString
290+
, animal :: String
291+
, age :: Int
292+
, color :: Maybe String
293+
}
294+
270295
-- | We have to fully apply `Form.build` in order to avoid
271296
-- | remounting this component on each render.
272297
userComponent
@@ -296,7 +321,7 @@ userForm = ado
296321
F.indent "First Name" Required
297322
$ F.focus (prop (SProxy :: SProxy "firstName"))
298323
$ F.warn (\x ->
299-
guard
324+
Monoid.guard
300325
(length x <= 2)
301326
(pure "First name should be longer than two characters (but it doesn't have to be).")
302327
)
@@ -335,25 +360,14 @@ userForm = ado
335360
addresses <-
336361
F.focus (prop (SProxy :: SProxy "addresses"))
337362
$ F.warn (\as ->
338-
guard (Array.null as) (pure "No address added.")
363+
Monoid.guard (Array.null as) (pure "No address added.")
339364
)
340365
$ F.array
341366
{ label: "Address"
342367
, addLabel: "Add address"
343368
, defaultValue: formDefaults
344369
, editor: addressForm
345370
}
346-
favoriteColor <-
347-
F.withKey "favoriteColor"
348-
$ F.indent "Favorite Color" Neither
349-
$ F.focus (prop (SProxy :: SProxy "favoriteColor"))
350-
$ F.asyncSelectByKey
351-
(SProxy :: SProxy "loadColor")
352-
(SProxy :: SProxy "loadColors")
353-
identity
354-
identity
355-
identity
356-
(R.text <<< _.label)
357371
leastFavoriteColors <-
358372
F.indent "Least Favorite Colors" Neither
359373
$ F.focus (prop (SProxy :: SProxy "leastFavoriteColors"))
@@ -371,6 +385,85 @@ userForm = ado
371385
$ F.focus (prop (SProxy :: SProxy "notes"))
372386
$ F.textarea
373387

388+
F.section "Pets"
389+
pets <-
390+
F.focus (prop (SProxy :: SProxy "pets"))
391+
$ F.warn (\pets ->
392+
Monoid.guard (Array.null pets) (pure "You should adopt a pet.")
393+
)
394+
$ FT.editableTable
395+
{ addLabel: "Add pet"
396+
, defaultValue: Just
397+
{ firstName: F.Fresh ""
398+
, lastName: F.Fresh ""
399+
, animal: F.Fresh Nothing
400+
, age: F.Fresh "1"
401+
, color: Nothing
402+
}
403+
, maxRows: top
404+
, summary: mempty
405+
, formBuilder: ado
406+
name <- FT.column_ "Name" ado
407+
firstName <-
408+
F.focus (prop (SProxy :: SProxy "firstName"))
409+
$ F.validated (F.nonEmpty "First name")
410+
$ F.textbox
411+
lastName <-
412+
F.focus (prop (SProxy :: SProxy "lastName"))
413+
$ F.warn (\lastName -> do
414+
guard (not String.null lastName)
415+
pure "Did you really give your pet a surname?"
416+
)
417+
$ F.textbox
418+
in
419+
appendString firstName
420+
$ foldMap (" " <> _)
421+
$ Monoid.guard (not String.null lastName)
422+
$ Just lastName
423+
animal <-
424+
FT.column_ "Animal"
425+
$ F.focus (prop (SProxy :: SProxy "animal"))
426+
$ F.validated (F.nonNull "Animal")
427+
$ F.select identity pure
428+
$ map (\value -> { label: value, value })
429+
[ "Bird"
430+
, "Cat"
431+
, "Cow"
432+
, "Dog"
433+
, "Duck"
434+
, "Fish"
435+
, "Horse"
436+
, "Rabbit"
437+
, "Rat"
438+
, "Turle"
439+
]
440+
age <-
441+
FT.column_ "Age"
442+
$ F.focus (prop (SProxy :: SProxy "age"))
443+
$ F.validated (F.validInt "Age")
444+
$ F.number
445+
{ step: Input.Step 1.0
446+
, min: Just 0.0
447+
, max: Nothing
448+
}
449+
color <-
450+
FT.column_ "Color"
451+
$ F.focus (prop (SProxy :: SProxy "color"))
452+
$ F.asyncSelectByKey
453+
(SProxy :: SProxy "loadColor")
454+
(SProxy :: SProxy "loadColors")
455+
identity
456+
identity
457+
identity
458+
(R.text <<< _.label)
459+
in
460+
{ name
461+
, animal
462+
, age
463+
, color
464+
}
465+
}
466+
374467
F.section "Images"
375468
avatar <-
376469
F.indent "Avatar" Optional
@@ -403,8 +496,9 @@ userForm = ado
403496
, password
404497
, admin
405498
, height
499+
, pets
500+
, leastFavoriteColors
406501
, addresses
407-
, favoriteColor
408502
, notes
409503
, avatar
410504
}

src/Lumi/Components/Form.purs

Lines changed: 23 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -45,7 +45,7 @@ module Lumi.Components.Form
4545
import Prelude
4646

4747
import Color (cssStringHSLA)
48-
import Data.Array (mapWithIndex, (:))
48+
import Data.Array ((:))
4949
import Data.Array as Array
5050
import Data.Either (Either(..))
5151
import Data.Foldable (fold, surround)
@@ -85,7 +85,6 @@ import Lumi.Components.Upload as Upload
8585
import Prim.Row (class Nub, class Union, class Cons)
8686
import React.Basic (JSX, createComponent, element, empty, fragment, keyed, makeStateless)
8787
import React.Basic.Components.Async (async, asyncWithLoader)
88-
import React.Basic.DOM (css, unsafeCreateDOMComponent)
8988
import React.Basic.DOM as R
9089
import React.Basic.DOM.Events (capture, stopPropagation, targetChecked, targetValue)
9190
import React.Basic.Events as Events
@@ -148,10 +147,10 @@ build editor = makeStateless (createComponent "Form") render where
148147
, validationError: validationError
149148
, required: required
150149
, forceTopLabel: forceTopLabels
151-
, style: css {}
150+
, style: R.css {}
152151
}
153152

154-
in element (unsafeCreateDOMComponent "lumi-form")
153+
in element (R.unsafeCreateDOMComponent "lumi-form")
155154
{ "class": String.joinWith " " $ fold
156155
[ guard inlineTable ["inline-table"]
157156
, guard readonly ["readonly"]
@@ -189,7 +188,7 @@ inputBox inputProps = formBuilder_ \{ readonly } s onChange ->
189188
else Input.input inputProps
190189
{ value = s
191190
, onChange = capture targetValue (traverse_ onChange)
192-
, style = css { width: "100%" }
191+
, style = R.css { width: "100%" }
193192
}
194193

195194
-- | A simple text box makes a `FormBuilder` for strings
@@ -223,7 +222,7 @@ textarea = formBuilder_ \{ readonly } s onChange ->
223222
else Textarea.textarea Textarea.defaults
224223
{ value = s
225224
, onChange = capture targetValue (traverse_ onChange)
226-
, style = css { width: "100%" }
225+
, style = R.css { width: "100%" }
227226
}
228227

229228
-- | A `switch` is an editor for booleans which displays Yes or No.
@@ -441,7 +440,7 @@ asyncSelect l toSelectOption optionRenderer =
441440
, loadOptions: get l props
442441
, onChange: onChange
443442
, className: ""
444-
, style: css {}
443+
, style: R.css {}
445444
, searchable: true
446445
, id: ""
447446
, name: ""
@@ -488,7 +487,7 @@ asyncSelectByKey k l fromId toId toSelectOption optionRenderer =
488487
Just _ -> alignToInput
489488
case data_ of
490489
Nothing -> loader
491-
{ style: css { width: "20px", height: "20px", borderWidth: "2px" }
490+
{ style: R.css { width: "20px", height: "20px", borderWidth: "2px" }
492491
, testId: toNullable Nothing
493492
}
494493
Just data_' -> text body
@@ -500,7 +499,7 @@ asyncSelectByKey k l fromId toId toSelectOption optionRenderer =
500499
, loadOptions: get l props
501500
, onChange: onChange <<< map (toId <<< _.value <<< toSelectOption)
502501
, className: ""
503-
, style: css {}
502+
, style: R.css {}
504503
, searchable: true
505504
, id: ""
506505
, name: ""
@@ -692,7 +691,7 @@ arrayModal { label, addLabel, defaultValue, summary, component, componentProps }
692691
, actionButtonTitle: addLabel
693692
, component
694693
, componentProps
695-
, style: css {}
694+
, style: R.css {}
696695
}
697696
}
698697
})
@@ -709,7 +708,7 @@ arrayModal { label, addLabel, defaultValue, summary, component, componentProps }
709708
, actionButtonTitle: addLabel
710709
, component
711710
, componentProps
712-
, style: css {}
711+
, style: R.css {}
713712
}
714713
})
715714
, validate: pure xs
@@ -922,7 +921,7 @@ withKey
922921
withKey key editor = FormBuilder \props value ->
923922
let { edit, validate } = un FormBuilder editor props value
924923
in { edit: \onChange ->
925-
edit onChange # mapWithIndex case _, _ of
924+
edit onChange # Array.mapWithIndex case _, _ of
926925
i, Child a -> Child a { key = Just (key <> "--" <> show i) }
927926
i, Wrapper a -> Wrapper a { key = Just (key <> "--" <> show i) }
928927
i, Node n -> Node n { key = Just (key <> "--" <> show i) }
@@ -1005,6 +1004,18 @@ styles = jss
10051004
{ extend: labeledFieldValidationWarningStyles
10061005
, marginBottom: "calc(4 * 4px)"
10071006
}
1007+
1008+
, "& lumi-editable-table":
1009+
{ "& table tr td:not(.lumi)":
1010+
{ verticalAlign: "top"
1011+
, "& lumi-column":
1012+
{ flex: "1 1 auto"
1013+
}
1014+
}
1015+
, "& .labeled-field--validation-error, & .labeled-field--validation-warning":
1016+
{ marginBottom: "0"
1017+
}
1018+
}
10081019
}
10091020
}
10101021
}

0 commit comments

Comments
 (0)