Add options to poll

This commit is contained in:
Konrad Merz 2015-03-28 17:03:10 +01:00
parent 44c0eb1749
commit 8768ed8775
2 changed files with 51 additions and 13 deletions

View file

@ -2,16 +2,28 @@
module Noodle.Views.Show where
import Text.Blaze.Html5
import Text.Blaze.Html5.Attributes
import Text.Blaze.Html5 as H
import Text.Blaze.Html5.Attributes as A
import Text.Blaze.Html.Renderer.Text
import Data.Monoid ((<>))
render poll = do
html $ do
body $ do
h3 "Show of poll"
h5 "Name:"
p $ toHtml $ fst poll
h5 "Description"
p $ toHtml $ snd poll
render (pollId, pollName, pollDesc) options = do
H.html $ do
H.body $ do
H.h3 "Show of poll"
H.h5 "Name:"
H.p $ toHtml pollName
H.h5 "Description"
H.p $ toHtml pollDesc
H.h5 "Options"
H.ul $ do
mapM_ renderLn options
H.br
H.legend "New option:"
H.form ! A.method "post" ! A.action "/options/" $ do
H.label "Name: "
H.input ! A.name "name"
H.input ! A.type_ "hidden" ! A.value (H.stringValue (show pollId)) !
A.name "id"
H.input ! A.type_ "submit" ! A.value "Add Options"
where renderLn o = H.li $ H.toHtml $ (snd o)

View file

@ -28,6 +28,10 @@ share [mkPersist sqlSettings, mkMigrate "migrateAll"] [persistLowerCase|
name String
desc String
deriving Show
Option
pollId PollId
name String
deriving Show
|]
blaze = S.html . renderHtml
@ -49,13 +53,23 @@ scottySite = do
S.get "/polls/:id" $ do
id <- S.param "id"
poll <- liftIO $ getPollById id
blaze $ Noodle.Views.Show.render $ pollValues $ head poll
options <- liftIO $ getOptionsByPollId id
blaze $ Noodle.Views.Show.render (pollValues $ head poll)
(optionsValues options)
S.post "/polls/" $ do
name <- S.param "name"
desc <- S.param "desc"
createPoll name desc
polls <- liftIO $ allPolls
blaze $ Noodle.Views.Index.render $ pollNames $ polls
S.post "/options/" $ do
name <- S.param "name" :: S.ActionM String
pId <- S.param "id":: S.ActionM String
createOption pId name
poll <- liftIO $ getPollById pId
options <- liftIO $ getOptionsByPollId pId
blaze $ Noodle.Views.Show.render (pollValues $ head poll)
(optionsValues options)
initDb = do
runSqlite "noodle.db" $ do
@ -78,5 +92,17 @@ pollNames = map (\i -> ((getPollId i), (pollName (entityVal i))))
getPollId x = unSqlBackendKey $ unPollKey $ entityKey x
pollValues :: Entity Poll -> (String, String)
pollValues i = ((pollName (entityVal i)), (pollDesc (entityVal i)))
pollValues i = ((getPollId i), (pollName (entityVal i)), (pollDesc (entityVal i)))
optionsValues = map (\o -> ((getOptionId o),
(optionName (entityVal o))))
getOptionsByPollId id = do
runSqlite "noodle.db" $ do
selectList [OptionPollId ==. (toSqlKey (read id))] []
getOptionId x = unSqlBackendKey $ unOptionKey $ entityKey x
createOption pId name = do
runSqlite "noodle.db" $ do
insert $ Option (toSqlKey (read pId)) name