[Haskell-cafe] Re: OO in Haskell

Benjamin Franksen benjamin.franksen at bessy.de
Mon Nov 29 16:18:08 EST 2004


On Monday 29 November 2004 21:47, Keean Schupke wrote:
> Benjamin Franksen wrote:
> >I still have problems. They are probably due to a wrong definition of the
> >operator (#). Note that (#) is nowhere defined inside the HList sources,
> > so I assumed an inverse application operator. This is my program now:
>
> No, # is the record selection operator from the HList based records.
>
> infixr 9 #
> m # field = m .!. field

Of course, stupid me. Ok, I changed that. Still won't compile. I post only the 
first of four type errors (they are all about 40 lines long; note that the 
inferred type below is almost longer than the complete test program).

TestObject.hs:16:
    No instances for (HFind' b4
                             (Proxy GetX)
                             (HCons (Proxy GetX) (HCons (Proxy MoveD) HNil))
                             n1,
                      HEq (Proxy GetX) (Proxy MutableX) b4,
                      HFind' b3
                             (Proxy MoveD)
                             (HCons (Proxy GetX) (HCons (Proxy MoveD) HNil))
                             n,
                      HEq (Proxy MoveD) (Proxy MutableX) b3,
                      HLookupByHNat n
                                    (HCons (IORef a) (HCons (IO a) (HCons (a 
-> IO ()) HNil)))
                                    (a1 -> IO t),
                      HLookupByHNat n1
                                    (HCons (IORef a) (HCons (IO a) (HCons (a 
-> IO ()) HNil)))
                                    (IO a2),
                      HOr b2 HFalse HFalse,
                      HEq (Proxy GetX) (Proxy MoveD) b2,
                      HOr b b' HFalse,
                      HOr b1 HFalse b',
                      HEq (Proxy MutableX) (Proxy MoveD) b1,
                      HEq (Proxy MutableX) (Proxy GetX) b)
      arising from use of `.*.' at TestObject.hs:16
    In the second argument of `($)', namely
        `(mutableX .=. x)
         .*. ((getX .=. (readIORef x))
              .*. ((moveD .=. (\ d -> modifyIORef x ((+) d))) .*. 
emptyRecord))'
    In the result of a 'do' expression:
        returnIO
        $ ((mutableX .=. x)
           .*. ((getX .=. (readIORef x))
                .*. ((moveD .=. (\ d -> modifyIORef x ((+) d))) .*. 
emptyRecord)))
    In the definition of `point':
        point = do
                  x <- newIORef 0
                  returnIO
                  $ ((mutableX .=. x)
                     .*. ((getX .=. (readIORef x))
                          .*. ((moveD .=. (\ d -> modifyIORef x ((+) d))) .*. 
emptyRecord)))


Ben


More information about the Haskell-Cafe mailing list