Skip to content

Commit

Permalink
Draft: Make reify poly-kinded
Browse files Browse the repository at this point in the history
  • Loading branch information
RyanGlScott committed Mar 15, 2024
1 parent bebd103 commit e02402d
Showing 1 changed file with 10 additions and 3 deletions.
13 changes: 10 additions & 3 deletions fast/Data/Reflection.hs
Expand Up @@ -11,6 +11,9 @@
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeOperators #-}
#if __GLASGOW_HASKELL__ < 806
{-# LANGUAGE TypeInType #-}
#endif
#ifdef MIN_VERSION_template_haskell
-- TH-subset that works with stage1 & unregisterised GHCs
{-# LANGUAGE TemplateHaskellQuotes #-}
Expand Down Expand Up @@ -137,6 +140,10 @@ import System.IO.Unsafe
import Unsafe.Coerce
#endif

#if __GLASGOW_HASKELL__ < 806
import Data.Kind
#endif

#if MIN_VERSION_base(4,18,0)
import qualified GHC.TypeNats as TN
#endif
Expand All @@ -161,11 +168,11 @@ class Reifies s a | s -> a where
-- reified type.
reflect :: proxy s -> a

newtype Magic a r = Magic (forall (s :: *). Reifies s a => Proxy s -> r)
newtype Magic a r k = Magic (forall (s :: k). Reifies s a => Proxy s -> r)

-- | Reify a value at the type level, to be recovered with 'reflect'.
reify :: forall a r. a -> (forall (s :: *). Reifies s a => Proxy s -> r) -> r
reify a k = unsafeCoerce (Magic k :: Magic a r) (const a) Proxy
reify :: forall a r k. a -> (forall (s :: k). Reifies s a => Proxy s -> r) -> r
reify a k = unsafeCoerce (Magic k :: Magic a r k) (const a) Proxy
{-# INLINE_UNSAFE_COERCE reify #-}

instance KnownNat n => Reifies n Integer where
Expand Down

0 comments on commit e02402d

Please sign in to comment.