LoginSignup
8
8

More than 5 years have passed since last update.

型を表示する関数

Last updated at Posted at 2016-05-11

型を表示して何か嬉しいんだろうかと思ったけど、意外と面白かったので載せておきます。

一般的な型に対してログへの出力なんてことは出来ないので型クラスを作りました。
あとは出力出来る型を増やしたかったらTemplateHaskellとか使って頑張ってください。

Typeable使ったらできました。後述。

#!/usr/bin/env stack
-- stack --resolver lts-5.8 runghc

{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE PolyKinds #-}

import Data.Proxy
import System.IO

class ShowType (t :: k) where
    showType :: Proxy t -> String

instance ShowType () where
    showType _ = "()"
instance ShowType Int where
    showType _ = "Int"
instance ShowType Double where
    showType _ = "Double"
instance ShowType String where
    showType _ = "String"
instance ShowType Bool where
    showType _ = "Bool"
instance ShowType IO where
    showType _ = "IO"
instance ShowType Maybe where
    showType _ = "Maybe"
instance ShowType [] where
    showType _ = "[]"
instance ShowType (->) where
    showType _ = "(->)"


instance {-# OVERLAPPABLE #-} (ShowType a, ShowType b) => ShowType (a, b) where
    showType _ = "(" ++ showType (Proxy :: Proxy a) ++ ", " ++ showType (Proxy :: Proxy b) ++ ")"
instance {-# OVERLAPPABLE #-} ShowType a => ShowType [a] where
    showType _ = "[" ++ showType (Proxy :: Proxy a) ++ "]"
instance {-# OVERLAPPABLE #-} (ShowType b, ShowType c) => ShowType (b -> c) where
    showType _ = showType (Proxy :: Proxy b) ++ " -> " ++ showType (Proxy :: Proxy c)
instance {-# OVERLAPPABLE #-} (ShowType b, ShowType c, ShowType d) => ShowType ((b -> c) -> d) where
    showType _ = "(" ++ showType (Proxy :: Proxy b) ++ " -> " ++ showType (Proxy :: Proxy c) ++ ") -> " ++ showType (Proxy :: Proxy d)

instance {-# OVERLAPPABLE #-} (ShowType f, ShowType t) => ShowType (f t) where
    showType _ = showType (Proxy :: Proxy f) ++ " " ++ showType (Proxy :: Proxy t)
instance {-# OVERLAPPABLE #-} (ShowType a, ShowType b, ShowType c) => ShowType (a b c) where
    showType _ = showType (Proxy :: Proxy a)
        ++ " " ++ showType (Proxy :: Proxy b)
        ++ " " ++ showType (Proxy :: Proxy c)

logType :: forall t. ShowType t => t -> IO ()
logType _ = hPutStrLn stderr $ showType (Proxy :: Proxy t)

main = do
    logType (1 :: Int)
    logType (3.4 :: Double)
    logType getLine
    logType putStrLn
    logType (Just "Heyhey")
    logType (even :: Int -> Bool)
    logType ((+) :: Int -> Int -> Int)
    logType [True, False]
    logType (map :: (Int -> String) -> [Int] -> [String])
    logType (undefined :: [Int -> IO String] -> [Int] -> IO [String])
    logType (undefined :: ([(Int -> Int) -> IO String] -> [Int] -> IO [String]) -> Maybe Bool)
    logType (True, "hey")

関数渡すとその型が表示されるとか面白いですね。
型パラメータが残っているようなものは表示できません。

Typeableを使う

showsTypeRepという便利なものがあるそうです(一応探したつもりだった)

8
8
1

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
8
8