By | Chris Done |
At | 2013-02-28 |
Title | properly call annotations annotations in the codebase |
Description |
Edit file src/Main.hs 33188 → 33188
57 57 ,("/:id",run Paste.handle)
58 58 ,("/raw/:id",run Raw.handle)
59 59 ,("/report/:id",run Report.handle)
60 60 ,("/reported",run Reported.handle)
61 61 ,("/new",run New.handle)
- 62 ,("/edit/:id",run New.handle)
+ 62 ,("/annotate/:id",run New.handle)
63 63 ,("/new/:channel",run New.handle)
64 64 ,("/browse",run Browse.handle)
65 65 ,("/activity",run Activity.handle)
66 66 ,("/diff/:this/:that",run Diff.handle)
67 67 ]
… … … … Remove file src/Amelie/View/Edit.hs 33188
- 1 {-# OPTIONS -Wall -fno-warn-name-shadowing #-} - 2 {-# LANGUAGE OverloadedStrings #-} - 3 {-# LANGUAGE RecordWildCards #-} - 4 - 5 -- | Edit paste view. - 6 - 7 module Amelie.View.Edit - 8 (page) - 9 where - 10 - 11 import Amelie.Types - 12 import Amelie.View.Html - 13 import Amelie.View.Layout - 14 - 15 import Data.Monoid.Operator ((++)) - 16 import Prelude hiding ((++)) - 17 import Text.Blaze.Html5 as H hiding (map) - 18 import Data.Text.Lazy - 19 - 20 -- | Render the create edit paste page. - 21 page :: Paste -> Html -> Html - 22 page Paste{..} form = - 23 layoutPage $ Page { - 24 pageTitle = "Edit: " ++ pasteTitle - 25 , pageBody = lightSection ("Edit: " ++ fromStrict pasteTitle) form - 26 , pageName = "edit" - 27 } Edit file src/Amelie/View/Paste.hs 33188 → 33188
49 49 ppLangs
50 50 (zip ppAnnotations ppAnnotationHints)
51 51 , pageName = "paste"
52 52 }
53 53 - 54 -- | A formlet for paste submission / editing.
+ 54 -- | A formlet for paste submission / annotateing.
55 55 pasteFormlet :: PasteFormlet -> (Formlet PasteSubmit,Html)
56 56 pasteFormlet pf@PasteFormlet{..} =
57 57 let form = postForm ! A.action (toValue action) $ do
58 58 when pfSubmitted $
59 59 when (not (null pfErrors)) $
… … … … 61 61 mapM_ (p . toHtml) pfErrors
62 62 formletHtml (pasteSubmit pf) pfParams
63 63 submitInput "submit" "Submit"
64 64 in (pasteSubmit pf,form)
65 65 - 66 where action = case pfEditPaste of
- 67 Just Paste{..} -> "/edit/" ++ show (fromMaybe pasteId pasteParent)
+ 66 where action = case pfAnnotatePaste of
+ 67 Just Paste{..} -> "/annotate/" ++ show (fromMaybe pasteId pasteParent)
68 68 Nothing -> "/new"
69 69 70 70 -- | The paste submitting formlet itself.
71 71 pasteSubmit :: PasteFormlet -> Formlet PasteSubmit
72 72 pasteSubmit pf@PasteFormlet{..} =
73 73 PasteSubmit
74 74 <$> pure (getPasteId pf)
- 75 <*> req (textInput "title" "Title" editTitle)
+ 75 <*> req (textInput "title" "Title" annotateTitle)
76 76 <*> defaulting "Anonymous Coward" (textInput "author" "Author" Nothing)
77 77 <*> parse (traverse lookupLang)
78 78 (opt (dropInput languages "language" "Language" (snd defChan)))
79 79 <*> parse (traverse lookupChan)
80 80 (opt (dropInput channels "channel" "Channel" (fst defChan)))
- 81 <*> req (areaInput "paste" "Paste" editContent)
+ 81 <*> req (areaInput "paste" "Paste" annotateContent)
82 82 <*> opt (wrap (H.div ! aClass "spam") (textInput "email" "Email" Nothing))
83 83 84 84 where defaulting def = fmap swap where
85 85 swap "" = def
86 86 swap x = x
… … … … 88 88 languages = options languageName languageTitle pfLanguages
89 89 90 90 lookupLang slug = findOption ((==slug).languageName) pfLanguages languageId
91 91 lookupChan slug = findOption ((==slug).channelName) pfChannels channelId
92 92 - 93 defChan = maybe (fromMaybe "" editChan,fromMaybe "haskell" editLanguage)
+ 93 defChan = maybe (fromMaybe "" annotateChan,fromMaybe "haskell" annotateLanguage)
94 94 (channelName &&& trim.channelName)
95 95 (pfDefChan >>= findChan)
96 96 findChan name = find ((==name).trim.channelName) pfChannels
97 97 trim = T.dropWhile (=='#')
98 98 - 99 editContent = pastePaste <$> pfEditPaste
- 100 editTitle = ((++ " (annotation)") . pasteTitle) <$> pfEditPaste
- 101 editLanguage = join (fmap pasteLanguage pfEditPaste) >>= findLangById
- 102 editChan = join (fmap pasteChannel pfEditPaste) >>= findChanById
+ 99 annotateContent = pastePaste <$> pfAnnotatePaste
+ 100 annotateTitle = ((++ " (annotation)") . pasteTitle) <$> pfAnnotatePaste
+ 101 annotateLanguage = join (fmap pasteLanguage pfAnnotatePaste) >>= findLangById
+ 102 annotateChan = join (fmap pasteChannel pfAnnotatePaste) >>= findChanById
103 103 104 104 findChanById id = channelName <$> find ((==id).channelId) pfChannels
105 105 findLangById id = languageName <$> find ((==id).languageId) pfLanguages
106 106 107 107 -- | Get the paste id.
… … … … 160 160 pasteNav :: [Language] -> [Paste] -> Paste -> Html
161 161 pasteNav langs pastes paste =
162 162 H.div ! aClass "paste-nav" $ do
163 163 diffLink
164 164 stepsLink
- 165 href ("/edit/" ++ pack (show pid) ++ "") ("Annotate" :: Text)
+ 165 href ("/annotate/" ++ pack (show pid) ++ "") ("Annotate" :: Text)
166 166 " - "
167 167 href ("/report/" ++ pack (show pid) ++ "") ("Report/Delete" :: Text)
168 168 169 169 where pid = pasteId paste
170 170 pairs = zip (drop 1 pastes) pastes
… … … … Edit file src/Amelie/View/Report.hs 33188 → 33188
68 68 pasteContent :: Text -> Html
69 69 pasteContent paste =
70 70 lightNoTitleSection $
71 71 highlightHaskell paste
72 72 - 73 -- | A formlet for report submission / editing.
+ 73 -- | A formlet for report submission / annotating.
74 74 reportFormlet :: ReportFormlet -> (Formlet Text,Html)
75 75 reportFormlet ReportFormlet{..} =
76 76 let frm = form $ do
77 77 formletHtml reportSubmit rfParams
78 78 submitInput "submit" "Submit"
… … … … Edit file src/Amelie/View/Steps.hs 33188 → 33188
52 52 stepsForm form =
53 53 lightNoTitleSection $
54 54 div ! aClass "steps-expr" $
55 55 form
56 56 - 57 -- | A formlet for expr submission / editing.
+ 57 -- | A formlet for expr submission / annotating.
58 58 exprFormlet :: ExprFormlet -> (Formlet Text,Html)
59 59 exprFormlet ExprFormlet{..} =
60 60 let frm = form $ do
61 61 formletHtml exprSubmit efParams
62 62 submitInput "submit" "Submit"
… … … … Edit file src/Amelie/Types/Paste.hs 33188 → 33188
44 44 ,pastePaste :: Text
45 45 ,pasteViews :: Integer
46 46 ,pasteParent :: Maybe PasteId
47 47 } deriving Show
48 48 - 49 -- | A paste submission or edit.
+ 49 -- | A paste submission or annotate.
50 50 data PasteSubmit = PasteSubmit {
51 51 pasteSubmitId :: Maybe PasteId
52 52 ,pasteSubmitTitle :: Text
53 53 ,pasteSubmitAuthor :: Text
54 54 ,pasteSubmitLanguage :: Maybe LanguageId
… … … … 80 80 , pfErrors :: [Text]
81 81 , pfParams :: Params
82 82 , pfLanguages :: [Language]
83 83 , pfChannels :: [Channel]
84 84 , pfDefChan :: Maybe Text
- 85 , pfEditPaste :: Maybe Paste
+ 85 , pfAnnotatePaste :: Maybe Paste
86 86 }
87 87 88 88 data ExprFormlet = ExprFormlet {
89 89 efSubmitted :: Bool
90 90 , efParams :: Params
… … … … Edit file src/Amelie/Model/Paste.hs 33188 → 33188
8 8 -- | Paste model.
9 9 10 10 module Amelie.Model.Paste
11 11 (getLatestPastes
12 12 ,getPasteById
- 13 ,createOrEdit
+ 13 ,createOrAnnotate
14 14 ,createPaste
15 15 ,getAnnotations
16 16 ,getSomePastes
17 17 ,countPublicPastes
18 18 ,generateHints
… … … … 85 85 ,"WHERE annotation_of = ?"
86 86 ,"ORDER BY id ASC"]
87 87 (Only pid)
88 88 89 89 -- | Create a paste, or update an existing one.
- 90 createOrEdit :: [Language] -> [Channel] -> PasteSubmit -> Model (Maybe PasteId)
- 91 createOrEdit langs chans paste@PasteSubmit{..} = do
+ 90 createOrAnnotate :: [Language] -> [Channel] -> PasteSubmit -> Model (Maybe PasteId)
+ 91 createOrAnnotate langs chans paste@PasteSubmit{..} = do
92 92 case pasteSubmitId of
93 93 Nothing -> createPaste langs chans paste
94 94 Just pid -> do updatePaste pid paste
95 95 return $ Just pid
96 96 - 97 -- | Create a new paste (possibly editing an existing one).
+ 97 -- | Create a new paste (possibly annotating an existing one).
98 98 createPaste :: [Language] -> [Channel] -> PasteSubmit -> Model (Maybe PasteId)
99 99 createPaste langs chans ps@PasteSubmit{..} = do
100 100 res <- single ["INSERT INTO paste"
101 101 ,"(title,author,content,channel,language,annotation_of)"
102 102 ,"VALUES"
… … … … Edit file src/Amelie/Controller/New.hs 33188 → 33188
11 11 import Amelie.Controller.Paste (pasteForm,getPasteId)
12 12 import Amelie.Model
13 13 import Amelie.Model.Channel (getChannels)
14 14 import Amelie.Model.Language (getLanguages)
15 15 import Amelie.Model.Paste (getPasteById)
- 16 import Amelie.View.Edit as Edit (page)
+ 16 import Amelie.View.Annotate as Annotate (page)
17 17 import Amelie.View.New as New (page)
18 18 19 19 import Control.Applicative
20 20 import Data.Text.Encoding (decodeUtf8)
21 21 import Snap.Core
… … … … 30 30 case pid of
31 31 Just pid -> do
32 32 paste <- model $ getPasteById (fromIntegral pid)
33 33 form <- pasteForm chans langs defChan paste
34 34 justOrGoHome paste $ \paste -> do
- 35 output $ Edit.page paste form
+ 35 output $ Annotate.page paste form
36 36 Nothing -> do
37 37 form <- pasteForm chans langs defChan Nothing
38 38 output $ New.page form
… … … … Edit file src/Amelie/Controller/Paste.hs 33188 → 33188
60 60 , ppPaste = paste
61 61 , ppAnnotationHints = ahints
62 62 }
63 63 justOrGoHome html outputText
64 64 - 65 -- | Control paste editing / submission.
+ 65 -- | Control paste annotating / submission.
66 66 pasteForm :: [Channel] -> [Language] -> Maybe Text -> Maybe Paste -> Controller Html
- 67 pasteForm channels languages defChan editPaste = do
+ 67 pasteForm channels languages defChan annotatePaste = do
68 68 params <- getParams
69 69 submitted <- isJust <$> getParam "submit"
70 70 let formlet = PasteFormlet {
71 71 pfSubmitted = submitted
72 72 , pfErrors = []
73 73 , pfParams = params
74 74 , pfChannels = channels
75 75 , pfLanguages = languages
76 76 , pfDefChan = defChan
- 77 , pfEditPaste = editPaste
+ 77 , pfAnnotatePaste = annotatePaste
78 78 }
79 79 (getValue,_) = pasteFormlet formlet
80 80 value = formletValue getValue params
81 81 errors = either id (const []) value
82 82 (_,html) = pasteFormlet formlet { pfErrors = errors }
… … … … Add file src/Amelie/View/Annotate.hs 33188
+ 1 {-# OPTIONS -Wall -fno-warn-name-shadowing #-} + 2 {-# LANGUAGE OverloadedStrings #-} + 3 {-# LANGUAGE RecordWildCards #-} + 4 + 5 -- | Annotate paste view. + 6 + 7 module Amelie.View.Annotate + 8 (page) + 9 where + 10 + 11 import Amelie.Types + 12 import Amelie.View.Html + 13 import Amelie.View.Layout + 14 + 15 import Data.Monoid.Operator ((++)) + 16 import Prelude hiding ((++)) + 17 import Text.Blaze.Html5 as H hiding (map) + 18 import Data.Text.Lazy + 19 + 20 -- | Render the create annotate paste page. + 21 page :: Paste -> Html -> Html + 22 page Paste{..} form = + 23 layoutPage $ Page { + 24 pageTitle = "Annotate: " ++ pasteTitle + 25 , pageBody = lightSection ("Annotate: " ++ fromStrict pasteTitle) form + 26 , pageName = "annotate" + 27 }