[Fencommits] fenserve: fix the [edit page] link

Benja Fallenstein benja.fallenstein at gmail.com
Fri May 25 21:48:04 EEST 2007


Fri May 25 21:47:47 EEST 2007  Benja Fallenstein <benja.fallenstein at gmail.com>
  * fix the [edit page] link
diff -rN -u old-fenserve-1/fendata/Main.hs new-fenserve-1/fendata/Main.hs
--- old-fenserve-1/fendata/Main.hs	2007-05-25 21:48:04.000000000 +0300
+++ new-fenserve-1/fendata/Main.hs	2007-05-25 21:48:04.000000000 +0300
@@ -71,23 +71,12 @@
     s { stateSchema = Map.insert (uncapitalize name) [] $ stateSchema s}) where
     Just name = lookM req "name"
 
-expand s (Call n args) = case readFun s n of 
-    Fun _ _ body -> Just 
-        (foldr (\i e -> subst' i (case args !! i of Just x -> Just x; Nothing -> Just (Var i)) e) body [0..length args-1], n)
-expand _ _ = Nothing
-
 subst :: Int -> Exp -> Exp -> Exp
 subst i repl e = everywhere (mkT f)  e where
     f :: Exp -> Exp
     f (Var j) | j == i = repl
     f x = x
 
-subst' :: Int -> Maybe Exp -> Exp -> Exp
-subst' i repl e = everywhere (mkT f)  e where
-    f :: Maybe Exp -> Maybe Exp
-    f (Just (Var j)) | j == i = repl
-    f x = x
-
 
 --run :: (a -> MyState -> (String, MyState)) -> a -> blah
 run f x = do
@@ -102,14 +91,15 @@
         Right (s, state') -> do put state'; respond (s, html $ link s "link")
         Left e -> respond $ ("", "Internal server error: " ++ show e)
 
-potionPage exp args name s = (makePage s title expandLink body, s) where
+potionPage fun args name s = (makePage s title expandLink body, s) where
+    exp = Call fun (map (Just . Str) $ args)
     title = let ?state=s; ?link=False; ?name=name in renderExp exp id string
     env = Map.fromList $ zip [0..length args-1] args
     body = if (isComplete exp)
            then (HTML $ head $ evalStateT (runExp env exp) s)
            else toHTML "(Incomplete expression.)"
-    expanded = expand s exp
-    expandLink = (para $ link (?root++"potion?exp="++escape' (show e)++"&name="++n) "[edit page]")
+    Fun _ _ funBody = readFun s fun
+    expandLink = (para $ link (?root++"potion?exp="++escape' (show funBody)++"&name="++fun) "[edit page]")
              +++ maybe (HTML "") (\page ->
                    (if page `elem` stateSidebarPages s then HTML "" else
                     para $ formP (?root++"addToSidebar") (hidden "page" (show page)
@@ -120,7 +110,6 @@
                                          mapM (\a -> case a of Str s -> Just s
                                                                _ -> Nothing)
                         _ -> Nothing)
-        where Just (e,n) = expanded
 
 potionGet exp args name s = (makePage s "Custom page" "" $
               tag "div" [("style", "border: 1px solid black; \
@@ -276,7 +265,7 @@
                , h ["potion"] GET $ ok $ \() -> run $ 
                    \req s -> let ?root = "" in potionGet (read $ fromJust $ lookM req "exp") (readArgs req) (lookM req "name") s
                , h (Prefix ["potion"]) GET $ ok $ \(fun:args) -> run $ 
-                   \req s -> let ?root = concat (take (1 + length args) $ repeat "../") in potionPage (Call fun (map (Just . Str) $ args)) args (lookM req "name") s
+                   \req s -> let ?root = concat (take (1 + length args) $ repeat "../") in potionPage fun args (lookM req "name") s
                , h ["edit"] GET $ ok $ \() -> run $ \req ->
                      edit (read $ fromJust $ lookM req "exp",
                            read $ fromJust $ lookM req "old",




More information about the Fencommits mailing list