Generalizing Yesod.Form.MassInput

I’d like to understand the inner workings of the Yesod.Form.MassInput module. It is so old that not even Michael Snoyman feels able to advise on it. It is sparsely documented. Is there anyone here who could share insights on how it works? Are there comparable modules in other Haskell web frameworks?

I plan to generalize this module to arbitrary Generic types and asked on haskell-cafe and perfomed some experiments. As I understand it, frameworks such as Yesod’s MForm monad, while in principle can contain optional brances via monadic bind, in practice generate all fields and only process the posted content based on the monadic logic. That does not fly with potentially infinite data structures and algebraic sums.

If not with Yesod, I believe it would be beneficial for the Haskell webdev community as a whole if we had a way to generate HTML forms from the representation of a Generic type much in the spirit of Aeson’s Generic classes generating parsers and serializers, together with code to marshal the form’s contents back to a Haskell value.

Already suggested as relevant were: Grace and Tangible Values, both of which do not provide the full generality that GHC.Generics offers. In particular, branching and recursion are the problematic features.

Potentially infinite data structures requires laziness, which then raises the problem of space leaks. But according to the documentation:

https://hackage.haskell.org/package/transformers-0.6.1.1/docs/Control-Monad-Trans-RWS.html

and my version of GHC:

# ghci
GHCi, version 9.4.4: https://www.haskell.org/ghc/  :? for help
ghci> :m Control.Monad.Trans.RWS
ghci> :i RWS
type RWS :: * -> * -> * -> * -> *
type RWS r w s =
  RWST r w s Data.Functor.Identity.Identity :: * -> *
  	-- Defined in ‘Control.Monad.Trans.RWS.Lazy’
ghci> 

MForm relies on the lazy version of the RWS transformer type - can you confirm this in your version of GHC?

Yes, indeed:

> :info MForm
type MForm (m :: * -> *) a =
  transformers-0.5.6.2:Control.Monad.Trans.RWS.Lazy.RWST
    (Maybe (Env, FileEnv), HandlerSite m, [Lang]) Enctype Ints m a
  	-- Defined in ‘Yesod.Form.Types’

But lazyness is not the point, I guess. Lazyness is replaced by a stateful process that expands the form as the user traverses the spine of the data structure being input, akin to thunks in the runtime. The state in MForm is (isomorphic to) a non-empty list of Int which as far as I can see is used to generate unique identifiers for the individual input fields of the form. Hence the state-manipulating up and down functions in the source of Yesod.Form.MassInput. That said, the inputList form generates additional checkboxes for deleting and adding list elements, but these seem to have no dynamic effect. It appears that in order to use them, one must submit the form. But all I ever get when checking the “Add another row” box prior to submitting is a FormFailure complaining about a missing value. Am I using it wrong?

So in general, the first task is to find a way to traverse any Rep t value and number the K1 constructors or whatever is the placeholder for input fields. This numbering must be sensitive to the current choice of L1 or R1 anywhere in the form. That sounds like a doable sub-task in this endeavor.

My workplace uses Yesod forms ubiquitously. We have investigated ways of generalizing Form creation to handle Generic data types and each time we concluded that it is much, much simpler to just write out the MForm by hand.

One of the ways we’ve made this easier is by using type annotations to determine the shape of the result type, instead of using mopt and mreq. I took the time to factor out some work code into a minimal working example. The Field datatype is replaced by a class so that you can define a canonical instance for your type, and the functions to generate the HTML there become input and select to match their DOM tags and take a [(Text, Text)] input to handle all of the attributes, instead of having some special ones in the FieldSettings

Sometimes in situations where there may be too much strictness, a “quick-and-simple” way to try adding more laziness is to use the Lazy version of foundation types like RWST in MForm, in the same way it’s possible to import ST.Lazy instead of ST. But this can also add too much laziness, leading to space leaks: sometimes it’s too simple.

Given that the lazy version is already in use in this case, that “quick-and-simple” check is redundant so further investigation is needed. I just wanted to make sure it was the lazy version of RWST being used on your system.

With that confirmed: MForm is also a transformer type, so what is it being used to transform? The type signature of withDelete has the answer:

withDelete :: (xml ~ WidgetFor site (), RenderMessage site FormMessage)
           => AForm (HandlerFor site) a
           -> MForm (HandlerFor site) (Either xml (FormResult a, [FieldView site]))

And HandlerFor is defined as:

newtype HandlerFor site a = HandlerFor
    { unHandlerFor :: HandlerData site site -> IO a
    }
    deriving Functor

…it’s based on the monadic IO type, which is opaque and strict. So your earlier remark about processing the posted content based on the monadic logic appears to be correct: using the strict IO type can thoroughly hinder the use of infinite data structures.

Are you perhaps missing providing required values for other fields in the Form? You need to submit the forms to generate a new row, it doesn’t have any Javascript that runs on the frontend to add a new row.

The way yesod-form works is by deterministically generating identifiers for the form fields (name attribute). This means:

  1. When you are generating the form, usually on a GET request, you generate all the fields with the name attributes like f1, f2, f3, and so on
  2. When you receive the form data on a POST request, we regenerate the Form and all the identifiers should match with the ones that you have generated previously. So, for instance on a POST request were you to call a newFormIdent that you haven’t called when generating the Form on a GET request, all the Form fields would now be offset by 1 i.e. what was before f1 would now be f2 and so on and this would cause the Form fields to be associated with the wrong haskell fields and you would most likely get Form errors.

In an inputList, you basically extend this concept to a two dimensional structure where the multiple rows in the list get their own identifiers, like f1-1, f1-2, f1-3, and so on. This also means with a bit of javascript, you can increment thecount value on the frontend (it’s a hidden input field) and add a new row with names f1-4 and it’ll be valid and accepted by yesod-form.

For the example,

data T = Number Int | Check Bool T

it must be possible to contort yesod-form to achieve what you want, by having a function similar to textField,

tField :: Field m a
tField = Field {
    fieldParse = parser_,
    fieldView = \_theId _name _attrs _val _isReq ->
        [whamlet|
$newline never
<select name="T">
    <option value="Number">Number</option>
    <option value="Check">Check</option>
</select>
|]
    , fieldEnctype = UrlEncoded

you will have to generate the other input fields dynamically in Javascript but you should follow a naming like:
Number 3T_number = 3
Check True (Number 1)T_check_0 = True, T_check_1 = “number”, so look in T_check_1_number = 1
Check True (Check False (Number 2))T_check_0 = True, T_check_1 = “check”, so look in T_check_1_check_0=False and then look up T_check_1_check_1=“number” => T_check_1_check_1_number = 2

We can then provide the parser_ function to generate a T by following the above naming scheme. (We can also have shorter names by numbering the ADTs serially, so T_number becomes T_0 and T_check_[0,1] becomes T_1_0, T_1_1

1 Like