{-# LANGUAGE DataKinds            #-}
{-# LANGUAGE FlexibleContexts     #-}
{-# LANGUAGE FlexibleInstances    #-}
{-# LANGUAGE TypeOperators        #-}
{-# LANGUAGE UndecidableInstances #-}

{-# OPTIONS -Wno-unticked-promoted-constructors #-}

-- | "GHC.Generics" definition of 'mempty'
module Data.DerivingVia.GHC.Generics.Monoid
  ( GMonoid (..)
  )
where

import GHC.Generics
import GHC.TypeLits

class GMonoid rep where
  gmempty :: rep x

instance Monoid c => GMonoid (K1 i c) where
  gmempty :: K1 i c x
gmempty = c -> K1 i c x
forall k i c (p :: k). c -> K1 i c p
K1 c
forall a. Monoid a => a
mempty

instance GMonoid f => GMonoid (M1 i c f) where
  gmempty :: M1 i c f x
gmempty = f x -> M1 i c f x
forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 f x
forall (rep :: * -> *) x. GMonoid rep => rep x
gmempty

instance GMonoid V1 where
  gmempty :: V1 x
gmempty = [Char] -> V1 x
forall a. HasCallStack => [Char] -> a
error [Char]
"GMonoid V1"

instance GMonoid U1 where
  gmempty :: U1 x
gmempty = U1 x
forall k (p :: k). U1 p
U1

instance (GMonoid l, GMonoid r) => GMonoid (l :*: r) where
  gmempty :: (:*:) l r x
gmempty = l x
forall (rep :: * -> *) x. GMonoid rep => rep x
gmempty l x -> r x -> (:*:) l r x
forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
:*: r x
forall (rep :: * -> *) x. GMonoid rep => rep x
gmempty

instance TypeError (     Text "No Generics definition of "
                    :<>: ShowType Monoid
                    :<>: Text " for types with multiple constructors "
                    :<>: ShowType (l :+: r)
                   )
      => GMonoid (l :+: r) where
  gmempty :: (:+:) l r x
gmempty = [Char] -> (:+:) l r x
forall a. HasCallStack => [Char] -> a
error [Char]
"GMonoid :+:"