[add import module PAF01143@nifty.ne.jp**20081201085805] { hunk ./Development/Hake/RunHake.hs 31 -import Control.Monad.Tools (unlessM) +import Control.Monad.Tools (unlessM, filterM) hunk ./Development/Hake/RunHake.hs 34 -import Text.RegexPR (gsubRegexPR) +import Text.RegexPR (gsubRegexPR, ggetbrsRegexPR) hunk ./Development/Hake/RunHake.hs 50 + when (null othrs) $ do + mods <- getModules src + fmap or $ flip mapM mods + $ apply2way (updateFile commentPair) id $ + (hakeDir ++) + return () hunk ./Development/Hake/RunHake.hs 68 + +getModules :: FilePath -> IO [ FilePath ] +getModules hf = do + cont <- readFile hf + let mods_ = map (!!1) $ ggetbrsRegexPR "^import\\s+([^\n\\([:blank:]]+)" cont + mods <- filterM doesFileExist $ map (++".hs") mods_ + return mods adddir ./examples/testModule addfile ./examples/testModule/Hakefile hunk ./examples/testModule/Hakefile 1 +import Module1 +import Module2(var2) +import Module2 (var3) + +main = do + putStrLn var1 + putStrLn var2 + putStrLn var3 addfile ./examples/testModule/Module1.hs hunk ./examples/testModule/Module1.hs 1 +module Module1 where + +var1 = "var1" addfile ./examples/testModule/Module2.hs hunk ./examples/testModule/Module2.hs 1 +module Module2 where + +var2 = "var2" +var3 = "var3" hunk ./hake.cabal 2 -Version: 1.0 +Version: 1.1 hunk ./hake.cabal 72 - Build-Depends: directory, process, yjtools >= 0.9.6, regexpr >= 0.3 + Build-Depends: directory, process, yjtools >= 0.9.7, regexpr >= 0.5.1 hunk ./memo.ja_JP.utf8 261 +2008.12.1 Mon. +map (!!1) . ggetbrsRegexPR "^import\\s+([^\n\\([:blank:]]+)" +これを利用して Hakefile が同じディレクトリのモジュールを利用できるようにする。 + +upload する前に yjtools 0.9.7 を upload すること。 + hunk ./todo.ja_JP.utf8 7 -[ ] 上2つのあとに1.0にするか。 +[*] 上2つのあとに1.0にするか。 hunk ./todo.ja_JP.utf8 10 -[ ] web page で、あとは getVals とか、hakefileIs とか、-f option とかかな。 -[ ] web page で、さらに getNewers とか、FunSetIO とか、 -[ ] web page で、getNewers と FunSetIO を紹介するときは、ar の例を使おうか。 +[*] web page で、あとは getVals とか、hakefileIs とか +[ ] web page で、-f option とかかな。 +[*] web page で、さらに getNewers とか、FunSetIO とか、 +[*] web page で、getNewers と FunSetIO を紹介するときは、ar の例を使おうか。 hunk ./todo.ja_JP.utf8 15 -[ ] upload する前に、yjtools を 0.9.6 に upload すること。 +[ ] upload する前に、yjtools 0.9.7 を upload すること。 hunk ./web_page/Hakefile 25 -hakeSrc = "../dist/hake-1.0.tar.gz" +hakeSrc = "../dist/hake-1.1.tar.gz" hunk ./web_page/Hakefile 85 - ("index.xhtml", [hakeSrc]) + ("index.xhtml", [hakeSrc] ++ ["versions_file"]) hunk ./web_page/Hakefile 88 + , + ("short_tutorial.xhtml", ["versions_file"]) adddir ./web_page/samples/use_module addfile ./web_page/samples/use_module/Hakefile hunk ./web_page/samples/use_module/Hakefile 1 +import Development.Hake +import Development.Hake.FunSetRaw +import Variables(target) + +main = hake $ [ + + dflt [ target ] + , + rule "" ".c" $ \t (s:_) -> [ [ "cc", "-o", t, s ] ] + , + task "clean" [ [ "rm", "-f", target ] ] + + ] addfile ./web_page/samples/use_module/Variables.hs hunk ./web_page/samples/use_module/Variables.hs 1 +module Variables where + +target = "hello" addfile ./web_page/samples/use_module/hello.c hunk ./web_page/samples/use_module/hello.c 1 +#include + +int +main (int argc, char *argv[]) +{ + + printf( "Hello, world!\n" ); + return 0; + + } hunk ./web_page/short_tutorial.xhtml.ehs 44 -

10. use hakefileIs

-

10.1. hakefileIs function

+

10. use module

+

10.1. files

hunk ./web_page/short_tutorial.xhtml.ehs 47 -

10.3. and something

-

11. use delRules

-

11.1. delRules function

+

11. use hakefileIs

+

11.1. hakefileIs function

hunk ./web_page/short_tutorial.xhtml.ehs 50 +

11.3. and something

+

12. use delRules

+

12.1. delRules function

+

12.2. try

hunk ./web_page/short_tutorial.xhtml.ehs 60 -hake <%== fmap ((!!1) . getbrsRegexPR "hackage_version:\\s*(.*)") $ readFile "versions_file" %> +hake <%== fmap ((!!1) . getbrsRegexPR "my_home_version:\\s*(.*)") $ readFile "versions_file" %> hunk ./web_page/short_tutorial/Hakefile 24 +useModuleXhtml = "use_module.xhtml" hunk ./web_page/short_tutorial/Hakefile 38 +useModuleXhtmlMoreFile = [ "Hakefile_use_module" ] ++ moreMoreFile2 hunk ./web_page/short_tutorial/Hakefile 53 + , useModuleXhtml hunk ./web_page/short_tutorial/Hakefile 69 + ++ useModuleXhtmlMoreFile hunk ./web_page/short_tutorial/Hakefile 72 +moreMoreFile2 = [ "Variables.hs_use_module" ] hunk ./web_page/short_tutorial/Hakefile 87 + , (useModuleXhtml , useModuleXhtmlMoreFile ++ [ "Variables.hs" ] ) hunk ./web_page/short_tutorial/use_delRules.xhtml.ehs 8 -

11. use delRules

+

12. use delRules

hunk ./web_page/short_tutorial/use_delRules.xhtml.ehs 13 -

11.1. delRules function

+

12.1. delRules function

hunk ./web_page/short_tutorial/use_delRules.xhtml.ehs 18 -

11.2. try

+

12.2. try

hunk ./web_page/short_tutorial/use_hakefileIs.xhtml.ehs 5 -10. use hakefileIs +11. use hakefileIs hunk ./web_page/short_tutorial/use_hakefileIs.xhtml.ehs 8 -

10. use hakefileIs

+

11. use hakefileIs

hunk ./web_page/short_tutorial/use_hakefileIs.xhtml.ehs 11 -

10.1. hakefileIs function

+

11.1. hakefileIs function

hunk ./web_page/short_tutorial/use_hakefileIs.xhtml.ehs 18 -

10.2. try

+

11.2. try

hunk ./web_page/short_tutorial/use_hakefileIs.xhtml.ehs 22 -

10.3. and something

+

11.3. and something

addfile ./web_page/short_tutorial/use_module.xhtml.ehs hunk ./web_page/short_tutorial/use_module.xhtml.ehs 1 + +<%% import Variables %%> +<%% import System.Time %%> +> +use module + + +

10. use module

+

updated at <%==$ getClockTime %>

+ +

You can use module only by import if module's source code is in same directory.

+ +

10.1. files

+
> ls
+Hakefile Variables.hs hello.c
+<%== catHakefile "use_module" %> +<%== catFile "Variables.hs" "use_module" %> + +

10.2. try

+
> hake
+cc -o hello hello.c
+ + + hunk ./web_page/versions_file 2 -my_home_version: 1.0 +my_home_version: 1.1 }