Lenses for Web Data Electronic Communications of the EASST Volume 57 (2013) Proceedings of the Second International Workshop on Bidirectional Transformations (BX 2013) Lenses for Web Data Raghu Rajkumar, Sam Lindley, Nate Foster, James Cheney 21 pages Guest Editors: Perdita Stevens, James F. Terwilliger Managing Editors: Tiziana Margaria, Julia Padberg, Gabriele Taentzer ECEASST Home Page: http://www.easst.org/eceasst/ ISSN 1863-2122 http://www.easst.org/eceasst/ ECEASST Lenses for Web Data Raghu Rajkumar1, Sam Lindley2, Nate Foster1, James Cheney3 1 Cornell University 2 University of Strathclyde 3 University of Edinburgh Abstract: Putting data on the web typically involves implementing two transfor- mations: one to convert the data into HTML, and another to parse modifications out of interactions with clients. Unfortunately, in current systems, these transfor- mations are usually implemented using two separate functions—an approach that replicates functionality across multiple pieces of code, and makes programs diffi- cult to write, reason about, and maintain. This paper presents a different approach: an abstraction based on formlets that makes it easy to bridge the gap between data stored on a server and values embedded in HTML forms. We introduce formlenses, which combine the advantages of formlets with those of lenses to provide com- positional, bidirectional form-based views of Web data. We show that formlenses can be viewed as monoidal functors over lenses, analogously to formlets, which are applicative functors. Finally, we investigate the connection between linearity and bidirectional transformations and describe a translation from a linear pattern syntax into formlens combinators. Keywords: Formlets, lenses, applicative functors, monoidal functors. 1 Introduction Putting data on the web typically involves implementing two transformations: one to convert the data into HTML, and another to parse modifications out of interactions with clients. Unfor- tunately, in current systems, these transformations are usually implemented using two separate functions—an approach that replicates functionality across multiple pieces of code, and makes programs difficult to write, reason about, and maintain. To illustrate, suppose that we have a database of visiting speakers, and we want to build an application that supports viewing and editing this database through a Web browser. Figure 1 gives a possible implementation of this application in Haskell. The render function converts a single Speaker value into HTML with an embedded form, which allows a user to edit the details associated with the speaker and submit the modifications back to the server. The function collect handles these responses by extracting an updated Speaker value out of the association list Env, which is returned to the server by the browser. Readers unfamiliar with Haskell language can find documentation for the functions used in this paper at http://www.haskell.org/hoogle. This example uses several functions based on the Text.Html module and the standard prelude: inputTag constructs an input element, brTag con- structs a linebreak, lineToHtml converts a string to HTML, (+++) concatenates HTML, lookup retrieves a value from an association list and returns a Maybe value, fromJust extracts the encap- 1 / 21 Volume 57 (2013) http://www.haskell.org/hoogle Lenses for Web Data data Date = Date {month :: Int,day :: Int} data Speaker = Speaker {name :: String,date :: Date} render :: Speaker → Html render (Speaker n (Date m d)) = inputTag {name = "name",value = n}+++ brTag +++ lineToHtml "Month: "+++ inputTag {name = "month",value = show m}+++ brTag +++ lineToHtml "Day: " +++ inputTag {name = "day",value = show d} data Env = [(String,String)] collect :: Env → Speaker collect e = let n = fromJust (lookup "name" e) in let m = read (fromJust (lookup "month" e)) in let d = read (fromJust (lookup "day" e)) in Speaker n (Date m d) Figure 1: Haskell code for Speaker example. sulated value out of a Maybe value, show converts an Int into a String, and read parses an Int back out of a String. Together, the render and collect functions effectively present a single Speaker value on the Web. But in general, developing applications this way quickly leads to complications: First, it requires the programmer to explicitly coerce the data to and from HTML—something that is easy to get wrong, especially in larger examples. Second, it requires them to construct the form manually, including choosing a name for each field. Although these names are semantically immaterial they must be globally unique to avoid clashes. Moreover, the field names used by render must be synchronized with the names used by collect. These constraints make it difficult to construct forms in a compositional manner. For example, we cannot iterate render and collect to obtain a program for a list of Speakers because specific field names are “baked into” the code. Formlets. In prior work, Cooper et al. [CLWY08] introduced a high-level abstraction for build- ing Web forms called formlets. Formlets encapsulate several low-level details including selecting field names for elements and parsing data from client responses. Formlets can be represented in Haskell as functions that take a source of names as an argument, concretely, an Int, and produce a triple consisting of an HTML document, a collect function, and a modified namesource. type Formlet a = Int → (Html,Env → a,Int) The names of any generated form fields are drawn from the namesource, and the collect function looks up precisely these names. As a simple example of a formlet, consider the html combinator, which generates static HTML without any embedded form elements, html :: Html → Formlet () html h i = (h,λ → (),i) Proc. BX 2013 2 / 21 ECEASST the text combinator, which wraps plain text as HTML, text :: String → Formlet () text s = html (stringToHtml s) and the inputInt combinator, which builds a form that accepts an integer: inputInt :: Formlet Int inputInt i = let n = show i in (inputTag {name = n,value = ""},λ e → read (fromJust (lookup n e)),i + 1) Combinators for inputting other primitive types such as String and Bool can be defined similarly. Formlets can be combined into larger formlets using the interface of applicative functors, a generic mathematical structure for representing computations with effects [MP08]. We give the definition of applicative functors here using a Haskell type class. A type class defines an interface that can be provided by different instances for different types. For example, the standard Eq type class provides an equality function: class Eq a where (≡) :: a → a → Bool and it can be instantiated with different types replaced by a, defining different behaviors: data Fraction ={num :: Int,denom :: Int} instance Eq Fraction where (n1,d1)≡ (n2,d2) = n1 ∗d2 ≡ n2 ∗d1 Readers unfamiliar with type classes may with consult the Haskell Tutorial1 for further details. The Haskell standard library includes a Functor type class that corresponds roughly to the category-theoretic notion of functor. class Functor f where fmap :: (a → b)→ f a → f b Here, f is a type constructor—that is, an operation f :∗→∗ that takes a type and produces another type—and Functor f provides the fmap function that lifts a function from a → b to a function from f a→ f b. For example, in Haskell, [ ] is the list type constructor, and there is a built-instance Functor [ ], whose fmap is defined as the usual map function on lists map :: (a → b)→ [a]→ [b]. Similarly, Maybe is a type constructor defining optional values, data Maybe a = Just a | Nothing and there is a standard Functor Maybe instance: instance Functor Maybe where fmap f Nothing = Nothing fmap f (Just a) = Just (f a) 1 http://www.haskell.org/tutorial/classes.html 3 / 21 Volume 57 (2013) Lenses for Web Data Applicative functors are defined by extending the Functor type class with two operations: class (Functor f )⇒ Applicative f where pure :: a → f a (⊗) :: f (a → b)→ f a → f b Intuitively, the pure function injects a value of type a into the type f a, while ⊗ applies the underlying function to its argument, accumulating effects from left to right. Applicative functor instances are expected to obey the following conditions relating pure and ⊗: pure id⊗u = u pure (◦)⊗u⊗v⊗w = u⊗(v⊗w) pure f ⊗pure x = pure (f x) u⊗pure x = pure (λ f → f x)⊗u The applicative functor instance for formlets is defined as follows: instance Applicative Formlet where pure a i = (noHtml,λ → a,i) (f ⊗g) i = let (x,p,i′) = f i in let (y,q,i′′) = g i′ in (x +++ y,λ e → p e (q e),i′′) The pure formlet generates empty HTML and has the constant collect function. The render component of the ⊗ operator threads the namesource through its arguments from left to right and accumulates the generated HTML. The collect function applies the function (of type a → b) produced by f to the value (of type a) produced by g. Using the applicative functor interface and the simple combinators just defined, we can define a formlet for Speakers as follows: dateForm :: Formlet Date dateForm = pure (λ m d → Date m d) ⊗text "Month: "⊗inputInt⊗html br ⊗text "Day: " ⊗inputInt⊗html br speakerForm :: Formlet Speaker speakerForm = pure Speaker⊗inputString⊗dateForm The arguments in the anonymous function supplied to pure discard the () values produced by the text and html combinators. Formlenses. Formlets are a useful abstraction, but they only address one half of the problem— they make it easy to construct a function that produces a value of type a, but they do not provide a way to describe a function that consumes a value of type a and embeds it in a form. Of course, programmers could write functions of type a → Formlet a (similar to the approach in Hanus’ WUI library [Han06]), but such functions do not support the applicative functor interface, so Proc. BX 2013 4 / 21 ECEASST large examples would need to be expressed as monolithic programs. Moreover, such functions do not guarantee reasonable behavior, so programmers would have to prove that values are preserved on round-trips by hand. A different way to think about this problem is to observe that forms are often used to present an updatable view of the underlying data source. The fundamental difficulty in putting data on the Web stems from the fact that programmers are maintaining these views manually, writing explicit forward transformations that put the data into forms, and separate backward transformations that propagate collected values back to the underlying sources. As this terminology suggests, we have a solution to this problem in mind: use ideas from bidirectional transformations [CFH+09] to define formlets that behave like updatable views. The main goal of this paper is to show how formlets and bidirectional transformations such as lenses [FGM+07] can be combined, yielding an abstraction called Formlenses. A formlens takes a value of type a, renders it as a form that can be dispatched to the Web client, translates the response back to a new value of type a, and merges the result with the old value. Intuitively, one can think of a Formlens a as a bidirectional mapping between an a value and a web page that contains an editable a. But unlike manual approaches, where programmers write explicit render and collect functions, or the approach using functions of type a → Formlet a described above, we can design the formlens abstraction to support composition and strong semantic guarantees. Challenges. Combining formlets and lenses turns out to be nontrivial. If a value of type Formlens a consumes a values, then a must appear in a negative position in its type. Conversely, if a value of type Formlens a produces a values, then a must appear positively in its type. These observations lead to serious problems defining Formlens as a type operator in Haskell: Formlens cannot be a covariant Functor over the category Hask of Haskell types and functions, and it cannot be a contravariant functor over this category either. To avoid this difficulty, we shift perspective and consider functors from lenses to (the category of) Haskell types and functions. However, even after restricting attention to these functors, the applicative functor interface is still too strong. Consider the following interface, which general- izes McBride and Paterson’s definition to allow applicative functors on lenses: class LApplicative f where lpure :: a → f a lapp :: f (Lens a b)→ f a → f b To instantiate LApplicative Formlens, we would need to define functions lpure :: a → Formlens a lapp :: Formlens (Lens a b)→ Formlens a → Formlens b For the latter, we would need to (somehow) combine a form that consumes and produces a Lens a b with another form that produces and consumes an a to obtain a form that produces and consumes a b. This does not seem possible to do in a natural way. Moreover, from a categorical perspective, lapp would not make sense because the category of lenses over Haskell types does not have exponential objects. This remains true if we consider contravariant functors. 5 / 21 Volume 57 (2013) Lenses for Web Data Fortunately we can sidestep these problems by observing that the extra structure of Applicative functors is not required for Formlets or Formlenses—monoidal structure suffices. By adapting the basic ideas of Formlets to different (weaker) mathematical structures we are able to employ Formlets in a broader range of settings. More specifically, we can compose formlets with lenses while retaining the ability to compose formlets using a monoidal interface. Contributions. Overall, this paper makes the following contributions: • We present a new foundation for formlets based on monoidal functors over lenses, which makes it possible to give them a bidirectional semantics; • We describe an implementation of formlenses as a combinator library in Haskell; • We explore the connection between linear syntax and bidirectional transformations and describe a translation from a language of linear patterns into formlens combinators. The rest of the paper is structured as follows: Section 2 presents the design of formlenses by generalizing the classic definition based on formlets and showing that they are monoidal functors over lenses. Section 3 describes the formlens implementation, including syntactic sugar for describing formlenses using linear patterns. Section 4 briefly reviews related work. Section 5 concludes. The appendix presents background material on monoidal functors that may be helpful for some readers. 2 Formlens Design This section defines formlenses, the main abstraction presented in this paper. We begin by re- viewing the definition of monoidal functors as represented in Haskell. The built-in type class Functor models functors from Hask to Hask. class Functor f where fmap :: (a → b)→ f a → f b That is, instances of Functor are required to supply a function fmap that lifts functions from a to b to functions from f a to f b. To allow formlenses to both produce and consume values, we will work with functors from Lens to Hask, where Lens is the category of (asymmetric) lenses, data Lens a b = Lens {get :: a → b,put :: Maybe a → b → a} where get and put must satisfy: put (Just a) (get a) = a -- GetPut get (put (Just a) b) = b -- PutGet get (put Nothing b) = b -- CreateGet It is straightforward to show that Lens has an identity and is closed under composition, and therefore forms a category. Proc. BX 2013 6 / 21 ECEASST We model functors from Lens to Hask using the following type class: class LFunctor f where lmap :: Lens a b → f b → f a For technical reasons, we use the contravariant formulation: given a lens from a to b, an LFunctor f maps an f b to a f a. As we shall see below, this will allow us to use a Lens a b to transform a formlens on b values into one on a values. The Lens category has monoidal structure, meaning that it supports the following operations: class Category c ⇒ MonoidalCategory c where (·×·) :: c a1 b1 → c a2 b2 → c (a1,a2) (b1,b2) munitl :: Iso c ((),a) a munitr :: Iso c (a,()) a massoc :: Iso c (a,(b,d)) ((a,b),d) Here, Iso c a b is simply a pair of maps c a b and c b a witnessing an isomorphism. Monoidal categories are also required to satisfy several additional laws (see MacLane [Mac98]), which all hold for Lens and are elided here. Next, we consider monoidal functors2 providing a unit and binary operations, class Functor f ⇒ Monoidal f where unit :: f () (?) :: f a → f b → f (a,b) and satisfying the following laws: fmap (g×h) (u ? v) = fmap g u ? fmap h u fmap fst (u ? unit) = u fmap assoc (u ?(v ? w)) = (u ? v)? w fmap snd (unit ? u) = u Note that these definitions assume we are working in Hask, as well as operations fst :: (a,b)→ a and snd :: (a,b) → b, which are not available in all monoidal categories. Since we are interested in functors from Lens to Hask, a minor variant (adapted from MacLane [Mac98]) suffices: (M1) lmap (f ×g) (u ? v) = lmap f u ? lmap g u (M2) lmap munitl (unit ? u) = u (M3) lmap munitr (u ? unit) = u (M4) lmap massoc (u ?(v ? w)) = (u ? v)? w We are now in a position to define the Formlens type and show that it is a monoidal functor: type Formlens a = Maybe a → [Int]→ (Html,Env → Maybe a,[Int]) 2 Some authors, such as McBride and Paterson, call these lax monoidal functors to distinguish them from other kinds of monoidal functors, but these distinctions are unimportant in this paper so we will just say monoidal. 7 / 21 Volume 57 (2013) Lenses for Web Data The differences between this definition and the standard definition for formlets are relatively minor: we have added an extra Maybe a parameter that provides an optional initial value of the form, changed the namesource to a list of integers, and allowed the collect function to return an optional value. However, the type variable a appears both covariantly and contravariantly, which means that Formlens cannot be an ordinary Haskell functor, let alone an applicative func- tor. Hence, we are forced to consider formlenses as functors on Lens, whose arrows reflect their bidirectionality. But then since Lens is not closed, formlenses cannot be applicative functors. Fortunately, we will be able to show they are monoidal functors, which are weaker than applica- tive functors but still provide an interface that supports composition of formlenses. As a first step, we show that Formlenses are lens functors: instance LFunctor Formlens where lmap lns f = Formlens (λ v i → let (html,c,i′) = f (fmap (get l) v) i in (html,fmap (put l v)◦c,i′) When we map a lens lns :: Lens a b over a formlens f :: Formlens b, to obtain a Formlens a, we render f using the lens’s get function (to transform the a value to a b), then we post-compose the function c with the lens’s put function applied to the original a. Note that this construction would not work with covariant LFunctors, because given lns :: Lens a b and f :: Formlens a, and a b value, there would be no way to use lns’s put function to construct an appropriate a value to use as argument to f . Next we show that Formlens admits monoidal operations: instance Monoidal Formlens where unit = Formlens (λ i → (noHtml,λ → Just (),i)) f ? g = Formlens (λ v i → let (a,b) = split v in let (ha,ca,i′) = f a i (hb,cb,i′′) = g b i′ in (h1 +++ h2,λ e → liftM2 (,) (ca e) (cb e),i′′) where split v = case v of Just (a,b)→ (Just a,Just b) → (Nothing,Nothing) That is, unit generates no HTML, allocates no names, and collects (), whereas f ? g combines two formlenses that separately handle an a and a b to obtain one that handles a pair of a and b by concatenating the rendered HTML and using the two collect functions to form the result. The following theorem states that this definition satisfies the monoidal functor laws: Theorem 1 Formlens is a monoidal LFunctor. Example. To get a taste for formlenses, let us build a bidirectional version of the dateForm formlet from the introduction starting with formlens versions of html, text, and inputInt: htmlL :: Html → Formlens () htmlL h = Formlens (λ i → (h,λ → Just (),i)) textL :: String → Formlens () Proc. BX 2013 8 / 21 ECEASST textL s = htmlL (stringToHtml s) inputIntL :: Formlens Int inputIntL = Formlens (λ v i@(h : t)→ let n = intercalate "_" (map show i) in (inputTag {name = n,value = (maybe "" show v)}, λ e → fmap read (lookup n e), (h + 1) : t) Note that the collect functions for these combinators ignore the initial value, if any—i.e., the formlens is essentially bijective. The only situation where this does not happen is when we lmap a lens over a formlens. In this case, only a projection of the initial value is displayed on the form, and the part that was projected out is restored from the initial value when the form is collected. Next we define two helper operators, (〈?) and (?〉), which streamline definitions where we combine formlenses on () values. These operators behave like (?) but combine a Formlens a and Formlens () into a Formlens a, rather than a Formlens (a,()) and Formlens ((),a) respectively. (〈?) :: (Monoidal f ,LFunctor f )⇒ f a → f ()→ f a f 〈? g = lmap (munitr :: Iso Lens (a,()) a) (f ? g) The definition of the (?〉) combinator is symmetric, but eliminates the () value using munitl. Next, we define a lens on Date values: dateL :: Lens (Int,Int) Date dateL = Lens (λ (m,d)→ Date m d) (λ (Date m d)→ (m,d)) Finally, putting all these pieces together, we define a formlens for Dates as follows: dateFormlens :: Formlens Date dateFormlens = lmap dateL (textL "Month: "? inputIntL〈? htmlL brTag〈? textL "Day: " ? inputIntL〈? htmlL brTag) Compared to the formlet dateForm, we have replaced (⊗) with (?), (〈?), and (?〉) as appropriate, and applied lmap dateL at the top-level. Overall, dateFormlens maps bidirectionally between a Date value and an HTML form that encodes a date, as desired. Semantic Properties Classic lenses satisfy natural well-behavedness conditions such as the GETPUT and PUTGET laws. A natural question to ask is: are there analogous laws for form- lenses, and are they preserved by operations such as (?) and lmap? To answer this question positively, we must restrict our attention to formlenses that satisfy certain well-formedness properties: a formlens should only draw names from the namesource provided as an argument, and the collect function should only look up corresponding names. Let extract be a function from Html to Env that extracts an environment containing the names and values of all form fields from an HTML document. Also, for every formlens f and name- sources n,n′, define an equivalence relation on Env values as follows: e ∼n,n ′ f e ′ ∆⇐⇒ ∀v :: Maybe a. ( ,c, ) = f v n and ( ,c′, ) = f v n′ implies c e = c′ e′ 9 / 21 Volume 57 (2013) Lenses for Web Data Figure 2: Screenshot of Speakers formlens running in a browser. We say that a formlens f is well behaved if it satisfies the following properties, which are analo- gous to GETPUT and PUTGET (the property for CREATEGET is similar): Definition 1 (Acceptability) A formlens f :: Formlens a is acceptable if for all v :: a, n :: Int, and e :: Env, if (h,c, ) = f (Just v) n and extract h ⊆ e, then c e = Just v. Definition 2 (Consistency) A formlens f :: Formlens a is consistent if for all v :: a, v′ :: Maybe a, n,n′ :: Int, and e :: Env, if ( ,c, ) = f v′ n′ and c e = (Just v) and (h, , ) = f (Just v) n, then extract h ∼n,n ′ f e. Readers familiar with lenses may note that these properties are essentially the quotient lens laws [FPP08]. Each of the primitive formlenses described in the next section satisfies these laws, and each of the formlens combinators preserves them. 3 Implementation We have developed an implementation of formlenses in Haskell. This implementation provides a collection of formlens primitives and a translation from a higher-level syntax based on linear patterns into these primitives, and it runs on top of the Happstack Web server [Hap12]. Combinator library. Our formlens combinator library provides a rich collection of formlens primitives and formlens combinators that allow a wide variety of data to be presented on the Web. The library includes primitives for building forms containing integers, strings, booleans, checkboxes, radio groups, buttons, and other values as HTML. It also includes combinators for combining smaller formlenses into larger ones. Most important are the following: ? ::Formlens a → Formlens b → Formlens (a,b) ⊕::Formlens a → Formlens b → Formlens (Either a b) iter :: Formlens a → Formlens [a] Proc. BX 2013 10 / 21 ECEASST The ? operator composes formlenses “horizontally” using the monoidal functor interface dis- cussed in the previous section. The ⊕ operator behaves like a conditional operator on formlenses that branches on the Left and Right tags attached to Either values. Finally, the iter operator it- erates a lens over a list of values. This operator turns out to be especially interesting due to the way it uses namesources—to allow in-place modifications to the list on the HTML side, it is convenient to make the namesource a list of integers rather than a single integer. The definitions of the ⊕ and iter combinators are presented in appendix B. To showcase the use of these combinators, we have built a website for viewing and editing a database of Speakers as shown in Figure 2. The main functionality of this formlens is given by applying iter to the formlens for Speaker values. The formlens also introduces appropriate HTML rendering and uses a JavaScript library to allow the collect function to be invoked through an AJAX interface instead of (slower) POST requests. In addition, the list allows elements to be added or removed from any location, and also edited in place. Linear patterns. Writing programs using combinators can be extremely tedious because the structure of the values produced (and consumed) by the formlens closely matches the structure of the combinator program itself. For example, if f is a Formlens Int and g is a Formlens () then f ? g is a Formlens (Int,()). If the programmer wishes to obtain a Formlens Int instead, they must lmap the bijection munitr on the result to eliminate the spurious (). Of course, the derived 〈? operator does this, but having to remember when to use ? versus 〈? and ?〉 is inconvenient. This section describes a better alternative: we define a syntax for describing formlenses based on pattern matching, and we give a translation from this high-level syntax into our low-level formlens combinators. Our translation extends previous work by Cooper et al. [CLWY08] on translating formlet syntax into combinators using applicative functors. We have implemented this syntax using Haskell’s quasi-quotation features [Mai07] and Template Haskell [SJ02]. To describe a formlens using the high-level syntax, the programmer defines a pair of patterns over a shared set of variables. The pattern on the left matches Haskell values, while the pat- tern on the right matches HTML. When read from left to right, programs written in this way denote transformations from values to HTML forms; when read from right to left, they denote transformations from form responses back to values. Formally, we define a formlens using the syntax [| formlens | p ↔ n1 ... nk |], where p is a Haskell pattern and ns is a sequence of elements n1 ... nk, text nodes s, spliced HTML expressions {e}, or nested formlens bindings {f → p}. The complete syntax is given in the top half of Figure 3. The pattern p may bind some of the variables referenced in ns and ignore others (by using the wildcard symbol ). However, to ensure that the overall formlens is well- defined, the pattern must be linear—variables mentioned in the pattern and any sub-formlenses must be used exactly once on the other side. The bottom half of Figure 3 defines the translation from the high-level syntax into combina- tors. The translation of the body using (−)◦ goes by structural recursion, producing formlens combinators such as textL, htmlL, and tagL as results. Sequences of nodes are combined using the (?) operator and unit, which handles the empty sequence. On the other side, we extract pat- terns from the form using (−)†, again following a straightforward structural recursion. Next, the lens functor map operation lmap is used to combine the results of the sub-lens bound in the body 11 / 21 Volume 57 (2013) Lenses for Web Data Meta variables e Haskell expression f Formlens expression s string literal p Haskell pattern t HTML tag atts HTML attribute list Syntax l ::= [formlens | p ↔ ns |] (Formlens) n ::= ns | s | {e} |{f → p} (HTML node) ns ::= n1 ... nk (HTML node sequence) s◦ = textL s {e}◦ = htmlL e {f → p}◦ = f ns◦ = tagL t atts ns◦ (n1 ... nk) ◦ = n1◦?...? nk◦ s† = () {e}† = () {f → p}† = p ns† = (ns)† (n1 ... nk)† = (n † 1,...,n † k) � = (x,x,⊥) where x is fresh x� = ( ,x,x) (p1,..., pk) � = ((p′1,..., p ′ k),(e1,...,ek),(e ′ 1,...,e ′ k)) where (p′i,ei,e ′ i) = pi �, 1 6 i 6 k (K p)� = (K p′,K e,K e′) where (p′,e,e′) = p� [formlens | p ↔ ns |] = lmap (Lens get put) (ns)◦ where (pold, pnew, pcreate) = p� get = λ p → (ns)† put = λ e (ns)† → case e of Just (pold)→ pnew Nothing → pcreate Figure 3: Linear pattern syntax and translation. Proc. BX 2013 12 / 21 ECEASST through extracted patterns. Finally, we construct a lens to pre-compose with the generated form, which means we need to construct an appropriate put function. As we are now mapping a lens over the formlens, we must construct a put function taking an extra argument representing the original input value. The pattern pold binds the parts of the original input value that are ignored by the formlens. The pattern pnew (which is also an expression as it contains no wildcards) com- bines the ignored part of the input bound by pold with the output produced by the formlens. Any wildcard patterns that appear in the interface pattern are filled in using the additional argument to put. If no wildcards appear in the pattern, then the lens we construct is essentially a (partial) bijection—the linearity constraint guarantees that the form data is in bijective correspondence with the pattern data. As a simple example, suppose we want a form, based on the Speaker example from the intro- duction, that only allows us to see and edit the date of a speaker, while maintaining the name, then we can write the following code, speakerFormL :: Formlens Speaker speakerFormL = [formlens | Speaker d ↔ Name :{stringToHtml name}< br / > {dateFormL → d} |] which translates into, speakerFormL = lmap (Lens (λ (Speaker d)→ ((),((),((),d)))) (λ p0 ((),((),((),d)))→ case p0 of Just (Speaker x0 )→ Speaker x0 d Nothing → Speaker ⊥ d)) (textL "Name: "? htmlL (stringToHtml name) ? tag "br" [ ] [ ]? dateFormL) where x0 is a fresh variable that tracks the old name value. The translation handles the tedious tasks of generating the boilerplate lens code to map from the underlying type ((),((),((),Date))) of the formlens body and generating textL and htmlL combinators representing the HTML form components themselves. Overall, programs written using the high-level syntax are both more concise and easier to maintain than the generated code. 4 Related work Formlets. There is a variety of earlier work on declarative abstractions for web forms. Cooper et al. [CLWY08] first proposed expressing formlets as the composition of several primitive ap- plicative functors, and gives a detailed comparison to prior work. The abstraction in Hanus’s WUI (Web User Interface) library [Han06] has several similarities to the formlenses. In particu- lar, WUI includes a combinator for lifting a bijection to WUIs, similar to our LFunctor Formlens instance (restricted to bijections); however, Hanus did not consider Applicative or Monoidal equational laws on WUIs, nor constructing them as functors over lenses. Formlets were originally developed as part of Links [CLWY07]. Formlet libraries have since been implemented for Haskell, F#, Scala, OCaml, Racket, and Javascript. Eidhof’s Haskell 13 / 21 Volume 57 (2013) Lenses for Web Data library [Eid08] evolved first into digestive functors [dJ12], and most recently the reform pack- age [SJ12]. The latter integrates with various other libraries, and extends formlets with better support for validation and for separating layout from formlet structure. The F# WebSharper library [BTG11] introduces flowlets, which combine formlets with functional reactive program- ming [EH97] allowing forms to change dynamically at run-time. Bidirectional transformations. Languages for describing bidirectional transformations have been extensively studied in recent years; a recent Dagstuhl seminar report [HSST11] presents a comprehensive survey. The original paper on lenses [FGM+07] describes work on databases and programming languages; another more recent survey also discusses work from the software engineering literature [CFH+09]. The XSugar [BMS08] language defines bidirectional transfor- mations between XML documents and strings. Similarly, the biXid [KH06] language specifies essentially bijective conversions between pairs of XML documents. Transformations in both XSugar and biXid are specified using pairs of intertwined grammars, which resemble our high- level pattern syntax. The most closely related work we are aware of is by Rendel et al. [RO10]. They propose using functors over partial isomorphisms to describe invertible syntax descrip- tions. Our design for formlenses is similar, but also supports using non-bijective bidirectional transformations, while allowing for a convenient high-level syntax similar to formlets. Applicative and monoidal functors. Applicative functors have been used extensively as an al- ternative to monads for structuring effectful computation. They were used (implicitly) by Swier- stra and Duponcheel [SD96] for parser combinators, and named and recognized as a lighter- weight alternative to monads by McBride and Paterson [MP08]. The relationships among mon- ads, arrows, and applicative functors were further elucidated by Lindley et al. [LWY11]. The connection to monoidal functors was explored further by Paterson [Pat12], who also observes that it is often much easier to work with monoidal functors. However, Paterson focuses attention on functors on cartesian closed categories and Lens is not closed. Functors on categories other than Hask have appeared in other contexts. Functors over isomor- phisms are used in the fclabels library [VHEV12]. However, fclabels also provides an applicative functor interface, which can be used to produce intuitively incorrect bidirectional transforma- tions. Similarly, functors over partial isomorphisms from Iso to Hask are essential in Rendel and Ostermann’s invertible syntax descriptions [RO10]. They also employ a variant of Monoidal functors (which they call ProductFunctors). A natural question for further work is whether Monoidal functors over partial isomorphisms suffice for invertible syntax descriptions, so that one can easily compose parser or pretty-printer combinators with formlenses. To the best of our knowledge, we are the first to use (monoidal) functors over lenses for programming. 5 Conclusion Formlenses combine the features of formlets and lenses in a powerful abstraction that makes it easy for programmers to present data on the web. Our work on formlenses is ongoing. In the future, we plan to further develop the semantic properties of formlenses, investigate additional combinators and generic programming techniques for formlenses, and examine other formalisms Proc. BX 2013 14 / 21 ECEASST for Web interaction, such as flowlets [BTG11]. We also plan to investigate ways of interacting with browsers that are not based on forms such as JavaScript. Finally, we plan to explore ways of leveraging the semantic properties of formlenses to obtain efficient mechanisms for maintaining the HTML even as the underlying data changes. Acknowledgements: The authors wish to thank Arjun Guha, James McKinna, Ross Tate, Philip Wadler, Daniel Wagner, the Cornell DB Group, and the BX ’13 reviewers for helpful comments. This work is supported in part by a Google Research Award (Lindley), EPSRC grant EP/J014591/1 (Lindley), National Science Foundation awards CCF-1253165 and CCF-0964409 (Rajkumar and Foster), a Sloan Research Fellowship (Foster), and a Royal Society University Research Fellowship (Cheney). Bibliography [Bie95] G. M. Bierman. What is a Categorical Model of Intuitionistic Linear Logic? In TLCA. Pp. 78–93. 1995. [BMS08] C. Brabrand, A. Møller, M. I. Schwartzbach. Dual Syntax for XML Languages. Information Systems 33(4–5):385–406, 2008. Short version in DBPL ’05. [BTG11] J. Bjornson, A. Tayanovskyy, A. Granicz. Composing Reactive GUIs in F# Using WebSharper. In IFL. LNCS 6647, pp. 203–216. Springer, 2011. [CFH+09] K. Czarnecki, J. N. Foster, Z. Hu, R. Lämmel, A. Schürr, J. F. Terwilliger. Bidi- rectional Transformations: A Cross-Discipline Perspective. GRACE Meeting notes, State of the Art, and Outlook. In ICMT. Pp. 260–283. June 2009. [CLWY07] E. Cooper, S. Lindley, P. Wadler, J. Yallop. Links: Web Programming Without Tiers. In FMCO. Pp. 266–296. 2007. [CLWY08] E. Cooper, S. Lindley, P. Wadler, J. Yallop. The Essence of Form Abstraction. In APLAS. Pp. 205–220. Springer, 2008. [EH97] C. Elliott, P. Hudak. Functional Reactive Animation. In ICFP. Pp. 263–273. 1997. [Eid08] C. Eidhof. Formlets in Haskell. 2008. Available at http://blog.tupil.com/ formlets-in-haskell. [FGM+07] J. N. Foster, M. B. Greenwald, J. T. Moore, B. C. Pierce, A. Schmitt. Combina- tors for bidirectional tree transformations: A linguistic approach to the view-update problem. ACM Trans. Program. Lang. Syst. 29(3), May 2007. [FPP08] J. N. Foster, A. Pilkiewcz, B. C. Pierce. Quotient Lenses. In ICFP. Pp. 383–395. Sept. 2008. [Han06] M. Hanus. Type-oriented construction of web user interfaces. In PPDP. Pp. 27–38. 2006. 15 / 21 Volume 57 (2013) http://blog.tupil.com/formlets-in-haskell http://blog.tupil.com/formlets-in-haskell Lenses for Web Data [Hap12] The Happstack web server. 2012. Available from http://happstack.com. [HSST11] Z. Hu, A. Schürr, P. Stevens, J. Terwilliger. Bidirectional Transformation “bx”. Dagstuhl Reports 1(1):42–67, 2011. Available at http://drops.dagstuhl.de/opus/ volltexte/2011/3144. [dJ12] J. V. der Jeugt. The digestive-functors package. 2012. http://hackage.haskell.org/package/digestive-functors. [KH06] S. Kawanaka, H. Hosoya. biXid: a bidirectional transformation language for XML. In ICFP. Pp. 201–214. Sept. 2006. [KW12] E. Kmett, D. Wagner. category-extras metapackage version 1.0.2. 2012. Available at http://hackage.haskell.org/package/category-extras. [LWY11] S. Lindley, P. Wadler, J. Yallop. Idioms are Oblivious, Arrows are Meticulous, Monads are Promiscuous. Electron. Notes Theor. Comput. Sci. 229(5):97–117, Mar. 2011. [Mac98] S. MacLane. Categories for the working mathematician (second edition). Springer- Verlag, 1998. [Mai07] G. Mainland. Why it’s nice to be quoted: Quasiquoting for Haskell. In Haskell. Pp. 73–82. 2007. [MP08] C. McBride, R. Paterson. Applicative Programming with Effects. Journal of Func- tional Programming 18(1):1–13, Jan. 2008. [Pat12] R. Paterson. Constructing Applicative Functors. In MPC. LNCS 7342, pp. 300–323. Springer, 2012. [RO10] T. Rendel, K. Ostermann. Invertible Syntax Descriptions: Unifying Parsing and Pretty Printing. In Haskell. Pp. 1–12. 2010. [SD96] S. D. Swierstra, L. Duponcheel. Deterministic, Error-Correcting Combinator Parsers. In Second International School on Advanced Functional Programming. LNCS 1129, pp. 184–207. Springer, 1996. [SJ02] T. Sheard, S. P. Jones. Template metaprogramming for Haskell. In Haskell. Pp. 1–16. 2002. [SJ12] J. Shaw, J. V. der Jeugt. The reform package. 2012. Available at http://hackage. haskell.org/package/reform-0.1.1. [VHEV12] S. Visser, E. Hesselink, C. Eidhof, S. Visscher. The fclabels package, version 1.1.3. May 2012. Available at http://hackage.haskell.org/package/fclabels. [Vis11] S. Visscher. data-category package version 0.4.1. 2011. Available at http://hackage. haskell.org/package/data-category. Proc. BX 2013 16 / 21 http://happstack.com http://drops.dagstuhl.de/opus/volltexte/2011/3144 http://drops.dagstuhl.de/opus/volltexte/2011/3144 http://hackage.haskell.org/package/digestive-functors http://hackage.haskell.org/package/category-extras http://hackage.haskell.org/package/reform-0.1.1 http://hackage.haskell.org/package/reform-0.1.1 http://hackage.haskell.org/package/fclabels http://hackage.haskell.org/package/data-category http://hackage.haskell.org/package/data-category ECEASST A Monoidal categories and functors The key to our approach is to use monoidal rather than applicative functors to define formlenses. This section reviews the (mostly standard) definitions for categories and monoidal functors. Categories. A category is a collection of objects and arrows such that every object has an identity arrow and arrows compose associatively. class Category c where id :: c x x (◦) :: c y z → c x y → c x z Here, c :∗→∗→∗ is a two-argument type constructor, and we can think of c a b as the type of arrows from a to b. The class does not explicitly define the set of types that correspond to objects of the category. The variables x, y, and z are free type variables, so technically the type of id is ∀x.c x x, that is, the identity arrow can be applied at any type, and similarly (◦) has type ∀x,y,z.c y z → c x y → c x z, which means that composition can be applied to any arrows whose range and domain match in the usual way. Haskell functions, bijections, and lenses each form a category. instance Category (→) where id = λ x → x f ◦g = λ x → f (g x) instance Category Bij where id = Bij id id f ◦g = Bij (fwd f ◦fwd g) (bwd g◦bwd f ) instance Category Lens where id = Lens id (const $ id) l◦m = Lens (get l◦get m) (λ a c → put m a (put l (get m a) c)) An isomorphism in a category c is an arrow f :: c a b with an “inverse” g :: c b a satisfying f ◦g = id = g◦f . In a computational setting, it is convenient to represent isomorphisms explicitly. data Iso c a b = Iso {fwdI :: c a b,bwdI :: c b a} Isomorphisms are expected to satisfy the following condition: fwdI iso◦bwdI iso = id = bwdI iso◦fwdI iso Note that Bij is just Iso (→). However, we will keep the notation separate to avoid confusion. Monoidal categories. A monoidal category is a category with additional structure, namely a unit and product on objects in the category. For simplicity, we will use the following definition of monoidal categories, which is specialized to Haskell’s unit () and pairing types (,) and also includes pairing on c-arrows (·×·) as well as c-isomorphisms relating unit and pairing: 17 / 21 Volume 57 (2013) Lenses for Web Data class Category c ⇒ MonoidalCategory c where (·×·) :: c a1 b1 → c a2 b2 → c (a1,a2) (b1,b2) munitl :: Iso c ((),a) a munitr :: Iso c (a,()) a massoc :: Iso c (a,(b,d)) ((a,b),d) Monoidal categories are expected to satisfy a number of additional laws, which essentially state that () is a unit with respect to (,) and “all diagrams involving the above operations com- mute” [Mac98]. We will also omit discussion of the relevant laws of monoidal categories; the standard laws hold for all of the monoidal categories we will consider in this paper. Haskell types and functions form a monoidal category (→), with the following operations: instance MonoidalCategory (→) where f ×g = λ (a,b)→ (f a,g b) munitl = Iso (λ ((),a)→ a) (λ a → ((),a)) munitr = Iso (λ (a,())→ a) (λ a → (a,())) massoc = Iso (λ (a,(b,d))→ ((a,b),d)) (λ ((a,b),d)→ (a,(b,d))) In fact, any category with finite products is monoidal, but there are many monoidal categories whose monoidal product does not form a full Cartesian product. This is the case, for example, for bijections, since the fst and snd mappings are not bijections; models of linear type theory [Bie95] provide more examples. Two examples of monoidal categories that are relevant for our purposes are Bij and Lens. For Bij, we first show how to lift isomorphisms on Hask to Bij (there is some redundancy here, which we tolerate for the sake of uniformity): iso2bij :: Iso (→) a b → Iso Bij a b iso2bij (Iso to fro) = Iso (Bij to fro) (Bij fro to) instance MonoidalCategory Bij where f ×g = Bij (λ (a,b)→ (fwd f a,fwd g b)) (λ (fa,gb)→ (bwd f fa,bwd g gb)) munitl = iso2bij munitl munitr = iso2bij munitr massoc = iso2bij massoc For Lens, we first lift the coercion bij2lens from bijections to lenses to act on isomorphisms: iso2lens :: Iso Bij a b → Iso Lens a b iso2lens (Iso to fro) = Iso (bij2lens to) (bij2lens fro) instance MonoidalCategory Lens where l1 ×l2 = l1 ×L l2 munitl = iso2lens munitl munitr = iso2lens munitr massoc = iso2lens massoc Proc. BX 2013 18 / 21 ECEASST Dual categories. Every category has a dual, obtained by reversing arrows: newtype cop a b = Co {unCo :: c b a} instance Category c ⇒ Category cop where id = Co id (Co f )◦(Co g) = Co (g◦f ) The dual of any monoidal category is also monoidal: iso2dual :: Iso c a b → Iso cop a b iso2dual (Iso to fro) = Iso (Co fro) (Co to) instance MonoidalCategory c ⇒ MonoidalCategory cop where (Co l1)×(Co l2) = Co (l1 ×l2) munitl = iso2dual munitl munitr = iso2dual munitr massoc = iso2dual massoc In particular, Lensop is monoidal. This fact will be useful later since Formlens a is a contravariant functor from Lens to Hask. Functors. The built-in Haskell Functor type class models functors from Hask to Hask. For our purposes, we will need to generalize its definition slightly3 to consider functors from other categories (such as Bij and Lens) to Hask. Accordingly, we introduce the following type class: class LFunctor f where lmap :: Lens a b → f b → f a Again, since we are interested only in Hask-valued functors rather than functors between arbi- trary categories, this type class is specialized to functors from Lens to Hask. Monoidal functors. Next, we consider monoidal functors: class Monoidal f where unit :: f () (?) :: f a → f b → f (a,b) Note that we do not explicitly identify the domain of f in the type class Monoidal f ; this is not necessary (and leads to typechecking complications due to the unconstrained type variable) since the signature of the operations of a monoidal functor depends only on the codomain category (which for us is always Hask). However, in stating the laws for monoidal functors, we will implicitly assume that the domain is a monoidal category—in particular, that ·×·, munitl, munitr, and massoc are defined. 3 Others have proposed much more general libraries for categorical concepts in Haskell [KW12, Vis11]; we believe our approach could be framed using such a library, but prefer to keep the focus on the needed concepts to retain ac- cessibility to readers not already familiar with these libraries. This is also an appropriate place to mention that correct use of categorical concepts in Haskell requires some additional side-conditions such as avoidance of nontermination; we treat this issue informally. 19 / 21 Volume 57 (2013) Lenses for Web Data (M1) gmap (f ×g) (u ? v) = fmap f u ? fmap g u (M2) gmap munitl (unit ? u) = u (M3) gmap munitr (u ? unit) = u (M4) gmap massoc (u ?(v ? w)) = (u ? v)? w B Formlens Combinators : ⊕ and iter This section presents definitions of the ⊕ and iter formlens combinators in Haskell. We first define several helper functions: makeName :: [Int]→ String makeName l = intercalate "_" (map show l) readName :: String → [Int] readName s = map read (split "_" s) next :: [Int]→ [Int] next (hd : tl) = (hd + 1) : tl branch :: [Int]→ [Int] branch l = 0 : l Next we define the ⊕ combinator: (⊕) :: Formlens a → Formlens b → Formlens (Either a b) (f ⊕g) v t = let s = makeName t t′ = next t in let collect ca cb e = case lookup s e of Just "left" → fmap Left (ca e) Just "right"→ fmap Right (cb e) → Nothing in case v of Just (Left a) → let (ha,ca,t1) = f a t′ ( ,cb,t2) = g Nothing t′ in (hidden s "left"+++ ha,collect ca cb,max t1 t2) Just (Right b)→ let ( ,ca,t1) = f Nothing t′ in (hb,cb,t2) = g b t′ in (hidden s "right"+++ hb,collect ca cb,max t1 t2) Nothing → let ( ,ca,t1) = f Nothing t′ in ( ,cb,t2) = g Nothing t′ in (hidden s "nothing",collect ca cb,max t1 t2)) Finally we define the iter combinator: iter :: Formlens a → Formlens [a] iter f v t = (render v t,collect f v t,next t)) Proc. BX 2013 20 / 21 ECEASST where render (Just (hd : tl)) t = let t′ = branch t in let (h, ,t′′) = f (Just hd) t′ in hidden (makeName t) (makeName t′) +++ h +++ render (Just tl) t′′ render t = hidden (makeName t) "none" collect f v t e = case lookup (makeName t) e of Nothing → Nothing Just "none"→ Just [ ] Just s → let t′ = readName s in case v of Just (hd : tl)→ let ( ,c,t′′) = f (Just hd) t′ in do hd′ ← c e tl′ ← collect f (Just tl) t′′ e return (hd′ : tl′) → let ( ,c,t′′) = f Nothing t′ in do hd′ ← c e tl′ ← collect f v t′′ e return (hd′ : tl′) 21 / 21 Volume 57 (2013) Introduction Formlens Design Implementation Related work Conclusion Monoidal categories and functors Formlens Combinators : and iter