{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeOperators #-}
module Data.Functor.ProductIsomorphic.GenericInstances () where
import GHC.Generics
(U1 (U1), K1 (K1), M1 (M1), (:*:) ((:*:)), )
import Data.Functor.ProductIsomorphic.Unsafe (ProductConstructor (..))
instance ProductConstructor (U1 p) where
productConstructor :: U1 p
productConstructor = forall k (p :: k). U1 p
U1
{-# INLINEABLE productConstructor #-}
instance ProductConstructor (c -> K1 i c p) where
productConstructor :: c -> K1 i c p
productConstructor = forall k i c (p :: k). c -> K1 i c p
K1
{-# INLINEABLE productConstructor #-}
instance ProductConstructor (f p -> M1 i c f p) where
productConstructor :: f p -> M1 i c f p
productConstructor = forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1
{-# INLINEABLE productConstructor #-}
instance ProductConstructor (f x -> g x -> (f :*: g) x) where
productConstructor :: f x -> g x -> (:*:) f g x
productConstructor = forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
(:*:)
{-# INLINEABLE productConstructor #-}