Heterogeneous Data Structures - Nested Pairs and functional references
 
            Hi, I've been thinking a lot lately about heterogeneous and extensible data structures for which HList certainly offers a solution. While HList is implemented through type-level programming I wonder if I can achieve similar results through value-level programming alone. This is where I was thinking of functional references. I wonder if or rather how one could do this: Let's say there was some clever monad ... someMonad = do h1 <- add "twenty" h2 <- add False h3 <- add 16 ..... modify h2 True and get a ("twenty",(True, 16)) back. And while *in* the monad some accessors available. Now come to think of it I think I actually read about this somewhere so I doubt this is truly my idea. Anybody got some thoughts on this? Günther
 
            On Feb 16, 2010, at 12:14 PM, Günther Schmidt wrote:
Let's say there was some clever monad ...
someMonad = do h1 <- add "twenty" h2 <- add False h3 <- add 16 ..... modify h2 True
and get a ("twenty",(True, 16)) back. And while *in* the monad some accessors available.
Your return value will be wrapped a bit more strongly if you use monads and try to combine types. Basically, build a monad with lots of values with no free monadic variables. For example, in Maybe, Just has a free variable, whereas Nothing doesn't. You can create values free in the monadic variable to carry any SPECIFIC type you want. (Or even type class instances, if you use existential types)
data Accumulator value = AtomicAccumulator value | StringAccumulator String | IntAccumulator Int | ConcatAccumulators (Accumulator value) (Accumulator value)
(Accumulator String)s are (Accumulator value)s for any value. So you can build things like:
ConcatAccumulators (IntAccumulator 10) (StringAccumulator "Hi")
I would build up accessors to these values using record syntax. Here's a meaty example I've been working on: data View view = (Left view) `ConcatViews` (Right view) | NestViews (Left view) (Middle view) (Right view) | EmptyView | AtomicView view | ReturnView view -- View Nodes: | DocumentView { document_title_view :: View view , document_toc :: View view , document_footer :: View view , document_header :: View view , document_contents :: View view } | PageView { page_title :: View view , page_contents :: View view } | TableView { table_title_view :: View view , table_heading_view :: View view , table_row_view :: View view , table_subtotal_row_view :: View view , table_total_row_view :: View view } | SectionView { section_title :: View view , section_heading_view :: View view , section_contents :: View view } | SidebarView { sidebar_title :: View view , sidebar_heading :: View view , sidebar_contents :: View view } | FieldView | HeadingView String | ListView [ View view ] -- View of list, not list of views. | PageFooterView | PageHeaderView | PageHeadingView String | ParagraphView String | RowView | TableTitleView String | TextView String deriving Show instance Monoid (View view) where mempty = EmptyView EmptyView `mappend` right = right left `mappend` EmptyView = left left `mappend` right = ConcatViews left right data Field = Field { field_name :: String , field_description :: String } data Row = HeadingRow [Field] instance Monad View where return = ReturnView (AtomicView view) >>= f = f view (ConcatViews left right) >>= f = ( ConcatViews (left >>= f) (right >>=f) ) (DocumentView title toc footer header content) >>= f = ( DocumentView (title >>= f) (toc >>= f) (footer >>= f) (header >>= f) (content >>= f) ) (NestViews l m r) >>= f = ( NestViews (l >>= f) (m >>= f) (r >>= f) ) (EmptyView) >>= f = EmptyView (HeadingView string) >>= f = HeadingView string (ReturnView view) >>= f = f view (PageView t c) >>= f = ( PageView (t >>= f) (c >>= f) ) (TableView title heading row subtotal total) >>= f = ( TableView (title >>= f) (heading >>= f) (row >>= f) (subtotal >>= f) (total >>= f) ) (SectionView title heading contents) >>= f = ( SectionView (title >>= f) (heading >>= f) (contents >>= f) ) (ListView views) >>= f = ListView (fmap (>>= f) views) (SidebarView title heading contents) >>= f = ( SidebarView (title >>= f) (heading >>= f) (contents >>= f) ) (TextView string ) >>= f = TextView string (ParagraphView string ) >>= f = ParagraphView string (TableTitleView string ) >>= f = TableTitleView string (RowView ) >>= f = RowView (FieldView ) >>= f = FieldView (PageFooterView ) >>= f = PageFooterView (PageHeadingView string ) >>= f = PageHeadingView string (PageHeaderView ) >>= f = PageHeaderView
 
            Hi Alex, this looks very very interesting, gimme some time to figure it. I hope you'll take questions later ... Günther Am 16.02.10 22:34, schrieb Alexander Solla:
On Feb 16, 2010, at 12:48 PM, Alexander Solla wrote:
(Accumulator String)s are (Accumulator value)s for any value. So you can build things like:
Sorry, I made a typo. I meant "StringAccumulator String"s are "Accumulator value"s for any value.
 
            Hi Alexander Your monad looks equivalent to the Identity monad but over a much bigger syntax. What advantages do you get from it being a monad, rather than just a functor? Best wishes Stephen
 
            On Feb 16, 2010, at 2:11 PM, Stephen Tetley wrote:
Your monad looks equivalent to the Identity monad but over a much bigger syntax. What advantages do you get from it being a monad, rather than just a functor?
= f)), we can do it in terms of arbitrary constructors, as long as = induced a partial order. This approach has some interesting
I replied to Stephen, but forgot to include the list. I took the liberty of making some changes. I mostly use this construct functorially. Defining a monad instance can be done in O(n) lines, but an applicative functor instance needs O(n^2) lines, where n is the number of type constructors. The monadic structure doesn't interfere with the semantics I want, so I went with that. As you said, this is basically an identity monad, but it's not too hard to turn it into a sequencing monad. For example, instead of defining (NestViews l m r) >>= f as (NestViews (l >>= f) (m >>= f) (r potential.
 
            Hi Alexander, sry for being a bit thick, but how would this code be used? I'm unable to figure out the application yet. Could you give some examples how you use it? Günther
 
            sry for being a bit thick, but how would this code be used?
I'm unable to figure out the application yet. Could you give some examples how you use it?
Günther
So, the type (View view) -- ignoring class instances -- is basically isomorphic to this (slightly simpler) type: data View = EmptyView | TextView String | ConcatView View View | NestViews View View View | ... instance Monoid View where ... Now, consider the problem of "generic programming" on the simpler type: you quantify over the data constructors "generically", and in doing so you gain "traversals" for the type.[1] You gain the same things by turning View into (View view) -- a functor, a foldable functor, and so on. When it comes time to "render" a format for a View (for example, a bit of Html from Text.XHtml.Strict), I use some higher order functions I'm already familiar with. Something like renderXHtml :: (View view) -> Html renderXHtml (ConcatViews l r) = fold $ renderXHtml (ConcatViews l r) renderXHtml (NestViews l m r) = fold $ renderXHtml (NestViews l m r) renderXHtml (TextView string) = stringToHtml string renderXHtml (PageView v_title, v_heading, v_header, v_footer, v_contents) = (the_title << (renderXHtml v_title)) +++ -- (We assume v_title is a TextView String) (body << ( renderXHtml v_header ) +++ (render_page_contents v_contents v_heading) +++ (renderXHtml v_footer) ) where render_page_contents contents heading = undefined -- takes a View and uses the page's heading View -- so I guess we assume v_heading is a function -- into a TextView ... You could potentially use (>>=) for this, directly. And if you were using the simpler type, you could do the same thing with Uniplate, for example. It's going to construct an automorphism for you. [1] Actually, it's "the other way around". But the container/ contained adjunction makes them equivalent.
 
            Alexander Solla wrote:
So, the type (View view) -- ignoring class instances -- is basically isomorphic to this (slightly simpler) type:
data View = EmptyView | TextView String | ConcatView View View | NestViews View View View | ... instance Monoid View where ...
Now, consider the problem of "generic programming" on the simpler type: you quantify over the data constructors "generically", and in doing so you gain "traversals" for the type.[1] You gain the same things by turning View into (View view) -- a functor, a foldable functor, and so on. When it comes time to "render" a format for a View (for example, a bit of Html from Text.XHtml.Strict), I use some higher order functions I'm already familiar with. Something like
renderXHtml :: (View view) -> Html renderXHtml (ConcatViews l r) = fold $ renderXHtml (ConcatViews l r) renderXHtml (NestViews l m r) = fold $ renderXHtml (NestViews l m r) renderXHtml (TextView string) = stringToHtml string renderXHtml (PageView v_title, v_heading, v_header, v_footer, v_contents) = (the_title << (renderXHtml v_title)) +++ -- (We assume v_title is a TextView String) (body << ( renderXHtml v_header ) +++ (render_page_contents v_contents v_heading) +++ (renderXHtml v_footer) ) where render_page_contents contents heading = undefined
But isn't the line renderXHtml (ConcatView l r) = fold $ renderXHtml (ConcatViews l r) a type error? I'm assuming Data.Foldable.fold :: (Foldable m, Monoid t) => m t -> t being applied to the result type of renderXHtml which is Html and not of the form m t . Your intention reminds me of the use of type variables to get functor-like behavior for free, like in data RGB' a = RGB a a a -- auxiliary type constructor type RGB = RGB' Int -- what we're interested in instance Functor RGB' where fmap f (RGB x y z) = RGB (f x) (f y) (f z) mapRGB :: (Int -> Int) -> RGB -> RGB mapRGB = fmap but I don't quite see what you're doing with the free monad here, Alexander? Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com
 
            On Feb 20, 2010, at 10:25 AM, Heinrich Apfelmus wrote:
But isn't the line
renderXHtml (ConcatView l r) = fold $ renderXHtml (ConcatViews l r)
a type error? I'm assuming
Data.Foldable.fold :: (Foldable m, Monoid t) => m t -> t
being applied to the result type of renderXHtml which is Html and not of the form m t .
Yup, that's a type error. I mean to fold the View (in this case a ConcatView) into a monoid. I think I meant
foldMap renderXHtml (ConcatViews l r)
Your intention reminds me of the use of type variables to get functor-like behavior for free, like in
data RGB' a = RGB a a a -- auxiliary type constructor type RGB = RGB' Int -- what we're interested in
but I don't quite see what you're doing with the free monad here, Alexander?
As you noticed, I am seeking that functorial behavior in order to gain some genericity. bind and return do encode some logic about the nature of monadic adjunction, which I am relying on theoretically. I could have used a Functor instance just as easily, but I would have lost my "intention" of defining co-equalizers implicitly. (http://en.wikipedia.org/wiki/Beck%27s_monadicity_theorem ) Also, it was easier to write a monad instance than an Applicative instance, at least on my first try. ;-)
 
            Alexander Solla wrote:
Yup, that's a type error. I mean to fold the View (in this case a ConcatView) into a monoid. I think I meant
foldMap renderXHtml (ConcatViews l r)
Hm, that would require a type renderXHtml :: Monoid t => View t -> Html
Your intention reminds me of the use of type variables to get functor-like behavior for free, like in
data RGB' a = RGB a a a -- auxiliary type constructor type RGB = RGB' Int -- what we're interested in
but I don't quite see what you're doing with the free monad here, Alexander?
As you noticed, I am seeking that functorial behavior in order to gain some genericity. bind and return do encode some logic about the nature of monadic adjunction, which I am relying on theoretically. I could have used a Functor instance just as easily, but I would have lost my "intention" of defining co-equalizers implicitly. (http://en.wikipedia.org/wiki/Beck%27s_monadicity_theorem)
I don't know, the new ReturnView constructor which gives rise to the monad does allow us to represent "views with variables". But to me, this doesn't seem to add much genericity. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com
 
            Günther Schmidt wrote:
I've been thinking a lot lately about heterogeneous and extensible data structures for which HList certainly offers a solution.
While HList is implemented through type-level programming I wonder if I can achieve similar results through value-level programming alone.
This is where I was thinking of functional references.
I wonder if or rather how one could do this:
Let's say there was some clever monad ...
someMonad = do h1 <- add "twenty" h2 <- add False h3 <- add 16 ..... modify h2 True
and get a ("twenty",(True, 16)) back. And while *in* the monad some accessors available.
Now come to think of it I think I actually read about this somewhere so I doubt this is truly my idea.
Anybody got some thoughts on this?
Dropping the part involving modification, I think you want to write something like this val "twenty" `pair` (val False `pair` left) where left is a "magic function" that returns the previous entry of the pair, so that the whole expression yields ("twenty", (False, False)) The difficult part is to keep track of the types. But fortunately, there is a neat trick by Oliver Danvy which does exactly that, see also Oliver Danvy. Functional unparsing. http://www.brics.dk/RS/98/12/BRICS-RS-98-12.pdf Namely, let's assume we are already given a "magic" type constructor |- (so magic that it's not even legal Haskell syntax) with the property that A |- B somehow denotes an expression of type B with free variables of type A . In other words, the result of type B is somehow allowed to depend on values of type A . Given this type, we can now assign types to our functions: pair :: (a |- b) -> ((a,b) |- c) -> (a |- (b,c)) left :: (a,b) |- b val :: x -> (a |- x) In other words, everything may depend on additional free variables of some type a . But of course, A |- B is just the same as A -> B , which readily suggest the implementation pair f g = \a -> let b = f a in (b, g (a,b)) left = \(a,b) -> b val x = \a -> x For instance, we get example :: a -> (String, (Bool, Bool)) example = val "twenty" `pair` (val True `pair` left) and example undefined = ("twenty",(True,True)) While the functionality is a bit limited, I'm confident that this approach can be extended considerably. Whether the result is useful is another question, of course. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com
 
            On Feb 24, 2010, at 10:15 AM, Heinrich Apfelmus wrote:
Namely, let's assume we are already given a "magic" type constructor |- (so magic that it's not even legal Haskell syntax) with the property that
A |- B
somehow denotes an expression of type B with free variables of type A . In other words, the result of type B is somehow allowed to depend on values of type A .
In the context of this post, when I say "functor", I don't mean a Functor instance. I mean the mathematical object which maps between categories. As you noted, functions satisfy your "magic". A function from a type A to B is a functor from A to B from a different point of view. (One is "in" some kind of algebra in A and B, and the other is in the category of small categories). But you lose something important by using functions. Consider the parallel type specification of (my) Views with types, guided by your example code: concat_views :: a -> v -> v -> (a, (v, v)) -- v's are meant to be the result of calling a *_view function. nest_views :: a -> v -> v -> v -> (a, (v, v, v)) page_view :: a -> v -> v -> v -> v -> (a, [v]) text_view :: String -> v -> (String, v) As you can see from the types, these are functions that take values and "wrap them up". These functions trivially induce functors of the form View a :: v -> (a, [v]) (let's call them lists for the purposes of "form" since there can be any number of v's). What are we gaining? What are we losing? My Functor-based implementation had a uniform interface to all the View's innards, which we have lost. And if we want to turn these functions into an algebra, we need to define a fair amount of plumbing. If you take the time to do that, you'll see that the implementation encodes a traversal for each of result types. An fmap equivalent for this implementation. In short, before you can do anything with your construct, you will need to normalize the return result. You can do that by reifying them:
data View view = EmptyView | TextView String | ConcatViews (View view) (View view) | ...
or by doing algebra on things of the form (a, [v]). Notice, also, that the View view data constructors are (basically) functions of the form [View] -> (a, [View]) or a -> (a, [View]) for some a. (The tricky bit is the "some a" part. Consider why EmptyView and (TextView String) is a (View view) no matter what type view is). The parallel for EmptyView is:
empty_view :: a -> v -> (a, v) empty_view a v = (a, ()) --? I guess that works. Dummy arguments for empty things. Ikky.
My example code had some problems, but I really think it's a superior solution for the problem of making reusable renderable fragments. Indeed, this post described how I refactored your approach into mine, when I wrote my View code in the first place. Then again, I also got tired of wrestling with Data.Foldable and moved on to using a plain initial algebra and Uniplate.
participants (4)
- 
                 Alexander Solla Alexander Solla
- 
                 Günther Schmidt Günther Schmidt
- 
                 Heinrich Apfelmus Heinrich Apfelmus
- 
                 Stephen Tetley Stephen Tetley