{-# LANGUAGE DeriveGeneric, GeneralizedNewtypeDeriving, TypeFamilies #-}
module Game.LambdaHack.Common.ContentData
( ContentId(ContentId), ContentData, Freqs, Rarity
, contentIdIndex, validateRarity, emptyContentData, makeContentData
, okind, omemberGroup, oisSingletonGroup, ouniqGroup, opick
, ofoldrWithKey, ofoldlWithKey', ofoldlGroup', omapVector, oimapVector
, olength
) where
import Prelude ()
import Game.LambdaHack.Common.Prelude
import Control.DeepSeq
import Data.Binary
import Data.Function
import Data.Hashable (Hashable)
import qualified Data.Map.Strict as M
import Data.Ord
import qualified Data.Text as T
import qualified Data.Vector as V
import GHC.Generics (Generic)
import Game.LambdaHack.Common.Frequency
import Game.LambdaHack.Common.Misc
import qualified Game.LambdaHack.Common.PointArray as PointArray
import Game.LambdaHack.Common.Random
newtype ContentId c = ContentId Word16
deriving (Show, Eq, Ord, Enum, Binary, Generic)
instance PointArray.UnboxRepClass (ContentId k) where
type UnboxRep (ContentId k) = Word16
toUnboxRepUnsafe (ContentId k) = k
fromUnboxRep = ContentId
instance NFData (ContentId c)
instance Hashable (ContentId c)
data ContentData c = ContentData
{ contentVector :: V.Vector c
, groupFreq :: M.Map (GroupName c) [(Int, (ContentId c, c))]
}
deriving Generic
instance NFData c => NFData (ContentData c)
type Freqs a = [(GroupName a, Int)]
type Rarity = [(Double, Int)]
maxContentId :: ContentId k
maxContentId = ContentId maxBound
contentIdIndex :: ContentId k -> Int
{-# INLINE contentIdIndex #-}
contentIdIndex (ContentId k) = fromEnum k
validateRarity :: Rarity -> [Text]
validateRarity rarity =
let sortedRarity = sortBy (comparing fst) rarity
in [ "rarity not sorted" | sortedRarity /= rarity ]
++ [ "rarity depth thresholds not unique"
| nubBy ((==) `on` fst) sortedRarity /= sortedRarity ]
++ [ "rarity depth not between 0 and 10"
| case (sortedRarity, reverse sortedRarity) of
((lowest, _) : _, (highest, _) : _) ->
lowest <= 0 || highest > 10
_ -> False ]
emptyContentData :: ContentData a
emptyContentData = ContentData V.empty M.empty
makeContentData :: (NFData c, Show c)
=> String
-> (c -> Text)
-> (c -> Freqs c)
-> (c -> [Text])
-> ([c] -> ContentData c -> [Text])
-> [c]
-> ContentData c
{-# INLINE makeContentData #-}
makeContentData contentName getName getFreq validateSingle validateAll content =
let contentVector = V.fromList content
groupFreq =
let tuples = [ (cgroup, (n, (i, k)))
| (i, k) <- zip (map ContentId [0..]) content
, (cgroup, n) <- getFreq k
, n > 0 ]
f m (cgroup, nik) = M.insertWith (++) cgroup [nik] m
in foldl' f M.empty tuples
cd = ContentData {..}
contentData = deepseq cd cd
correct a = not (T.null (getName a)) && all ((> 0) . snd) (getFreq a)
incorrectOffenders = filter (not . correct) content
singleOffenders = [ (offences, a)
| a <- content
, let offences = validateSingle a
, not (null offences) ]
allOffences = validateAll content contentData
in assert (null incorrectOffenders
`blame` contentName ++ ": some content items not correct"
`swith` incorrectOffenders) $
assert (null singleOffenders
`blame` contentName ++ ": some content items not valid"
`swith` singleOffenders) $
assert (null allOffences
`blame` contentName ++ ": the content set is not valid"
`swith` allOffences) $
assert (V.length contentVector <= contentIdIndex maxContentId
`blame` contentName ++ ": the content has too many elements")
contentData
okind :: ContentData a -> ContentId a -> a
{-# INLINE okind #-}
okind ContentData{contentVector} !i = contentVector V.! contentIdIndex i
omemberGroup :: ContentData a -> GroupName a -> Bool
omemberGroup ContentData{groupFreq} cgroup = cgroup `M.member` groupFreq
oisSingletonGroup :: ContentData a -> GroupName a -> Bool
oisSingletonGroup ContentData{groupFreq} cgroup =
case M.lookup cgroup groupFreq of
Just [_] -> True
_ -> False
ouniqGroup :: Show a => ContentData a -> GroupName a -> ContentId a
ouniqGroup ContentData{groupFreq} !cgroup =
let freq = let assFail = error $ "no unique group"
`showFailure` (cgroup, groupFreq)
in M.findWithDefault assFail cgroup groupFreq
in case freq of
[(n, (i, _))] | n > 0 -> i
l -> error $ "not unique" `showFailure` (cgroup, l)
opick :: Show a
=> ContentData a
-> GroupName a -> (a -> Bool) -> Rnd (Maybe (ContentId a))
opick ContentData{groupFreq} !cgroup !p =
case M.lookup cgroup groupFreq of
Just freqRaw ->
let freq = toFreq ("opick ('" <> tshow cgroup <> "')")
$ filter (p . snd . snd) freqRaw
in if nullFreq freq
then return Nothing
else Just . fst <$> frequency freq
_ -> return Nothing
ofoldrWithKey :: ContentData a -> (ContentId a -> a -> b -> b) -> b -> b
ofoldrWithKey ContentData{contentVector} f z =
V.ifoldr (\i c a -> f (ContentId $ toEnum i) c a) z contentVector
ofoldlWithKey' :: ContentData a -> (b -> ContentId a -> a -> b) -> b -> b
ofoldlWithKey' ContentData{contentVector} f z =
V.ifoldl' (\a i c -> f a (ContentId $ toEnum i) c) z contentVector
ofoldlGroup' :: ContentData a
-> GroupName a
-> (b -> Int -> ContentId a -> a -> b) -> b -> b
ofoldlGroup' ContentData{groupFreq} cgroup f z =
case M.lookup cgroup groupFreq of
Just freq -> foldl' (\acc (p, (i, a)) -> f acc p i a) z freq
_ -> error $ "no group '" ++ show cgroup
++ "' among content that has groups "
++ show (M.keys groupFreq)
`showFailure` ()
omapVector :: ContentData a -> (a -> b) -> V.Vector b
omapVector d f = V.map f $ contentVector d
oimapVector :: ContentData a -> (ContentId a -> a -> b) -> V.Vector b
oimapVector d f = V.imap (\i a -> f (ContentId $ toEnum i) a) $ contentVector d
olength :: ContentData a -> Int
olength ContentData{contentVector} = V.length contentVector