testing 7.02-candidate

Ian Lynagh igloo at earth.li
Sun Mar 20 18:04:32 CET 2011


Hi Serge,

> [ 3 of 17] Compiling T_cubeext        ( T_cubeext.hs, T_cubeext.o )
> 
> T_cubeext.hs:143:9:
>     Overlapping instances for LinSolvRing (UPol k)
>       arising from a use of `ct'
>     Matching instances:
>       instance [overlap ok] EuclideanRing a => LinSolvRing (UPol a)
>         -- Defined in docon-2.12:Pol2_
>       instance [overlap ok] (LinSolvRing (Pol a), CommutativeRing a) =>
>                             LinSolvRing (UPol (Pol a))
>         -- Defined in docon-2.12:Pol3_
>     (The choice depends on the instantiation of `k'
>      To pick the first instance above, use -XIncoherentInstances
>      when compiling the other instance declarations)
>     In the first argument of `(.)', namely `ct unE'
>     In the expression: ct unE . kToB
>     In an equation for `kToE': kToE = ct unE . kToB

Thanks for the report. I've taken a look, but it'll need someone like
Simon or Dimitrios to give a definitive answer as to which behaviour is
right and which is wrong.

I've put a cut-down (but not standalone) version of the offending module
below. I believe the relevant steps are then:

The ct application means we need an instance for:
      Cast (ResidueI (Pol (ResidueE (UPol k))))
                     (Pol (ResidueE (UPol k)))

Need: Cast (ResidueI (Pol (ResidueE (UPol k))))
                     (Pol (ResidueE (UPol k)))
Have:     instance LinSolvRing a => Cast (ResidueI a) a

Now need: LinSolvRing (Pol (ResidueE (UPol k)))
Have:     instance EuclideanRing a => LinSolvRing (Pol a)

Now need: EuclideanRing (ResidueE (UPol k))
Have:     instance (EuclideanRing a, Ring (ResidueE a) )
                => EuclideanRing (ResidueE a)

Now need: EuclideanRing (UPol k)
Have:     instance Field a => EuclideanRing (UPol a)

Now need: LinSolvRing (UPol k)    (from the EuclideanRing class constraints)
Have:     instance EuclideanRing a => LinSolvRing (UPol a)  (Pol2_.hs:95)
And:      instance (LinSolvRing (Pol a), CommutativeRing a)
                => LinSolvRing (UPol (Pol a))

A different instance should be used depending on whether or not
    k = Pol x
(for some x).


module T_cubeext (cubicExt) where

import Prelude (undefined)
import DPrelude (ct)
import Categs (ResidueE)
import SetGroup ()
import RingModule (Field, FactorizationRing)
import VecMatr  ()
import Fraction ()
import Pol (Pol, UPol)
import Residue (ResidueI)
import GBasis  ()

cubicExt :: forall k . (Field k, FactorizationRing (UPol k))
         => k -> ()
cubicExt _ = undefined
 where unE :: ResidueI (Pol (ResidueE (UPol k)))
       unE  = undefined

       kToE :: Pol (ResidueE (UPol k)) -> ResidueI (Pol (ResidueE (UPol k)))
       kToE = ct unE


Thanks
Ian




More information about the Glasgow-haskell-users mailing list