Skip to content

Instantly share code, notes, and snippets.

@adamgundry
Created March 4, 2020 22:13
Show Gist options
  • Star 4 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save adamgundry/37e29ca9c8a30e3d94f61b0ee11d67a8 to your computer and use it in GitHub Desktop.
Save adamgundry/37e29ca9c8a30e3d94f61b0ee11d67a8 to your computer and use it in GitHub Desktop.
Being a horrible abuse of INCOHERENT to determine whether Generic instances exist
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# OPTIONS_GHC -Wall #-}
module GenericDiscrimination where
import Data.Kind (Type)
import GHC.Generics
-- | Constraint representing the ability to decide at runtime whether @r@ is an
-- application of 'Rep' to a type with a defined 'Generic' representation.
class IsDefinedRep (r :: Type -> Type) where
isDefinedRep :: Bool
instance IsDefinedRep (f x) where
isDefinedRep = True
instance {-# INCOHERENT #-} IsDefinedRep r where
isDefinedRep = False
-- | Constraint representing the ability to decide at runtime whether @t@ was
-- declared with a 'Generic' instance.
type HasGeneric t = IsDefinedRep (Rep t)
-- | Returns a boolean indicating whether the type to which it is applied has a
-- 'Generic' instance.
hasGeneric :: forall t . HasGeneric t => Bool
hasGeneric = isDefinedRep @(Rep t)
{-
GenericDiscrimination.hs:36:15: warning: [-Wsimplifiable-class-constraints]
• The constraint ‘IsDefinedRep (Rep t)’ matches
instance forall (r :: * -> *). IsDefinedRep r
-- Defined at GenericDiscrimination.hs:27:29
This makes type inference for inner bindings fragile;
either use MonoLocalBinds, or simplify it using the instance
• In the type signature:
hasGeneric :: forall t. HasGeneric t => Bool
-}
data A = MkA
deriving Generic
data A' = MkA'
ok :: Bool
ok = hasGeneric @A
&& not (hasGeneric @A')
&& hasGeneric @Bool
&& hasGeneric @()
&& not (hasGeneric @Int)
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment