Skip to content

Commit

Permalink
more things
Browse files Browse the repository at this point in the history
  • Loading branch information
Derek Gonyeo committed Mar 1, 2018
1 parent b595ad8 commit ee52765
Show file tree
Hide file tree
Showing 17 changed files with 155 additions and 52 deletions.
1 change: 1 addition & 0 deletions cyanide.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -44,6 +44,7 @@ executable cyanide
, Cyanide.UI.PurchaseCreationScreen
, Cyanide.UI.Util
, Cyanide.UI.MainSelectionScreen
, Cyanide.UI.ErrorScreen
, Cyanide.UI.IngredientClassSelectionScreen
, Cyanide.UI.IngredientClassDeletionScreen
, Cyanide.UI.IngredientClassInputScreen
Expand Down
2 changes: 1 addition & 1 deletion src/Cyanide/Data/Recipes.hs
Original file line number Diff line number Diff line change
Expand Up @@ -140,7 +140,7 @@ getRecipesToGlasses conn = do
getRecipesIngredientAvailability :: DBConn -> IO [(Int,Bool)]
getRecipesIngredientAvailability conn = do
P.query_ conn
"SELECT query1.id, query1.avail AND query2.avail FROM (SELECT query1_1.id, coalesce(bool_and(avail),FALSE) AS avail FROM (SELECT recipes.id, ingredient_classes.id as icid, coalesce(bool_or(ingredients.available), FALSE) AS avail FROM recipes INNER JOIN ingredients_to_recipes ON recipe_id = recipes.id INNER JOIN ingredient_classes ON ingredient_class_id = ingredient_classes.id LEFT OUTER JOIN ingredients ON ingredients.class = ingredient_classes.id GROUP BY (ingredient_classes.id,recipes.id)) AS query1_1 GROUP BY query1_1.id) AS query1 INNER JOIN (SELECT recipes.id, bool_and(ingredients.available) as avail FROM recipes INNER JOIN ingredients_to_recipes ON ingredients_to_recipes.recipe_id = recipes.id INNER JOIN ingredients ON ingredient_id = ingredients.id GROUP BY recipes.id) AS query2 ON query1.id = query2.id order by query1.id"
"SELECT query1.id, query1.avail AND query2.avail FROM (SELECT query1_1.id, coalesce(bool_and(avail),FALSE) AS avail FROM (SELECT recipes.id, ingredient_classes.id as icid, coalesce(bool_or(ingredients.available), FALSE) AS avail FROM recipes INNER JOIN ingredients_to_recipes ON recipe_id = recipes.id INNER JOIN ingredient_classes ON ingredient_class_id = ingredient_classes.id LEFT OUTER JOIN ingredients ON ingredients.class = ingredient_classes.id WHERE (ingredients.notForRecipes = FALSE OR ingredients.notForRecipes IS NULL) GROUP BY (ingredient_classes.id,recipes.id)) AS query1_1 GROUP BY query1_1.id) AS query1 INNER JOIN (SELECT recipes.id, bool_and(ingredients.available) as avail FROM recipes INNER JOIN ingredients_to_recipes ON ingredients_to_recipes.recipe_id = recipes.id INNER JOIN ingredients ON ingredient_id = ingredients.id WHERE ingredients.notForRecipes = FALSE GROUP BY recipes.id) AS query2 ON query1.id = query2.id order by query1.id"

newRecipe :: DBConn -> (Maybe T.Text,T.Text,T.Text,Maybe Glass,Maybe Ingredient,[IngredientListItem]) -> IO Recipe
newRecipe conn (mName,garnish,instr,mGlass,mIngr,ingredients) = do
Expand Down
6 changes: 6 additions & 0 deletions src/Cyanide/UI/App.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,6 +21,7 @@ import qualified Cyanide.UI.RecipeInputScreen as RecipeInputScreen
import qualified Cyanide.UI.RecipeInputIngredientScreen as RecipeInputIngredientScreen
import qualified Cyanide.UI.RecipeDeletionScreen as RecipeDeletionScreen
import qualified Cyanide.UI.MainSelectionScreen as MainSelectionScreen
import qualified Cyanide.UI.ErrorScreen as ErrorScreen
import qualified Cyanide.UI.GlassSelectionScreen as GlassSelectionScreen
import qualified Cyanide.UI.GlassDeletionScreen as GlassDeletionScreen
import qualified Cyanide.UI.GlassInputScreen as GlassInputScreen
Expand Down Expand Up @@ -54,6 +55,7 @@ attrMap = B.attrMap Vty.defAttr
, (BL.listSelectedFocusedAttr, Vty.black `B.on` Vty.white)
]
++ MainSelectionScreen.attrMap
++ ErrorScreen.attrMap
++ RecipeDetailScreen.attrMap
++ RecipeInputScreen.attrMap
++ RecipeInputIngredientScreen.attrMap
Expand All @@ -79,6 +81,8 @@ attrMap = B.attrMap Vty.defAttr
handleEvent :: CyanideState -> B.BrickEvent Name () -> B.EventM Name (B.Next CyanideState)
handleEvent s@(CyanideState _ _ MainSelectionScreen) e =
MainSelectionScreen.handleEvent s e
handleEvent s@(CyanideState _ _ (ErrorScreen _ _)) e =
ErrorScreen.handleEvent s e
handleEvent s@(CyanideState _ _ (GlassSelectionScreen _)) e =
GlassSelectionScreen.handleEvent s e
handleEvent s@(CyanideState _ _ (GlassDeletionScreen _)) e =
Expand Down Expand Up @@ -121,6 +125,8 @@ handleEvent s@(CyanideState _ _ (IngredientClassInputScreen _ _ _)) e =
drawUI :: CyanideState -> [B.Widget Name]
drawUI s@(CyanideState _ _ MainSelectionScreen) =
MainSelectionScreen.drawUI s
drawUI s@(CyanideState _ _ (ErrorScreen _ _)) =
ErrorScreen.drawUI s
drawUI s@(CyanideState _ _ (GlassSelectionScreen _)) =
GlassSelectionScreen.drawUI s
drawUI s@(CyanideState _ _ (GlassDeletionScreen _)) =
Expand Down
40 changes: 40 additions & 0 deletions src/Cyanide/UI/ErrorScreen.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,40 @@
{-# LANGUAGE OverloadedStrings #-}

module Cyanide.UI.ErrorScreen where

import Lens.Micro ((^.))
import qualified Brick as B
import qualified Brick.Widgets.List as BL
import qualified Graphics.Vty as Vty
import qualified Data.Text as T
import qualified Data.Vector as V
import qualified Brick.Widgets.Center as BC
import qualified Brick.Widgets.Border as BB
import Data.Monoid
import Control.Monad.IO.Class

import Cyanide.UI.State
import Cyanide.UI.Util

attrMap :: [(B.AttrName, Vty.Attr)]
attrMap = []

handleEvent :: CyanideState -> B.BrickEvent Name () -> B.EventM Name (B.Next CyanideState)
handleEvent s@(CyanideState conn _ (ErrorScreen _ prev)) (B.VtyEvent e) =
case e of
Vty.EvKey (Vty.KEsc) [] ->
B.continue $ s { stateScreen = prev }

_ -> B.continue s
handleEvent s _ = B.continue s

drawUI :: CyanideState -> [B.Widget Name]
drawUI (CyanideState conn _ (ErrorScreen msg _)) = [ui]
where ui = BC.center
$ B.hLimit 80
$ B.vLimit 25 $ B.vBox
[ BC.hCenter $ B.txtWrap msg
, B.txt " "
, renderInstructions [ ("Esc","Previous screen")
]
]
2 changes: 1 addition & 1 deletion src/Cyanide/UI/IngredientClassDeletionScreen.hs
Original file line number Diff line number Diff line change
Expand Up @@ -46,7 +46,7 @@ drawUI (CyanideState conn _ (IngredientClassDeletionScreen l)) = [ui]
ui = BC.center
$ B.hLimit 80
$ B.vLimit 25 $ B.vBox
[ BC.hCenter $ B.txt $ "Are you sure you want to delete the following glass?"
[ BC.hCenter $ B.txt $ "Are you sure you want to delete the following ingredient class?"
, BC.hCenter $ B.padAll 1 $ B.txt n
, renderInstructions [ ("y","Yes")
, ("n","No")
Expand Down
1 change: 1 addition & 0 deletions src/Cyanide/UI/IngredientClassInputScreen.hs
Original file line number Diff line number Diff line change
Expand Up @@ -45,6 +45,7 @@ handleEvent s@(CyanideState conn _ (IngredientClassInputScreen ed mic l)) (B.Vty
newIngredientClass <- liftIO $ IngredientClasses.newIngredientClass conn newIngredientClassName
let newList = BL.listInsert (length l) newIngredientClass l
B.continue $ s { stateScreen = (IngredientClassSelectionScreen newList) }
_ -> B.continue s

ev -> do
newEdit <- BE.handleEditorEvent e ed
Expand Down
55 changes: 46 additions & 9 deletions src/Cyanide/UI/IngredientDetailScreen.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,13 +15,15 @@ import qualified Brick.Focus as BF
import Data.Monoid
import Control.Monad.IO.Class
import Data.Maybe
import qualified Data.List as L

import Cyanide.UI.State
import qualified Cyanide.UI.RecipeInputScreen as RecipeInput
import qualified Cyanide.UI.IngredientInputScreen as IngredientInput
import qualified Cyanide.Data.IngredientClasses as IngredientClasses
import qualified Cyanide.Data.Types as Types
import qualified Cyanide.Data.Ingredients as Ingredients
import qualified Cyanide.Data.Purchases as Purchases
import qualified Cyanide.Data.Recipes as Recipes
import qualified Cyanide.Data.Postgres as Postgres
import qualified Cyanide.Data.Units as Units
Expand All @@ -37,6 +39,34 @@ purchasesListName = "IngredientDetailPurchases"
recipesListName :: Name
recipesListName = "IngredientDetailRecipes"

newIngredientDetailScreen :: Postgres.DBConn -> Types.Ingredient -> (Maybe Types.Ingredient -> CyanideScreen) -> IO CyanideScreen
newIngredientDetailScreen conn ingr prev = do
purchases <- Purchases.getPurchasesForIngredient conn ingr
recipes <- getRecipesUsedIn conn ingr
recipeForIngr <- Recipes.getRecipeForIngredient conn ingr
let f = BF.focusRing $ [purchasesListName]
++ if Types.notForRecipes ingr
then []
else [recipesListName]
purchasesList = BL.list purchasesListName (V.fromList purchases) 1
usedInList = BL.list recipesListName (V.fromList recipes) 1
return $ IngredientDetailScreen ingr purchasesList usedInList recipeForIngr f prev

getRecipesUsedIn :: Postgres.DBConn -> Types.Ingredient -> IO [Types.Recipe]
getRecipesUsedIn conn ingr = do
recipes1 <- liftIO $ Recipes.getRecipesUsingIngredient conn ingr
recipes2 <- case Types.ingredientClass ingr of
Just ic -> do
rlst <- liftIO $ Recipes.getRecipesUsingIngredientClass conn ic
return rlst
Nothing -> return []
return $ L.sortBy (\r1 r2 -> compare (getRecipeName r1) (getRecipeName r2))
$ recipes1 ++ recipes2
where getRecipeName :: Types.Recipe -> T.Text
getRecipeName r = case Types.recipeName r of
Left t -> t
Right i -> "recipe for " `T.append` Types.ingredientName i

handleEvent :: CyanideState -> B.BrickEvent Name () -> B.EventM Name (B.Next CyanideState)
handleEvent s@(CyanideState conn _ scr@(IngredientDetailScreen i ps rs mr f prev)) (B.VtyEvent e) =
case e of
Expand Down Expand Up @@ -76,14 +106,20 @@ handleEvent s@(CyanideState conn _ scr@(IngredientDetailScreen i ps rs mr f prev
in case matches of
[(i,_)] -> i
_ -> 0
goBack Nothing = scr
goBack (Just (ingr,_)) = scr { ingredient = ingr }
goBack Nothing = return $ scr
goBack (Just (ingr,_)) = do
recipes <- liftIO $ getRecipesUsedIn conn ingr
let newIndex = BL.listSelectedElement rs >>= (Just . fst)
newList = BL.listReplace (V.fromList recipes) newIndex rs
return $ scr { ingredient = ingr
, ingredientUsedIn = newList
}

Vty.EvKey (Vty.KChar 'r') [] ->
case mr of
Just r -> do
ingrs <- liftIO $ Recipes.getIngredientsForRecipe conn r
B.continue $ s { stateScreen = RecipeDetailScreen r Nothing ingrs goBack }
B.continue $ s { stateScreen = RecipeDetailScreen r Nothing ingrs (return . goBack) }
Nothing -> do
newScr <- liftIO $ RecipeInput.newRecipeInputScreen conn Nothing [] (Just i) Nothing (return . goBack)
B.continue $ s { stateScreen = newScr }
Expand All @@ -98,10 +134,11 @@ handleEvent s@(CyanideState conn _ scr@(IngredientDetailScreen i ps rs mr f prev
B.continue $ s { stateScreen = RecipeDetailScreen r glass ingrs (goBack j) }
(_,_) -> B.continue s
where goBack j Nothing = let newList = BL.listRemove j rs
in scr { ingredientUsedIn = newList }
goBack _ (Just (r,_,_)) = let newList = BL.listModify (\_ -> r) rs
in scr { ingredientUsedIn = newList }

in return $ scr { ingredientUsedIn = newList }
goBack j (Just _) = do
recipes <- liftIO $ getRecipesUsedIn conn i
let newList = BL.listReplace (V.fromList recipes) (Just j) rs
return $ scr { ingredientUsedIn = newList }
Vty.EvKey (Vty.KChar 'd') [] ->
if BF.focusGetCurrent f == Just purchasesListName
then case BL.listSelectedElement ps of
Expand Down Expand Up @@ -156,8 +193,8 @@ drawUI (CyanideState conn _ (IngredientDetailScreen ing pl rl mr f prev)) = [ui]
]
, B.padLeft (B.Pad 2) $ B.vBox
[ if isJust mr
then B.txt " r - View recipe"
else B.txt " r - Create recipe"
then B.txt "r - View recipe"
else B.txt "r - Create recipe"
, B.txt "a - Toggle availability"
, B.txt "e - Edit ingredient"
]
Expand Down
11 changes: 7 additions & 4 deletions src/Cyanide/UI/IngredientInputScreen.hs
Original file line number Diff line number Diff line change
Expand Up @@ -34,8 +34,9 @@ attrMap = []
handleEvent :: CyanideState -> B.BrickEvent Name () -> B.EventM Name (B.Next CyanideState)
handleEvent s@(CyanideState conn _ scr@(IngredientInputScreen ed cl f si mi prev)) (B.VtyEvent e) =
case e of
Vty.EvKey (Vty.KEsc) [] ->
B.continue $ s { stateScreen = prev Nothing }
Vty.EvKey (Vty.KEsc) [] -> do
newScr <- liftIO $ prev Nothing
B.continue $ s { stateScreen = newScr }

Vty.EvKey (Vty.KChar '\t') [] ->
let newFocus = BF.focusNext f
Expand All @@ -53,13 +54,15 @@ handleEvent s@(CyanideState conn _ scr@(IngredientInputScreen ed cl f si mi prev
let Just (_,iclass) = BL.listSelectedElement cl

newIngredient <- liftIO $ Ingredients.updateIngredient conn (Types.ingredientId oldIng) (n,iclass,si)
B.continue $ s { stateScreen = prev (Just (newIngredient,iclass)) }
newScr <- liftIO $ prev (Just (newIngredient,iclass))
B.continue $ s { stateScreen = newScr }
-- We're creating a new ingredient
(Nothing,Just n) -> do
let Just (_,iclass) = BL.listSelectedElement cl

newIngredient <- liftIO $ Ingredients.newIngredient conn (n,iclass,si)
B.continue $ s { stateScreen = prev (Just (newIngredient,iclass)) }
newScr <- liftIO $ prev (Just (newIngredient,iclass))
B.continue $ s { stateScreen = newScr }

ev -> if BF.focusGetCurrent (f) == Just editorName then do
newEdit <- BE.handleEditorEvent ev ed
Expand Down
23 changes: 3 additions & 20 deletions src/Cyanide/UI/IngredientSelectionScreen.hs
Original file line number Diff line number Diff line change
Expand Up @@ -64,25 +64,8 @@ handleEvent s@(CyanideState conn _ scr@(IngredientSelectionScreen l orig se f))
Vty.EvKey Vty.KEnter [] ->
if BF.focusGetCurrent (f) == Just ingredientsName then do
let Just (j,ingr) = BL.listSelectedElement l
purchases <- liftIO $ Purchases.getPurchasesForIngredient conn ingr
recipes1 <- liftIO $ Recipes.getRecipesUsingIngredient conn ingr
recipes2 <- case Types.ingredientClass ingr of
Just ic -> do
rlst <- liftIO $ Recipes.getRecipesUsingIngredientClass conn ic
return rlst
Nothing -> return []
recipeForIngr <- liftIO $ Recipes.getRecipeForIngredient conn ingr
let f = BF.focusRing $ [IngredientDetail.purchasesListName]
++ if Types.notForRecipes ingr
then []
else [IngredientDetail.recipesListName]
B.continue $ s { stateScreen = IngredientDetailScreen
ingr
(BL.list IngredientDetail.purchasesListName (V.fromList purchases) 1)
(BL.list IngredientDetail.recipesListName (V.fromList (recipes1++recipes2)) 1)
recipeForIngr
f
(goBack j) }
newScr <- liftIO $ IngredientDetail.newIngredientDetailScreen conn ingr (goBack j)
B.continue $ s { stateScreen = newScr }
else if BF.focusGetCurrent (f) == Just searchName then
let newFocus = BF.focusNext f
in B.continue $ s { stateScreen = scr { ingredientListFocusRing = newFocus } }
Expand Down Expand Up @@ -121,7 +104,7 @@ handleEvent s@(CyanideState conn _ scr@(IngredientSelectionScreen l orig se f))
f = BF.focusRing [ IngredientInput.editorName
, IngredientInput.classesName
]
B.continue $ s { stateScreen = (IngredientInputScreen ed iclist f False Nothing goBack) }
B.continue $ s { stateScreen = IngredientInputScreen ed iclist f False Nothing (return . goBack) }
where goBack Nothing = scr
goBack (Just (i,_)) =
let newList = BL.listInsert (length l) i l
Expand Down
2 changes: 1 addition & 1 deletion src/Cyanide/UI/MainSelectionScreen.hs
Original file line number Diff line number Diff line change
Expand Up @@ -76,7 +76,7 @@ drawUI (CyanideState conn _ MainSelectionScreen) =
$ B.vLimit 25
$ B.hBox [ bottle1
, B.txt " "
, B.hLimit 34
, B.hLimit 35
$ B.vBox [ BC.hCenter $ B.txt "Cyanide: home bar management system"
, BC.hCenter $ BB.hBorder
, renderInstructions [ ("r","Recipes")
Expand Down
5 changes: 3 additions & 2 deletions src/Cyanide/UI/PurchaseCreationScreen.hs
Original file line number Diff line number Diff line change
Expand Up @@ -56,7 +56,7 @@ handleEvent s@(CyanideState conn _ scr@(PurchaseCreationScreen ing le ce ae ue f
case (readMaybe (T.unpack $ c),readMaybe (T.unpack a)) of
(Just cn,Just an) ->
if cn < 0 || an < 0 || cn > 999999 || an > 999999
then B.continue s
then B.continue $ s { stateScreen = ErrorScreen "The cost and amount must be between 0 and 999999." scr }
else do
-- mark the ingredient as available
liftIO $ Ingredients.updateIngredientAvailability conn (ing,True)
Expand All @@ -67,7 +67,8 @@ handleEvent s@(CyanideState conn _ scr@(PurchaseCreationScreen ing le ce ae ue f
let today = utctDay now
liftIO $ Purchases.newPurchase conn (ing,today,l,cn,an,u)
B.continue $ s { stateScreen = prev (Just (newIngredient,Types.Purchase today l cn an u)) }
_ -> B.continue s
(Nothing,_) -> B.continue $ s { stateScreen = ErrorScreen "Couldn't parse the cost. Please enter the cost in cents, so $12.95 would become 1295." scr }
(_,Nothing) -> B.continue $ s { stateScreen = ErrorScreen "Couldn't parse the amount. Please enter an integer." scr }
_ -> B.continue s

ev -> if BF.focusGetCurrent (fe) == Just locationEditorName then do
Expand Down
13 changes: 8 additions & 5 deletions src/Cyanide/UI/RecipeDeletionScreen.hs
Original file line number Diff line number Diff line change
Expand Up @@ -26,15 +26,18 @@ attrMap = []
handleEvent :: CyanideState -> B.BrickEvent Name () -> B.EventM Name (B.Next CyanideState)
handleEvent s@(CyanideState conn _ (RecipeDeletionScreen r prev)) (B.VtyEvent e) =
case e of
Vty.EvKey (Vty.KEsc) [] ->
B.continue $ s { stateScreen = prev False }
Vty.EvKey (Vty.KEsc) [] -> do
newScr <- liftIO $ prev False
B.continue $ s { stateScreen = newScr }

Vty.EvKey (Vty.KChar 'n') [] ->
B.continue $ s { stateScreen = prev False }
Vty.EvKey (Vty.KChar 'n') [] -> do
newScr <- liftIO $ prev False
B.continue $ s { stateScreen = newScr }

Vty.EvKey (Vty.KChar 'y') [] -> do
newScr <- liftIO $ prev True
liftIO $ Recipes.deleteRecipe conn r
B.continue $ s { stateScreen = prev True }
B.continue $ s { stateScreen = newScr }

_ -> B.continue s
handleEvent s _ = B.continue s
Expand Down
Loading

0 comments on commit ee52765

Please sign in to comment.