#2695: bogus "syntactically distinct contexts" error
---------------------------------+------------------------------------------
    Reporter:  conal             |       Owner:                  
        Type:  bug               |      Status:  new             
    Priority:  normal            |   Component:  Compiler        
     Version:  6.11              |    Severity:  normal          
    Keywords:                    |    Testcase:                  
Architecture:  Unknown/Multiple  |          Os:  Unknown/Multiple
---------------------------------+------------------------------------------
 {{{
 {-# LANGUAGE TypeOperators, FlexibleContexts
   , MultiParamTypeClasses, FunctionalDependencies
   , TypeFamilies
   -- , ScopedTypeVariables
   #-}

 -- The ScopedTypeVariables is there just as a bug work-around.  Without:
 --
 --     Mutually dependent functions have syntactically distinct contexts
 --     When matching the contexts of the signatures for
 --       dZero :: forall b a s.
 --                (AdditiveGroup b, HasBasis a s, HasTrie (Basis a)) =>
 --                a :> b
 --       pureD :: forall b a s.
 --                (AdditiveGroup b, HasBasis a s, HasTrie (Basis a)) =>
 --                b -> a :> b
 --     The signature contexts in a mutually recursive group should all be
 identical
 --     When generalising the type(s) for dZero, pureD
 --
 -- This bug was introduced between ghc 6.9.20080622 and 6.10.0.20081007.

 {-# OPTIONS_GHC -fno-warn-missing-methods #-}


 import Control.Applicative

 class AdditiveGroup v where
   zeroV   :: v
   (^+^)   :: v -> v -> v
   negateV :: v -> v

 class AdditiveGroup v => VectorSpace v s | v -> s where
   (*^)  :: s -> v -> v


 -- | Mapping from all elements of @a@ to the results of some function
 class HasTrie a where
     data (:->:) a :: * -> *

 instance HasTrie a => Functor ((:->:) a)

 instance HasTrie a => Applicative ((:->:) a)

 class VectorSpace v s => HasBasis v s where
   type Basis v :: *

 -- | Linear map, represented a as a memo function from basis to values.
 type u :-* v = Basis u :->: v

 data a :> b = D { powVal :: b, derivative :: a :-* (a :> b) }

 dZero :: (AdditiveGroup b, HasBasis a s, HasTrie (Basis a)) => a:>b
 dZero = pureD zeroV

 pureD :: (AdditiveGroup b, HasBasis a s, HasTrie (Basis a)) => b -> a:>b
 pureD b = b `D` pure dZero

 }}}

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/2695>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to