module Lambdabot.Plugin.Haskell.Instances (instancesPlugin) where
import Text.ParserCombinators.Parsec
import Lambdabot.Config.Haskell
import Lambdabot.Plugin
import Lambdabot.Util
import Lambdabot.Plugin.Haskell.Eval (findL_hs)
import Control.Applicative ((*>))
import Control.Monad
import Data.Char
import Data.List
import Data.List.Split
import Data.Maybe
import System.FilePath
import System.Process
import Text.Regex.TDFA
type Instance = String
type ClassName = String
type ModuleName = String
instancesPlugin :: Module ()
instancesPlugin = newModule
{ moduleCmds = return
[ (command "instances")
{ help = say "instances <typeclass>. Fetch the instances of a typeclass."
, process = fetchInstances >=> say
}
, (command "instances-importing")
{ help = say $
"instances-importing [<module> [<module> [<module...]]] <typeclass>. " ++
"Fetch the instances of a typeclass, importing specified modules first."
, process = fetchInstancesImporting >=> say
}
]
}
eitherToMaybe :: Either a b -> Maybe b
eitherToMaybe = either (const Nothing) Just
instanceP :: ClassName -> CharParser st Instance
instanceP cls
= string "instance " *> (try constrained <|> unconstrained) *> skipMany space
*> anyChar `manyTill` end
where constrained = noneOf "=" `manyTill` string ("=> " ++ cls)
unconstrained = string cls
end = void (try (string "--")) <|> eof
parseInstance :: ClassName -> String -> Maybe Instance
parseInstance cls = fmap (strip isSpace) . eitherToMaybe
. parse (instanceP cls) "GHCi output"
getInstances :: String -> ClassName -> [Instance]
getInstances s cls
| not classFound
= ["Couldn't find class `"++cls++"'. Try @instances-importing"]
| otherwise = sort $ mapMaybe doParse (tail splut)
where classFound = s =~ ("class.*" ++ cls ++ ".*where")
splut = splitOn "instance" s
notOperator = all (\c -> or
[ isAlpha c,
isSpace c,
c `elem` "()" ])
unbracket str | head str == '(' && last str == ')' &&
all (/=',') str && notOperator str && str /= "()" =
init $ tail str
| otherwise = str
doParse = fmap unbracket . parseInstance cls . ("instance"++)
stdMdls :: [ModuleName]
stdMdls = controls
where monads = map ("Monad."++)
[ "Cont", "Error", "Fix", "Reader", "RWS", "ST",
"State", "Trans", "Writer" ]
controls = map ("Control." ++) $ monads ++ ["Arrow"]
fetchInstances :: MonadLB m => ClassName -> m String
fetchInstances cls = fetchInstances' cls stdMdls
fetchInstancesImporting :: MonadLB m => String -> m String
fetchInstancesImporting args = fetchInstances' cls mdls
where args' = words args
cls = last args'
mdls = nub $ init args' ++ stdMdls
fetchInstances' :: MonadLB m => String -> [ModuleName] -> m String
fetchInstances' cls mdls = do
load <- findL_hs
let s = unlines $ map unwords
[ [":l", load]
, ":m" : "+" : mdls
, [":i", cls]
]
ghci <- getConfig ghciBinary
(_, out, err) <- io $ readProcessWithExitCode ghci ["-ignore-dot-ghci","-fglasgow-exts"] s
let is = getInstances out cls
return $ if null is
then err
else intercalate ", " is