module Main where import Control.Monad import Control.Monad.Trans.Maybe import Control.Monad.IO.Class import Data.List import Data.Maybe import System.Cmd import System.Exit import System.Environment import System.Process main :: IO() main = do args <- getArgs case elemIndex "-c" args of Nothing -> putStrLn usage Just i -> (mapM_ (runOn cs) $ zip [0..] fs) `catch` (putStrLn . show) where (fs, (_:cs)) = splitAt i args runOn :: [String] -> (Integer, String) -> IO () runOn [] _ = fail "No command specified" runOn cs (n, f) = do cs' <- mapM (trans (n, f)) cs putStr $ "do#" ++ show (n+1) ++ ": " putStrLn $ unwords cs' system $ unwords $ map (("\""++) . (++"\"")) cs' putStrLn "" trans :: (Integer, String) -> String -> IO String trans (n, f) c = mapM (transBrk (n, f)) (splitBrk c) >>= return . concat splitBrk :: String -> [String] splitBrk c = map (`takeRange` c) $ zip bs'' (tail bs'') where ns = zip [0..] $ scanl (+) 0 $ map (\x -> if x=='{' then 1 else if x=='}' then -1 else 0) c bs = map fst $ filter (\((_,x),(_,y))->(x==0&&y==1)||(x==1&&y==0)) $ zip ns $ tail ns bs' = map (\(i,b)->if b==0 then i else i+1) bs bs'' = [0] ++ bs' ++ [length c] takeRange :: (Int, Int) -> [a] -> [a] takeRange (i,j) = drop i . take j transBrk :: (Integer, String) -> String -> IO String transBrk (n, f) b | null b || (head b /= '{') || (last b /= '}') = return b | otherwise = transPtn (n, f) $ takeRange (1, length b - 1) b transPtn :: (Integer, String) -> String -> IO String transPtn (n, f) p = runMaybeT (msum [asEmpty f p, asNum n p, asSed f p, return p]) >>= return . fromJust asEmpty :: String -> String -> MaybeT IO String asEmpty f p = if null p then return f else mzero asNum :: Integer -> String -> MaybeT IO String asNum n p = if all (`elem` "0123456789") p then return $ show $ (read p :: Integer) + n else mzero asSed :: String -> String -> MaybeT IO String asSed f p = do (c, o, e) <- liftIO $ readProcessWithExitCode "sed" [p] f case c of ExitSuccess -> return o ExitFailure _ -> liftIO $ fail e -- usage info -- usage = "fordo 0.1 by Lars (songcq@gmail.com), updated at Nov 20th, 2010 \n\ \ \n\ \Usage: \n\ \ fordo files -c command [args] \n\ \ \n\ \Description \n\ \ Run command on a list of file. Before running command, \n\ \ 1. {} is replaced to the file name; \n\ \ 2. {n} is replaced to file counter starting from n; (n can be any number) \n\ \ 3. {s/ab*c/ac/g} is replaced to the result of 'sed \"s/ab*c/ac/g\"' on file name; (any other sed scripts also work) \n\ \ \n\ \Examples: \n\ \ To convert all bmp files to jpg format: (convert is a command from ImageMagick) \n\ \ \n\ \ 1. Keep the original basenames\n\ \ fordo *.bmp -c convert {} {s/bmp$/jpg/} \n\ \ \n\ \ 2. Convert files to 0.jpg, 1.jpg, 2.jpg ... \n\ \ fordo *.bmp -c convert {} {0}.jpg \n\ \"