A basic problem.

  Being able to have a common method to lookup elements based
  on the index and to map the elements of both [(i,e)],
  Array i e, Cont1 i e, and Cont2_ ie.

The solution within current Haskell.

  class Find c i e where
    find :: i -> c -> e

  class Elmap c e d f where
    elmap :: (e -> f) -> c -> d

  data Pair fst snd = ...
  data Cont1 i e = ...
  data Cont2_ ie = ...
  type Cont2 i e = Cont2 (Pair i e)

  instance Eq i => Find [(i,e)] i e ...
  instance Elmap [(i,e)] e f [(i,f)]

  instance Find (Array i e) i e ...
  instance Elmap (Array i e) e f (Array i f) ...

  ...etc

The problem with this solution:

  When used with a function like show it will lead to an unresolved 
  overloading becuase haskell can't figure out the return type.

  The instance declaration are unnecessary ugly.

  The Elmap functions does not promise to return a container 
  of the same type based on the class declaration.

  The class signatures are in general vague.

A solution using "Nameable type parameters:"

  class Find c i e where
           -- i -> A c whose Ix type is i 
           -- and whose El type is e -> Maybe e
    find :: i -> c Ix:i El:e -> Maybe e

  class Elmap c e f where
          -- (e -> f) -> A c whose El type is e 
                          -> A c whose El type is f
    elmap :: (e -> f) -> c El:e -> c El:f


  -- Create a new data type Pair whose 1st type and Fst type 
  -- is fst and whose 2nd type is snd and whose 2nd type is snd
  data Pair Fst:fst Snd:snd = ...
  -- Create a new data type Cont1 whose 1st type and Ix type is i ...
  data Cont1 Ix:i El:e = ...
  data Cont2_ ie = ...
  type Cont2 i e = Cont2 (Pair i e)

  -- If the kind of an object is [] -> (() -> i -> *) 
  -- then its Ix type is i
  Ix [(i,_)] = i
  -- If the kind of an object is [] -> (() -> * -> e) 
  -- then its El type is e
  El [(_,e)] = e

  Ix (Array i _) = i
  El (Array _ e) = e

  -- If the kind of an object is Cont2_ -> ie then its
  -- Ix type is the Fst type of ie  if  ie has a type Fst
  Ix (Cont2_ ie) = Fst ie
  -- If the kind of an object is Cont2_ -> ie then its 
  -- El type is the Snd type of ie  if  ie has a type Snd
  El (Cont2_ ie) = Snd ie

  instance (Eq i) => Find [] i e ...
  instance Elmap [] e f ...

  ... etc

The problems:

  None once Haskell supports it.

The question:

  Has anyone else thought of something like this.

-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/


Reply via email to