sdist: Setup
        ./Setup sdist
 
-.PHONY: build run clean install doc sdist
+.PHONY: build run clean install doc sdist test
 
 Name:          Rakka
-Synopsis:      Wiki engine with Subversion backend
+Synopsis:      RESTful Wiki engine with Subversion backend
 Description:
-    Rakka is a wiki engine with Subversion backend. Its syntax is
-    similar to MediaWiki.
+    Rakka is a RESTful wiki engine with Subversion backend. Its syntax
+    is similar to MediaWiki.
 Version:       0.1
 License:       PublicDomain
 Author:        PHO <pho at cielonegro dot org>
 
                                         >>>
                                         writeDocumentToString [ (a_indent, v_1) ]
                                       )
-         output resultStr
+         output $ UTF8.encodeString resultStr
 
 
 outputXmlPage' :: XmlTree -> IOSArrow XmlTree XmlTree -> Resource ()
                                     >>>
                                     writeDocumentToString [ (a_indent, v_1) ]
                                   )
-        output xmlStr
+        output $ UTF8.encodeString xmlStr
 
 
 getUserID :: Environment -> Resource (Maybe String)
 
                                                                 >>>
                                                                 writeDocumentToString [ (a_indent, v_1) ]
                                                               )
-                                 output resultStr
+                                 output $ UTF8.encodeString resultStr
 
                        _   -> do BaseURI baseURI <- getSysConf (envSysConf env)
                                  let uri = mkPageFragmentURI
 
     )
     where
 
+import qualified Codec.Binary.UTF8.String as UTF8
 import           Control.Arrow
 import           Control.Arrow.ArrowIO
 import           Control.Arrow.ArrowList
                                      >>>
                                      writeDocumentToString [ (a_indent, v_1) ]
                                    )
-         output xmlStr
+         output $ UTF8.encodeString xmlStr
 
 
 render :: (ArrowXml a, ArrowChoice a, ArrowIO a) =>
 
     )
     where
 
-import qualified Codec.Binary.UTF8.String as UTF8
+import qualified Codec.Binary.UTF8.Generic as UTF8
 import           Control.Monad.Trans
+import           Data.List
 import           Data.Maybe
 import           Data.Time
 import           Network.HTTP.Lucu
 maxSectionWindowSize = 10
 
 
+findQueryParam :: String -> [FormData] -> Maybe String
+findQueryParam name qps
+    = do fd <- find (\ qp -> fdName qp == name) qps
+         return $ UTF8.toString $ fdContent fd
+
 {-
   <searchResult query="foo bar baz"
                 from="0"
 handleSearch env
     = do params <- getQueryForm
 
-         let query = UTF8.decodeString $ fromMaybe ""  $ lookup "q" params
-             order = fmap UTF8.decodeString (lookup "order" params)
+         let query = fromMaybe "" $ findQueryParam "q" params
+             order = findQueryParam "order" params
              from  = fromMaybe 0
-                     $ fmap read $ lookup "from" params
+                     $ fmap read $ findQueryParam "from" params
              to    = fromMaybe (from + resultsPerSection)
-                     $ fmap read $ lookup "to"   params
+                     $ fmap read $ findQueryParam "to" params
 
          cond   <- liftIO $ mkCond query order from to
          result <- searchPages (envStorage env) cond
 
                                      >>>
                                      writeDocumentToString [ (a_indent, v_1) ]
                                    )
-         output xmlStr
+         output $ UTF8.encodeString xmlStr
     where
       mkResponseTree :: ArrowXml a => a b XmlTree
       mkResponseTree 
 
+-- -*- coding: utf-8 -*-
 module Rakka.Storage.Repos
     ( findAllPagesInRevision
     , getDirContentsInRevision
                      unless exists
                          $ do createParentDirectories path
                               makeFile path
-                     applyText path Nothing (serializeToString attachment)
+                     applyText path Nothing (encodeString $ serializeToString attachment)
          case ret of
            Left  _ -> return Conflict
            Right _ -> return NoContent
 
 attachXHtmlNS = processTopDown (changeQName attach `when` isElem)
     where
       attach :: QName -> QName
-      attach qn = qn {
-                    namePrefix   = "xhtml"
-                  , namespaceUri = "http://www.w3.org/1999/xhtml"
-                  }
+      attach = setNamePrefix'   (newXName "xhtml") .
+               setNamespaceUri' (newXName "http://www.w3.org/1999/xhtml")
 
 import System.Cmd
 import System.Exit
 
-main = defaultMainWithHooks (defaultUserHooks { runTests = runTestUnit })
+main = defaultMainWithHooks (autoconfUserHooks { runTests = runTestUnit })
     where
       runTestUnit _ _ _ _
           = system "./dist/build/RakkaUnitTest/RakkaUnitTest" >> return ()
 
-AC_INIT([Rakka], [], [phonohawk at ps dot sakura dot ne dot jp])
+AC_INIT([Rakka], [], [pho at cielonegro dot org])
 
 AC_CONFIG_SRCDIR([Rakka.cabal])