From 4ce9751c9e645916fdde71874c2cdadd252f32a0 Mon Sep 17 00:00:00 2001 From: Joris Guyonvarch Date: Mon, 6 Jul 2015 00:16:45 +0200 Subject: Setting up Scotty, Persistent, Clay, Blaze, Esqueleto, Elm --- src/client/Main.elm | 43 ++++++++++++++++++++++++++++ src/client/View/Page.elm | 18 ++++++++++++ src/server/Application.hs | 62 ++++++++++++++++++++++++++++++++++++++++ src/server/Design/Color.hs | 6 ++++ src/server/Design/Global.hs | 21 ++++++++++++++ src/server/Main.hs | 32 +++++++++++++++++++++ src/server/Model/Database.hs | 44 ++++++++++++++++++++++++++++ src/server/Model/Json/Payment.hs | 21 ++++++++++++++ src/server/Model/Payment.hs | 36 +++++++++++++++++++++++ src/server/Model/User.hs | 30 +++++++++++++++++++ src/server/View/Page.hs | 30 +++++++++++++++++++ 11 files changed, 343 insertions(+) create mode 100644 src/client/Main.elm create mode 100644 src/client/View/Page.elm create mode 100644 src/server/Application.hs create mode 100644 src/server/Design/Color.hs create mode 100644 src/server/Design/Global.hs create mode 100644 src/server/Main.hs create mode 100644 src/server/Model/Database.hs create mode 100644 src/server/Model/Json/Payment.hs create mode 100644 src/server/Model/Payment.hs create mode 100644 src/server/Model/User.hs create mode 100644 src/server/View/Page.hs (limited to 'src') diff --git a/src/client/Main.elm b/src/client/Main.elm new file mode 100644 index 0000000..dd87b8c --- /dev/null +++ b/src/client/Main.elm @@ -0,0 +1,43 @@ +module Main + ( main + ) where + +import Graphics.Element exposing (..) + +import Html exposing (Html) + +import Http +import Json.Decode as Json exposing ((:=)) +import Task exposing (..) +import Date exposing (..) + +import View.Page exposing (renderPage) + +main : Html +main = renderPage + +getPayments : Task Http.Error (List Payment) +getPayments = Http.get paymentsDecoder "/payments" + +type alias Payments = List Payment + +type alias Payment = + { creation : Date + , name : String + , cost : Int + , userName : String + } + +paymentsDecoder : Json.Decoder Payments +paymentsDecoder = Json.list paymentDecoder + +paymentDecoder : Json.Decoder Payment +paymentDecoder = + Json.object4 Payment + ("creation" := dateDecoder) + ("name" := Json.string) + ("cost" := Json.int) + ("userName" := Json.string) + +dateDecoder : Json.Decoder Date +dateDecoder = Json.customDecoder Json.string Date.fromString diff --git a/src/client/View/Page.elm b/src/client/View/Page.elm new file mode 100644 index 0000000..47e0c1c --- /dev/null +++ b/src/client/View/Page.elm @@ -0,0 +1,18 @@ +module View.Page + ( renderPage + ) where + +import Html exposing (..) +import Html as H +import Html.Attributes exposing (..) +import Html.Attributes as A +import Html.Events exposing (..) + +renderPage : Html +renderPage = + header + [] + [ h1 + [] + [ text "Payments" ] + ] diff --git a/src/server/Application.hs b/src/server/Application.hs new file mode 100644 index 0000000..344b38c --- /dev/null +++ b/src/server/Application.hs @@ -0,0 +1,62 @@ +{-# LANGUAGE OverloadedStrings #-} + +module Application + ( getIndexAction + , getUsersAction + , getPaymentsAction + , addUserAction + , deleteUserAction + , insertPaymentAction + ) where + +import Web.Scotty + +import Network.HTTP.Types.Status (badRequest400) + +import Database.Persist + +import Control.Monad.IO.Class (liftIO) + +import Data.Text (Text) +import Data.String (fromString) + +import Model.Database (runDb) +import Model.User +import Model.Payment + +import View.Page (page) + +getIndexAction :: ActionM () +getIndexAction = do + html $ page + +getUsersAction :: ActionM () +getUsersAction = do + users <- liftIO $ runDb getUsers + html . fromString . show $ users + +getPaymentsAction :: ActionM () +getPaymentsAction = do + payments <- liftIO $ runDb getPayments + json payments + +addUserAction :: Text -> Text -> ActionM () +addUserAction email name = do + _ <- liftIO . runDb $ insertUser email name + html "Ok" + +deleteUserAction :: Text -> ActionM () +deleteUserAction email = do + _ <- liftIO . runDb $ deleteUser email + html "Ok" + +insertPaymentAction :: Text -> Text -> Int -> ActionM () +insertPaymentAction email name cost = do + maybeUser <- liftIO . runDb $ getUser email + case maybeUser of + Just user -> do + _ <- liftIO . runDb $ insertPayment (entityKey user) name cost + return () + Nothing -> do + status badRequest400 + html "Not found" diff --git a/src/server/Design/Color.hs b/src/server/Design/Color.hs new file mode 100644 index 0000000..bc7fca0 --- /dev/null +++ b/src/server/Design/Color.hs @@ -0,0 +1,6 @@ +module Design.Color where + +import qualified Clay.Color as C + +brown :: C.Color +brown = C.brown diff --git a/src/server/Design/Global.hs b/src/server/Design/Global.hs new file mode 100644 index 0000000..cc16e2e --- /dev/null +++ b/src/server/Design/Global.hs @@ -0,0 +1,21 @@ +module Design.Global + ( globalDesign + ) where + +import Clay + +import Data.Text.Lazy (Text) + +import Design.Color as C + +globalDesign :: Text +globalDesign = renderWith compact [] global + +global :: Css +global = + header ? + h1 ? do + fontSize (px 40) + textAlign (alignSide sideCenter) + margin (px 30) (px 0) (px 30) (px 0) + color C.brown diff --git a/src/server/Main.hs b/src/server/Main.hs new file mode 100644 index 0000000..981c865 --- /dev/null +++ b/src/server/Main.hs @@ -0,0 +1,32 @@ +{-# LANGUAGE OverloadedStrings #-} + +import Web.Scotty + +import Network.Wai.Middleware.Static + +import Data.Text (Text) + +import Application + +import Model.Database (runMigrations) + +main :: IO () +main = do + runMigrations + scotty 3000 $ do + middleware $ staticPolicy (noDots >-> addBase "public") + get "/" getIndexAction + get "/users" getUsersAction + get "/payments" getPaymentsAction + post "/user/add" $ do + email <- param "email" :: ActionM Text + name <- param "name" :: ActionM Text + addUserAction email name + post "/user/delete" $ do + email <- param "email" :: ActionM Text + deleteUserAction email + post "/payment/add" $ do + email <- param "email" :: ActionM Text + name <- param "name" :: ActionM Text + cost <- param "cost" :: ActionM Int + insertPaymentAction email name cost diff --git a/src/server/Model/Database.hs b/src/server/Model/Database.hs new file mode 100644 index 0000000..abf235d --- /dev/null +++ b/src/server/Model/Database.hs @@ -0,0 +1,44 @@ +{-# LANGUAGE EmptyDataDecls #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE GADTs #-} +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE QuasiQuotes #-} +{-# LANGUAGE TemplateHaskell #-} +{-# LANGUAGE TypeFamilies #-} + +module Model.Database where + +import Control.Monad.Logger (NoLoggingT, runNoLoggingT) +import Control.Monad.Trans.Resource (runResourceT, ResourceT) + +import Data.Text +import Data.Time.Clock (UTCTime) + +import Database.Persist.Sqlite +import Database.Persist.TH + +share [mkPersist sqlSettings, mkMigrate "migrateAll"] [persistLowerCase| +User + creation UTCTime + email Text + name Text + EmailKey email + deriving Show +Payment + userId UserId + creation UTCTime + name Text + cost Int + deriving Show +|] + +type Persist a = SqlPersistT (ResourceT (NoLoggingT IO)) a + +runDb :: Persist a -> IO a +runDb = runNoLoggingT . runResourceT . withSqliteConn "database" . runSqlConn + +runMigrations :: IO () +runMigrations = runDb $ runMigration migrateAll diff --git a/src/server/Model/Json/Payment.hs b/src/server/Model/Json/Payment.hs new file mode 100644 index 0000000..de6beb9 --- /dev/null +++ b/src/server/Model/Json/Payment.hs @@ -0,0 +1,21 @@ +{-# LANGUAGE DeriveGeneric #-} + +module Model.Json.Payment + ( Payment(..) + ) where + +import GHC.Generics + +import Data.Time +import Data.Text (Text) +import Data.Aeson + +data Payment = Payment + { creation :: UTCTime + , name :: Text + , cost :: Int + , userName :: Text + } deriving (Show, Generic) + +instance FromJSON Payment +instance ToJSON Payment diff --git a/src/server/Model/Payment.hs b/src/server/Model/Payment.hs new file mode 100644 index 0000000..b35e13c --- /dev/null +++ b/src/server/Model/Payment.hs @@ -0,0 +1,36 @@ +module Model.Payment + ( getPayments + , insertPayment + ) where + +import Data.Text (Text) +import Data.Time.Clock (getCurrentTime) + +import Control.Monad.IO.Class (liftIO) + +import Database.Persist +import Database.Esqueleto +import qualified Database.Esqueleto as E + +import Model.Database +import qualified Model.Json.Payment as P + +getPayments :: Persist [P.Payment] +getPayments = do + xs <- select $ + from $ \(payment `InnerJoin` user) -> do + on (payment ^. PaymentUserId E.==. user ^. UserId) + return (payment, user) + return (map getJsonPayment xs) + +getJsonPayment :: (Entity Payment, Entity User) -> P.Payment +getJsonPayment (paymentEntity, userEntity) = + let payment = entityVal paymentEntity + user = entityVal userEntity + in P.Payment (paymentCreation payment) (paymentName payment) (paymentCost payment) (userName user) + + +insertPayment :: UserId -> Text -> Int -> Persist PaymentId +insertPayment userId name cost = do + now <- liftIO getCurrentTime + insert $ Payment userId now name cost diff --git a/src/server/Model/User.hs b/src/server/Model/User.hs new file mode 100644 index 0000000..ddca0fb --- /dev/null +++ b/src/server/Model/User.hs @@ -0,0 +1,30 @@ +module Model.User + ( getUsers + , getUser + , insertUser + , deleteUser + ) where + +import Data.Text (Text) +import Data.Time.Clock (getCurrentTime) + +import Control.Monad.IO.Class (liftIO) + +import Database.Persist + +import Model.Database + +getUsers :: Persist [User] +getUsers = map entityVal <$> selectList [] [Desc UserCreation] + +getUser :: Text -> Persist (Maybe (Entity User)) +getUser email = selectFirst [UserEmail ==. email] [] + +insertUser :: Text -> Text -> Persist UserId +insertUser email name = do + now <- liftIO getCurrentTime + insert $ User now email name + +deleteUser :: Text -> Persist () +deleteUser email = + deleteWhere [UserEmail ==. email] diff --git a/src/server/View/Page.hs b/src/server/View/Page.hs new file mode 100644 index 0000000..aa4df72 --- /dev/null +++ b/src/server/View/Page.hs @@ -0,0 +1,30 @@ +{-# LANGUAGE OverloadedStrings #-} + +module View.Page + ( page + ) where + +import Data.Text.Internal.Lazy (Text) + +import Text.Blaze.Html +import Text.Blaze.Html5 +import Text.Blaze.Html5.Attributes +import qualified Text.Blaze.Html5 as H +import Text.Blaze.Html.Renderer.Text (renderHtml) + +import Design.Global (globalDesign) + +page :: Text +page = + renderHtml . docTypeHtml $ do + H.head $ do + meta ! charset "UTF-8" + H.title "Payments" + script ! src "/javascripts/client.js" $ "" + link ! rel "stylesheet" ! type_ "text/css" ! href "/css/reset.css" + link ! rel "stylesheet" ! href "/css/font-awesome/css/font-awesome.min.css" + link ! rel "stylesheet" ! type_ "text/css" ! href "/css/global.css" + link ! rel "icon" ! type_ "image/png" ! href "/images/icon.png" + H.style $ toHtml globalDesign + body $ + script ! src "/javascripts/elmLauncher.js" $ "" -- cgit v1.2.3