[edit web page PAF01143@nifty.ne.jp**20081127102232] { hunk ./web_page/Hakefile 3 -import Text.RegexPR (matchRegexPR) -import Data.Maybe (fromJust) -import System.IO (stdout, hFlush) -import System.Cmd (rawSystem) -import Data.IORef (IORef, newIORef, writeIORef, readIORef) +import Text.RegexPR (matchRegexPR) +import Data.Maybe (fromJust) +import System.IO (stdout, hFlush) +import System.Cmd (rawSystem) +import Data.IORef (IORef, newIORef, writeIORef, readIORef) +import Control.Monad (unless) hunk ./web_page/Hakefile 13 -target :: String -target = "index.xhtml" +targets :: [ String ] +targets = [ "index.xhtml", "hakefile_examples.xhtml" ] hunk ./web_page/Hakefile 31 - dflt [ target ] + dflt targets hunk ./web_page/Hakefile 35 - file [ "upload" ] [ "upload_index", "upload_others" ] $ const $ return ExitSuccess + file [ "upload" ] [ "upload_index", "upload_others" ] $ const $ do + rawSystemE [ "touch", "upload_done" ] hunk ./web_page/Hakefile 38 - file [ "upload_index" ] [ target ] $ \_ -> do - psswd <- getIfNothing password - putStrLn $ "uploading " ++ target - rawSystem - "yjftp" [ "put", target, address ++ directory, user_name, "-p", psswd ] + file [ "upload_index" ] targets $ \_ -> do + newers <- getNewers "upload_done" targets + if (null newers) + then return ExitSuccess + else do + psswd <- getIfNothing password + mapM (\f -> do + putStrLn $ "uploading " ++ f + rawSystem "yjftp" + [ "put", f, address ++ directory, user_name, "-p", psswd ]) newers + return ExitSuccess hunk ./web_page/Hakefile 50 - file [ "upload_others" ] [ target ] $ \_ -> do - psswd <- getIfNothing password - fmap last $ mapM (\f -> do - putStrLn $ "uploading " ++ f - rawSystem - "yjftp" ["put", f , address ++ directory, user_name, "-p", psswd ]) - moreFile + file [ "upload_others" ] moreFile $ \_ -> do + newers <- getNewers "upload_done" moreFile + if null newers + then return ExitSuccess + else do + psswd <- getIfNothing password + mapM (\f -> do + putStrLn $ "uploading " ++ f + rawSystem + "yjftp" ["put", f , address ++ directory, user_name, "-p", psswd ]) + newers + return ExitSuccess hunk ./web_page/Hakefile 82 - (target, moreFile) + (targets !! 1, moreFile) addfile ./web_page/hakefile_examples.xhtml.ehs hunk ./web_page/hakefile_examples.xhtml.ehs 1 + +<%% import Text.RegexPR %%> + + + haskell hake: Hakefile examples + + +

Hakefile Examples

+

* Simple

+
<%== fmap (gsubRegexPR ">" ">") $
+                      readFile "Hakefile.simple" %>
+

* use ruleSS

+
<%== fmap (gsubRegexPR ">" ">") $
+                      readFile "Hakefile.ruleSS" %>
+

* use addDeps

+
<%== fmap (gsubRegexPR ">" ">") $
+                      readFile "Hakefile.addDeps" %>
+

Use other file

+

You can use other file and other modules by use 'hakefileIs'

+

* use hakefileIs

+
<%== fmap (gsubRegexPR ">" ">") $
+                      readFile "Hakefile.hakefileIs" %>
+ + hunk ./web_page/index.xhtml.ehs 5 +<%% import Data.Maybe (fromJust) %%> +<%% getV :: String -> String -> String %%> +<%% getV k = fromJust . lookup 1 . snd . fromJust . matchRegexPR (k ++ "\\s*:\\s*(.+)") %%> +<% ver_cont <- readFile "versions_file" %> hunk ./web_page/index.xhtml.ehs 11 - hake + haskell hake hunk ./web_page/index.xhtml.ehs 19 -

hackage

+

">hackage

hunk ./web_page/index.xhtml.ehs 21 -

hake 0.9.6 updated at <%==$ - getModificationTime "../dist/hake-0.9.6.tar.gz" %>

+

.tar.gz">hake <%= getV "my_home_version" ver_cont %> updated at <%==$ + getModificationTime $ "../dist/hake-" ++ getV "my_home_version" ver_cont ++ ".tar.gz" %>

hunk ./web_page/index.xhtml.ehs 29 -

* Simple

-
<%== fmap (gsubRegexPR ">" ">") $
-                      readFile "Hakefile.simple" %>
-

* use ruleSS

-
<%== fmap (gsubRegexPR ">" ">") $
-                      readFile "Hakefile.ruleSS" %>
-

* use addDeps

-
<%== fmap (gsubRegexPR ">" ">") $
-                      readFile "Hakefile.addDeps" %>
-

Use other file

-

You can use other file and other modules by use 'hakefileIs'

-

* use hakefileIs

-
<%== fmap (gsubRegexPR ">" ">") $
-                      readFile "Hakefile.hakefileIs" %>
+

hakefile examples

addfile ./web_page/versions_file hunk ./web_page/versions_file 1 +hackage_version: 0.9.9 +my_home_version: 0.9.9 }