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 ---------------------------------- END CODE ------------------------------- Thanks, Brandon Simmons http://coder.bsimmons.name/blog/ _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe