{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE PolyKinds #-}
module Ivory.Language.Proxy
(
Proxy(..)
, SProxy
, ANat
, NatType
, aNat
, fromTypeNat
, ASymbol
, SymbolType
, aSymbol
, fromTypeSym
) where
import Data.Proxy (Proxy (..))
import GHC.TypeLits (KnownNat, KnownSymbol, Nat, Symbol, natVal, symbolVal)
type SProxy a = Proxy (a :: *)
type ANat n = KnownNat n
type NatType n = Proxy n
aNat :: KnownNat n => Proxy n
aNat = Proxy
type ASymbol s = (KnownSymbol s)
type SymbolType s = Proxy s
aSymbol :: KnownSymbol s => Proxy s
aSymbol = Proxy
fromTypeSym :: KnownSymbol sym => proxy (sym :: Symbol) -> String
fromTypeSym = symbolVal
fromTypeNat :: KnownNat i => proxy (i :: Nat) -> Integer
fromTypeNat = natVal