#4259: Relax restrictions on type family instance overlap
----------------------------------------+-----------------------------------
    Reporter:  lilac                    |        Owner:              
        Type:  feature request          |       Status:  new         
    Priority:  normal                   |    Milestone:  7.4.1       
   Component:  Compiler (Type checker)  |      Version:  6.12.1      
    Keywords:                           |     Testcase:              
   Blockedby:                           |   Difficulty:              
          Os:  Unknown/Multiple         |     Blocking:              
Architecture:  Unknown/Multiple         |      Failure:  None/Unknown
----------------------------------------+-----------------------------------

Comment(by basvandijk):

 I would like to give another use-case for overlapping type family
 instances:

 As explained in ticket #5595 I'm giving `monad-control`
 [https://github.com/basvandijk/monad-
 control/blob/master/Control/Monad/Trans/Control.hs a new design].

 My [http://hackage.haskell.org/package/regions regions] package uses
 `monad-control` so I'm now adapting that package to the new design.
 However I'm stuck because I can't use an overlapped instance of an
 associated data type. First some background:

 For [https://github.com/basvandijk/regions/wiki/unsafeLiftControlIO
 safety-reasons] I don't want to make `RegionT` an instance of
 `MonadControlIO`. However I do need the ability to lift control operators
 like `bracket` or `alloca` into regions.

 So what I did is, I created a class which is isomorphic to
 `MonadControlIO` called
 [http://hackage.haskell.org/packages/archive/regions/0.11/doc/html
 /Control-Monad-Trans-Region.html#t:RegionControlIO RegionControlIO]. Just
 like `MonadControlIO` has the method `liftControlIO`, this class has the
 method [http://hackage.haskell.org/packages/archive/regions/0.11/doc/html
 /Control-Monad-Trans-Region-Unsafe.html#v:unsafeLiftControlIO
 unsafeLiftControlIO]. This method however is only exported from the
 `Unsafe` module. So users are warned when using it. (I plan to use
 `SafeHaskell` to formalize this)

 I made `RegionT` an instance of `RegionControlIO`:

 {{{
 instance RegionControlIO pr ⇒ RegionControlIO (RegionT s pr) where
     unsafeLiftControlIO f = ...
 }}}

 Besides that I added a catch-all instance:

 {{{
 {-# LANGUAGE OverlappingInstances #-}

 instance MonadControlIO m ⇒ RegionControlIO m where
     unsafeLiftControlIO = liftControlIO
 }}}

 These two instances allows you to lift control operators into a stack of
 regions with an arbitrary stack of monad transformers at its base. For
 example: `RegionT s1 (RegionT s2 (RegionT s3 (StateT Int (WriterT String
 IO))))`

 Now back to the problem. As said, I'm adapting `regions` to use the new
 design of `monad-control`. The `RegionControlIO` type class now looks like
 this:

 {{{
 class MonadIO m ⇒ RegionControlIO m where
     data RegionStIO m ∷ * → *

     unsafeLiftControlIO ∷ (RegionRunInIO m → IO α) → m α

     unsafeRestore ∷ RegionStIO m α → m α

 type RegionRunInIO m = ∀ β. m β → IO (RegionStIO m β)
 }}}

 regions are again made an instance of this type class:

 {{{
 instance RegionControlIO pr ⇒ RegionControlIO (RegionT s pr) where
     newtype RegionStIO (RegionT s pr) α = StIOR (RegionStIO pr ... α))

     unsafeLiftControlIO f = ...

     unsafeRestore (StIOR stIO) = ...
 }}}

 As before, I also want to add a catch-all instance:

 {{{
 instance MonadControlIO m ⇒ RegionControlIO m where
     newtype RegionStIO m α = StIOG (StIO m α)
     unsafeLiftControlIO f = liftControlIO $ \runInIO → f $ liftM StIOG ∘
 runInIO

     unsafeRestore (StIOG st) = restore st
 }}}

 However this is not allowed because type families may not overlap:

 {{{
 Conflicting family instance declarations:
   newtype RegionStIO (RegionT s pr) α
   newtype RegionStIO m α
 }}}

 This is currently blocking me to use the new design of `monad-control` in
 my `regions` library.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4259#comment:11>
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