{-# LANGUAGE PatternGuards #-}
module Lambdabot.Plugin.Haskell.Type (typePlugin, query_ghci) where
import Lambdabot.Config.Haskell
import Lambdabot.Plugin
import Lambdabot.Util
import Lambdabot.Plugin.Haskell.Eval (findL_hs)
import Codec.Binary.UTF8.String
import Data.Char
import Data.Maybe
import System.Process
import Text.Regex.TDFA
typePlugin :: Module ()
typePlugin = newModule
{ moduleCmds = return
[ (command "type")
{ help = say "type <expr>. Return the type of a value"
, process = runit ":t"
}
, (command "kind")
{ help = say "kind <type>. Return the kind of a type"
, process = runit ":k"
}
]
, contextual = \text ->
let (prefix, expr) = splitAt 3 text
in case prefix of
":t " -> runit ":t" expr
":k " -> runit ":k" expr
_ -> return ()
}
runit :: MonadLB m =>
String -> String -> Cmd m ()
runit s expr = query_ghci s expr >>= say
theCommand :: [Char] -> [Char] -> [Char]
theCommand cmd foo = cmd ++ " " ++ foo
signature_regex :: Regex
signature_regex = makeRegex
"^(\\*?[A-Z][_a-zA-Z0-9]*(\\*?[A-Z][_a-zA-Z0-9]*)*>)? *(.*[ -=:].*)"
stripComments :: String -> String
stripComments [] = []
stripComments ('\n':_) = []
stripComments ('-':'-':_) = []
stripComments ('{':'-':cs)= stripComments (go 1 cs)
stripComments (c:cs) = c : stripComments cs
go :: Int -> String -> String
go 0 xs = xs
go _ ('-':[]) = []
go n ('-':x:xs)
| x == '}' = go (n-1) xs
| otherwise = go n (x:xs)
go _ ('{':[]) = []
go n ('{':x:xs)
| x == '-' = go (n+1) xs
| otherwise = go n (x:xs)
go n (_:xs) = go n xs
go _ _ = []
extract_signatures :: String -> Maybe String
extract_signatures output
= fmap reverse . removeExp . reverse .
(' ':) .
unwords . map (dropWhile isSpace . expandTab 8) .
mapMaybe ((>>= last') . fmap mrSubList . matchM signature_regex) .
lines $ output
where
last' [] = Nothing
last' xs = Just $ last xs
removeExp :: String -> Maybe String
removeExp [] = Nothing
removeExp xs = removeExp' 0 xs
removeExp' :: Int -> String -> Maybe String
removeExp' 0 (' ':':':':':' ':_) = Just []
removeExp' n ('(':xs) = ('(':) `fmap` removeExp' (n+1) xs
removeExp' n (')':xs) = (')':) `fmap` removeExp' (n-1) xs
removeExp' n (x :xs) = (x :) `fmap` removeExp' n xs
removeExp' _ [] = Nothing
query_ghci :: MonadLB m => String -> String -> m String
query_ghci cmd expr = do
l <- findL_hs
exts <- getConfig languageExts
let context = ":load "++l++"\n:m *L\n"
extFlags = ["-X" ++ ext | ext <- exts]
ghci <- getConfig ghciBinary
(_, output, errors) <- io $ readProcessWithExitCode ghci
("-v0":"-fforce-recomp":"-iState":"-ignore-dot-ghci":extFlags)
(context ++ theCommand cmd (stripComments (decodeString expr)))
let ls = extract_signatures output
return $ case ls of
Nothing -> encodeString . unlines . take 3 . filter (not . null) . map cleanRE2 .
lines . expandTab 8 . cleanRE . filter (/='\r') $ errors
Just t -> t
where
cleanRE, cleanRE2 :: String -> String
cleanRE s
| s =~ notfound = "Couldn\'t find qualified module."
| Just m <- s =~~ ghci_msg = mrAfter m
| otherwise = s
cleanRE2 s
| Just m <- s =~~ ghci_msg = mrAfter m
| otherwise = s
ghci_msg = "<interactive>:[^:]*:[^:]*: ?"
notfound = "Failed to load interface"