
Thanks all for your solutions!
Here is a summary:
- floating a value to the top level; then with -Wall GHC will give the type
since we didn't give a value,
- adding :: () to the value to check, GHC will complain equally,
- using TemplateHaskell (hereunder),
- waiting for the release of the next GHC with TypeHoles.
Corentin
On Sat, Apr 27, 2013 at 8:46 PM, Ilya Portnov
**
В письме от 27 апреля 2013 18:55:16 пользователь Corentin Dupont написал:
Hi Cafe, can I ask the compiler to display the type of an inferred value during compile time? It would be great if I can output a string during compilation with the type. A little bit like running :type in GHCi, but without GHCi... Because running GHCi is sometime painful (I have to clean my code first).
I'm thinking of something like:
main :: IO () main = do a <- someCode displayTypeAtCompileTime a return ()
$ ghc -c test.hs test.hs:4:3: your type is: Foo
Thanks, Corentin
Hi.
What about TemplateHaskell? Smth like:
{-# LANGUAGE TemplateHaskell #-}
module DisplayType where
import Language.TH
displayTypeAtCompileTime :: Name -> Q Exp
displayTypeAtComileTime name = do
reified <- reify name
-- inspect reified structure, see TH haddock documentation
runIO $ putStrLn $ show theType
[| undefined |] -- you need to return some expression; since you are not to use it's value, it may be even undefined, it seems.
###
{-# LANGUAGE TemplateHaskell #-}
module Main where
import DisplayType
main = do
...
$displayTypeAtCompileTime 'a
...
WBR, Ilya Portnov.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe