apfelmus wrote:
>   {-# OPTIONS_GHC -fglasgow-exts -#}
>   import Prelude hiding (lookup)
> 
>   class Map map key a | map key -> a where
>       lookup ::             key -> map -> Maybe a
>       adjust :: (a -> a) -> key -> map -> map
> 
>   instance (Map m k m', Map m' k' a) => Map m (k,k') a where
>       lookup (k,k') m   = lookup k m >>= lookup k'
>       adjust f (k,k') m = adjust (adjust f k') k m

Uh, that actually needs -fundecidable-instances or something similar.
Using explicit functor composition doesn't resolve the problem

  class Map map key | map -> key where
     lookup ::             key -> map a -> Maybe a
     adjust :: (a -> a) -> key -> map a -> map a

  data O f g a = O (f (g a))

  instance (Map m k, Map m' k') => Map (m `O` m') (k,k') a where
    ...

  -- but how to make ((m `O` m') a) a map for (m' a)?

With associated type synonyms, this program can't even be formulated.
Any ideas?


For the time being, you can specialize the key-pairing for concrete maps
in question.

  newtype UniverseF a = UniverseF [a]
  newtype GalaxyF   a = GalaxyF [a]

  type Universe       = UniverseF Galaxy
  type Galaxy         = GalaxyF Planet
  data Planet         = ...

  instance Map (UniverseF a) k a where ...
  instance Map m k a => Map (UniverseF m) (Int,k) a where ...

Oh, and you need a dummy instance for Planets as "singleton"-maps.

  instance Map Planet () Planet where ...

Regards,
apfelmus

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

Reply via email to