Skip to content

Commit

Permalink
Add ability to generate a record of symbol proxies for large forms (#13)
Browse files Browse the repository at this point in the history
* First cut at generating proxies

* Remove duplicate code.

* Generating symbol proxies

* Other versions...

* Added ability to generate symbol proxies for particularly large forms.
  • Loading branch information
thomashoneyman authored Jul 31, 2018
1 parent dc87a1e commit f3a24b8
Show file tree
Hide file tree
Showing 15 changed files with 164 additions and 122 deletions.
10 changes: 5 additions & 5 deletions example/external-components/Component.purs
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,7 @@ import Effect.Console as Console
import Example.App.UI.Element as UI
import Example.App.UI.Typeahead as TA
import Example.ExternalComponents.RenderForm (formless)
import Example.ExternalComponents.Spec (User, _email, _language, _whiskey, formSpec, submitter, validator)
import Example.ExternalComponents.Spec (User, proxies, formSpec, submitter, validator)
import Example.ExternalComponents.Types (ChildQuery, ChildSlot, Query(..), Slot(..), State)
import Formless as F
import Halogen as H
Expand Down Expand Up @@ -72,13 +72,13 @@ component =

Typeahead slot (TA.SelectionsChanged new) a -> case slot of
Email -> a <$ do
H.query unit $ H.action $ F.ModifyValidate (F.setInput _email new)
H.query unit $ H.action $ F.ModifyValidate (F.setInput proxies.email new)

Whiskey -> a <$ do
_ <- H.query unit $ H.action $ F.ModifyValidate (F.setInput _whiskey new)
_ <- H.query unit $ H.action $ F.ModifyValidate (F.setInput proxies.whiskey new)
-- We'll clear the email field when a new whiskey is selected
_ <- H.query unit $ H.action $ F.Reset (F.resetField _email)
_ <- H.query unit $ H.action $ F.Reset (F.resetField proxies.email)
H.query unit $ H.action $ F.Send Email (H.action TA.Clear)

Language -> a <$ do
H.query unit $ H.action $ F.ModifyValidate (F.setInput _language new)
H.query unit $ H.action $ F.ModifyValidate (F.setInput proxies.language new)
10 changes: 5 additions & 5 deletions example/external-components/RenderForm.purs
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@ import Prelude
import Effect.Aff (Aff)
import Example.App.UI.Element as UI
import Example.App.UI.Typeahead as TA
import Example.ExternalComponents.Spec (Form, User, _email, _language, _name, _whiskey)
import Example.ExternalComponents.Spec (Form, User, proxies)
import Example.ExternalComponents.Types (Query(..), Slot(..))
import Formless as F
import Halogen as H
Expand All @@ -21,7 +21,7 @@ formless state =
{ label: "Name"
, help: "Write your name"
, placeholder: "Dale"
, sym: _name
, sym: proxies.name
} state
, email state
, whiskey state
Expand Down Expand Up @@ -55,7 +55,7 @@ email :: F.State Form User Aff -> F.HTML Query (TA.Query String) Slot Form User
email state =
UI.field
{ label: "Email"
, help: UI.resultToHelp "Choose an email address -- carefully." (F.getResult _email state.form)
, help: UI.resultToHelp "Choose an email address -- carefully." (F.getResult proxies.email state.form)
}
[ HH.slot Email TA.single
{ placeholder: "me@you.com"
Expand All @@ -74,7 +74,7 @@ whiskey :: F.State Form User Aff -> F.HTML Query (TA.Query String) Slot Form Use
whiskey state =
UI.field
{ label: "Whiskey"
, help: UI.resultToHelp "Select a favorite whiskey" (F.getResult _whiskey state.form)
, help: UI.resultToHelp "Select a favorite whiskey" (F.getResult proxies.whiskey state.form)
}
[ HH.slot Whiskey TA.single
{ placeholder: "Lagavulin 12"
Expand All @@ -92,7 +92,7 @@ language :: F.State Form User Aff -> F.HTML Query (TA.Query String) Slot Form Us
language state =
UI.field
{ label: "Language"
, help: UI.resultToHelp "Choose your favorite programming language." (F.getResult _language state.form)
, help: UI.resultToHelp "Choose your favorite programming language." (F.getResult proxies.language state.form)
}
[ HH.slot Language TA.single
{ placeholder: "Haskell"
Expand Down
14 changes: 5 additions & 9 deletions example/external-components/Spec.purs
Original file line number Diff line number Diff line change
Expand Up @@ -4,12 +4,10 @@ import Prelude

import Data.Maybe (Maybe, fromMaybe)
import Data.Newtype (class Newtype)
import Data.Symbol (SProxy(..))
import Example.App.Validation as V
import Formless.Spec (FormSpec, InputType, InputField, OutputType, OutputField)
import Formless.Spec.Transform (mkFormSpecFromRow, unwrapOutput)
import Formless.Spec (FormProxy(..), FormSpec, InputField, OutputField, OutputType)
import Formless.Spec.Transform (SProxies, mkFormSpecFromProxy, mkSProxies, unwrapOutput)
import Formless.Validation.Semigroup (applyOnInputFields)
import Type.Row (RProxy(..))

type User = Record (FormRow OutputType)

Expand All @@ -24,13 +22,11 @@ type FormRow f =
)

-- | You'll usually want symbol proxies for convenience
_name = SProxy :: SProxy "name"
_email = SProxy :: SProxy "email"
_whiskey = SProxy :: SProxy "whiskey"
_language = SProxy :: SProxy "language"
proxies :: SProxies Form
proxies = mkSProxies $ FormProxy :: FormProxy Form

formSpec :: Form FormSpec
formSpec = mkFormSpecFromRow $ RProxy :: RProxy (FormRow InputType)
formSpec = mkFormSpecFromProxy $ FormProxy :: FormProxy Form

validator :: Form InputField -> Form InputField
validator = applyOnInputFields
Expand Down
30 changes: 18 additions & 12 deletions example/polyform/Component.purs
Original file line number Diff line number Diff line change
Expand Up @@ -2,13 +2,13 @@ module Example.Polyform.Component where

import Prelude

import Example.App.UI.Element as UI
import Data.Maybe (Maybe(..))
import Data.Newtype (class Newtype)
import Data.Symbol (SProxy(..))
import Effect.Aff (Aff)
import Effect.Class (class MonadEffect)
import Effect.Console as Console
import Example.App.UI.Element as UI
import Example.App.Validation as V
import Formless as F
import Formless.Validation.Polyform (applyOnInputFields)
Expand All @@ -18,7 +18,6 @@ import Halogen.HTML.Events as HE
import Halogen.HTML.Properties as HP
import Polyform.Validation as Validation
import Record (delete)
import Type.Row (RProxy(..))

data Query a = HandleFormless (F.Message' Form User) a

Expand Down Expand Up @@ -72,7 +71,7 @@ component =
, HH.slot
unit
F.component
{ formSpec: F.mkFormSpecFromRow $ RProxy :: RProxy (FormRow F.InputType)
{ formSpec: F.mkFormSpecFromProxy _form
, validator
, submitter: pure <<< F.unwrapOutput
, render: renderFormless
Expand All @@ -84,23 +83,29 @@ component =
----------
-- Formless

-- We can recover both our user type and our form from the same row.
type User = Record (FormRow F.OutputType)

newtype Form f = Form (Record (FormRow f))
derive instance newtypeForm :: Newtype (Form f) _

-- This proxy will let us generate all the SProxies for our form as
-- well as our entire initial form.
_form = F.FormProxy :: F.FormProxy Form

-- This is a record of symbol proxies, which we can now pass to the
-- various Formless functions that require them. See the render function
-- below as an example in practice.
proxies :: F.SProxies Form
proxies = F.mkSProxies _form

type FormRow f =
( name :: f V.Errs String V.Name
, email :: f V.Errs String V.Email
, city :: f V.Errs String String
, state :: f V.Errs String String
)

_name = SProxy :: SProxy "name"
_email = SProxy :: SProxy "email"
_city = SProxy :: SProxy "city"
_state = SProxy :: SProxy "state"

validator :: m. MonadEffect m => Form F.InputField -> m (Form F.InputField)
validator = applyOnInputFields
{ name: V.Name <$> (V.minLength 5 *> V.maxLength 10)
Expand All @@ -117,28 +122,28 @@ renderFormless state =
{ label: "Name"
, help: "Write your name"
, placeholder: "Dale"
, sym: _name
, sym: proxies.name
} state
, UI.formlessField
UI.input
{ label: "Email Address"
, help: "Write your email"
, placeholder: "me@you.com"
, sym: _email
, sym: proxies.email
} state
, UI.formlessField
UI.input
{ label: "City"
, help: "Write your favorite city"
, placeholder: "Los Angeles"
, sym: _city
, sym: proxies.city
} state
, UI.formlessField
UI.input
{ label: "State"
, help: "Write your favorite state of mind"
, placeholder: ""
, sym: _state
, sym: proxies.state
} state
, HH.br_
, UI.p_ $
Expand All @@ -162,3 +167,4 @@ renderFormless state =
[ HH.text "Reset" ]
]
]

29 changes: 14 additions & 15 deletions example/real-world/Component.purs
Original file line number Diff line number Diff line change
Expand Up @@ -10,8 +10,7 @@ import Example.App.UI.Dropdown as DD
import Example.App.UI.Element (css)
import Example.App.UI.Element as UI
import Example.App.UI.Typeahead as TA
import Example.RealWorld.Data.Group (Group(..), _admin, _applications, _pixels, _secretKey1, _secretKey2, _whiskey)
import Example.RealWorld.Data.Options (Options(..), _enable, _metric)
import Example.RealWorld.Data.Group as G
import Example.RealWorld.Data.Options as O
import Example.RealWorld.Render.GroupForm as GroupForm
import Example.RealWorld.Render.OptionsForm as OptionsForm
Expand Down Expand Up @@ -109,7 +108,7 @@ component =
F.component
{ formSpec: defaultOptionsSpec
, validator: pure <$> optionsFormValidate
, submitter: pure <<< Options <<< F.unwrapOutput
, submitter: pure <<< O.Options <<< F.unwrapOutput
, render: OptionsForm.render
}
(HE.input OptionsForm)
Expand Down Expand Up @@ -143,7 +142,7 @@ component =
-- Here, we'll construct our new group from the two form outputs.
case mbGroupForm, mbOptionsForm of
Just g, Just v -> do
H.modify_ _ { group = map (over Group (_ { options = v })) g }
H.modify_ _ { group = map (over G.Group (_ { options = v })) g }
_, _ -> H.liftEffect (Console.error "Forms did not validate.")
st <- H.get
H.liftEffect $ Console.log $ show st.group
Expand All @@ -163,22 +162,22 @@ component =
pure a

TASingle (TA.SelectionsChanged new) a -> a <$ do
H.query' CP.cp1 unit $ H.action $ F.ModifyValidate (F.setInput _whiskey new)
H.query' CP.cp1 unit $ H.action $ F.ModifyValidate (F.setInput G.proxies.whiskey new)

TAMulti slot (TA.SelectionsChanged new) a -> a <$ case slot of
Applications ->
H.query' CP.cp1 unit $ H.action $ F.ModifyValidate (F.setInput _applications new)
H.query' CP.cp1 unit $ H.action $ F.ModifyValidate (F.setInput G.proxies.applications new)
Pixels ->
H.query' CP.cp1 unit $ H.action $ F.ModifyValidate (F.setInput _pixels new)
H.query' CP.cp1 unit $ H.action $ F.ModifyValidate (F.setInput G.proxies.pixels new)

AdminDropdown m a -> a <$ do
_ <- H.query' CP.cp1 unit $ H.action $ F.Reset (F.resetField _secretKey1)
_ <- H.query' CP.cp1 unit $ H.action $ F.Reset (F.resetField _secretKey2)
_ <- H.query' CP.cp1 unit $ H.action $ F.Reset (F.resetField G.proxies.secretKey1)
_ <- H.query' CP.cp1 unit $ H.action $ F.Reset (F.resetField G.proxies.secretKey2)
case m of
DD.Selected x -> do
H.query' CP.cp1 unit $ H.action $ F.ModifyValidate (F.setInput _admin (Just x))
H.query' CP.cp1 unit $ H.action $ F.ModifyValidate (F.setInput G.proxies.admin (Just x))
DD.Cleared -> do
H.query' CP.cp1 unit $ H.action $ F.ModifyValidate (F.setInput _admin Nothing)
H.query' CP.cp1 unit $ H.action $ F.ModifyValidate (F.setInput G.proxies.admin Nothing)

-----
-- Options Form
Expand All @@ -191,10 +190,10 @@ component =
st' <- H.modify _
{ optionsFormErrors = fstate.errors
, optionsFormDirty = fstate.dirty
, optionsEnabled = F.getInput _enable fstate.form
, optionsEnabled = F.getInput O.proxies.enable fstate.form
}

let submitter = pure <<< Options <<< F.unwrapOutput
let submitter = pure <<< O.Options <<< F.unwrapOutput
validator = pure <$> optionsFormValidate

-- The generated spec will set enabled to false, but we'll want it to be true before
Expand All @@ -212,6 +211,6 @@ component =

MetricDropdown m a -> a <$ case m of
DD.Selected x -> do
H.query' CP.cp2 unit $ H.action $ F.ModifyValidate (F.setInput _metric (Just x))
H.query' CP.cp2 unit $ H.action $ F.ModifyValidate (F.setInput O.proxies.metric (Just x))
DD.Cleared -> do
H.query' CP.cp2 unit $ H.action $ F.ModifyValidate (F.setInput _metric Nothing)
H.query' CP.cp2 unit $ H.action $ F.ModifyValidate (F.setInput O.proxies.metric Nothing)
12 changes: 3 additions & 9 deletions example/real-world/Data/Group.purs
Original file line number Diff line number Diff line change
Expand Up @@ -41,12 +41,6 @@ type GroupRow f r =
| r
)

_name = SProxy :: SProxy "name"
_admin = SProxy :: SProxy "admin"
_applications = SProxy :: SProxy "applications"
_pixels = SProxy :: SProxy "pixels"
_whiskey = SProxy :: SProxy "whiskey"

-- | Here's the Group data type we'll use throughout our application. After we send
-- | a form result off to the server, this is what we'll get in return.
newtype Group = Group
Expand All @@ -70,12 +64,12 @@ _options = SProxy :: SProxy "options"
newtype GroupForm f = GroupForm (Record (GroupFormRow f))
derive instance newtypeGroupForm :: Newtype (GroupForm f) _

proxies :: F.SProxies GroupForm
proxies = F.mkSProxies $ F.FormProxy :: F.FormProxy GroupForm

-- | In order to generate our fields automatically using mkFormSpecFromRow, we'll make
-- | sure to have the new row as a new type.
type GroupFormRow f = GroupRow f
( secretKey1 :: f Errs String String
, secretKey2 :: f Errs String String
)

_secretKey1 = SProxy :: SProxy "secretKey1"
_secretKey2 = SProxy :: SProxy "secretKey2"
20 changes: 3 additions & 17 deletions example/real-world/Data/Options.purs
Original file line number Diff line number Diff line change
Expand Up @@ -8,10 +8,8 @@ import Prelude

import Data.Generic.Rep (class Generic)
import Data.Generic.Rep.Show (genericShow)
import Data.Maybe (Maybe(..))
import Data.Maybe (Maybe)
import Data.Newtype (class Newtype)
import Data.String.Read (class Read)
import Data.Symbol (SProxy(..))
import Example.App.Validation (class ToText, Errs)
import Formless as F

Expand Down Expand Up @@ -44,12 +42,6 @@ instance toTextMetric :: ToText Metric where
toText ClickCost = "Click Cost"
toText InstallCost = "Install Cost"

instance readMetric :: Read Metric where
read "View Cost" = Just ViewCost
read "Click Cost" = Just ClickCost
read "Install Cost" = Just InstallCost
read _ = Nothing

-- | This data type will be used in radio buttons, and so if we
-- | want to generate an initial form from our row, we'll need an
-- | instance of the F.Initial type class
Expand Down Expand Up @@ -85,14 +77,8 @@ type OptionsRow f =
, speed :: f Unit Speed Speed
)

_enable = SProxy :: SProxy "enable"
_metric = SProxy :: SProxy "metric"
_viewCost = SProxy :: SProxy "viewCost"
_clickCost = SProxy :: SProxy "clickCost"
_installCost = SProxy :: SProxy "installCost"
_size = SProxy :: SProxy "size"
_dimensions = SProxy :: SProxy "dimensions"
_speed = SProxy :: SProxy "speed"
proxies :: F.SProxies OptionsForm
proxies = F.mkSProxies $ F.FormProxy :: F.FormProxy OptionsForm

-- | This is the data type used throughout the application. In this case, it's the same
-- | as the form and the underlying row.
Expand Down
Loading

0 comments on commit f3a24b8

Please sign in to comment.