[Haskell-cafe] represent data sturcture using function
Ryan Ingram
ryani.spam at gmail.com
Mon Dec 29 18:15:38 EST 2008
On Mon, Dec 29, 2008 at 4:29 AM, <raeck at msn.com> wrote:
> Would you please give me a complete example of code that I could have more
> information
> on the idea?
Sure, I put up an example at http://ryani.freeshell.org/haskell/gmap.hs
class MapKey k where
data (:->) k :: * -> *
newMap :: (k -> v) -> (k :-> v)
fetch :: (k :-> v) -> (k -> v)
update :: k -> (v -> v) -> (k :-> v) -> (k :-> v)
assign :: k -> v -> (k :-> v) -> (k :-> v)
assign k v m = update k (const v) m
empty :: v -> (k :-> v)
empty = newMap . const
with instances & associated data types:
instance MapKey () where
-- A single value
newtype () :-> v = UMap v
instance MapKey Bool where
-- A value for False and True
data Bool :-> v = BMap v v
instance (MapKey k1, MapKey k2) => MapKey (k1,k2) where
-- A "curried" map
newtype (k1,k2) :-> v = PMap (k1 :-> k2 :-> v)
instance (MapKey k1, MapKey k2) => MapKey (Either k1 k2) where
-- sub-maps for Left k1 and Right k2
data (Either k1 k2 :-> v) = EMap (k1 :-> v) (k2 :-> v)
instance MapKey k => MapKey (Maybe k) where
-- Now we can build up from existing structures!
newtype (Maybe k) :-> v = MaybeM (Either () k :-> v)
instance MapKey k => MapKey [k] where
-- Value for [] and map for (head:tail)
--
-- Note that this includes a recursive ([k] :-> v) map
-- in the pair map (k,[k]) :-> v
data [k] :-> v = ListM v ((k,[k]) :-> v)
instance MapKey Positive where
-- We just convert a positive number into
-- a list of Bools, then make a map of those
newtype Positive :-> v = PosMap ([Bool] :-> v)
instance MapKey Integer where
-- Now an integer is either negative, zero, or positive.
-- So we store a map for negative numbers, a zero value,
-- and a map for positive numbers.
data Integer :-> v = IntMap (Positive :-> v) v (Positive :-> v)
The rest of the class functions are reasonably easy to derive from
their type and these data types.
-- ryan
More information about the Haskell-Cafe
mailing list