[edit web page PAF01143@nifty.ne.jp**20081128095614] { hunk ./memo.ja_JP.utf8 252 +2008.11.28 Fri. +掲示板を作成しよう。 + hunk ./web_page/Hakefile 14 -targets = [ "index.xhtml", "hakefile_examples.xhtml" ] +targets = [ "index.xhtml", "hakefile_examples.xhtml", "short_tutorial.xhtml" ] hunk ./web_page/Hakefile 19 - "Hakefile.hakefileIs", "../dist/hake-0.9.6.tar.gz" + "Hakefile.hakefileIs", "../dist/hake-0.9.9.tar.gz" hunk ./web_page/hakefile_examples.xhtml.ehs 3 - + hunk ./web_page/hakefile_examples.xhtml.ehs 10 -
<%== fmap (gsubRegexPR ">" ">") $
+ <%== fmap (flip (foldr (uncurry gsubRegexPR)) [ (">",">"), ("<","<") ]) $
hunk ./web_page/index.xhtml.ehs 9
-
+<% let { my_home_version = getV "my_home_version" ver_cont } %>
+<% let { hackage_version = getV "hackage_version" ver_cont } %>
+
hunk ./web_page/index.xhtml.ehs 21
-
+
hunk ./web_page/index.xhtml.ehs 25
- .tar.gz">hake <%= getV "my_home_version" ver_cont %> updated at <%==$
- getModificationTime $ "../dist/hake-" ++ getV "my_home_version" ver_cont ++ ".tar.gz" %>
+ hake <%= my_home_version %> updated at <%==$
+ getModificationTime $ "../dist/hake-" ++ my_home_version ++ ".tar.gz" %>
hunk ./web_page/index.xhtml.ehs 30
+ Short Tutorial
+
adddir ./web_page/samples
adddir ./web_page/samples/first_sample
addfile ./web_page/samples/first_sample/Hakefile
hunk ./web_page/samples/first_sample/Hakefile 1
+import Development.Hake
+import Development.Hake.FunSet
+
+main = hake [
+
+ file [ "hello" ] [ "hello.c" ] $ const [ "cc -o hello hello.c" ]
+
+ ]
addfile ./web_page/samples/first_sample/hello.c
hunk ./web_page/samples/first_sample/hello.c 1
+#include
+
+int
+main (int argc, char *argv[])
+{
+ printf( "Hello, world!\n" );
+ return 0;
+ }
adddir ./web_page/short_tutorial
addfile ./web_page/short_tutorial.xhtml.ehs
hunk ./web_page/short_tutorial.xhtml.ehs 1
+
+<%% import System.Time (getClockTime) %%>
+<%% import Text.RegexPR (gsubRegexPR) %%>
+
+short tutorial
+
+Short tutorial for hake
+updated at <%==$ getClockTime %>
+I'm sorry. My English is bad.
+
+0. first of all
+Please get and install hake by your favorite way.
+If your distribution doesn't have package of hake, you should use cabal directly.
+If installing succeed, you can done following command.
+> hake --version
+hake 0.9.9
+
+contents
+1. first sample
+1.1. next, prepare for first sample
+1.2. write Hakefile and run hake
+
+next, prepare for first sample
+Please prepare a directory and a source file for test.
+> mkdir first_sample
+> vim hello.c
+(I love vim. But please use your favorite editor:-))
+> cat hello.c
+<%== fmap (flip (foldr (uncurry gsubRegexPR)) [ (">",">"), ("<","<") ]) $
+ readFile "samples/first_sample/hello.c" %>
+
+write Hakefile and run hake
+Hakefile is haskell source code.
+> vim Hakefile
+> cat Hakefile
+<%== readFile "samples/first_sample/Hakefile" %>
+> hake hello
+cc -o hello hello.c
+>./hello
+Hello, world!
+
+
+
addfile ./web_page/short_tutorial/Hakefile
hunk ./web_page/short_tutorial/Hakefile 1
+import Development.Hake
+import Development.Hake.FunSetIO
+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)
+
+getV :: String -> String -> String
+getV k = fromJust . lookup 1 . snd . fromJust . matchRegexPR (k ++ "\\s*:\\s*(.+)")
+
+targets :: [ String ]
+targets = [ "first_sample.xhtml" ]
+
+moreFile :: [ String ]
+moreFile = [
+ ]
+
+main :: IO ()
+main = do
+ addrs <- readFile "../../address_file"
+ let address = getV "address" addrs
+ directory = getV "document_directory" addrs
+ user_name = getV "user" addrs
+ password <- newIORef Nothing
+ hake $ [
+
+ dflt targets
+ ,
+ rule "" ".ehs" $ \t (s:_) -> rawSystemE [ "ehs", s, "-o", t ]
+ ,
+ file [ "upload" ] [ "upload_index", "upload_others" ] $ const $ do
+ rawSystemE [ "touch", "upload_done" ]
+ ,
+ 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 ++ "short_tutorial", user_name, "-p", psswd ]) newers
+ return ExitSuccess
+ ,
+ 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
+ {-
+ ,
+ file [ "upload" ] [ target ] $ \t -> do
+ psswd <- getPsswd
+ putStrLn $ "uploading " ++ target
+ rawSystem
+ "yjftp" [ "put", target, address ++ directory, user_name, "-p", psswd ]
+ fmap last $ mapM (\f -> do
+ putStrLn $ "uploading " ++ f
+ rawSystem
+ "yjftp" ["put", f , address ++ directory, user_name, "-p", psswd ])
+ moreFile
+ -}
+ ,
+ task "test" $ do putStrLn $ getV "address" addrs
+ putStrLn $ getV "document_directory" addrs
+ return ExitSuccess
+
+ ] `addDeps` [
+
+ (targets !! 0, moreFile)
+
+ ]
+
+getPsswd :: IO String
+getPsswd = do
+ putStr "Passwd: "
+ hFlush stdout
+ rawSystem "stty" [ "-echo" ]
+ pass <- getLine
+ rawSystem "stty" [ "echo" ]
+ putStrLn ""
+ return pass
+
+getIfNothing :: IORef (Maybe String) -> IO String
+getIfNothing pss = do
+ c <- readIORef pss
+ case c of
+ Just p -> return p
+ Nothing -> do p <- getPsswd
+ writeIORef pss $ Just p
+ return p
addfile ./web_page/short_tutorial/first_sample.xhtml.ehs
hunk ./web_page/short_tutorial/first_sample.xhtml.ehs 1
+
+<%% import System.Time (getClockTime) %%>
+
+
+I'm sorry, this page is under construction now (<%==$ getClockTime %>)
+
+
}