{-# LANGUAGE OverloadedLabels #-}
{-# LANGUAGE PackageImports #-}
module Octane.Utility.ClassPropertyMap
( getClassPropertyMap
, getPropertyMap
, getActorMap
, getClass
) where
import Data.Function ((&))
import qualified Data.Bimap as Bimap
import qualified Data.IntMap.Strict as IntMap
import qualified Data.List as List
import qualified Data.Map.Strict as Map
import qualified Data.Maybe as Maybe
import qualified Data.Text as StrictText
import qualified Octane.Data as Data
import qualified Octane.Type.ReplayWithoutFrames as Replay
import qualified Octane.Type.Word32 as Word32
import qualified "regex-compat" Text.Regex as Regex
getClassPropertyMap :: Replay.ReplayWithoutFrames
-> IntMap.IntMap (IntMap.IntMap StrictText.Text)
getClassPropertyMap replay =
let basicClassPropertyMap = getBasicClassPropertyMap replay
classMap = getClassMap replay
in replay & getClassIds &
map
(\classId ->
let ownProperties =
case IntMap.lookup classId basicClassPropertyMap of
Nothing -> IntMap.empty
Just x -> x
parentProperties =
case IntMap.lookup classId classMap of
Nothing -> IntMap.empty
Just parentClassIds ->
parentClassIds &
map
(\parentClassId ->
case IntMap.lookup parentClassId basicClassPropertyMap of
Nothing -> IntMap.empty
Just x -> x) &
IntMap.unions
properties = IntMap.union ownProperties parentProperties
in (classId, properties)) &
IntMap.fromList
getClassCache :: Replay.ReplayWithoutFrames
-> [(Int, StrictText.Text, Int, Int)]
getClassCache replay = do
let classNames = replay & getActorMap & Bimap.toMapR
replay & #cache & #unpack &
Maybe.mapMaybe
(\cacheItem -> do
let classId = cacheItem & #classId & Word32.fromWord32
className <- Map.lookup classId classNames
let cacheId = cacheItem & #cacheId & Word32.fromWord32
let parentCacheId = cacheItem & #parentCacheId & Word32.fromWord32
pure (classId, className, cacheId, parentCacheId))
getClassIds :: Replay.ReplayWithoutFrames -> [Int]
getClassIds replay = replay & getClassCache & map (\(x, _, _, _) -> x)
getParentClassId :: StrictText.Text
-> Int
-> [(Int, StrictText.Text, Int, Int)]
-> Maybe Int
getParentClassId className parentCacheId xs =
case Map.lookup className Data.parentClasses of
Just parentClassName ->
xs & filter (\(_, name, _, _) -> name == parentClassName) &
filter (\(_, _, cacheId, _) -> cacheId == parentCacheId) &
map (\(classId, _, _, _) -> classId) &
Maybe.listToMaybe
Nothing ->
case dropWhile (\(_, _, cacheId, _) -> cacheId /= parentCacheId) xs of
[] ->
if parentCacheId <= 0
then Nothing
else getParentClassId className (parentCacheId - 1) xs
(parentClassId, _, _, _):_ -> Just parentClassId
getBasicClassMap :: Replay.ReplayWithoutFrames -> IntMap.IntMap Int
getBasicClassMap replay =
replay & getClassCache & reverse & List.tails &
Maybe.mapMaybe
(\xs ->
case xs of
[] -> Nothing
(classId, className, _, parentCacheId):ys -> do
parentClassId <- getParentClassId className parentCacheId ys
pure (classId, parentClassId)) &
IntMap.fromList
getParentClassIds :: Int -> IntMap.IntMap Int -> [Int]
getParentClassIds classId basicClassMap =
case IntMap.lookup classId basicClassMap of
Nothing -> []
Just parentClassId ->
parentClassId : getParentClassIds parentClassId basicClassMap
getClassMap :: Replay.ReplayWithoutFrames -> IntMap.IntMap [Int]
getClassMap replay =
let basicClassMap = getBasicClassMap replay
in replay & getClassIds &
map (\classId -> (classId, getParentClassIds classId basicClassMap)) &
IntMap.fromList
getPropertyMap :: Replay.ReplayWithoutFrames -> IntMap.IntMap StrictText.Text
getPropertyMap replay =
replay & #objects & #unpack & map #unpack & zip [0 ..] & IntMap.fromList
getBasicClassPropertyMap :: Replay.ReplayWithoutFrames
-> IntMap.IntMap (IntMap.IntMap StrictText.Text)
getBasicClassPropertyMap replay =
let propertyMap = getPropertyMap replay
in replay & #cache & #unpack &
map
(\x ->
let classId = x & #classId & Word32.fromWord32
properties =
x & #properties & #unpack &
Maybe.mapMaybe
(\y ->
let streamId = y & #streamId & Word32.fromWord32
propertyId = y & #objectId & Word32.fromWord32
in case IntMap.lookup propertyId propertyMap of
Nothing -> Nothing
Just name -> Just (streamId, name)) &
IntMap.fromList
in (classId, properties)) &
IntMap.fromList
getActorMap :: Replay.ReplayWithoutFrames -> Bimap.Bimap StrictText.Text Int
getActorMap replay =
replay & #classes & #unpack &
map
(\x ->
let className = x & #name & #unpack
classId = x & #streamId & Word32.fromWord32
in (className, classId)) &
Bimap.fromList
getClass
:: (Monad m)
=> IntMap.IntMap StrictText.Text
-> Map.Map StrictText.Text StrictText.Text
-> Map.Map StrictText.Text Int
-> Int
-> m (Int, StrictText.Text)
getClass propertyIdsToNames propertyNamesToClassNames classNamesToIds propertyId = do
rawPropertyName <- getPropertyName propertyIdsToNames propertyId
let propertyName = normalizeName rawPropertyName
className <- getClassName propertyNamesToClassNames propertyName
classId <- getClassId classNamesToIds className
pure (classId, className)
getPropertyName
:: (Monad m)
=> IntMap.IntMap StrictText.Text -> Int -> m StrictText.Text
getPropertyName propertyNames propertyId = do
case IntMap.lookup propertyId propertyNames of
Nothing -> do
fail ("Could not find name for property " ++ show propertyId)
Just propertyName -> do
pure propertyName
normalizeName :: StrictText.Text -> StrictText.Text
normalizeName name =
name & StrictText.unpack & replace "_[0-9]+$" "" &
replace "^[A-Z_a-z]+[.]TheWorld:" "TheWorld:" &
StrictText.pack
replace :: String -> String -> String -> String
replace needle replacement haystack =
Regex.subRegex (Regex.mkRegex needle) haystack replacement
getClassName
:: (Monad m)
=> Map.Map StrictText.Text StrictText.Text
-> StrictText.Text
-> m StrictText.Text
getClassName classNames propertyName = do
case Map.lookup propertyName classNames of
Nothing -> do
fail ("Could not find class for property " ++ show propertyName)
Just className -> do
pure className
getClassId
:: (Monad m)
=> Map.Map StrictText.Text Int -> StrictText.Text -> m Int
getClassId classIds className = do
case Map.lookup className classIds of
Nothing -> do
fail ("Could not find ID for class " ++ show className)
Just classId -> do
pure classId