{-# OPTIONS_GHC -Wno-simplifiable-class-constraints #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Generic.Data.Internal.Meta where
import Data.Proxy
import GHC.Generics
import GHC.TypeLits (Symbol, Nat, KnownNat, type (+), natVal, TypeError, ErrorMessage(..))
import Generic.Data.Internal.Functions
gdatatypeName :: forall a. (Generic a, GDatatype (Rep a)) => String
gdatatypeName = gDatatypeName @(Rep a)
gmoduleName :: forall a. (Generic a, GDatatype (Rep a)) => String
gmoduleName = gModuleName @(Rep a)
gpackageName :: forall a. (Generic a, GDatatype (Rep a)) => String
gpackageName = gPackageName @(Rep a)
gisNewtype :: forall a. (Generic a, GDatatype (Rep a)) => Bool
gisNewtype = gIsNewtype @(Rep a)
fromDatatype :: forall d r. Datatype d => (M1 D d Proxy () -> r) -> r
fromDatatype f = f (M1 Proxy :: M1 D d Proxy ())
class GDatatype f where
gDatatypeName :: String
gModuleName :: String
gPackageName :: String
gIsNewtype :: Bool
instance Datatype d => GDatatype (M1 D d f) where
gDatatypeName = fromDatatype @d datatypeName
gModuleName = fromDatatype @d moduleName
gPackageName = fromDatatype @d packageName
gIsNewtype = fromDatatype @d isNewtype
gconName :: forall a. Constructors a => a -> String
gconName = conIdToString . conId
gconFixity :: forall a. Constructors a => a -> Fixity
gconFixity = gConFixity . from
gconIsRecord :: forall a. Constructors a => a -> Bool
gconIsRecord = gConIsRecord . from
gconNum :: forall a. Constructors a => Int
gconNum = gConNum @(Rep a)
gconIndex :: forall a. Constructors a => a -> Int
gconIndex = conIdToInt . conId
newtype ConId a = ConId Int
deriving (Eq, Ord, Show)
conId :: forall a. Constructors a => a -> ConId a
conId = toConId . gConId . from
conIdToInt :: forall a. ConId a -> Int
conIdToInt (ConId i) = i
conIdToString :: forall a. Constructors a => ConId a -> String
conIdToString = gConIdToString . fromConId
conIdEnum :: forall a. Constructors a => [ConId a]
conIdEnum = fmap ConId [0 .. n]
where
ConId n = conIdMax @a
conIdMin :: forall a. Constructors a => ConId a
conIdMin = ConId 0
conIdMax :: forall a. Constructors a => ConId a
conIdMax = toConId gConIdMax
conIdNamed :: forall s a. ConIdNamed s a => ConId a
conIdNamed = ConId (fromInteger (natVal (Proxy @(ConIdNamed' s a))))
class (Generic a, GConstructors (Rep a)) => Constructors a
instance (Generic a, GConstructors (Rep a)) => Constructors a
class (Generic a, KnownNat (ConIdNamed' n a)) => ConIdNamed n a
instance (Generic a, KnownNat (ConIdNamed' n a)) => ConIdNamed n a
newtype GConId r = GConId Int
deriving (Eq, Ord)
gConIdToInt :: GConId r -> Int
gConIdToInt (GConId i) = i
toConId :: forall a. Generic a => GConId (Rep a) -> ConId a
toConId (GConId i) = ConId i
fromConId :: forall a. Generic a => ConId a -> GConId (Rep a)
fromConId (ConId i) = GConId i
reGConId :: GConId r -> GConId s
reGConId (GConId i) = GConId i
gConIdMin :: forall r. GConstructors r => GConId r
gConIdMin = GConId 0
gConIdMax :: forall r. GConstructors r => GConId r
gConIdMax = GConId (gConNum @r - 1)
class GConstructors r where
gConIdToString :: GConId r -> String
gConId :: r p -> GConId r
gConNum :: Int
gConFixity :: r p -> Fixity
gConIsRecord :: r p -> Bool
instance GConstructors f => GConstructors (M1 D c f) where
gConIdToString = gConIdToString @f . reGConId
gConId = reGConId . gConId . unM1
gConNum = gConNum @f
gConFixity = gConFixity . unM1
gConIsRecord = gConIsRecord . unM1
instance (GConstructors f, GConstructors g) => GConstructors (f :+: g) where
gConIdToString (GConId i) =
if i < nf then
gConIdToString @f (GConId i)
else
gConIdToString @g (GConId (i - nf - 1))
where
GConId nf = gConIdMax @f
gConId (L1 x) = reGConId (gConId x)
gConId (R1 y) = let GConId i = gConId y in GConId (nf + 1 + i)
where
GConId nf = gConIdMax @f
gConNum = gConNum @f + gConNum @g
gConFixity (L1 x) = gConFixity x
gConFixity (R1 y) = gConFixity y
gConIsRecord (L1 x) = gConIsRecord x
gConIsRecord (R1 y) = gConIsRecord y
instance Constructor c => GConstructors (M1 C c f) where
gConIdToString _ = conName (M1 Proxy :: M1 C c Proxy ())
gConId _ = GConId 0
gConNum = 1
gConFixity = conFixity
gConIsRecord = conIsRecord
type ConIdNamed' n t = GConIdNamedIf n t (GConIdNamed n (Rep t))
type GConIdNamed n f = GConIdNamed' n f 0 'Nothing
type family GConIdNamed' (n :: Symbol) (f :: k -> *) (i :: Nat) (o :: Maybe Nat) :: Maybe Nat where
GConIdNamed' n (M1 D _c f) i r = GConIdNamed' n f i r
GConIdNamed' n (f :+: g) i r = GConIdNamed' n f i (GConIdNamed' n g (i + NConstructors f) r)
GConIdNamed' n (M1 C ('MetaCons n _f _s) _g) i _r = 'Just i
GConIdNamed' n (M1 C ('MetaCons _n _f _s) _g) _i r = r
GConIdNamed' _n V1 _i r = r
type family GConIdNamedIf (n :: Symbol) (t :: *) (o :: Maybe Nat) :: Nat where
GConIdNamedIf _n _t ('Just i) = i
GConIdNamedIf n t 'Nothing = TypeError
('Text "No constructor named " ':<>: 'ShowType n
':<>: 'Text " in generic type " ':<>: 'ShowType t)
type family MetaOf (f :: * -> *) :: Meta where
MetaOf (M1 i d f) = d
type family MetaDataName (m :: Meta) :: Symbol where
MetaDataName ('MetaData n _m _p _nt) = n
type family MetaDataModule (m :: Meta) :: Symbol where
MetaDataModule ('MetaData _n m _p _nt) = m
type family MetaDataPackage (m :: Meta) :: Symbol where
MetaDataPackage ('MetaData _n _m p _nt) = p
type family MetaDataNewtype (m :: Meta) :: Bool where
MetaDataNewtype ('MetaData _n _m _p nt) = nt
type family MetaConsName (m :: Meta) :: Symbol where
MetaConsName ('MetaCons n _f _s) = n
type family MetaConsFixity (m :: Meta) :: FixityI where
MetaConsFixity ('MetaCons _n f s) = f
type family MetaConsRecord (m :: Meta) :: Bool where
MetaConsRecord ('MetaCons _n _f s) = s
type family MetaSelNameM (m :: Meta) :: Maybe Symbol where
MetaSelNameM ('MetaSel mn _su _ss _ds) = mn
type family MetaSelName (m :: Meta) :: Symbol where
MetaSelName ('MetaSel ('Just n) _su _ss _ds) = n
type family MetaSelUnpack (m :: Meta) :: SourceUnpackedness where
MetaSelUnpack ('MetaSel _mn su _ss _ds) = su
type family MetaSelSourceStrictness (m :: Meta) :: SourceStrictness where
MetaSelSourceStrictness ('MetaSel _mn _su ss _ds) = ss
type family MetaSelStrictness (m :: Meta) :: DecidedStrictness where
MetaSelStrictness ('MetaSel _mn _su _ss ds) = ds
type DummyMeta = 'MetaData "" "" "" 'False
type family UnM1 (f :: k -> *) :: k -> *
type instance UnM1 (M1 i c f) = f