]> ruin.nu Git - yawbih.git/blobdiff - Main.hs
Rewrote the bold parser and added emphasis
[yawbih.git] / Main.hs
diff --git a/Main.hs b/Main.hs
index 93a56168c0c75507a639ba35b78eb3816f43e645..2457b058632e32edc520c090bf631d33f86b5063 100644 (file)
--- a/Main.hs
+++ b/Main.hs
 module Main where 
 
-import CGI hiding (div, head, map, span)
+import CGI hiding (div, head, map, span, Text)
 import RawCGIInternal
 import CGIOutput
+import CGITypes
+import System
+import Wiki
 
-main = start [] cgi
-
-cgi CGIInfo {cgiUrl = url, cgiPathInfo = pi, cgiContentType = ct, cgiContents = c, cgiCookies = co, cgiArgs = as, cgiHandle = h} parms = do 
-       putStr "content-type: text/html\n\n"
-       print parms
-       print url
-       print pi
-       print ct
-       print co
-       print co
-       print as
-       print h
-       case assocParm "test" parms of
-               Nothing -> putStr "Parameter 'test' not provided"
-               Just x -> putStr $ "Value of test = "++x
+import Text.ParserCombinators.Parsec
+
+testDB = createPGB "wave" "wiki" "wiki" "12wiki34db"
+
+--main = start [] cgi
+
+main = do 
+       db <- testDB
+       runWithHook [] (\(key:act) -> showPage db (filter (/= '\\') key)) $ showPage db "MainPage"
+
+ps a = standardQuery "Hello" a
+
+editPage db key = do 
+       s <- io $ getCurrent db key 
+       s' <- case s of
+               Nothing -> return ""
+               Just (x,_) -> return x
+       standardQuery key $ do
+               t <- p $ makeTextarea s' (attr_SS "rows" "10" ## attr_SS "cols" "75" ## attr_SS "colspan" "2")
+               p empty
+               text "Author: "
+               a <- textInputField (fieldSIZE 20)
+               p empty
+               text "Comment: "
+               c <- textInputField (fieldSIZE 20)
+               --p $ submit (F2 t a) testing (attr "value" "Send")
+               p $ defaultSubmit (F3 t a c) (savePage db key) (attr "value" "Send")
+               --submit0 (sp db key []) (attr "value" "Send1")
+
+
+savePage db key (F3 t a c) = do
+       io $ update db key fulltext author comment
+       showPage db key 
+  where
+       fulltext = value t
+       author = value a
+       comment = value c 
+
+showPage db key = do
+       s <- io $ getCurrent db key 
+       standardQuery key $ do
+               case s of
+                       Nothing -> text "No text added for this keyword"
+                       Just (full, date) -> do
+                               parseText full  
+                               p $ tt $ text $ "Last edited: "++date
+               footer db key
+
+parseText full = case parse wikiParser "" full of
+       Right n -> ex n 
+       Left e -> do
+               text "PARSE ERROR: "
+               text (show e)
+               p $ text full
+
+footer db key = do
+       hr empty
+       table $ tr $ do
+               td $ submitLink0 (editPage db key) (text "Edit this keyword")
+               td $ submitLink0 (listRevs db key) (text "List old versions")
+               td $ text "Keyword: " 
+               td $ activate (showPage db) textInputField empty
+
+listRevs db key = do 
+       list <- io $ getList db key 
+       standardQuery key $ table $ do
+               tr $ mapM (\header -> th (text header))
+                       ["Id", "Date", "Author", "Comment"]
+               mapM (revRow db key) list
+
+linkKey db key = submitLink0 (showPage db key) (text key)
+
+revRow db key (id, date, author, comment) = tr $ do
+       td $ submitLink0 (showRev db key id) (text id) 
+       td $ text date
+       td $ linkKey db author
+       td $ text comment
+
+showRev db key id = do
+       s <- io $ get db key id
+       standardQuery key $ do
+               case s of 
+                       Nothing -> text "No such revision"
+                       Just s -> parseText s
+               p empty
+               submitLink0 (changeCurrent db key id) (text "Set this version as the current one")
+               footer db key
+changeCurrent db key id = do
+       b <- io $ setCurrent db key id
+       if b then showPage db key
+               else standardQuery key $ do
+                       text "Could not set this revision as the current active one."
+                       p empty
+                       linkKey db key
+       
+ex [] = return ()
+ex ((Paragraph):xs) = do
+       p empty
+       ex xs
+ex ((Text s):xs) = do
+       text s
+       ex xs
+ex ((Link l d):xs) = do
+       hlink (URL {unURL = ("wiki?"++l)}) (text d)
+       ex xs
+ex ((Bold d):xs) = do
+       b (ex d)
+       ex xs
+ex ((Emph d):xs) = do
+       em (ex d)
+       ex xs
+
+ex2 [] = []
+ex2 ((Paragraph):xs) = "<p>"++ex2 xs
+ex2 ((Text s):xs) = s++ex2 xs
+ex2 ((Link l d):xs) = "<link: "++l++" desc: "++d++">"++ex2 xs
+ex2 ((Bold d):xs) = "<b>"++ex2 d++"</b>"++ex2 xs
+ex2 ((Emph d):xs) = "<em>"++ex2 d++"</em>"++ex2 xs
+
+
+test s = case parse wikiParser "" s of
+                                       Right n -> do 
+                                               print (ex2 n)
+                                       Left e -> do
+                                               print e