While I can use reify
to get information about most other syntactic constructs, I couldn't find anything that would give some information about a module.
Asked
Active
Viewed 384 times
7

Petr
- 62,528
- 13
- 153
- 317
-
1TH can give you information about entire modules if the entire module, except for imports/exports, is in a TH splice. If this is not the case, you can use `haskell-src-meta` to parse entire Haskell files. Disclaimer: it doesn't support most extensions. You can also use `Language.Haskell.TH.Quote.quoteFile` but this again requires that the file not contain import or export statements (which would mean it probably isn't valid Haskell code). – user2407038 Dec 16 '13 at 09:17
-
2Take a look at the `haskell-names` package. – Sjoerd Visscher Dec 16 '13 at 11:38
1 Answers
4
Unfortunately Template Haskell currently has no such capabilities. All the solutions involve parsing of the module's source-code. However the location
and loc_filename
functions of TH make it easy to locate the module with the calling splice.
Here is a solution extracted from the source code of one of my projects:
{-# LANGUAGE LambdaCase, TupleSections #-}
import Language.Haskell.TH
import qualified Data.Attoparsec.Text as AP
import qualified Data.Text.IO as Text
import qualified Data.Text as Text
import qualified Data.Char as Char
import Data.Maybe
import Data.List
import Control.Applicative
import Data.Traversable
import Prelude hiding (mapM)
reifyLocalFunctions :: Q [(Name, Type)]
reifyLocalFunctions =
listTopLevelFunctionLikeNames >>=
mapM (\name -> reifyFunction name >>= mapM (return . (name, ))) >>=
return . catMaybes
where
listTopLevelFunctionLikeNames = do
loc <- location
text <- runIO $ Text.readFile $ loc_filename loc
return $ map (mkName . Text.unpack) $ nub $ parse text
where
parse text =
either (error . ("Local function name parsing failure: " ++)) id $
AP.parseOnly parser text
where
parser =
AP.sepBy (optional topLevelFunctionP <* AP.skipWhile (not . AP.isEndOfLine))
AP.endOfLine >>=
return . catMaybes
where
topLevelFunctionP = do
head <- AP.satisfy Char.isLower
tail <- many (AP.satisfy (\c -> Char.isAlphaNum c || c `elem` ['_', '\'']))
return $ Text.pack $ head : tail
reifyFunction :: Name -> Q (Maybe Type)
reifyFunction name = do
tryToReify name >>= \case
Just (VarI _ t _ _) -> return $ Just $ t
_ -> return Nothing
tryToReify :: Name -> Q (Maybe Info)
tryToReify n = recover (return Nothing) (fmap Just $ reify n)

Nikita Volkov
- 42,792
- 11
- 94
- 169