LoginSignup
2
1

More than 5 years have passed since last update.

準クォートとTemplate Haskell

Posted at

TemplateHaskellとか準クォートに興味があったので触ってみました。
型プログラミングの手助けになるモジュールを作ってみたいな、と思いつつ今回はとりあえず型の表示をさせてみることにします。

TypeChecker.hs
{-# LANGUAGE TemplateHaskell, QuasiQuotes #-}
module TypeChecker where

import Language.Haskell.TH
import Language.Haskell.TH.Quote

import Text.Regex.Posix
import qualified Data.Text as Text

type FunctionList = [Name]

parseFunc :: String -> Maybe FunctionList
parseFunc s = do
  mList <- mayToList s
  return $ map mkName mList

mayToList :: String -> Maybe [String]
mayToList s =
  case s =~ "^\\[(.*)\\]$" :: Bool of
    True -> Just $ (map (Text.unpack . Text.strip) s'')
    False -> Nothing

  where
    s'' :: [Text.Text]
    s'' = Text.splitOn (Text.pack ",") (Text.tail $ Text.init s')

    s' :: Text.Text
    s' = Text.pack s

fList :: QuasiQuoter
fList = QuasiQuoter { quoteExp = parseExp,
                      quotePat = undefined,
                      quoteType = undefined,
                      quoteDec = undefined }

parseExp :: String -> ExpQ
parseExp s =
  case parseFunc s of
    Just fs -> do
      info <- mapM reify fs
      runIO $ putStrLn $ pprint info
      return $ AppE (VarE 'return) (ConE '())
    Nothing -> undefined

ghciで起動させるなら -XTemplateHaskell -XQuasiQuotes のオプションと import Language.Haskell.TH が必要です。
[fList|[a,b,c,d]|]などとすれば、定義済みの函数a,b,c,dの型を表示してくれます。


実行例

~$ ghci -XTemplateHaskell -XQuasiQuotes
GHCi, version 7.4.1: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
Prelude> import Language.Haskell.TH
Prelude Language.Haskell.TH> :l TypeChecker.hs 
[1 of 1] Compiling TypeChecker      ( TypeChecker.hs, interpreted )
Ok, modules loaded: TypeChecker.
*TypeChecker Language.Haskell.TH> [fList|[print, curry, $, mapM]|]
Loading package array-0.4.0.0 ... linking ... done.
Loading package deepseq-1.3.0.0 ... linking ... done.
Loading package bytestring-0.9.2.1 ... linking ... done.
Loading package containers-0.4.2.1 ... linking ... done.
Loading package transformers-0.2.2.0 ... linking ... done.
Loading package mtl-2.0.1.0 ... linking ... done.
Loading package regex-base-0.93.2 ... linking ... done.
Loading package pretty-1.1.1.0 ... linking ... done.
Loading package regex-posix-0.95.1 ... linking ... done.
Loading package text-0.11.1.13 ... linking ... done.
Loading package template-haskell ... linking ... done.
System.IO.print :: forall a_0 . GHC.Show.Show a_0 =>
                                a_0 -> GHC.Types.IO ()
Data.Tuple.curry :: forall a_1 b_2 c_3 . ((a_1, b_2) -> c_3) ->
                                         a_1 -> b_2 -> c_3
GHC.Base.$ :: forall a_4 b_5 . (a_4 -> b_5) -> a_4 -> b_5
infixr 0 GHC.Base.$
Control.Monad.mapM :: forall (m_6 :: * -> *) a_7 b_8 . GHC.Base.Monad m_6 =>
                                                       (a_7 -> m_6 b_8) -> [a_7] -> m_6 ([b_8])

2
1
0

Register as a new user and use Qiita more conveniently

  1. You get articles that match your needs
  2. You can efficiently read back useful information
  3. You can use dark theme
What you can do with signing up
2
1