[edit web page: add first_of_all.xhtml
PAF01143@nifty.ne.jp**20081219042038] {
hunk ./todo.ja_JP.utf8 8
+[ ] <- の右辺で type 指定を可能にする。
hunk ./web_page/XMLTools.hs 3
+, mkContents
hunk ./web_page/XMLTools.hs 6
-import System.Time (getClockTime)
+import System.Time (getClockTime)
+import System.Directory (doesFileExist)
+import Control.Monad.Tools (ifM)
+import Control.Applicative ((<$>))
hunk ./web_page/XMLTools.hs 21
+
+mkContents :: Int -> String -> IO ()
+mkContents n t = do
+ cont <- filter ((/=n).fst) <$> read <$> ifM (doesFileExist contFile)
+ (readFile contFile)
+ (return "[]")
+ putStr $ take (length cont - length cont) "dummy"
+ writeFile contFile $ show $ (n,t):cont
+ where
+ contFile = "contents"
hunk ./web_page/short_tutorial.xhtml.ehs 2
-<%% import XMLTools (intoBody) %%>
+<%% import XMLTools (intoBody) %%>
+<%% import Text.RegexPR (gsubRegexPR) %%>
+<%% mkContItem :: (Int, String) -> String %%>
+<%% mkContItem (n, t) = "
" ++ atag ++ show n ++ ". " ++ t ++ "
\n"
+ where
+ atag = ""
+ address = "short_tutorial/" ++ gsubRegexPR " " "_" t ++ ".xhtml" %%>
+
+<% cont <- (fmap read $ readFile "short_tutorial/contents" :: IO [(Int, String)]) %>
hunk ./web_page/short_tutorial.xhtml.ehs 14
+<%= concatMap mkContItem cont %>
hunk ./web_page/short_tutorial/Hakefile 4
+import System.Cmd (rawSystem)
+import System.IO (stdout, hFlush)
hunk ./web_page/short_tutorial/Hakefile 10
+projName = "ehaskell/short_tutorial/"
hunk ./web_page/short_tutorial/Hakefile 21
- file [ "upload" ] [] $ const2 $ return ExitSuccess
+ file [ "upload" ] targets $ \_ ss -> do
+ newers <- getNewers "upload_done" ss
+ psswd <- if null newers then return "" else getPsswd
+ mapM (\s -> putStrLn ("uploading " ++ s) >> rawSystem "yjftp" [ "put", s,
+ "ftp37.nifty.com/homepage/second/projects/" ++ projName ++ "/",
+ "hc751476", "-p", psswd ]) newers
+ rawSystemE [ "touch", "upload_done" ]
hunk ./web_page/short_tutorial/Hakefile 34
+
+getPsswd :: IO String
+getPsswd = do
+ putStr "Passwd: "
+ hFlush stdout
+ rawSystem "stty" [ "-echo" ]
+ pass <- getLine
+ rawSystem "stty" [ "echo" ]
+ putStrLn ""
+ return pass
hunk ./web_page/short_tutorial/first_of_all.xhtml.ehs 1
-<% intoBody "0. first of all" -%>
+<% intoBody (show sectionN ++ ". " ++ sectionT) -%>
hunk ./web_page/short_tutorial/first_of_all.xhtml.ehs 6
-<% cont <- read <$> ifM (doesFileExist "contents")
- (readFile "contents")
- (return "[\"test\"]") %>
-<%= cont !! 0 %>
+<%% sectionN = 0 %%>
+<%% sectionT = "first of all" %%>
+<% mkContents sectionN sectionT %>
+This page is under construction
}