{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE TemplateHaskellQuotes #-}
{-# LANGUAGE Safe #-}
{-# OPTIONS_HADDOCK show-extensions #-}
module Clash.Promoted.Symbol
(SSymbol (..), ssymbolProxy, ssymbolToString)
where
import Language.Haskell.TH.Syntax
import GHC.TypeLits (KnownSymbol, Symbol, symbolVal)
data SSymbol (s :: Symbol) where
SSymbol :: KnownSymbol s => SSymbol s
instance KnownSymbol s => Lift (SSymbol (s :: Symbol)) where
lift :: SSymbol s -> Q Exp
lift t :: SSymbol s
t = Exp -> Q Exp
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Exp -> Type -> Exp
AppTypeE (Name -> Exp
ConE 'SSymbol) Type
tt)
where
tt :: Type
tt = TyLit -> Type
LitT (String -> TyLit
StrTyLit (SSymbol s -> String
forall (s :: Symbol). SSymbol s -> String
ssymbolToString SSymbol s
t))
instance Show (SSymbol s) where
show :: SSymbol s -> String
show s :: SSymbol s
s@SSymbol s
SSymbol = SSymbol s -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal SSymbol s
s
{-# INLINE ssymbolProxy #-}
ssymbolProxy :: KnownSymbol s => proxy s -> SSymbol s
ssymbolProxy :: proxy s -> SSymbol s
ssymbolProxy _ = SSymbol s
forall (s :: Symbol). KnownSymbol s => SSymbol s
SSymbol
{-# INLINE ssymbolToString #-}
ssymbolToString :: SSymbol s -> String
ssymbolToString :: SSymbol s -> String
ssymbolToString s :: SSymbol s
s@SSymbol s
SSymbol = SSymbol s -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal SSymbol s
s