11{-# LANGUAGE UndecidableInstances #-}
22{-# LANGUAGE UndecidableSuperClasses #-}
3+ {-# LANGUAGE CPP #-}
34-- | Codes and interpretations
45module Generics.SOP.Universe where
56
@@ -8,13 +9,20 @@ import Data.Coerce (Coercible, coerce)
89import Data.Proxy
910import qualified GHC.Generics as GHC
1011
12+ #if MIN_VERSION_base(4,17,0)
13+ import GHC.Generics (Generically (Generically ))
14+ #else
15+ import GHC.Generics.Generically (Generically (Generically ))
16+ #endif
17+
1118import Generics.SOP.BasicFunctors
1219import Generics.SOP.Constraint
1320import Generics.SOP.NP
1421import Generics.SOP.NS
1522import Generics.SOP.GGP
1623import Generics.SOP.Metadata
1724import qualified Generics.SOP.Type.Metadata as T
25+ import Language.Haskell.TH (Extension (DeriveLift ))
1826
1927-- | The (generic) representation of a datatype.
2028--
@@ -270,3 +278,29 @@ newtypeFrom = coerce
270278newtypeTo :: IsNewtype a x => x -> a
271279newtypeTo = coerce
272280{-# INLINE newtypeTo #-}
281+
282+ -- | Derive 'Generic' via 'Generically'
283+ --
284+ #if MIN_VERSION_GLASGOW_HASKELL(8,6,1,0)
285+ -- >>> :set -XDerivingStrategies -XDerivingVia -XDeriveGeneric -XUndecidableInstances
286+ -- >>> data A = B Int | C Bool deriving stock GHC.Generic deriving Generic via Generically A
287+ -- >>> :kind! Code A
288+ -- Code A :: [[*]]
289+ -- = '[ '[Int], '[Bool]]
290+ -- >>> from (B 4)
291+ -- SOP (Z (I 4 :* Nil))
292+ -- >>> from (C False)
293+ -- SOP (S (Z (I False :* Nil)))
294+ #endif
295+ --
296+ -- @since 0.5.2.0
297+ instance
298+ (GHC. Generic a
299+ , GFrom a
300+ , GTo a
301+ , Rep a ~ SOP I (GCode a )
302+ , All SListI (Code a )
303+ ) => Generic (Generically a ) where
304+ type Code (Generically a ) = GCode a
305+ from (Generically a) = gfrom a
306+ to rep = Generically (gto rep)
0 commit comments