[Haskell-cafe] Pattern-matching & substitution for haskell-src-exts?

Gwern Branwen gwern0 at gmail.com
Wed Jan 18 21:32:20 CET 2012


On Wed, Jan 18, 2012 at 3:05 PM, Conal Elliott <conal at conal.net> wrote:
> Has anyone implemented pattern-matching & substitution for
> haskell-src-exts?  - Conal

I don't know what exactly you are looking for, but I remember banging
together a function-name search script using haskell-src-exts and
'find' last summer, which pattern-matches, looking for use of
particular function-names. Presumably you could change
`functionSearch` to not call `length` but instead replace the matched
function with another function and then write out the modules? Well,
maybe the source will be helpful, maybe not:

import System.Environment (getArgs)
import Language.Haskell.Exts
import qualified Data.Foldable as F (concat)
import Data.Generics.Uniplate.Data
-- import Debug.Trace

main :: IO ()
main = do (func:_) <- getArgs
          args <- fmap lines $ getContents
          mapM_ (checkAndPrint func) args

checkAndPrint :: String -> FilePath -> IO ()
checkAndPrint fn fs = do print fs
                         x <- readFile fs
                         let exts = F.concat $ readExtensions x
                         let parsed = parseFileContentsWithMode
(defaultParseMode { fixities = fixes, extensions = exts }) x
                         case parsed of
                          ParseFailed _ _ -> (return ())
                          ParseOk a -> functionSearch fn a
                         return ()

-- the default fixities augmented with everything necessary to parse my corpus
fixes :: Maybe [Fixity]
fixes = Just $ baseFixities ++ infixr_ 0 ["==>"]

functionSearch :: String -> Module -> IO ()
functionSearch fun md = do
  let x = length [ () | Var (UnQual (Ident a)) <- universeBi md, a == fun]
  putStrLn $ "Found " ++ show x ++ " occurences of function " ++ fun

-- 
gwern
http://www.gwern.net



More information about the Haskell-Cafe mailing list