Skip to content

Commit

Permalink
add darts as dungeon items, a bit more rare than swords
Browse files Browse the repository at this point in the history
  • Loading branch information
Mikolaj committed Mar 14, 2011
1 parent 6097568 commit 0940258
Show file tree
Hide file tree
Showing 2 changed files with 16 additions and 8 deletions.
1 change: 1 addition & 0 deletions src/Grammar.hs
Expand Up @@ -39,6 +39,7 @@ objectItem _ n Amulet = makeObject n id "amulet"
objectItem _ n Gem = makeObject n id "gem"
objectItem _ n Gold = makeObject n id "gold piece"
objectItem _ n (Sword i) = makeObject n id ("(+" ++ show i ++ ") sword")
objectItem _ n Dart = makeObject n id "dart"

subjectVerbIObject :: State -> Movable -> String -> Item -> String -> String
subjectVerbIObject state m v o add =
Expand Down
23 changes: 15 additions & 8 deletions src/Item.hs
@@ -1,6 +1,7 @@
module Item where

import Data.Binary
import Data.Binary.Put
import Data.Map as M
import Data.Set as S
import Data.List as L
Expand Down Expand Up @@ -28,6 +29,7 @@ data ItemType =
| Gem
| Gold
| Sword Int
| Dart
deriving (Eq, Ord, Show)

data PotionType =
Expand Down Expand Up @@ -62,14 +64,15 @@ instance Binary Item where
get = liftM3 Item get get get

instance Binary ItemType where
put Ring = putWord8 0
put Scroll = putWord8 1
put (Potion t) = putWord8 2 >> put t
put Wand = putWord8 3
put Amulet = putWord8 4
put Gem = putWord8 5
put Gold = putWord8 6
put (Sword i) = putWord8 7 >> put i
put Ring = putWord16le 0
put Scroll = putWord16le 1
put (Potion t) = putWord16le 2 >> put t
put Wand = putWord16le 3
put Amulet = putWord16le 4
put Gem = putWord16le 5
put Gold = putWord16le 6
put (Sword i) = putWord16le 7 >> put i
put Dart = putWord16le 8
get = do
tag <- getWord8
case tag of
Expand All @@ -81,6 +84,7 @@ instance Binary ItemType where
5 -> return Gem
6 -> return Gold
7 -> liftM Sword get
8 -> return Dart

instance Binary PotionType where
put PotionWater = putWord8 0
Expand All @@ -106,6 +110,7 @@ itemFrequency =
[
(100, Gold),
(70, Sword (-1)),
(40, Dart),
(30, Gem),
(20, Ring),
(30, Scroll),
Expand All @@ -117,6 +122,7 @@ itemFrequency =

itemQuantity :: Int -> ItemType -> Rnd Int
itemQuantity n Gold = (2 * n) *~ d 8
itemQuantity _ Dart = d 10
itemQuantity _ _ = return 1

itemStrength :: Int -> ItemType -> Rnd ItemType
Expand Down Expand Up @@ -198,6 +204,7 @@ viewItem :: ItemType -> Assocs -> (Char, Attr -> Attr)
viewItem i a = viewItem' i (M.lookup i a)
where
viewItem' (Sword {}) _ = (')', id)
viewItem' Dart _ = (')', id)
viewItem' Ring _ = ('=', id)
viewItem' Scroll _ = ('?', id)
viewItem' (Potion {}) (Just Clear) = ('!', setBold . setFG blue)
Expand Down

0 comments on commit 0940258

Please sign in to comment.