On Tue, Jul 27, 2010 at 1:59 AM, Jason Dagit <da...@codersbase.com> wrote: > > > On Mon, Jul 26, 2010 at 9:00 PM, Brandon Simmons > <brandon.m.simm...@gmail.com> wrote: >> >> I had the idea for a simple generic Zipper data structure that I >> thought would be possible to implement using type-threaded lists >> provided by Gabor Greif's thrist package: >> >> http://hackage.haskell.org/package/thrist >> >> ...and the fclabels package by Sebastiaan Visser, Erik Hesselink, >> Chris Eidhof and Sjoerd Visscher: >> >> http://hackage.haskell.org/package/fclabels >> >> It would (ideally) work as follows: >> >> - the zipper would consist simply of a tuple: >> (type threaded list of constructor sections , current "context") >> - in the type threaded list we store functions (constructor with hole >> -> complete constructor), so the >> "one hole context" is represented as a lambda expression where the >> free variable will be filled >> by the current "context" (the snd of the tuple) >> - we "go down" through our structure by passing to our `moveTo` >> function a first-class label >> corresponding to the constructor we want to descend into. `moveTo` >> uses this both as a "getter" >> to extract the next level down from the current level, and as a >> "setter" to form the lambda expression >> which acts as the "constructor with a piece missing" >> - "going up" means popping the head off the thrist and applying it to >> the current context, making that >> the new context, exiting the zipper would be a fold in the same manner >> >> >> After throwing together a quick attempt I realized that I'm not sure >> if it would be possible to make the `moveUp` function type-check and >> be usable. I'm still new to GADTs, existential types, template haskell >> etc. and am stuck. >> >> Here is the code I wrote up, which doesn't currently compile: >> >> >> ---------------------------------- START CODE >> ------------------------------- >> >> {-# LANGUAGE TypeOperators, GADTs #-} >> module ZipperGenerator >> ( >> viewC --lets user pattern match against context >> , moveTo >> , moveUp >> , genZippers >> , zipper >> , unzipper >> , (:->) >> , ZipperGenerator >> , Zipper >> ) where >> >> -- these provide the secret sauce >> import Data.Record.Label >> import Data.Thrist >> import Language.Haskell.TH >> >> >> type ZipperGenerator = [Name] -> Q [Dec] >> >> -- the Template Haskell function that does the work of generating >> -- first-class labels used to move about the zipper: >> genZippers :: ZipperGenerator >> genZippers = mkLabels >> >> -- hide the innards: >> newtype Zipper t c = Z (Thrist (->) c t, c) >> >> -- returns the current "context" (our location in the zipper) for pattern >> -- matching and inspection: >> viewC :: Zipper t c -> c >> viewC (Z(_,c)) = c >> >> -- takes a first-class label corresponding to the record in the current >> context >> -- that we would like to move to: >> moveTo :: (c :-> c') -> Zipper t c -> Zipper t c' >> moveTo lb (Z(thr,c)) = Z (Cons (\a-> set lb a c) thr , get lb c) >> >> >> -- backs up a level in the zipper, returning `Nothing` if we are already >> at the >> -- top level: >> moveUp :: Zipper t c -> Maybe (Zipper t b) >> moveUp (Z (Nil,_)) = Nothing >> moveUp (Z (Cons f thr,c)) = Just $ Z (thr, f c) >> >> -- create zipper with focus on topmost constructor level: >> zipper :: t -> Zipper t t >> zipper t = Z (Nil,t) >> >> -- close zipper >> unzipper :: Zipper t c -> t >> unzipper (Z(thr,c)) = undefined --foldThrist ($) id thr c > > Hmm...I think you just need to change ($) to (.). I haven't tested it. > But, if you have Thrist (->) c t, then what you have is a transformation > from c to t, or more simply, c -> t. So, conceptually at least, you just > need to compose the elements in your Thrist. ($) is application, but in the > space of functions it is identity. So, if you think the elements in your > thrist as being values in the space of functions, you're asking for a right > fold that is like, v1 `id` (v2 `id` (v3 `id` ...), which I hope you agree > doesn't make that much sense. So try this: > unzipper (Z(thr,c)) = foldThrist (.) id thr c > In the darcs source we use our own custom thrists for storing sequences of > patches. We have two variants, forward lists (FL) and reverse lists (RL). > In our parlance, we have foldlFL defined thusly: > foldlFL :: (forall w y. a -> b w y -> a) -> a -> FL b x z -> a > foldlFL _ x NilFL = x > foldlFL f x (y:>:ys) = foldlFL f (f x y) ys > We don't use Control.Arrow, so in our notation the 'b' in the type signature > plays the same role as (~>) but in prefix notation, of course. And we use > (:>:) instead of Cons. It's supposed to look like normal list cons but with > an arrow pointing forward. The cons for RL is (:<:). Perhaps we should use > arrow though, as I think that looks pretty nice. > For comparison, here is the definition of foldThrist: > foldThrist :: (forall i j k . (i ~> j) -> (j ~> k) -> (i ~> k)) > -> c ~> c > -> Thrist (~>) a c > -> a ~> c > foldThrist _ v Nil = v > foldThrist f v (Cons h t) = h `f` (foldThrist f v t) > As you can see, our fold is a left fold and the thrist fold is a right fold. > I don't think a left fold will help you here, but you might keep it in mind > as it should be easy to define for thrists, should you need it. > Florent Becker created zippers for the darcs custom FL/RL types recently: > http://darcs.net/src/Darcs/Witnesses/WZipper.hs > Don't let the C(foo) in the types throw you off. That's just a CPP macro > that conditionally expands to foo or nothing depending on whether the type > threading is turned on or off (cabal flag is -ftype-witnesses vs. > -f-type-witnesses). His approach is quite different than yours. I should > probably study the fclabels package. > Thanks for the interesting code! > Jason
Jason, thanks for the great response. I'll be interested to look at the Darcs code you mentioned and to learn a few things. I left the `unzipper` function unimplemented mostly out of laziness, but thanks for the help on it. After reading your reply and the type signature for `foldThrist` I think it would be implemented as: unzipper :: Zipper t c -> t unzipper (Z(thr,c)) = foldThrist (flip(.)) id thr c My main source of trouble is still with the `moveUp` function. I think it shows that my idea is flawed. I was thinking there could be hope for this if `moveTo` worked only on recursive constructors, so it would take a first class label of type: (t :-> t). We could just use a plain list in that case. But with that method we can't descend through mutually-recursive data types, and the TH stuff from the fclabels package becomes less of a good fit. If I'm going to be writing my own template haskell, I might as well create an entire custom "zipper generater" in it. Brandon _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe