Skip to content

Commit

Permalink
Small speedup
Browse files Browse the repository at this point in the history
  • Loading branch information
bartavelle committed Feb 8, 2018
1 parent 8e15649 commit d83e483
Show file tree
Hide file tree
Showing 2 changed files with 10 additions and 5 deletions.
5 changes: 5 additions & 0 deletions src/RMultiSet.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,6 +15,7 @@ module RMultiSet
, delete
, difference
, toSet
, RMultiSet.null
) where

import qualified Data.Set as S
Expand Down Expand Up @@ -53,6 +54,10 @@ toList :: ResourceSet -> [Resource]
toList = concatMap (uncurry (flip replicate)) . toOccurList
{-# INLINE toList #-}

null :: ResourceSet -> Bool
null (ResourceSet r) = r == 0
{-# INLINE null #-}

occur :: Resource -> ResourceSet -> Int
occur r (ResourceSet s) = fromIntegral ((s `shiftR` (fromEnum r * 8)) .&. 0xff)
{-# INLINE occur #-}
Expand Down
10 changes: 5 additions & 5 deletions src/Startups/Utils.hs
Original file line number Diff line number Diff line change
Expand Up @@ -79,7 +79,6 @@ availableResources qt p =
(cv, cn) <- x
rst <- getCombination xs
return (MS.insertMany cv cn rst)

in getCombination effects

-- | Computes if it is possible to get a cheap exchange rate for a given
Expand Down Expand Up @@ -190,9 +189,10 @@ getCardActions :: Age
-> S.Set T.Text
-> [MS.ResourceSet]
-> [MS.ResourceSet]
-> [MS.ResourceSet]
-> Card
-> [(PlayerAction, Exchange, Maybe SpecialInformation)]
getCardActions age playerstate alreadyBuilt lplayer rplayer card
getCardActions age playerstate alreadyBuilt myresources lplayer rplayer card
-- We can't build 2 cards with the same name
| alreadyBuilt ^. contains cardname = []
-- We can have a card that enable free construction of this card
Expand All @@ -215,7 +215,6 @@ getCardActions age playerstate alreadyBuilt lplayer rplayer card
-- Some helpers ...
build e s = (PlayerAction Play card, e, s)
cardname = view cName card
myresources = availableResources OwnRes playerstate
myfunding = playerstate ^. pFunds
Cost neededresources neededfunding = card ^. cCost
-- This is suboptimal : we keep all exchanges that cost the least
Expand Down Expand Up @@ -255,15 +254,16 @@ allowableActions age pid necards players =
nstagecard = getResourceCard comp (succ cstage)
maxstage = getMaxStage comp
alreadyBuilt = setOf (pCards . traverse . cName) playerstate
myresources = availableResources OwnRes playerstate
compaction | cstage == maxstage = mempty
| otherwise = do
(_, exch, si) <- getCardActions age playerstate alreadyBuilt lplayer rplayer nstagecard
(_, exch, si) <- getCardActions age playerstate alreadyBuilt myresources lplayer rplayer nstagecard
-- you can't build your company using a special ability. This is artificial,
-- this check should be done at the "getCardActions" part.
guard (has _Nothing si)
cardToDrop <- _NonEmpty # necards
return (PlayerAction BuildCompany cardToDrop, exch, Nothing)
in concatMap (getCardActions age playerstate alreadyBuilt lplayer rplayer) (_NonEmpty # necards) ++ compaction
in concatMap (getCardActions age playerstate alreadyBuilt myresources lplayer rplayer) (_NonEmpty # necards) ++ compaction
_ -> []

-- | Creates an initial gamestate.
Expand Down

0 comments on commit d83e483

Please sign in to comment.