{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module TextShow.GHC.Generics () where
import Generics.Deriving.Base
import TextShow.Classes (TextShow(..), TextShow1(..), TextShow2(..))
import TextShow.Data.Char ()
import TextShow.Data.Floating ()
import TextShow.Data.Integral ()
import TextShow.TH.Internal (deriveTextShow, deriveTextShow1, makeShowbPrec,
makeLiftShowbPrec, makeLiftShowbPrec2)
$(deriveTextShow1 ''U1)
instance TextShow (U1 p) where
showbPrec = liftShowbPrec undefined undefined
$(deriveTextShow ''Par1)
$(deriveTextShow1 ''Par1)
instance TextShow (f p) => TextShow (Rec1 f p) where
showbPrec = $(makeShowbPrec ''Rec1)
$(deriveTextShow1 ''Rec1)
instance TextShow c => TextShow (K1 i c p) where
showbPrec = liftShowbPrec undefined undefined
instance TextShow c => TextShow1 (K1 i c) where
liftShowbPrec = liftShowbPrec2 showbPrec showbList
instance TextShow2 (K1 i) where
liftShowbPrec2 = $(makeLiftShowbPrec2 ''K1)
instance TextShow (f p) => TextShow (M1 i c f p) where
showbPrec = $(makeShowbPrec ''M1)
instance TextShow1 f => TextShow1 (M1 i c f) where
liftShowbPrec = $(makeLiftShowbPrec ''M1)
instance (TextShow (f p), TextShow (g p)) => TextShow ((f :+: g) p) where
showbPrec = $(makeShowbPrec ''(:+:))
$(deriveTextShow1 ''(:+:))
instance (TextShow (f p), TextShow (g p)) => TextShow ((f :*: g) p) where
showbPrec = $(makeShowbPrec ''(:*:))
$(deriveTextShow1 ''(:*:))
instance TextShow (f (g p)) => TextShow ((f :.: g) p) where
showbPrec = $(makeShowbPrec ''(:.:))
$(deriveTextShow1 ''(:.:))
instance TextShow (UChar p) where
showbPrec = $(makeShowbPrec 'UChar)
$(deriveTextShow1 'UChar)
instance TextShow (UDouble p) where
showbPrec = $(makeShowbPrec 'UDouble)
$(deriveTextShow1 'UDouble)
instance TextShow (UFloat p) where
showbPrec = $(makeShowbPrec 'UFloat)
$(deriveTextShow1 'UFloat)
instance TextShow (UInt p) where
showbPrec = $(makeShowbPrec 'UInt)
$(deriveTextShow1 'UInt)
instance TextShow (UWord p) where
showbPrec = $(makeShowbPrec 'UWord)
$(deriveTextShow1 'UWord)
$(deriveTextShow ''Associativity)
$(deriveTextShow ''Fixity)
#if MIN_VERSION_base(4,9,0)
$(deriveTextShow ''SourceUnpackedness)
$(deriveTextShow ''SourceStrictness)
$(deriveTextShow ''DecidedStrictness)
#else
$(deriveTextShow ''Arity)
#endif