hrefなるもの

hrefなるものがあるとか。知らんかった。やっぱすげーなー青木さんは。gorouさんのzshのハックもナイスだ。インスパイアされましたよ、僕は。

  • HaskellHaskellの関数の定義を検索します。
  • findしてgrepするだけなんだけどね、本当は。
  • ならHaskellじゃなくても...。
  • 引数を解析する処理が未実装です。今のところはlibDirとfuncNameをハードコードしてます。
  • 今日は疲れたからそのうちヤル。

(追記)
ヤッタ。
(さらに追記)
ちょっとリファクタ。少しはキレイになった。でも致命的な欠陥があるなぁ...。まあfindしてgrepだからねぇ...。

module Main where

import Directory
import Monad
import Text.Regex

import System
import System.IO
import System.Console.GetOpt

data Flag = Lib String

options :: [OptDescr Flag]
options = [
    Option ['l'] ["lib"] (ReqArg (\x -> Lib x) "Lib") "specify libraries dir"
  ]

analyze :: [String] -> IO ([Flag], [String])
analyze argv =
  case getOpt Permute options argv of
    (o, n, [])   -> return (o, n)
    (_, _, errs) -> ioError $ userError $ concat errs

dispatch :: ([Flag], [String]) -> IO (String, String)
dispatch (os, ns)
  | ns == []  = ioError $ userError $ "Must specify function name"
  | otherwise = case os of
      Lib l:_ -> return (l, ns!!0)
      _       -> ioError $ userError $ "Unknown Option"

main = do
  (libDir, funcName) <- dispatch =<< analyze =<< getArgs
  files <- searchHs libDir
  ret <- mapM (Main.matchRegex $ Main.mkRegex funcName) files
  mapM_ putStrLn $ filter ((/=) []) ret

searchHs path = do
  contents <- getDirectoryContents path
  let hs = find (isHs) contents
      others = find (not . isHs) (filter notParentAndCurrent contents)
    in do dirs <- filterM (doesDirectoryExist) others
          if dirs == []
            then return hs
            else liftM ((++ hs) . concat) (mapM searchHs dirs)
  where
    isHs = \x -> reverse (take 3 (reverse x)) == ".hs"
    add = (++) . flip (++) "/"
    find f = map (add path) . filter f
    notParentAndCurrent = \x -> and $ map (/= x) ["..", "."]

matchRegex re file = do
  lines <- readFile file
  case recursiveSearch re lines of
    [] -> return []
    xs -> return $ ("--" ++ file ++ "\n") ++ xs
  where
    recursiveSearch re str =
      case matchRegexAll re str of
        Just (_,_,a,xs) -> xs!!0 ++ "\n" ++ recursiveSearch re a
        _               -> []

mkRegex func = mkRegexWithOpts ("(^" ++ func ++ " .*$)") True True

今のところこんな感じ。

$ runghc HSView.hs -l /usr/lib/hugs/libraries foldr
--/usr/lib/hugs/libraries/Hugs/Prelude.hs
foldr            :: (a -> b -> b) -> b -> [a] -> b
foldr f z []      = z
foldr f z (x:xs)  = f x (foldr f z xs)

シェルにまとめて使うことにする。あっチョー便利かも。しかも中身Haskellだからオシャレだし。(なんだそれ)

$ hv foldr
--/usr/lib/hugs/libraries/Hugs/Prelude.hs
foldr            :: (a -> b -> b) -> b -> [a] -> b
foldr f z []      = z
foldr f z (x:xs)  = f x (foldr f z xs)
  • 関数合成が(ようやく)(ちょっと)つかえるようになってきた。
  • たたみこみ関数が(ようやく)(ちょっと)つかえるようになってきた。
  • いつも、もっと短く、もっとキレイにできる気がする。やっぱり面白い。