module Octane.Utility.ClassPropertyMap where
import Data.Function ((&))
import qualified Data.Char as Char
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.Type.CacheItem as CacheItem
import qualified Octane.Type.CacheProperty as CacheProperty
import qualified Octane.Type.ClassItem as ClassItem
import qualified Octane.Type.List as List
import qualified Octane.Type.ReplayWithoutFrames as ReplayWithoutFrames
import qualified Octane.Type.Text as Text
import qualified Octane.Type.Word32 as Word32
getClassPropertyMap :: ReplayWithoutFrames.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 :: ReplayWithoutFrames.ReplayWithoutFrames -> [(Int, Int, Int)]
getClassCache replay = replay
& ReplayWithoutFrames.cache
& List.unpack
& map (\ x ->
( x & CacheItem.classId & Word32.fromWord32
, x & CacheItem.cacheId & Word32.fromWord32
, x & CacheItem.parentCacheId & Word32.fromWord32
))
getClassIds :: ReplayWithoutFrames.ReplayWithoutFrames -> [Int]
getClassIds replay = replay
& getClassCache
& map (\ (x, _, _) -> x)
getParentClassId :: Int -> [(Int, Int, Int)] -> Maybe Int
getParentClassId parentCacheId xs =
case dropWhile (\ (_, cacheId, _) -> cacheId /= parentCacheId) xs of
[] -> if parentCacheId <= 0
then Nothing
else getParentClassId (parentCacheId 1) xs
(parentClassId, _, _) : _ -> Just parentClassId
getBasicClassMap :: ReplayWithoutFrames.ReplayWithoutFrames -> IntMap.IntMap Int
getBasicClassMap replay = replay
& getClassCache
& reverse
& List.tails
& Maybe.mapMaybe (\ xs -> case xs of
[] -> Nothing
(classId, _, parentCacheId) : ys -> do
parentClassId <- getParentClassId parentCacheId ys
return (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 :: ReplayWithoutFrames.ReplayWithoutFrames -> IntMap.IntMap [Int]
getClassMap replay = let
basicClassMap = getBasicClassMap replay
in replay
& getClassIds
& map (\ classId ->
( classId
, getParentClassIds classId basicClassMap
))
& IntMap.fromList
getPropertyMap :: ReplayWithoutFrames.ReplayWithoutFrames -> IntMap.IntMap StrictText.Text
getPropertyMap replay = replay
& ReplayWithoutFrames.objects
& List.unpack
& map Text.unpack
& zip [0 ..]
& IntMap.fromList
getBasicClassPropertyMap :: ReplayWithoutFrames.ReplayWithoutFrames -> IntMap.IntMap (IntMap.IntMap StrictText.Text)
getBasicClassPropertyMap replay = let
propertyMap = getPropertyMap replay
in replay
& ReplayWithoutFrames.cache
& List.unpack
& map (\ x -> let
classId = x & CacheItem.classId & Word32.fromWord32
properties = x
& CacheItem.properties
& List.unpack
& Maybe.mapMaybe (\ y -> let
streamId = y & CacheProperty.streamId & Word32.fromWord32
propertyId = y & CacheProperty.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 :: ReplayWithoutFrames.ReplayWithoutFrames -> Map.Map StrictText.Text Int
getActorMap replay = replay
& ReplayWithoutFrames.classes
& List.unpack
& map (\ x -> let
className = x & ClassItem.name & Text.unpack
classId = x & ClassItem.streamId & Word32.fromWord32
in (className, classId))
& Map.fromList
getClass
:: IntMap.IntMap StrictText.Text
-> Map.Map StrictText.Text StrictText.Text
-> Map.Map StrictText.Text Int
-> Int
-> Maybe (Int, StrictText.Text)
getClass propertyIdsToNames propertyNamesToClassNames classNamesToIds propertyId =
case IntMap.lookup propertyId propertyIdsToNames of
Nothing -> Nothing
Just rawPropertyName -> let
propertyName = rawPropertyName & StrictText.dropWhileEnd Char.isDigit
in case Map.lookup propertyName propertyNamesToClassNames of
Nothing -> Nothing
Just className -> case Map.lookup className classNamesToIds of
Nothing -> Nothing
Just classId -> Just (classId, className)