From 5052da408a92789628bef30c83ad6da65d7d6fc9 Mon Sep 17 00:00:00 2001 From: Gregor Kleen Date: Fri, 10 Mar 2017 00:43:03 +0100 Subject: Bar.hs --- bragi/bar.hs | 80 ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 80 insertions(+) create mode 100755 bragi/bar.hs (limited to 'bragi/bar.hs') diff --git a/bragi/bar.hs b/bragi/bar.hs new file mode 100755 index 00000000..43e1306b --- /dev/null +++ b/bragi/bar.hs @@ -0,0 +1,80 @@ +#! /usr/bin/env nix-shell +#! nix-shell -i runghc -p "haskellPackages.ghcWithPackages (p: with p; [ yesod persistent-postgresql ])" + + +{-# LANGUAGE RecordWildCards #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE GADTs #-} +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE QuasiQuotes #-} +{-# LANGUAGE TemplateHaskell #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE FlexibleInstances #-} + + +import Yesod +import Database.Persist.Postgresql +import Control.Monad.Logger (runStderrLoggingT) +import Control.Monad.Reader + +import Data.Time.Calendar + +import Data.Text (Text) +import qualified Data.Text as Text + +import Data.Map.Lazy (Map) +import qualified Data.Map.Lazy as Map + +import Data.Aeson + + +share [mkPersist sqlSettings, mkMigrate "migrateAll"] [persistLowerCase| +Item + kind Text + bought Day Maybe + expires Day Maybe + opened Day Maybe + deriving Show +|] + +instance ToJSON Item where + toJSON Item{..} = object + [ "kind" .= itemKind + , "bought" .= itemBought + , "expires" .= itemExpires + , "opened" .= itemOpened + ] + +instance ToJSON (Entity Item) where + toJSON = entityIdToJSON + + +data BarInventory = BarInventory + { sqlPool :: ConnectionPool + } + +mkYesod "BarInventory" [parseRoutes| +/ InventoryR GET +|] + +instance Yesod BarInventory + +instance YesodPersist BarInventory where + type YesodPersistBackend BarInventory = SqlBackend + + runDB action = runSqlPool action . sqlPool =<< getYesod + + +main = runStderrLoggingT . withPostgresqlPool "" 5 . runReaderT $ do + sqlPool <- ask + liftIO . warpEnv $ BarInventory{..} + + +getInventoryR :: Handler TypedContent +getInventoryR = do + stock <- runDB $ selectList [] [] + + selectRep $ do + provideRep . return . toJSON $ (stock :: [Entity Item]) -- cgit v1.2.3