Overloading Lists

Achim Krause info at achim-krause.de
Tue Sep 25 16:56:07 CEST 2012


As was mentioned in Haskell Cafe some days ago, there is some work going 
on on overloading lists by George Giorgidze, Jeroen Weijers and me.
We are implementing two approaches in fact. The first one is using a 
typeclass called FromList, defined as
class FromList l where
  type (Elem l)
  fromList :: [Elem l] -> l

And explicit lists and arithmetic sequences get just desugared in the 
obvious way using this, so, for example, [1,2,3] gets desugared to 
(fromList [1,2,3]).
The disadvantages of this (although being very easy to implement and 
use) is that this goes through recursive lists each time it gets used. 
Since explicit lists need not to be static (i.e. can contain variables), 
this can really matter.
The second approach thus is the following (kinda motivated from the way 
parallel arrays are desugared): There is a class
class Singleton l where
  type (Elem l)
  singleton :: Elem l -> l
and now explicit lists like [1,2,3] get desugared to (singleton 1) 
`mappend` (singleton 2) `mappend` (singleton 3).
Arithmetic sequences are simply done by providing a class "GenericEnum" 
containing slightly more general versions of the classical from, 
fromThen, fromTo, fromThenTo, and the desugaring then really is exactly 
the same as in the non-overloaded case.

I wrote a patch for the GHC which is supposed to do this stuff. It 
compiles, and the typechecking and desugaring of arithmetic sequences 
works just fine.
However, the explicit lists give me a runtime error, when used on a 
simple test file containing explicit list notation:

     Can't find interface-file declaration for variable 
base:Data.Monoid.mempty
       Probable cause: bug in .hi-boot file, or inconsistent .hi file
       Use -ddump-if-trace to get an idea of which file caused the error
     In the expression: []
     In an equation for `testlist': testlist = []

At first I thought that I forgot something about adding a new module to 
the PrelNames module, so I did the following: I created a class Monoid2 
(with functions mempty2 and mappend2) in the module GHC.Exts, because I 
know this module to work with wired-ins (For example, the fromList from 
the previous approach, the genericEnum and the singleton were also put 
there). The new error message became:

     Can't find interface-file declaration for variable 
base:GHC.Exts.mempty2
       Probable cause: bug in .hi-boot file, or inconsistent .hi file
       Use -ddump-if-trace to get an idea of which file caused the error
     In the expression: []
     In an equation for `testlist': testlist = []

I double-checked the stuff I did in PrelNames.hs. Since I was running 
short of Uniques (the code says that Template Hakell uses IdUniques 
200-499), I started to use IdUniques from 500 on, but not for memptyName 
and mappendName, so I'm pretty sure that PrelNames should work the way I 
did it.

A quick search for "Can't find interface-file" shows that the error 
originates from TcInterface. I assume now, that the error comes from how 
I typecheck ExplicitLists:

tcExpr (ExplicitList _ witness exprs) res_ty
   = case witness of
   Nothing -> do { (coi, elt_ty) <- matchExpectedListTy res_ty
                 ; exprs' <- mapM (tc_elt elt_ty) exprs
                 ; return $ mkHsWrapCo coi (ExplicitList elt_ty Nothing 
exprs') }
                   where
                   tc_elt elt_ty expr = tcPolyExpr expr elt_ty
   Just (singleton, mempty, mappend) -> do { elt_ty <- newFlexiTyVarTy 
liftedTypeKind
                                     ; mempty' <- tcSyntaxOp 
OverloadedListOrigin mempty res_ty
                                     ; mappend' <- tcSyntaxOp 
OverloadedListOrigin mappend (mkFunTys [res_ty, res_ty] res_ty)
                                     ; singleton' <- tcSyntaxOp 
OverloadedListOrigin singleton (mkFunTy elt_ty res_ty)
                                     ; exprs' <- mapM (tc_elt elt_ty) exprs
                                     ; return $ ExplicitList elt_ty 
(Just (singleton',mempty',mappend')) exprs'}
                                        where
                                           tc_elt elt_ty expr = 
tcPolyExpr expr elt_ty

A few remarks about that: I changed the ExplicitList constructor by 
adding a witness field of the type Maybe (SyntaxExpr, SyntaxExpr, 
SyntaxExpr). The renamer leaves this at Nothing, if the overloaded lists 
extension is turned off, otherwise it changes it to Just (singleton, 
mempty, mappend) where these are variables containing the respective names.
The Nothing case in the above code is just whats done for regular lists 
in the original code. The Just case is supposed to do the following:
If an overloaded list has type a, then the respective mempty should also 
have type a, and the respective mappend should have type a -> a -> a. If 
there are no instances with these types, then we should get an error, 
because overloaded lists should always be monoids, according to our 
desugaring rules.
There should now be some element type, appearing in the type signature 
of singleton. Therefore we introduce a type variable elt_ty and match 
singleton against the function elt_ty -> res_ty, this should give the 
instance we need and infer the element type. Then we match all elements 
of the list against this type just as is done in the original code.

My observations: If I interchange the mempty line with the mappend line, 
we get a similar error, but about mappend. If I comment both of these 
lines out, the error vanishes. (The last point is not that easy to 
check, because we need to return something, but if you replace the Just 
in the return thing by Nothing, everything works.)
So the error has to do something with these two lines (which is not that 
surprising, because this is the only point where mempty should become 
instantiated). I also tried to interchange these lines, this did not do 
anything (except when the mappend line comes before the mempty line the 
error talks about mappend2 instead of mempty2).
I do not have any ideas what to try and what could be wrong. I DID a 
complete clean build, so it's really about the code.
The code as it is now is on github, my account is "achimkrause". If 
anyone wants to test it, please do not forget to patch the base and the 
dph repository also: base contains my changes to GHC.Exts, and in dph I 
had to make some imports of GHC.Exts qualified, because there are also 
singleton functions.
Please feel free to ask questions.
I would be very happy if you could help us figure this out, we are 
fairly sure that this is some kind of common error.
Cheers, Achim











More information about the Glasgow-haskell-users mailing list