Skip to content

Instantly share code, notes, and snippets.

@sdiehl
Last active April 14, 2016 16:51
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 1 You must be signed in to fork a gist
  • Save sdiehl/b70d25b920a97f3002e8 to your computer and use it in GitHub Desktop.
Save sdiehl/b70d25b920a97f3002e8 to your computer and use it in GitHub Desktop.
Type Level String Concatenation
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
import TypeLevelString
import GHC.TypeLits
import Language.Haskell.TH
import Language.Haskell.TH.Syntax
type family (++) (as :: [k]) (bs :: [k]) :: [k] where
(++) a '[] = a
(++) '[] b = b
(++) (a ': as) bs = a ': (as ++ bs)
type Foo = [tstr|"Foo"|]
type Bar = [tstr|"Bar"|]
type FooBar = Foo ++ Bar
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE ScopedTypeVariables #-}
module TypeLevelString (
tstr,
) where
import Text.Read
import Data.Char
import Language.Haskell.TH
import Language.Haskell.TH.Quote
stype :: String -> Q Type
stype str = do
case readEither str of
Left err -> fail (show err)
Right n -> do
let chars = fmap (fromIntegral . ord) n
let tcons x y = AppT (AppT PromotedConsT x) y
let tnil = PromotedNilT
return $ foldr tcons tnil (fmap (LitT . NumTyLit) chars)
tstr :: QuasiQuoter
tstr = QuasiQuoter undefined undefined stype undefined
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment