On 24/10/12 12:08, Jon Fairbairn wrote:

Is there a convenient way of handling a data structure with lots
of fields of different types that may or may not be filled in?


Not sure about convenience, but here is a type safe solution with O(log n) lookups and updates. The idea is to define a GADT tree type with a fixed layout:

    -- define the structure
    type MyT = TBranch (TLeaf A) (TBranch (TLeaf B) (TLeaf C))
    -- a value level tree that uses that structure
    type My  = GTree MyT

You still have to define the paths to the members

    pa = GL GH
    pb = GR (GL GH)
    pc = GR (GR GH)

But once you have that you can perform lookups and updates:

    *Main> glookup pc (gupdate pa (Just A) (gupdate pc (Just C) gempty))
    Just C

It shouldn't be too hard to make a template haskell function that generates these paths. Or perhaps the corresponding lenses.


Twan
{-# LANGUAGE DataKinds, KindSignatures, GADTs #-}

data TTree a = TEmpty | TLeaf a | TBranch (TTree a) (TTree a)

data GTree (t :: TTree *) :: * where
  GEmpty  :: GTree t
  GLeaf   :: a -> GTree (TLeaf a)
  GBranch :: GTree l -> GTree r -> GTree (TBranch l r)

data GPath (t :: TTree *) (a :: *) :: * where
  GH :: GPath (TLeaf a) a
  GL :: GPath l a -> GPath (TBranch l r) a
  GR :: GPath r a -> GPath (TBranch l r) a

gempty :: GTree t
gempty = GEmpty

glookup :: GPath t a -> GTree t -> Maybe a
glookup GH     (GLeaf x)     = Just x
glookup (GL p) (GBranch x _) = glookup p x
glookup (GR p) (GBranch _ x) = glookup p x
glookup _      _             = Nothing

gupdate :: GPath t a -> Maybe a -> GTree t -> GTree t
gupdate GH     Nothing  _      = GEmpty
gupdate GH     (Just v) _      = GLeaf v
gupdate (GL p) v (GBranch l r) = GBranch (gupdate p v l) r
gupdate (GL p) v _             = GBranch (gupdate p v GEmpty) GEmpty
gupdate (GR p) v (GBranch l r) = GBranch l      (gupdate p v r)
gupdate (GR p) v _             = GBranch GEmpty (gupdate p v GEmpty)

-------------- Example

data A = A deriving Show
data B = B deriving Show
data C = C deriving Show
type MyT = TBranch (TLeaf A) (TBranch (TLeaf B) (TLeaf C))
type My  = GTree MyT
pa :: GPath MyT A
pa = GL GH
pb :: GPath MyT B
pb = GR (GL GH)
pc :: GPath MyT C
pc = GR (GR GH)

{-

*Main> glookup pc (gupdate pa (Just A) (gupdate pc (Just C) gempty))
Just C

-}

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to