#5499: Tagging constructors with record/product phantom type
---------------------------------+------------------------------------------
    Reporter:  basvandijk        |       Owner:                   
        Type:  feature request   |      Status:  new              
    Priority:  normal            |   Component:  libraries (other)
     Version:  7.2.1             |    Keywords:                   
    Testcase:                    |   Blockedby:                   
          Os:  Unknown/Multiple  |    Blocking:                   
Architecture:  Unknown/Multiple  |     Failure:  None/Unknown     
---------------------------------+------------------------------------------

Comment(by dreixel):

 I see the advantage in doing this statically. But I would hope this can
 already be done. And indeed it seems like it can, unfortunately not with
 type families, but with functional dependencies...:
 {{{
 {-# LANGUAGE TypeFamilies #-}
 {-# LANGUAGE TypeOperators #-}
 {-# LANGUAGE DeriveGeneric #-}
 {-# LANGUAGE UndecidableInstances #-}
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE OverlappingInstances #-}
 {-# LANGUAGE MultiParamTypeClasses #-}
 {-# LANGUAGE FunctionalDependencies #-}

 module Test where

 import GHC.Generics

 data Pair a   = Pair a a                  deriving Generic
 data Sum a b  = SL { recm :: a } | SR b   deriving Generic

 data True
 data False

 type family IsRec (f :: * -> *) :: *
 type instance IsRec (M1 D c f) = IsRec f
 -- Simplified: we should instead use a type-level Or
 type instance IsRec (f :+: g) = IsRec f
 type instance IsRec (M1 C c f) = IsRec f
 type instance IsRec (f :*: g) = IsRec f
 type instance IsRec (M1 S NoSelector f) = False
 -- Unfortunately we cannot give the following type instance, as they
 overlap
 --type instance IsRec (M1 S c f) = IsRec f

 -- With fundeps it works, though...
 class IsRecord (f :: * -> *) b | f -> b
 instance (IsRecord f b) => IsRecord (M1 D c f) b
 -- Simplified: we should instead use a type-level Or
 instance (IsRecord f b) => IsRecord (f :+: g) b
 instance (IsRecord f b) => IsRecord (M1 C c f) b
 -- For products we don't need an Or, either branch will do
 instance (IsRecord f b) => IsRecord (f :*: g) b
 instance IsRecord (M1 S NoSelector f) False
 -- We cannot set b directly to True here...
 instance (IsRecord f b) => IsRecord (M1 S c f) b
 -- ... but we can do it in what comes after the M1 S, namely the K1:
 instance IsRecord (K1 i c) True

 -- Testing if a type uses record syntax, statically
 class Test a where test :: a -> Bool

 instance (IsRecord (Rep (Sum x y)) True ) => Test (Sum x y) where
   test _ = True

 instance (IsRecord (Rep (Pair x) ) False) => Test (Pair x)  where
   test _ = False
 }}}

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