Skip to content

Commit

Permalink
finished first pass of save button
Browse files Browse the repository at this point in the history
  • Loading branch information
bbarker committed Jul 22, 2019
1 parent 3754e74 commit 090ce07
Show file tree
Hide file tree
Showing 2 changed files with 44 additions and 24 deletions.
46 changes: 41 additions & 5 deletions app/src/Metajelo/FormUtil.purs
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
module Metajelo.FormUtil where

import Prelude (class Show, Void, bind, join, pure, show, (+), (-), ($), (<$>), (<#>), (<<<))
import Prelude (class Show, Void, bind, join, pure, show, (+), (-), ($), (<$>), (<#>), (<<<), (==), (||))

import Concur.Core (Widget)
import Concur.React (HTML)
Expand All @@ -26,12 +26,14 @@ import Metajelo.Types as M
import Metajelo.Validation as V
import Metajelo.XPaths.Read as MR
import Prim.Row (class Cons)
import Prim.RowList (class RowToList)
import React.SyntheticEvent (SyntheticMouseEvent)
import Text.Email.Validate (EmailAddress)

-- Note: Common practice to use `Void` to represent "no error possible"

type MKFState form = F.State form (Widget HTML)
type MKValidators form = form Record (F.Validation form (Widget HTML))

-- | No validation is needed for this field type, as the input and ouput
-- | types (`io`) are the same.
Expand All @@ -43,7 +45,7 @@ mayToString Nothing = ""

emptyMeansOptional :: forall a. Show a => Maybe a -> String
emptyMeansOptional mayV = case mayV of
Nothing -> "(optional)"
Nothing -> "(None)"
x -> mayToString x

menu :: forall opt s form e o restF restI inputs fields
Expand Down Expand Up @@ -78,7 +80,41 @@ instance isOptionMaybeInstitutionContactType
fromOptionValue = join <<< hush <<< MR.readInstitutionContactType

formSaveButton :: forall form. MKFState form -> Widget HTML SyntheticMouseEvent
formSaveButton fstate =
if fstate.dirty then D.button [P.onClick] [D.text "Save"]
else D.button [P.disabled true] [D.text "Saved"]
formSaveButton fstate = D.button props [D.text "Save"]
where props = if fstate.dirty then [P.onClick] else [P.disabled true]


-- t1: inputs
-- t2: ?
-- t3: fields
-- t4: form


--TODO: this is in formless-independent
-- | Initialise the form state with default values.
-- | Passing in the initial inputs, and the validations.
initFormState
:: ixs form is fs m
. RowToList is ixs
=> Internal.InputFieldsToFormFields ixs is fs
=> Newtype (form Record F.InputField) { | is }
=> Newtype (form Record F.FormField) { | fs }
=> form Record F.InputField
-> form Record (F.Validation form m)
-> F.State form m
initFormState form validations =
{ validity: F.Incomplete
, dirty: false
, submitting: false
, errors: 0
, submitAttempts: 0
, form: Internal.inputFieldsToFormFields form
, internal: F.InternalState
{ initialInputs: form
, validators: validations
, allTouched: false
-- TODO
-- , debounceRef: ...
-- , validationRef: ...
}
}
22 changes: 3 additions & 19 deletions app/src/Metajelo/Forms/InstitutionContact.purs
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,7 @@ import Data.Monoid (mempty)
import Data.Newtype (class Newtype)
import Formless as F
import Formless.Internal.Transform as Internal
import Metajelo.FormUtil (IdentityField, MKFState, formSaveButton, menu)
import Metajelo.FormUtil (IdentityField, MKFState, MKValidators, formSaveButton, initFormState, menu)
import Metajelo.Types as M
import Metajelo.Validation as V
import Metajelo.View (contactWidg)
Expand All @@ -34,7 +34,7 @@ proxies = F.mkSProxies (F.FormProxy :: F.FormProxy InstContactForm)
-- Some type helpers
type InputForm = InstContactForm Record F.InputField
-- type OutputForm = InstContactForm Record F.OutputField
type Validators = InstContactForm Record (F.Validation InstContactForm (Widget HTML))
type Validators = MKValidators InstContactForm
type FState = MKFState InstContactForm

type InputRecord = {
Expand Down Expand Up @@ -92,24 +92,8 @@ contactSignal instContactMay = step instContactMay do
inputs <- pure $ F.wrapInputFields $ outToInRec instContactMay
instContact <- D.div' [
D.h2' [D.text "Institution Contact"]
, contactForm (initState inputs validators)
, contactForm (initFormState inputs validators)
, foldMap contactWidg instContactMay
]
pure $ contactSignal $ Just instContact


-- This should be in Formless
initState :: InputForm -> Validators -> FState
initState form validations =
{ validity: F.Incomplete
, dirty: false
, submitting: false
, errors: 0
, submitAttempts: 0
, form: Internal.inputFieldsToFormFields form
, internal: F.InternalState
{ initialInputs: form
, validators: validations
, allTouched: false
}
}

0 comments on commit 090ce07

Please sign in to comment.