{-# LANGUAGE CPP #-}
#ifdef SAFE
{-# LANGUAGE BangPatterns #-}
#elif __GLASGOW_HASKELL__ >= 704
{-# LANGUAGE Trustworthy #-}
#endif
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE FlexibleContexts #-}
#if __GLASGOW_HASKELL__ >= 706
{-# LANGUAGE PolyKinds #-}
#endif
module Data.Functor.Contravariant.Generic
( Deciding(..)
, Deciding1(..)
) where
import Data.Functor.Contravariant
import Data.Functor.Contravariant.Divisible
import GHC.Generics
#ifndef SAFE
import Unsafe.Coerce
#endif
class (Generic a, GDeciding q (Rep a)) => Deciding q a where
#ifndef HLINT
deciding :: Decidable f => p q -> (forall b. q b => f b) -> f a
#endif
instance (Generic a, GDeciding q (Rep a)) => Deciding q a where
deciding p q = contramap from $ gdeciding p q
class (Generic1 t, GDeciding1 q (Rep1 t)) => Deciding1 q t where
#ifndef HLINT
deciding1 :: Decidable f => p q -> (forall b. q b => f b) -> f a -> f (t a)
#endif
instance (Generic1 t, GDeciding1 q (Rep1 t)) => Deciding1 q t where
deciding1 p q r = contramap from1 $ gdeciding1 p q r
class GDeciding q t where
#ifndef HLINT
gdeciding :: Decidable f => p q -> (forall b. q b => f b) -> f (t a)
#endif
instance GDeciding q U1 where
gdeciding _ _ = conquer
instance GDeciding q V1 where
gdeciding _ _ = glose
instance (GDeciding q f, GDeciding q g) => GDeciding q (f :*: g) where
gdeciding p q = gdivide (gdeciding p q) (gdeciding p q)
instance (GDeciding q f, GDeciding q g) => GDeciding q (f :+: g) where
gdeciding p q = gchoose (gdeciding p q) (gdeciding p q)
#ifndef HLINT
instance q p => GDeciding q (K1 i p) where
#endif
gdeciding _ q = contramap unK1 q
instance GDeciding q f => GDeciding q (M1 i c f) where
gdeciding p q = contramap unM1 (gdeciding p q)
class GDeciding1 q t where
#ifndef HLINT
gdeciding1 :: Decidable f => p q -> (forall b. q b => f b) -> f a -> f (t a)
#endif
instance GDeciding1 q U1 where
gdeciding1 _ _ _ = conquer
instance GDeciding1 q V1 where
gdeciding1 _ _ _ = glose
instance (GDeciding1 q f, GDeciding1 q g) => GDeciding1 q (f :*: g) where
gdeciding1 p q r = gdivide (gdeciding1 p q r) (gdeciding1 p q r)
instance (GDeciding1 q f, GDeciding1 q g) => GDeciding1 q (f :+: g) where
gdeciding1 p q r = gchoose (gdeciding1 p q r) (gdeciding1 p q r)
glose :: Decidable f => f (V1 a)
#ifdef SAFE
glose = lose (\ !_ -> error "impossible")
#else
glose = lose unsafeCoerce
#endif
{-# INLINE glose #-}
gdivide :: Divisible f => f (g a) -> f (h a) -> f ((g:*:h) a)
#ifdef SAFE
gdivide = divide (\(f:*:g) -> (f,g))
#else
gdivide = divide unsafeCoerce
#endif
{-# INLINE gdivide #-}
gchoose :: Decidable f => f (g a) -> f (h a) -> f ((g:+:h) a)
#ifdef SAFE
gchoose = choose (\xs -> case xs of L1 a -> Left a; R1 b -> Right b)
#else
gchoose = choose unsafeCoerce
#endif
{-# INLINE gchoose #-}
#ifndef HLINT
instance q p => GDeciding1 q (K1 i p) where
gdeciding1 _ q _ = contramap unK1 q
#endif
instance GDeciding1 q f => GDeciding1 q (M1 i c f) where
gdeciding1 p q r = contramap unM1 (gdeciding1 p q r)
instance GDeciding1 q Par1 where
gdeciding1 _ _ r = contramap unPar1 r
instance Deciding1 q f => GDeciding1 q (Rec1 f) where
gdeciding1 p q r = contramap unRec1 (deciding1 p q r)