Skip to content

Commit

Permalink
[feat] allow deriving via Generically
Browse files Browse the repository at this point in the history
  • Loading branch information
MangoIV committed Aug 31, 2023
1 parent f5dd349 commit 7dee7cb
Show file tree
Hide file tree
Showing 2 changed files with 43 additions and 0 deletions.
3 changes: 3 additions & 0 deletions generics-sop/generics-sop.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -70,6 +70,9 @@ library
template-haskell >= 2.8 && < 2.21,
th-abstraction >= 0.4 && < 0.6,
ghc-prim >= 0.3 && < 0.11
if impl(ghc < 9.4.1)
build-depends: generically

hs-source-dirs: src
default-language: Haskell2010
ghc-options: -Wall
Expand Down
40 changes: 40 additions & 0 deletions generics-sop/src/Generics/SOP/Universe.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE UndecidableSuperClasses #-}
{-# LANGUAGE CPP #-}
-- | Codes and interpretations
module Generics.SOP.Universe where

Expand All @@ -8,13 +9,20 @@ import Data.Coerce (Coercible, coerce)
import Data.Proxy
import qualified GHC.Generics as GHC

#if MIN_VERSION_base(4,17,0)
import GHC.Generics (Generically(Generically))
#else
import GHC.Generics.Generically(Generically(Generically))
#endif

import Generics.SOP.BasicFunctors
import Generics.SOP.Constraint
import Generics.SOP.NP
import Generics.SOP.NS
import Generics.SOP.GGP
import Generics.SOP.Metadata
import qualified Generics.SOP.Type.Metadata as T
import Language.Haskell.TH (Extension(DeriveLift))

-- | The (generic) representation of a datatype.
--
Expand Down Expand Up @@ -270,3 +278,35 @@ newtypeFrom = coerce
newtypeTo :: IsNewtype a x => x -> a
newtypeTo = coerce
{-# INLINE newtypeTo #-}

#if MIN_VERSION_GLASGOW_HASKELL(8,6,1,0)
-- | Derive 'Generic' via 'Generically'
--
-- /Example:/
--
-- >>> :set -XDerivingStrategies -XDerivingVia -XDeriveGeneric -XUndecidableInstances
-- >>> data A = B Int | C Bool deriving stock GHC.Generic deriving Generic via Generically A
-- >>> :kind! Code A
-- Code A :: [[*]]
-- = '[ '[Int], '[Bool]]
-- >>> from (B 4)
-- SOP (Z (I 4 :* Nil))
-- >>> from (C False)
-- SOP (S (Z (I False :* Nil)))
--
-- @since 0.5.2.0
#else
-- | Derive 'Generic' via 'Generically'
--
-- @since 0.5.2.0
#endif
instance
(GHC.Generic a
, GFrom a
, GTo a
, Rep a ~ SOP I (GCode a)
, All SListI (Code a)
) => Generic (Generically a) where
type Code (Generically a) = GCode a
from (Generically a) = gfrom a
to rep = Generically (gto rep)

0 comments on commit 7dee7cb

Please sign in to comment.