[Haskell-cafe] Functional dependence nightmare

Edgar Gomes Araujo talktoedgar at gmail.com
Sat Mar 26 15:11:02 CET 2011


Hi,

I'm running in errors that, I think, is related with functional dependence.
But I don't know how to interpret or solve them.

I have basically 3 types: Edge, Face and Simplex (Tetrahedron) and I want to
combined them in a class type such that:
 - Edge and Face will produce a convex hull
 - Face and Simplex will produce a Delaunay triangulation
under the same MCB (Marriage Before Conquer) algorithm.

I first tried to use Multiparameter type class
with functional dependence relation:

class SubUnit subUnit unit | subUnit -> unit, unit -> subUnit where
    buildUnit      :: ActiveSubUnit subUnit -> [Point] -> Maybe unit
    build1stUnit   :: Plane -> [Point] -> [Point] -> [Point] -> Maybe unit
    getAllSubUnits :: unit -> [ActiveSubUnit subUnit]
    subUnitPos     :: BoxPair -> subUnit -> Position


but then I decide to go for a GADT form  (If someone wants to try to compile
it, one can get the complete code on GitHub:
http://github.com/EdgarGomes/DeUni) :

class SubUnit subUnit where
    type Unit subUnit :: *
    buildUnit      :: ActiveSubUnit subUnit -> [Point] -> Maybe (Unit
subUnit)
    build1stUnit   :: Plane -> [Point] -> [Point] -> [Point] -> Maybe (Unit
subUnit)
    getAllSubUnits :: Unit subUnit -> [ActiveSubUnit subUnit]
    subUnitPos     :: BoxPair -> subUnit -> Position




In both cases I get a couple of errors like:

src/DeUni.hs:265:39:
    Couldn't match type `Unit subUnit3' with `Unit subUnit2'
    NB: `Unit' is a type function, and may not be injective
    Expected type: Unit a
      Actual type: Unit subUnit2
    In the expression: un
    In the expression: [un]
    In the first argument of `return', namely
      `(([un], fromList $ getAllSubUnits un) ::
          SubUnit a => ([Unit a], SetActiveSubUnits a))'

src/DeUni.hs:265:39:
    Couldn't match type `Unit (ActiveSubUnit subUnit3)'
                   with `Unit subUnit2'
    NB: `Unit' is a type function, and may not be injective
    Expected type: Unit a
      Actual type: Unit subUnit2
    In the expression: un
    In the expression: [un]
    In the first argument of `return', namely
      `(([un], fromList $ getAllSubUnits un) ::
          SubUnit a => ([Unit a], SetActiveSubUnits a))'

src/DeUni.hs:265:44:
    Could not deduce (a1 ~ ActiveSubUnit subUnit3)
    from the context (SubUnit a)
      bound by the type signature for
                 mbc :: SubUnit a =>
                        [Point] -> SetActiveSubUnits a -> Box -> StateMBC a
[Unit a]
      at src/DeUni.hs:(260,1)-(317,53)
    or from (SubUnit a1)
      bound by an expression type signature:
                 SubUnit a1 => ([Unit a1], SetActiveSubUnits a1)
      at src/DeUni.hs:265:37-117
      `a1' is a rigid type variable bound by
           an expression type signature:
             SubUnit a1 => ([Unit a1], SetActiveSubUnits a1)
           at src/DeUni.hs:265:37
    Expected type: SetActiveSubUnits a
      Actual type: Set (ActiveSubUnit subUnit3)
    In the expression: fromList $ getAllSubUnits un
    In the first argument of `return', namely
      `(([un], fromList $ getAllSubUnits un) ::
          SubUnit a => ([Unit a], SetActiveSubUnits a))'

.....
.....


Any help is more than welcome!

Cheers,
Edgar Gomes (LambdaSteel)
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20110326/b4223316/attachment.htm>


More information about the Haskell-Cafe mailing list