
Hi cafe! I'm a bit confused by the DefaultSignatures extension. It's unclear whether to consider the following an example of clever use of this extension, or an example of abuse of it: {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE DefaultSignatures #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE UndecidableInstances #-} module SubClass where import GHC.Prim(Constraint) data Void (c :: * -> Constraint) = Void data Evidence c a where Evidence :: c a => Evidence c a class c1 :<= c2 where isSubClass :: c1 a => Void c1 -> Evidence c2 a default isSubClass :: c2 a => Void c1 -> Evidence c2 a isSubClass Void = Evidence instance Show :<= Show instance Floating :<= Fractional instance Real :<= Num -- instance Fractional :<= Floating -- NO ROTTEN WAY {- Examples -} data Wrapper c where Wrapper :: c a => a -> Wrapper c instance (c :<= Show) => Show (Wrapper c) where show (Wrapper (a :: t)) = case isSubClass (Void :: Void c) :: Evidence Show t of Evidence -> show a absWrap :: (c :<= Num) => Wrapper c -> Wrapper c absWrap (Wrapper (a :: t) :: Wrapper c) = case isSubClass (Void :: Void c) :: Evidence Num t of Evidence -> Wrapper (abs a) What do you think? Also, it's a bit strange that the first example (instance (c :<= Show) => Show (Wrapper c)) requires UndecidableInstances, while the second one (absWrap) requires FlexibleContexts - although being remarkably similar.
participants (1)
-
Miguel Mitrofanov