about summary refs log tree commit diff
path: root/users/grfn/xanthous/src/Xanthous/Entities/Item.hs
diff options
context:
space:
mode:
authorGriffin Smith <grfn@gws.fyi>2021-06-19T15·49-0400
committergrfn <grfn@gws.fyi>2021-06-23T21·52+0000
commitd8bd8e7eea5dcef4901bee14b8fe3027fd8605ac (patch)
tree0b9e02b87175ff8d16baa5a7d8a1c60a267cea28 /users/grfn/xanthous/src/Xanthous/Entities/Item.hs
parent8b97683f6ef53605130542ea6de1e587b353aa5b (diff)
feat(xanthous) Generate random volume+density for items r/2679
Generate random volumes and densities for items based on the ranges for
those two quantities in the raw when building instances of items.

Since this is the first time creating an item is impure, this also lifts
entity generation into a (random) monadic context

Change-Id: I2de4880e8144f7ff9e1304eb32806ed1d7affa18
Reviewed-on: https://cl.tvl.fyi/c/depot/+/3226
Reviewed-by: grfn <grfn@gws.fyi>
Tested-by: BuildkiteCI
Diffstat (limited to 'users/grfn/xanthous/src/Xanthous/Entities/Item.hs')
-rw-r--r--users/grfn/xanthous/src/Xanthous/Entities/Item.hs32
1 files changed, 23 insertions, 9 deletions
diff --git a/users/grfn/xanthous/src/Xanthous/Entities/Item.hs b/users/grfn/xanthous/src/Xanthous/Entities/Item.hs
index b50a5eab80..6647c42731 100644
--- a/users/grfn/xanthous/src/Xanthous/Entities/Item.hs
+++ b/users/grfn/xanthous/src/Xanthous/Entities/Item.hs
@@ -1,49 +1,63 @@
 {-# LANGUAGE TemplateHaskell #-}
 {-# LANGUAGE StandaloneDeriving #-}
+{-# LANGUAGE RecordWildCards #-}
 --------------------------------------------------------------------------------
 module Xanthous.Entities.Item
   ( Item(..)
   , itemType
+  , density
+  , volume
   , newWithType
   , isEdible
+  , weight
   ) where
 --------------------------------------------------------------------------------
 import           Xanthous.Prelude
-import           Test.QuickCheck
+import           Test.QuickCheck (Arbitrary, CoArbitrary, Function)
 import           Data.Aeson (ToJSON, FromJSON)
 import           Data.Aeson.Generic.DerivingVia
+import           Control.Monad.Random (MonadRandom)
 --------------------------------------------------------------------------------
-import           Xanthous.Entities.RawTypes hiding (Item, description, isEdible)
+import           Xanthous.Entities.RawTypes (ItemType)
 import qualified Xanthous.Entities.RawTypes as Raw
 import           Xanthous.Game.State
+import           Xanthous.Data (Grams, Per, Cubic, Meters, (|*|))
+import           Xanthous.Util.QuickCheck (GenericArbitrary(GenericArbitrary))
+import           Xanthous.Random (choose, FiniteInterval(..))
 --------------------------------------------------------------------------------
 
 data Item = Item
   { _itemType :: ItemType
+  , _density  :: Grams `Per` Cubic Meters
+  , _volume   :: Cubic Meters
   }
   deriving stock (Eq, Show, Ord, Generic)
   deriving anyclass (NFData, CoArbitrary, Function)
   deriving Draw via DrawRawChar "_itemType" Item
+  deriving Arbitrary via GenericArbitrary Item
   deriving (ToJSON, FromJSON)
        via WithOptions '[ FieldLabelModifier '[Drop 1] ]
                        Item
 makeLenses ''Item
 
-{-# ANN Item ("HLint: ignore Use newtype instead of data" :: String )#-}
-
 -- deriving via (Brainless Item) instance Brain Item
 instance Brain Item where step = brainVia Brainless
 
-instance Arbitrary Item where
-  arbitrary = Item <$> arbitrary
-
 instance Entity Item where
   description = view $ itemType . Raw.description
   entityChar = view $ itemType . Raw.char
   entityCollision = const Nothing
 
-newWithType :: ItemType -> Item
-newWithType = Item
+newWithType :: MonadRandom m => ItemType -> m Item
+newWithType _itemType = do
+  _density <- choose . FiniteInterval $ _itemType ^. Raw.density
+  _volume  <- choose . FiniteInterval $ _itemType ^. Raw.volume
+  pure Item {..}
 
 isEdible :: Item -> Bool
 isEdible = Raw.isEdible . view itemType
+
+-- | The weight of this item, calculated by multiplying its volume by the
+-- density of its material
+weight :: Item -> Grams
+weight item = (item ^. density) |*| (item ^. volume)