Skip to content

Commit

Permalink
Good bye lenses (OverloadedRecordDot works better right now)
Browse files Browse the repository at this point in the history
  • Loading branch information
flober committed Aug 1, 2024
1 parent 7fb3589 commit 449577e
Show file tree
Hide file tree
Showing 5 changed files with 40 additions and 46 deletions.
1 change: 0 additions & 1 deletion battlegrounds.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -42,7 +42,6 @@ library
MonadRandom
, base >=4.7 && <5
, containers ==0.6.7
, lens
, mtl ==2.3.1
, parsec
, random ==1.2.1.2
Expand Down
1 change: 0 additions & 1 deletion package.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -39,7 +39,6 @@ library:
- mtl == 2.3.1
- containers == 0.6.7
- uuid == 1.3.15
- lens
- random == 1.2.1.2
- MonadRandom
- parsec
Expand Down
5 changes: 2 additions & 3 deletions src/Logic.hs
Original file line number Diff line number Diff line change
Expand Up @@ -110,7 +110,7 @@ randomShop t = do
return [CardInstance uuid c | c <- shopCards | uuid <- ids]
where
availableCards :: [Card]
availableCards = filter (\card -> card._cardTier <= t) pool
availableCards = filter (\c -> c.cardTier <= t) pool

sampleNFromList :: (MonadRandom m) => Int -> [a] -> m [a]
sampleNFromList _ [] = return []
Expand All @@ -129,8 +129,7 @@ play ind ps = ps {board = ps.board ++ [findCard ind ps.hand], hand = remove ind
buy :: Index -> PlayerState -> PlayerState
buy ind ps =
let cardInstance = findCard ind ps.shop
card = cardInstance._card
cost = card._baseCost
cost = cardInstance.card.baseCost
moneyLeft = ps.curGold
in if cost > moneyLeft
then
Expand Down
41 changes: 19 additions & 22 deletions src/Model.hs
Original file line number Diff line number Diff line change
@@ -1,11 +1,6 @@
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE TemplateHaskell #-}

module Model (module Model) where

import Control.Lens hiding (Index)
import Data.UUID (UUID)
import System.Random (StdGen)

{-
Design Philosophy:
Expand All @@ -27,20 +22,18 @@ type CardCost = Int
data CardName = Dummy | Dumber | TriDummy | Dumbo | BigDumbo | KingDumbo | DummyWithALongNameItKeepsGoing deriving (Show)

data Card = Card
{ _cardName :: CardName,
_cardTier :: TavernTier,
_baseCost :: CardCost,
_attack :: Attack,
_health :: Health
{ cardName :: CardName,
cardTier :: TavernTier,
baseCost :: CardCost,
attack :: Attack,
health :: Health
}

data CardInstance = CardInstance
{ _cardId :: UUID,
_card :: Card
{ cardId :: UUID,
card :: Card
}

$(makeLenses ''Card)

type Gold = Int

type Hand = [CardInstance]
Expand All @@ -59,13 +52,15 @@ data Phase = HeroSelect | Recruit | Combat deriving (Eq)

-- For now, GameState just keeps track of the solo player and one AI.
data Player = Player | AI

data GameState = GameState
{ playerState :: PlayerState,
{ playerState :: PlayerState,
aiState :: PlayerState,
turn :: Turn
}

data CombatMoves = CombatMoves

data PlayerState = PlayerState
{ tier :: TavernTier,
maxGold :: Gold,
Expand All @@ -83,12 +78,14 @@ data PlayerState = PlayerState
combatSequence :: ([CombatMoves], Int)
}

data Env = Env
{ gen :: StdGen
}

type Index = Int

data GameAction = StartGame

data Command = EndTurn | Help | Buy Index | Sell Index | Play Index
data Command
= Buy Index
| Sell Index
| Play Index
| Refresh
| Freeze
| EndTurn
| Help
| Concede
38 changes: 19 additions & 19 deletions src/View.hs
Original file line number Diff line number Diff line change
Expand Up @@ -72,9 +72,9 @@ renderRecruit gs p =
]
where
ps = selectPlayer p gs
shopCardNames = [(abbrev maxCardNameDisplayLength . show . _cardName . _card) cardInstance | cardInstance <- shop ps]
boardCardNames = [(abbrev maxCardNameDisplayLength . show . _cardName . _card) cardInstance | cardInstance <- board ps]
handCardNames = [(abbrev maxCardNameDisplayLength . show . _cardName . _card) cardInstance | cardInstance <- hand ps]
shopCardNames = [(abbrev maxCardNameDisplayLength . show) cardInstance.card.cardName | cardInstance <- shop ps]
boardCardNames = [(abbrev maxCardNameDisplayLength . show) cardInstance.card.cardName | cardInstance <- board ps]
handCardNames = [(abbrev maxCardNameDisplayLength . show) cardInstance.card.cardName | cardInstance <- hand ps]
freezeText = if frozen ps then "Freeze: Yes" else "Freeze: No"
rerollCostText = "Reroll Cost: " ++ show (rerollCost ps)
tierUpCostText = "Upgrade Cost: " ++ show (tierUpCost ps)
Expand Down Expand Up @@ -103,20 +103,20 @@ helpMenu :: String
helpMenu =
intercalate
"\n"
[ "+--------------------------------------------+",
"| HELP MENU |",
"+--------------------------------------------+",
"| Command | Description |",
"+--------------------------------------------+",
"| buy <n> | Buy card at index <n> |",
"| b <n> | Shortcut for buy <n> |",
"| sell <n> | Sell minion at index <n> |",
"| s <n> | same as sell <n> |",
"| help | Display this menu |",
"| h | Shortcut for help |",
"| endturn | End your turn |",
"| e | Shortcut for endturn |",
"+--------------------------------------------+",
"| Note: number argument <n> starts at 1 |",
"+--------------------------------------------+"
[ "+-----------------------------------------------------+",
"| HELP MENU |",
"+-----------------------------------------------------+",
"| Command | Description |",
"+-----------------------------------------------------+",
"| buy <n> or b <n> | Buy card at shop pos <n> |",
"| sell <n> or s <n> | Sell minion at board pos <n> |",
"| play <n> or p <n> | Play minion at hand pos <n> |",
"| refresh or r | Refresh your tavern |",
"| freeze or f | Freeze your tavern |",
"| endturn or e | End your turn |",
"| help or h | Display this menu |",
"| concede | Concede! |",
"+-----------------------------------------------------+",
"| Note: <n> is a number that starts at 0 |",
"+-----------------------------------------------------+"
]

0 comments on commit 449577e

Please sign in to comment.