By | Chris Done;Chris Done |
At | 2013-02-28; 2013-02-28 |
Title | make sure annotation/edit's sorted |
Description |
Edit file src/Amelie/View/Paste.hs 33188 → 33188
63 63 submitInput "submit" "Submit"
64 64 in (pasteSubmit pf,form)
65 65 66 66 where action = case pfAnnotatePaste of
67 67 Just Paste{..} -> "/annotate/" ++ show (fromMaybe pasteId pasteParent)
+ 68 where pasteParent = case pasteType of
+ 69 AnnotationOf pid -> Just pid
+ 70 _ -> Nothing
68 71 Nothing ->
69 72 case pfEditPaste of
70 73 Just Paste{..} -> "/edit/" ++ show pasteId
71 74 Nothing -> "/new"
72 75 73 76 -- | The paste submitting formlet itself.
74 77 pasteSubmit :: PasteFormlet -> Formlet PasteSubmit
75 78 pasteSubmit pf@PasteFormlet{..} =
76 79 PasteSubmit
77 80 <$> pure (getPasteId pf)
+ 81 <*> pure (case pfAnnotatePaste of
+ 82 Just pid -> AnnotationOf (pasteId pid)
+ 83 _ -> case pfEditPaste of
+ 84 Just pid -> RevisionOf (pasteId pid)
+ 85 _ -> NormalPaste)
78 86 <*> req (textInput "title" "Title" (annotateTitle <|> editTitle))
79 87 <*> defaulting "Anonymous Coward" (textInput "author" "Author" Nothing)
80 88 <*> parse (traverse lookupLang)
81 89 (opt (dropInput languages "language" "Language" (snd defChan)))
82 90 <*> parse (traverse lookupChan)
83 91 (opt (dropInput channels "channel" "Channel" (fst defChan)))
- 84 <*> req (areaInput "paste" "Paste" annotateContent)
+ 92 <*> req (areaInput "paste" "Paste" (annotateContent <|> editContent))
85 93 <*> opt (wrap (H.div ! aClass "spam") (textInput "email" "Email" Nothing))
86 94 87 95 where defaulting def = fmap swap where
88 96 swap "" = def
89 97 swap x = x
… … … … 125 133 mapM_ (viewPaste pastes chans langs) annotations
126 134 127 135 -- | View a paste's details and content.
128 136 viewPaste :: [Paste] -> [Channel] -> [Language] -> (Paste,[Hint]) -> Html
129 137 viewPaste pastes chans langs (paste@Paste{..},hints) = do
- 130 case pasteParent of
- 131 Nothing -> return ()
- 132 Just{} -> let an = "a" ++ show (fromIntegral pasteId :: Integer)
- 133 in a ! A.name (toValue an) $ return ()
134 138 pasteDetails pastes chans langs paste
135 139 pasteContent langs paste
136 140 viewHints hints
137 141 138 142 -- | List the details of the page in a dark section.
… … … … Edit file src/Amelie/Types/Paste.hs 33188 → 33188
5 5 6 6 -- | The paste type.
7 7 8 8 module Amelie.Types.Paste
9 9 (Paste(..)
+ 10 ,PasteType(..)
10 11 ,PasteSubmit(..)
11 12 ,PasteFormlet(..)
12 13 ,ExprFormlet(..)
13 14 ,PastePage(..)
14 15 ,StepsPage(..)
… … … … 41 42 ,pasteAuthor :: Text
42 43 ,pasteLanguage :: Maybe LanguageId
43 44 ,pasteChannel :: Maybe ChannelId
44 45 ,pastePaste :: Text
45 46 ,pasteViews :: Integer
- 46 ,pasteParent :: Maybe PasteId
+ 47 ,pasteType :: PasteType
47 48 } deriving Show
+ 49 + 50 -- | The type of a paste.
+ 51 data PasteType
+ 52 = NormalPaste
+ 53 | AnnotationOf PasteId
+ 54 | RevisionOf PasteId
+ 55 deriving Show
48 56 49 57 -- | A paste submission or annotate.
50 58 data PasteSubmit = PasteSubmit {
51 59 pasteSubmitId :: Maybe PasteId
+ 60 ,pasteSubmitType :: PasteType
52 61 ,pasteSubmitTitle :: Text
53 62 ,pasteSubmitAuthor :: Text
54 63 ,pasteSubmitLanguage :: Maybe LanguageId
55 64 ,pasteSubmitChannel :: Maybe ChannelId
56 65 ,pasteSubmitPaste :: Text
… … … … 68 77 , pasteChannel = channel
69 78 , pastePaste = content
70 79 , pasteDate = zonedTimeToUTC date
71 80 , pasteId = pid
72 81 , pasteViews = views
- 73 , pasteParent = parent
+ 82 , pasteType = case annotation_of of
+ 83 Just pid -> AnnotationOf pid
+ 84 _ -> case revision_of of
+ 85 Just pid -> RevisionOf pid
+ 86 _ -> NormalPaste
74 87 }
- 75 where (pid,title,content,author,date,views,language,channel,parent) =
+ 88 where (pid,title,content,author,date,views,language,channel,annotation_of,revision_of) =
76 89 convertResults field values
77 90 78 91 data PasteFormlet = PasteFormlet {
79 92 pfSubmitted :: Bool
80 93 , pfErrors :: [Text]
… … … … 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 ,createOrAnnotate
+ 13 ,createOrUpdate
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 createOrAnnotate :: [Language] -> [Channel] -> PasteSubmit -> Model (Maybe PasteId)
- 91 createOrAnnotate langs chans paste@PasteSubmit{..} = do
+ 90 createOrUpdate :: [Language] -> [Channel] -> PasteSubmit -> Model (Maybe PasteId)
+ 91 createOrUpdate 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 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 ,"(title,author,content,channel,language,annotation_of)"
+ 101 ,"(title,author,content,channel,language,annotation_of,revision_of)"
102 102 ,"VALUES"
- 103 ,"(?,?,?,?,?,?)"
+ 103 ,"(?,?,?,?,?,?,?)"
104 104 ,"returning id"]
105 105 (pasteSubmitTitle,pasteSubmitAuthor,pasteSubmitPaste
- 106 ,pasteSubmitChannel,pasteSubmitLanguage,pasteSubmitId)
+ 106 ,pasteSubmitChannel,pasteSubmitLanguage,ann_pid,rev_pid)
107 107 when (lang == Just "haskell") $ just res $ createHints ps
108 108 just (pasteSubmitChannel >>= lookupChan) $ \chan ->
109 109 just res $ \pid -> do
110 110 annotated <- maybe (return Nothing) getPasteById pasteSubmitId
111 111 announcePaste annotated (channelName chan) ps pid
… … … … 113 113 114 114 where lookupChan cid = find ((==cid).channelId) chans
115 115 lookupLang lid = find ((==lid).languageId) langs
116 116 lang = pasteSubmitLanguage >>= (fmap languageName . lookupLang)
117 117 just j m = maybe (return ()) m j
+ 118 ann_pid = case pasteSubmitType of AnnotationOf pid -> Just pid; _ -> Nothing
+ 119 rev_pid = case pasteSubmitType of RevisionOf pid -> Just pid; _ -> Nothing
118 120 119 121 -- | Create the hints for a paste.
120 122 createHints :: PasteSubmit -> PasteId -> Model ()
121 123 createHints ps pid = do
122 124 hints <- generateHintsForPaste ps pid
… … … … 190 192 ,pasteSubmitLanguage
191 193 ,pasteSubmitChannel
192 194 ,pid)
193 195 return ()
194 196 - 195 where fields = "title author content channel language"
+ 197 where fields = "title author content language channel"
196 198 set key = unwords [key,"=","?"]
… … … … Edit file src/Amelie/Controller/New.hs 33188 → 33188
31 31 langs <- model $ getLanguages
32 32 defChan <- fmap decodeUtf8 <$> getParam "channel"
33 33 pid <- if style == NewPaste then return Nothing else getPasteId
34 34 case pid of
35 35 Just pid -> do
- 36 apaste <- if style == AnnotatePaste
- 37 then model $ getPasteById (fromIntegral pid)
- 38 else return Nothing
- 39 epaste <- if style == EditPaste
- 40 then model $ getPasteById (fromIntegral pid)
- 41 else return Nothing
- 42 let paste = apaste <|> epaste
+ 36 paste <- model $ getPasteById (fromIntegral pid)
+ 37 let apaste | style == AnnotatePaste = paste
+ 38 | otherwise = Nothing
+ 39 let epaste | style == EditPaste = paste
+ 40 | otherwise = Nothing
43 41 form <- pasteForm chans langs defChan apaste epaste
44 42 justOrGoHome paste $ \paste -> do
45 43 case style of
46 44 AnnotatePaste -> output $ Annotate.page paste form
47 45 EditPaste -> output $ Edit.page paste form
… … … … Edit file src/Amelie/Controller/Report.hs 33188 → 33188
13 13 import Amelie.Model
14 14 import Amelie.Model.Paste (getPasteById)
15 15 import Amelie.Model.Report
16 16 import Amelie.View.Report
17 17 import qualified Amelie.View.Thanks as Thanks
+ 18 import Amelie.Types.Cache as Key
+ 19 import Amelie.Controller.Cache (resetCache)
18 20 19 21 import Control.Applicative
20 22 import Data.ByteString.UTF8 (toString)
21 23 import Data.Maybe
22 24 import Data.Monoid.Operator ((++))
… … … … 38 40 (frm,val) <- exprForm
39 41 case val of
40 42 Just comment -> do
41 43 _ <- model $ createReport ReportSubmit { rsPaste = fromIntegral pid
42 44 , rsComments = comment }
+ 45 resetCache Key.Home
43 46 output $ Thanks.page "Reported" $
44 47 "Thanks, your comments have " ++
45 48 "been reported to the administrator."
46 49 Nothing -> maybe goHome (output . page frm) paste
47 50 … … … …