[Haskell-cafe] Difficulties in accessing inner elements of data types

David Miani davidmiani at gmail.com
Fri Mar 6 00:08:10 EST 2009


Well thanks to everyone that has replied so far - I've had an interesting time 
trying out different ideas.

Firstly, for Neil Mitchell's suggestions regarding uniplate:
I read through both uniplate and scrap your boilerplate libraries (found the 
second after reading about uniplate). For whatever reason, I understood syb 
better than uniplate (but thats probably just me). This actually worked quite 
well (note that I've changed the data types slightly, but it doesn't change 
the code that much):

eitherOr :: Either a b -> Either a b -> Either a b
eitherOr x@(Right _) _ = x
eitherOr  _ y  = y


getP14Desc :: OrgElement -> Either ErrString String
getP14Desc org = everything eitherOr (Left descError `mkQ` findDesc) =<<
                 everything eitherOr (Left findError `mkQ` findP14) org
    where
      findP14 h@(Heading {headingName=name})
          | name == "Project14" = Right h
      findP14 _ = Left findError

      findDesc (Paragraph {paragraphText=text})
          | text =~ "Description" = Right text
      findDesc _ = Left findError

      descError = "Couldn't find description for project"
      findError = "Couldn't find project."


While it isn't that many less loc than my original code, it was much simpler 
to get working. Also, the find methods could easily be factored out. My second 
problem, adding the tag "Hard" to Project2 was also fairly simple:

addHardTag org = everywhere (mkT addTagToP2) org where
    addTagToP2 h@(Heading {headingName=name}) 
               | name == "Project 2" = everywhere (mkT addTag) h
    addTagToP2 x = x
    addTag text 
           | text =~ "Tags:" = text ++ ",newtag"


However, I also wanted to try out Tim Docker's suggestion for using data-
accessor. That seemed to also be very promising, except for one thing - data-
accessor doesn't seem to be able to cope with multiple constructors! The code 
for this was faily simple though, so I went about making it work for multiple 
constructors.

The original definition for an Accessor d f (where d is the datatype and f is 
the type of the field) was 

Cons {decons :: d -> f -> (d, f)} -- (this wasn't exported by the module 
though)

There is a problem with that for multiple constructors though - its possible 
that there will be no return for a given accessor. Eg running get headingName' 
(Paragraph "some text") would not be possible. So I changed the code to this:

newtype Accessor1 d f = Accessor (d -> Maybe f, f -> d -> d)

If the getter failed, Nothing is returned. If the setter failed, it acts like 
id.

After using that for a while I realized there was potential to have an 
accessor automatically access all the children of a data type. This could be 
achieved by changing the return type of the getter to [f], and changing the 
setter function to a modifier function:

newtype MultiConAccessor d f = MultiConAccessor ((d -> [f]),((f -> f) -> d -> 
d))

I also wrote the chain function, which joins to accessors together

After a lot of definitions (although most should be able to be automated with 
template haskell), I could use the code:

projectAccessor name = headingChildren' `chain` -- top level elements
                       headingChildren' `chain` -- level 2 
                       liftFilterS (== name) headingName'



getP14Desc2 = getVal $
              projectAccessor "Project14" `chain`
              headingChildren' `chain`
              liftFilterS (=~ "Description:") paragraphText' `chain`
              paragraphText'

addHardTag2 = modVal
              (projectAccessor "Project 2" `chain`
               headingChildren' `chain`
               liftFilterS (=~ "Tags:") paragraphText' `chain`
               paragraphText') (++ ",newtag")

I've posted all the code at 
http://moonpatio.com/fastcgi/hpaste.fcgi/view?id=1778#a1778
It isn't very well documented, as I was just experimenting with this.

             
Finally, thanks Sean for your response. That blog post was very nice! Your 
solution also looks good (especially since most of the code was automated). I 
haven't had a chance to have a close look at EMGM but will in the next couple 
of days.

So I've gone from having no solution a few days ago to having 3 or 4 now! Not 
sure which solution I will stick with, any seem to do the job. 

So thanks everyone!
David



More information about the Haskell-Cafe mailing list