{-# LANGUAGE DeriveGeneric #-}
module Game.LambdaHack.Content.TileKind
( TileKind(..), makeData
, Feature(..), TileSpeedup(..), Tab(..)
, emptyTileSpeedup, emptyTab
, actionFeatures, isUknownSpace, unknownId
, isSuspectKind, isOpenableKind, isClosableKind
, talterForStairs, floorSymbol
#ifdef EXPOSE_INTERNAL
, validateSingle, validateAll
, validateDups, hardwiredTileGroups
#endif
) where
import Prelude ()
import Game.LambdaHack.Common.Prelude
import Control.DeepSeq
import Data.Binary
import qualified Data.Char as Char
import Data.Hashable
import qualified Data.IntSet as IS
import qualified Data.Text as T
import qualified Data.Vector.Unboxed as U
import GHC.Generics (Generic)
import Game.LambdaHack.Common.Color
import Game.LambdaHack.Common.ContentData
import Game.LambdaHack.Common.Misc
import Game.LambdaHack.Content.ItemKind (ItemKind)
data TileKind = TileKind
{ tsymbol :: Char
, tname :: Text
, tfreq :: Freqs TileKind
, tcolor :: Color
, tcolor2 :: Color
, talter :: Word8
, tfeature :: [Feature]
}
deriving (Show, Generic)
instance NFData TileKind
data Feature =
Embed (GroupName ItemKind)
| OpenTo (GroupName TileKind)
| CloseTo (GroupName TileKind)
| ChangeTo (GroupName TileKind)
| HideAs (GroupName TileKind)
| BuildAs (GroupName TileKind)
| RevealAs (GroupName TileKind)
| ObscureAs (GroupName TileKind)
| Walkable
| Clear
| Dark
| OftenItem
| OftenActor
| NoItem
| NoActor
| ConsideredByAI
| Trail
| Spice
deriving (Show, Eq, Ord, Generic)
instance Binary Feature
instance Hashable Feature
instance NFData Feature
data TileSpeedup = TileSpeedup
{ isClearTab :: Tab Bool
, isLitTab :: Tab Bool
, isWalkableTab :: Tab Bool
, isDoorTab :: Tab Bool
, isChangableTab :: Tab Bool
, isSuspectTab :: Tab Bool
, isHideAsTab :: Tab Bool
, consideredByAITab :: Tab Bool
, isOftenItemTab :: Tab Bool
, isOftenActorTab :: Tab Bool
, isNoItemTab :: Tab Bool
, isNoActorTab :: Tab Bool
, isEasyOpenTab :: Tab Bool
, alterMinSkillTab :: Tab Word8
, alterMinWalkTab :: Tab Word8
}
deriving Generic
instance NFData TileSpeedup
newtype Tab a = Tab (U.Vector a)
deriving Generic
instance NFData (Tab a)
emptyTileSpeedup :: TileSpeedup
emptyTileSpeedup = TileSpeedup emptyTab emptyTab emptyTab emptyTab emptyTab
emptyTab emptyTab emptyTab emptyTab emptyTab
emptyTab emptyTab emptyTab emptyTab emptyTab
emptyTab :: U.Unbox a => Tab a
emptyTab = Tab $! U.empty
validateSingle :: TileKind -> [Text]
validateSingle t@TileKind{..} =
[ "suspect tile is walkable" | Walkable `elem` tfeature
&& isSuspectKind t ]
++ [ "openable tile is open" | Walkable `elem` tfeature
&& isOpenableKind t ]
++ [ "closable tile is closed" | Walkable `notElem` tfeature
&& isClosableKind t ]
++ [ "walkable tile is considered for triggering by AI"
| Walkable `elem` tfeature
&& ConsideredByAI `elem` tfeature ]
++ [ "trail tile not walkable" | Walkable `notElem` tfeature
&& Trail `elem` tfeature ]
++ [ "OftenItem and NoItem on a tile" | OftenItem `elem` tfeature
&& NoItem `elem` tfeature ]
++ [ "OftenActor and NoActor on a tile" | OftenItem `elem` tfeature
&& NoItem `elem` tfeature ]
++ (let f :: Feature -> Bool
f OpenTo{} = True
f CloseTo{} = True
f ChangeTo{} = True
f _ = False
ts = filter f tfeature
in [ "more than one OpenTo, CloseTo and ChangeTo specification"
| length ts > 1 ])
++ (let f :: Feature -> Bool
f HideAs{} = True
f _ = False
ts = filter f tfeature
in ["more than one HideAs specification" | length ts > 1])
++ (let f :: Feature -> Bool
f BuildAs{} = True
f _ = False
ts = filter f tfeature
in ["more than one BuildAs specification" | length ts > 1])
++ concatMap (validateDups t)
[ Walkable, Clear, Dark, OftenItem, OftenActor, NoItem, NoActor
, ConsideredByAI, Trail, Spice ]
validateDups :: TileKind -> Feature -> [Text]
validateDups TileKind{..} feat =
let ts = filter (== feat) tfeature
in ["more than one" <+> tshow feat <+> "specification" | length ts > 1]
validateAll :: ContentData ItemKind -> [TileKind] -> ContentData TileKind
-> [Text]
validateAll coitem content cotile =
let g :: Feature -> Maybe (GroupName TileKind)
g (OpenTo grp) = Just grp
g (CloseTo grp) = Just grp
g (ChangeTo grp) = Just grp
g (HideAs grp) = Just grp
g (BuildAs grp) = Just grp
g (RevealAs grp) = Just grp
g (ObscureAs grp) = Just grp
g _ = Nothing
missingTileGroups =
[ (tname k, absGroups)
| k <- content
, let grps = mapMaybe g $ tfeature k
absGroups = filter (not . omemberGroup cotile) grps
, not $ null absGroups
]
h :: Feature -> Maybe (GroupName ItemKind)
h (Embed grp) = Just grp
h _ = Nothing
missingItemGroups =
[ (tname k, absGroups)
| k <- content
, let grps = mapMaybe h $ tfeature k
absGroups = filter (not . omemberGroup coitem) grps
, not $ null absGroups
]
missingHardwiredGroups =
filter (not . omemberGroup cotile) hardwiredTileGroups
in [ "first tile should be the unknown one"
| talter (head content) /= 1 || tname (head content) /= "unknown space" ]
++ [ "only unknown tile may have talter 1"
| any ((== 1) . talter) $ tail content ]
++ [ "mentioned tile groups not in content:" <+> tshow missingTileGroups
| not $ null missingTileGroups ]
++ [ "embedded item groups not in content:" <+> tshow missingItemGroups
| not $ null missingItemGroups ]
++ [ "hardwired groups not in content:" <+> tshow missingHardwiredGroups
| not $ null missingHardwiredGroups ]
hardwiredTileGroups :: [GroupName TileKind]
hardwiredTileGroups =
[ "unknown space", "legendLit", "legendDark", "unknown outer fence"
, "basic outer fence", "stair terminal" ]
actionFeatures :: Bool -> TileKind -> IS.IntSet
actionFeatures markSuspect t =
let stripLight grp = maybe grp toGroupName
$ maybe (T.stripSuffix "Dark" $ tshow grp) Just
$ T.stripSuffix "Lit" $ tshow grp
f feat = case feat of
Embed{} -> Just feat
OpenTo grp -> Just $ OpenTo $ stripLight grp
CloseTo grp -> Just $ CloseTo $ stripLight grp
ChangeTo grp -> Just $ ChangeTo $ stripLight grp
Walkable -> Just feat
Clear -> Just feat
HideAs{} -> Nothing
BuildAs{} -> Nothing
RevealAs{} -> if markSuspect then Just feat else Nothing
ObscureAs{} -> if markSuspect then Just feat else Nothing
Dark -> Nothing
OftenItem -> Nothing
OftenActor -> Nothing
NoItem -> Nothing
NoActor -> Nothing
ConsideredByAI -> Nothing
Trail -> Just feat
Spice -> Nothing
in IS.fromList $ map hash $ mapMaybe f $ tfeature t
isUknownSpace :: ContentId TileKind -> Bool
{-# INLINE isUknownSpace #-}
isUknownSpace tt = ContentId 0 == tt
unknownId :: ContentId TileKind
{-# INLINE unknownId #-}
unknownId = ContentId 0
isSuspectKind :: TileKind -> Bool
isSuspectKind t =
let getTo RevealAs{} = True
getTo ObscureAs{} = True
getTo _ = False
in any getTo $ tfeature t
isOpenableKind ::TileKind -> Bool
isOpenableKind t =
let getTo OpenTo{} = True
getTo _ = False
in any getTo $ tfeature t
isClosableKind :: TileKind -> Bool
isClosableKind t =
let getTo CloseTo{} = True
getTo _ = False
in any getTo $ tfeature t
talterForStairs :: Word8
talterForStairs = 3
floorSymbol :: Char.Char
floorSymbol = Char.chr 183
makeData :: ContentData ItemKind -> [TileKind] -> ContentData TileKind
makeData coitem =
makeContentData "TileKind" tname tfreq validateSingle (validateAll coitem)