Created
September 3, 2013 09:24
-
-
Save myuon/6421580 to your computer and use it in GitHub Desktop.
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# LANGUAGE ImplicitParams, BangPatterns #-} | |
----------------------------------------------------------------------------- | |
-- | | |
-- Module : Graphics.UI.FreeGame.GUI.GLFW | |
-- Copyright : (C) 2013 Fumiaki Kinoshita | |
-- License : BSD-style (see the file LICENSE) | |
-- | |
-- Maintainer : Fumiaki Kinoshita <[email protected]> | |
-- Stability : experimental | |
-- Portability : non-portable | |
-- | |
---------------------------------------------------------------------------- | |
module Graphics.UI.FreeGame.GUI.GLFW (runGame | |
-- * Implementation details | |
, Texture | |
, installTexture | |
, drawTexture | |
, drawTextureAt) where | |
import Control.Applicative | |
import Control.Monad | |
import Control.Monad.Free.Church | |
import Control.Monad.IO.Class | |
import Data.IORef | |
import Data.Color | |
import Foreign.ForeignPtr | |
import Graphics.UI.FreeGame.Base | |
import Graphics.UI.FreeGame.Data.Bitmap | |
import Graphics.UI.FreeGame.Internal.Finalizer | |
import Graphics.UI.FreeGame.GUI | |
import Graphics.Rendering.OpenGL.Raw.ARB.Compatibility | |
import qualified Data.Array.Repa.Repr.ForeignPtr as RF | |
import qualified Graphics.UI.GLFW as GLFW | |
import Graphics.Rendering.OpenGL.GL.StateVar | |
import qualified Data.IntMap as IM | |
import qualified Graphics.Rendering.OpenGL.GL as GL | |
import System.Mem | |
import Unsafe.Coerce | |
import Control.Bool | |
import Linear | |
runGame :: GUIParam -> F GUI a -> IO (Maybe a) | |
runGame param m = launch param $ \r s -> runF m (return . Just) (runAction param r s) | |
runAction :: GUIParam | |
-> IORef (IM.IntMap Texture) | |
-> IORef Int | |
-> GUI (FinalizerT IO (Maybe a)) -> FinalizerT IO (Maybe a) | |
runAction param refTextures refFrame _f = case _f of | |
LiftUI (Draw pic) -> {-# SCC "l.49:LiftUI,Draw" #-} let ?refTextures = refTextures in join $ runPicture 1 pic | |
EmbedIO m -> {-# SCC "l.50:EmbedIO" #-} join (liftIO m) | |
Bracket m -> {-# SCC "l.51:Bracket" #-} liftIO (runFinalizerT $ runF m (return.Just) (runAction param refTextures refFrame)) | |
>>= maybe (return Nothing) id | |
LiftUI (Input i) -> {-# SCC "l.53:LiftUI,Input" #-} join $ liftIO $ runInput i | |
Quit -> return Nothing | |
Tick cont -> {-# SCC "l.55:Tick" #-} do | |
liftIO $ {-# SCC "l.56:liftIO" #-} do | |
{-# SCC "l.57:GLmatrixMode" #-} GL.matrixMode $= GL.Projection | |
{-# SCC "l.58:swapBuffers" #-} GLFW.swapBuffers | |
{-# SCC "l.59:performGC" #-} performGC | |
t <- {-# SCC "l.60:getTime" #-} GLFW.getTime | |
n <- {-# SCC "l.61:refFrame" #-} readIORef refFrame | |
{-# SCC "l.62:sleep" #-} GLFW.sleep $ fromIntegral n / fromIntegral (_framePerSecond param) - t | |
if t > 1 | |
then GLFW.resetTime >> writeIORef refFrame 0 | |
else writeIORef refFrame (succ n) | |
r <- {-# SCC "l.67:windowIsOpen" #-} liftIO $ GLFW.windowIsOpen | |
if not r then return Nothing else do | |
liftIO $ {-# SCC "l.69:liftIO" #-} do | |
{-# SCC "l.70:GLclear" #-} GL.clear [GL.ColorBuffer] | |
{-# SCC "l.71:GLloadIdentity" #-} GL.loadIdentity | |
{-# SCC "l.72:GLScale" #-} GL.scale (gf 1) (-1) 1 | |
let V2 ox oy = _windowOrigin param | |
V2 ww wh = _windowSize param | |
windowL = realToFrac ox | |
windowR = realToFrac ox + fromIntegral ww | |
windowT = realToFrac oy | |
windowB = realToFrac oy + fromIntegral wh | |
{-# SCC "l.73:GLortho" #-} GL.ortho windowL windowR windowT windowB 0 (-100) | |
{-# SCC "l.80:GLmatrixMode" #-} GL.matrixMode $= GL.Modelview 0 | |
cont | |
type Texture = (GL.TextureObject, Double, Double) | |
launch :: GUIParam -> (IORef (IM.IntMap Texture) -> IORef Int -> FinalizerT IO (Maybe a)) -> IO (Maybe a) | |
launch param m = do | |
GLFW.initialize >>= bool (fail "Failed to initialize") (return ()) | |
pf <- GLFW.openGLProfile | |
let V2 ww wh = _windowSize param | |
(>>=bool (fail "Failed to initialize") (return ())) $ GLFW.openWindow $ GLFW.defaultDisplayOptions { | |
GLFW.displayOptions_width = ww | |
,GLFW.displayOptions_height = wh | |
,GLFW.displayOptions_displayMode = if _windowed param then GLFW.Window else GLFW.Fullscreen | |
,GLFW.displayOptions_windowIsResizable = False | |
,GLFW.displayOptions_openGLProfile = pf | |
} | |
GLFW.setWindowTitle $ _windowTitle param | |
GL.lineSmooth $= GL.Enabled | |
GL.blend $= GL.Enabled | |
GL.blendFunc $= (GL.SrcAlpha, GL.OneMinusSrcAlpha) | |
GL.shadeModel $= GL.Smooth | |
GL.textureFunction $= GL.Combine | |
let Color r g b a = _clearColor param in GL.clearColor $= GL.Color4 (gf r) (gf g) (gf b) (gf a) | |
res <- runFinalizerT $ join $ m <$> liftIO (newIORef IM.empty) <*> liftIO (newIORef 0) | |
GLFW.closeWindow | |
GLFW.terminate | |
return res | |
installTexture :: Bitmap -> FinalizerT IO Texture | |
installTexture bmp@(BitmapData ar _) = do | |
[tex] <- liftIO $ GL.genObjectNames 1 | |
liftIO $ GL.textureBinding GL.Texture2D GL.$= Just tex | |
let (width, height) = bitmapSize bmp | |
let siz = GL.TextureSize2D (gsizei width) (gsizei height) | |
liftIO $ withForeignPtr (RF.toForeignPtr ar) | |
$ GL.texImage2D Nothing GL.NoProxy 0 GL.RGBA8 siz 0 | |
. GL.PixelData GL.RGBA GL.UnsignedInt8888 | |
finalizer $ GL.deleteObjectNames [tex] | |
return (tex, fromIntegral width / 2, fromIntegral height / 2) | |
runInput :: GUIInput a -> IO a | |
runInput (ICharKey ch cont) = cont <$> GLFW.keyIsPressed (GLFW.CharKey ch) | |
runInput (ISpecialKey x cont) = cont <$> GLFW.keyIsPressed (mapSpecialKey x) | |
runInput (IMouseButtonL cont) = cont <$> GLFW.mouseButtonIsPressed GLFW.MouseButton0 | |
runInput (IMouseButtonR cont) = cont <$> GLFW.mouseButtonIsPressed GLFW.MouseButton1 | |
runInput (IMouseButtonM cont) = cont <$> GLFW.mouseButtonIsPressed GLFW.MouseButton2 | |
runInput (IMousePosition cont) = do | |
(x, y) <- GLFW.getMousePosition | |
return $ cont $ V2 (fromIntegral x) (fromIntegral y) | |
runInput (IMouseWheel cont) = cont <$> GLFW.getMouseWheel | |
runPicture :: (?refTextures :: IORef (IM.IntMap Texture)) => Double -> Picture a -> FinalizerT IO a | |
runPicture _ (LiftBitmap bmp@(BitmapData _ (Just h)) r) = do | |
m <- liftIO $ readIORef ?refTextures | |
case {-# SCC "l.139:IM.lookup" #-} IM.lookup h m of | |
Just t -> liftIO $ drawTexture t | |
Nothing -> do | |
t <- installTexture bmp | |
liftIO $ writeIORef ?refTextures $ IM.insert h t m | |
liftIO $ drawTexture t | |
finalizer $ modifyIORef ?refTextures $ IM.delete h | |
return r | |
runPicture _ (LiftBitmap bmp@(BitmapData _ Nothing) r) = do | |
liftIO $ runFinalizerT $ installTexture bmp >>= liftIO . drawTexture | |
return r | |
runPicture sc (Translate (V2 tx ty) cont) = preservingMatrix' $ do | |
liftIO $ GL.translate (GL.Vector3 (gd tx) (gd ty) 0) | |
runPicture sc cont | |
runPicture sc (RotateD theta cont) = preservingMatrix' $ do | |
liftIO $ GL.rotate (gd (-theta)) (GL.Vector3 0 0 1) | |
runPicture sc cont | |
runPicture sc (Scale (V2 sx sy) cont) = preservingMatrix' $ do | |
liftIO $ GL.scale (gd sx) (gd sy) 1 | |
runPicture (sc * max sx sy) cont | |
runPicture _ (PictureWithFinalizer m) = m | |
runPicture sc (Colored col cont) = do | |
oldColor <- liftIO $ get GL.currentColor | |
liftIO $ GL.currentColor $= unsafeCoerce col | |
res <- runPicture sc cont | |
liftIO $ GL.currentColor $= oldColor | |
return res | |
runPicture _ (Line path a) = do | |
liftIO $ GL.renderPrimitive GL.LineStrip $ runVertices path | |
return a | |
runPicture _ (Polygon path a) = do | |
liftIO $ GL.renderPrimitive GL.Polygon $ runVertices path | |
return a | |
runPicture _ (PolygonOutline path a) = do | |
liftIO $ GL.renderPrimitive GL.LineLoop $ runVertices path | |
return a | |
runPicture sc (Circle r a) = do | |
let s = 2 * pi / 64 * sc | |
liftIO $ GL.renderPrimitive GL.Polygon $ runVertices [V2 (cos t * r) (sin t * r) | t <- [0,s..2 * pi]] | |
return a | |
runPicture sc (CircleOutline r a) = do | |
let s = 2 * pi / 64 * sc | |
liftIO $ GL.renderPrimitive GL.LineLoop $ runVertices [V2 (cos t * r) (sin t * r) | t <- [0,s..2 * pi]] | |
return a | |
runPicture sc (Thickness t cont) = do | |
oldWidth <- liftIO $ get GL.lineWidth | |
liftIO $ GL.lineWidth $= gf t | |
res <- runPicture sc cont | |
liftIO $ GL.lineWidth $= oldWidth | |
return res | |
runVertices :: MonadIO m => [V2 Double] -> m () | |
runVertices = liftIO . mapM_ (GL.vertex . mkVertex2) | |
{-# INLINE runVertices #-} | |
preservingMatrix' :: MonadIO m => m a -> m a | |
preservingMatrix' m = do | |
liftIO $ glPushMatrix | |
r <- m | |
liftIO $ glPopMatrix | |
return r | |
drawTexture :: Texture -> IO () | |
drawTexture (tex, w, h) = drawTextureAt tex (V2 (-w) (-h)) (V2 w (-h)) (V2 w h) (V2 (-w) h) | |
{-# INLINE drawTexture #-} | |
drawTextureAt :: GL.TextureObject -> V2 Double -> V2 Double -> V2 Double -> V2 Double -> IO () | |
drawTextureAt tex a b c d = do | |
GL.texture GL.Texture2D $= GL.Enabled | |
GL.textureFilter GL.Texture2D $= ((GL.Nearest, Nothing), GL.Nearest) | |
GL.textureBinding GL.Texture2D $= Just tex | |
GL.renderPrimitive GL.Polygon $ do | |
GL.texCoord $ GL.TexCoord2 (0 :: GL.GLfloat) 0 | |
GL.vertex $ mkVertex2 a | |
GL.texCoord $ GL.TexCoord2 (1 :: GL.GLfloat) 0 | |
GL.vertex $ mkVertex2 b | |
GL.texCoord $ GL.TexCoord2 (1 :: GL.GLfloat) 1 | |
GL.vertex $ mkVertex2 c | |
GL.texCoord $ GL.TexCoord2 (0 :: GL.GLfloat) 1 | |
GL.vertex $ mkVertex2 d | |
GL.texture GL.Texture2D $= GL.Disabled | |
mapSpecialKey :: SpecialKey -> GLFW.Key | |
mapSpecialKey KeySpace = GLFW.KeySpace | |
mapSpecialKey KeyEsc = GLFW.KeyEsc | |
mapSpecialKey KeyLeftShift = GLFW.KeyLeftShift | |
mapSpecialKey KeyRightShift = GLFW.KeyRightShift | |
mapSpecialKey KeyLeftControl = GLFW.KeyLeftCtrl | |
mapSpecialKey KeyRightControl = GLFW.KeyRightCtrl | |
mapSpecialKey KeyUp = GLFW.KeyUp | |
mapSpecialKey KeyDown = GLFW.KeyDown | |
mapSpecialKey KeyLeft = GLFW.KeyLeft | |
mapSpecialKey KeyRight = GLFW.KeyRight | |
mapSpecialKey KeyTab = GLFW.KeyTab | |
mapSpecialKey KeyEnter = GLFW.KeyEnter | |
mapSpecialKey KeyBackspace = GLFW.KeyBackspace | |
mapSpecialKey KeyInsert = GLFW.KeyInsert | |
mapSpecialKey KeyDelete = GLFW.KeyDel | |
mapSpecialKey KeyPageUp = GLFW.KeyPageup | |
mapSpecialKey KeyPageDown = GLFW.KeyPagedown | |
mapSpecialKey KeyHome = GLFW.KeyHome | |
mapSpecialKey KeyEnd = GLFW.KeyEnd | |
mapSpecialKey KeyF1 = GLFW.KeyF1 | |
mapSpecialKey KeyF2 = GLFW.KeyF2 | |
mapSpecialKey KeyF3 = GLFW.KeyF3 | |
mapSpecialKey KeyF4 = GLFW.KeyF4 | |
mapSpecialKey KeyF5 = GLFW.KeyF5 | |
mapSpecialKey KeyF6 = GLFW.KeyF6 | |
mapSpecialKey KeyF7 = GLFW.KeyF7 | |
mapSpecialKey KeyF8 = GLFW.KeyF8 | |
mapSpecialKey KeyF9 = GLFW.KeyF9 | |
mapSpecialKey KeyF10 = GLFW.KeyF10 | |
mapSpecialKey KeyF11 = GLFW.KeyF11 | |
mapSpecialKey KeyF12 = GLFW.KeyF12 | |
mapSpecialKey KeyPad0 = GLFW.KeyPad0 | |
mapSpecialKey KeyPad1 = GLFW.KeyPad1 | |
mapSpecialKey KeyPad2 = GLFW.KeyPad2 | |
mapSpecialKey KeyPad3 = GLFW.KeyPad3 | |
mapSpecialKey KeyPad4 = GLFW.KeyPad4 | |
mapSpecialKey KeyPad5 = GLFW.KeyPad5 | |
mapSpecialKey KeyPad6 = GLFW.KeyPad6 | |
mapSpecialKey KeyPad7 = GLFW.KeyPad7 | |
mapSpecialKey KeyPad8 = GLFW.KeyPad8 | |
mapSpecialKey KeyPad9 = GLFW.KeyPad9 | |
mapSpecialKey KeyPadDivide = GLFW.KeyPadDivide | |
mapSpecialKey KeyPadMultiply = GLFW.KeyPadMultiply | |
mapSpecialKey KeyPadSubtract = GLFW.KeyPadSubtract | |
mapSpecialKey KeyPadAdd = GLFW.KeyPadAdd | |
mapSpecialKey KeyPadDecimal = GLFW.KeyPadDecimal | |
mapSpecialKey KeyPadEqual = GLFW.KeyPadEqual | |
mapSpecialKey KeyPadEnter = GLFW.KeyPadEnter | |
mkVertex2 :: V2 Double -> GL.Vertex2 GL.GLdouble | |
mkVertex2 = unsafeCoerce | |
{-# INLINE mkVertex2 #-} | |
gf :: Float -> GL.GLfloat | |
{-# INLINE gf #-} | |
gf x = unsafeCoerce x | |
gd :: Double -> GL.GLdouble | |
{-# INLINE gd #-} | |
gd x = unsafeCoerce x | |
gsizei :: Int -> GL.GLsizei | |
{-# INLINE gsizei #-} | |
gsizei x = unsafeCoerce x |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Tue Sep 3 18:17 2013 Time and Allocation Profiling Report (Final) | |
Main +RTS -p -RTS | |
total time = 123.01 secs (123007 ticks @ 1000 us, 1 processor) | |
total alloc = 3,965,139,476 bytes (excludes profiling overheads) | |
COST CENTRE MODULE %time %alloc | |
drawTextureAt Graphics.UI.FreeGame.GUI.GLFW 44.1 1.9 | |
runPicture Graphics.UI.FreeGame.GUI.GLFW 7.5 11.3 | |
>>=.\.\ Graphics.UI.FreeGame.Internal.Finalizer 5.4 9.6 | |
normalBullet Barrage 4.2 12.2 | |
liftIO.\ Graphics.UI.FreeGame.Internal.Finalizer 4.0 1.2 | |
fromBitmap Graphics.UI.FreeGame.Base 3.1 5.7 | |
>>=.\ Graphics.UI.FreeGame.Internal.Finalizer 2.8 3.5 | |
fmap Graphics.UI.FreeGame.GUI 2.6 6.8 | |
drawBullet Field 1.9 5.6 | |
updateField.\ Field 1.4 2.7 | |
rotateR Graphics.UI.FreeGame.Base 1.3 1.4 | |
l.69:liftIO Graphics.UI.FreeGame.GUI.GLFW 1.1 0.0 | |
drawBullet.img Field 1.1 0.0 | |
fmap Graphics.UI.FreeGame.Base 1.0 4.4 | |
fmap Graphics.UI.FreeGame.GUI 1.0 4.0 | |
fromPolar Global 1.0 2.2 | |
draw Field 0.9 2.2 | |
preservingMatrix' Graphics.UI.FreeGame.GUI.GLFW 0.8 2.9 | |
liftIO Graphics.UI.FreeGame.Internal.Finalizer 0.8 2.5 | |
_LiftUI Graphics.UI.FreeGame.Base 0.7 1.5 | |
$* Global 0.6 1.4 | |
translate Graphics.UI.FreeGame.Base 0.6 1.5 | |
_Draw Graphics.UI.FreeGame.GUI 0.6 1.5 | |
updateField Field 0.6 1.1 | |
fromBitmap Graphics.UI.FreeGame.Base 0.5 1.3 | |
loadBitmapFromFile Graphics.UI.FreeGame.Data.Bitmap 0.5 2.8 | |
runGame.\ Graphics.UI.FreeGame.GUI.GLFW 0.1 1.3 | |
individual inherited | |
COST CENTRE MODULE no. entries %time %alloc %time %alloc | |
MAIN MAIN 291 0 0.0 0.0 100.0 100.0 | |
main Main 586 0 0.0 0.0 100.0 100.0 | |
quit Graphics.UI.FreeGame.Base 2220 0 0.0 0.0 0.0 0.0 | |
runGame Graphics.UI.FreeGame.GUI.GLFW 2221 0 0.0 0.0 0.0 0.0 | |
runFinalizerT Graphics.UI.FreeGame.Internal.Finalizer 2222 0 0.0 0.0 0.0 0.0 | |
launch Graphics.UI.FreeGame.GUI.GLFW 2223 0 0.0 0.0 0.0 0.0 | |
liftIO Graphics.UI.FreeGame.Internal.Finalizer 2224 0 0.0 0.0 0.0 0.0 | |
liftIO.\ Graphics.UI.FreeGame.Internal.Finalizer 2225 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Internal.Finalizer 2226 0 0.0 0.0 0.0 0.0 | |
fmap.\ Graphics.UI.FreeGame.Internal.Finalizer 2227 0 0.0 0.0 0.0 0.0 | |
<*> Graphics.UI.FreeGame.Internal.Finalizer 2228 0 0.0 0.0 0.0 0.0 | |
<*>.\ Graphics.UI.FreeGame.Internal.Finalizer 2229 0 0.0 0.0 0.0 0.0 | |
<*>.\.\ Graphics.UI.FreeGame.Internal.Finalizer 2230 0 0.0 0.0 0.0 0.0 | |
<*>.\.\.\ Graphics.UI.FreeGame.Internal.Finalizer 2231 0 0.0 0.0 0.0 0.0 | |
runGame.\ Graphics.UI.FreeGame.GUI.GLFW 2232 0 0.0 0.0 0.0 0.0 | |
runAction Graphics.UI.FreeGame.GUI.GLFW 2233 1 0.0 0.0 0.0 0.0 | |
embedIO Graphics.UI.FreeGame.Base 669 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 683 1 0.0 0.0 0.0 0.0 | |
runGame Graphics.UI.FreeGame.GUI.GLFW 670 0 0.0 0.0 0.0 0.0 | |
runFinalizerT Graphics.UI.FreeGame.Internal.Finalizer 671 0 0.0 0.0 0.0 0.0 | |
launch Graphics.UI.FreeGame.GUI.GLFW 672 0 0.0 0.0 0.0 0.0 | |
liftIO Graphics.UI.FreeGame.Internal.Finalizer 673 1 0.0 0.0 0.0 0.0 | |
liftIO.\ Graphics.UI.FreeGame.Internal.Finalizer 674 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Internal.Finalizer 675 0 0.0 0.0 0.0 0.0 | |
fmap.\ Graphics.UI.FreeGame.Internal.Finalizer 676 0 0.0 0.0 0.0 0.0 | |
<*> Graphics.UI.FreeGame.Internal.Finalizer 677 0 0.0 0.0 0.0 0.0 | |
<*>.\ Graphics.UI.FreeGame.Internal.Finalizer 678 0 0.0 0.0 0.0 0.0 | |
<*>.\.\ Graphics.UI.FreeGame.Internal.Finalizer 679 0 0.0 0.0 0.0 0.0 | |
<*>.\.\.\ Graphics.UI.FreeGame.Internal.Finalizer 680 0 0.0 0.0 0.0 0.0 | |
runGame.\ Graphics.UI.FreeGame.GUI.GLFW 681 0 0.0 0.0 0.0 0.0 | |
runAction Graphics.UI.FreeGame.GUI.GLFW 682 1 0.0 0.0 0.0 0.0 | |
l.50:EmbedIO Graphics.UI.FreeGame.GUI.GLFW 684 1 0.0 0.0 0.0 0.0 | |
>>= Graphics.UI.FreeGame.Internal.Finalizer 685 1 0.0 0.0 0.0 0.0 | |
runGame Graphics.UI.FreeGame.GUI.GLFW 587 0 0.0 0.0 100.0 100.0 | |
fmap Graphics.UI.FreeGame.Internal.Finalizer 616 0 0.0 0.0 0.0 0.0 | |
fmap.\ Graphics.UI.FreeGame.Internal.Finalizer 617 1 0.0 0.0 0.0 0.0 | |
<*> Graphics.UI.FreeGame.Internal.Finalizer 613 0 0.0 0.0 0.0 0.0 | |
<*>.\ Graphics.UI.FreeGame.Internal.Finalizer 614 1 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Internal.Finalizer 619 0 0.0 0.0 0.0 0.0 | |
fmap.\ Graphics.UI.FreeGame.Internal.Finalizer 620 0 0.0 0.0 0.0 0.0 | |
>>= Graphics.UI.FreeGame.Internal.Finalizer 610 0 0.0 0.0 0.0 0.0 | |
>>=.\ Graphics.UI.FreeGame.Internal.Finalizer 611 1 0.0 0.0 0.0 0.0 | |
runFinalizerT Graphics.UI.FreeGame.Internal.Finalizer 608 1 0.0 0.0 99.8 100.0 | |
launch Graphics.UI.FreeGame.GUI.GLFW 623 0 0.0 0.0 99.8 100.0 | |
liftIO Graphics.UI.FreeGame.Internal.Finalizer 624 4897337 0.8 2.5 99.8 100.0 | |
liftIO.\ Graphics.UI.FreeGame.Internal.Finalizer 625 9750564 4.0 1.2 99.0 97.5 | |
installTexture Graphics.UI.FreeGame.GUI.GLFW 903 0 0.0 0.0 0.0 0.0 | |
embedIO Graphics.UI.FreeGame.Base 692 0 0.1 0.1 37.7 73.7 | |
fmap Graphics.UI.FreeGame.Internal.Finalizer 696 0 0.0 0.0 0.0 0.0 | |
fmap.\ Graphics.UI.FreeGame.Internal.Finalizer 697 0 0.0 0.0 0.0 0.0 | |
<*> Graphics.UI.FreeGame.Internal.Finalizer 698 0 0.0 0.0 0.0 0.0 | |
<*>.\ Graphics.UI.FreeGame.Internal.Finalizer 699 0 0.0 0.0 0.0 0.0 | |
<*>.\.\ Graphics.UI.FreeGame.Internal.Finalizer 700 0 0.0 0.0 0.0 0.0 | |
<*>.\.\.\ Graphics.UI.FreeGame.Internal.Finalizer 701 0 0.0 0.0 0.0 0.0 | |
runGame.\ Graphics.UI.FreeGame.GUI.GLFW 702 0 0.0 0.0 0.0 0.0 | |
runAction Graphics.UI.FreeGame.GUI.GLFW 791 1553 0.0 0.0 0.0 0.0 | |
l.50:EmbedIO Graphics.UI.FreeGame.GUI.GLFW 792 1553 0.0 0.0 0.0 0.0 | |
>>= Graphics.UI.FreeGame.Internal.Finalizer 793 1553 0.0 0.0 0.0 0.0 | |
initLoad Main 703 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 693 4773265 1.0 4.3 37.6 73.6 | |
mainloop Main 794 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.GUI 721 4770159 0.9 3.8 4.7 10.5 | |
step Main 1845 0 0.0 0.0 0.0 0.0 | |
keySpecial Graphics.UI.FreeGame.Base 1846 0 0.0 0.0 0.0 0.0 | |
draw Field 965 0 0.1 0.0 0.3 0.0 | |
drawBullet Field 2096 0 0.0 0.0 0.2 0.0 | |
translate Graphics.UI.FreeGame.Base 2097 0 0.0 0.0 0.2 0.0 | |
rotateR Graphics.UI.FreeGame.Base 2098 0 0.0 0.0 0.2 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 2099 0 0.2 0.0 0.2 0.0 | |
main.run Main 2109 0 0.0 0.0 0.0 0.0 | |
mainloop Main 2110 0 0.0 0.0 0.0 0.0 | |
update Key 2111 0 0.0 0.0 0.0 0.0 | |
keyChar Graphics.UI.FreeGame.Base 2112 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Internal.Finalizer 2113 0 0.0 0.0 0.0 0.0 | |
fmap.\ Graphics.UI.FreeGame.Internal.Finalizer 2114 0 0.0 0.0 0.0 0.0 | |
<*> Graphics.UI.FreeGame.Internal.Finalizer 2115 0 0.0 0.0 0.0 0.0 | |
<*>.\ Graphics.UI.FreeGame.Internal.Finalizer 2116 0 0.0 0.0 0.0 0.0 | |
<*>.\.\ Graphics.UI.FreeGame.Internal.Finalizer 2117 0 0.0 0.0 0.0 0.0 | |
<*>.\.\.\ Graphics.UI.FreeGame.Internal.Finalizer 2118 0 0.0 0.0 0.0 0.0 | |
runGame.\ Graphics.UI.FreeGame.GUI.GLFW 2119 0 0.0 0.0 0.0 0.0 | |
runAction Graphics.UI.FreeGame.GUI.GLFW 2120 0 0.0 0.0 0.0 0.0 | |
l.53:LiftUI,Input Graphics.UI.FreeGame.GUI.GLFW 2121 0 0.0 0.0 0.0 0.0 | |
runInput Graphics.UI.FreeGame.GUI.GLFW 2122 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.GUI 2106 0 0.0 0.0 0.0 0.0 | |
main.run Main 2107 0 0.0 0.0 0.0 0.0 | |
mainloop Main 2108 0 0.0 0.0 0.0 0.0 | |
drawEnemy Field 1939 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 1940 0 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 1941 0 0.0 0.0 0.0 0.0 | |
main.run Main 1948 0 0.0 0.0 0.0 0.0 | |
mainloop Main 1949 0 0.0 0.0 0.0 0.0 | |
update Key 1950 0 0.0 0.0 0.0 0.0 | |
keyChar Graphics.UI.FreeGame.Base 1951 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Internal.Finalizer 1952 0 0.0 0.0 0.0 0.0 | |
fmap.\ Graphics.UI.FreeGame.Internal.Finalizer 1953 0 0.0 0.0 0.0 0.0 | |
<*> Graphics.UI.FreeGame.Internal.Finalizer 1954 0 0.0 0.0 0.0 0.0 | |
<*>.\ Graphics.UI.FreeGame.Internal.Finalizer 1955 0 0.0 0.0 0.0 0.0 | |
<*>.\.\ Graphics.UI.FreeGame.Internal.Finalizer 1956 0 0.0 0.0 0.0 0.0 | |
<*>.\.\.\ Graphics.UI.FreeGame.Internal.Finalizer 1957 0 0.0 0.0 0.0 0.0 | |
runGame.\ Graphics.UI.FreeGame.GUI.GLFW 1958 0 0.0 0.0 0.0 0.0 | |
runAction Graphics.UI.FreeGame.GUI.GLFW 1959 0 0.0 0.0 0.0 0.0 | |
l.53:LiftUI,Input Graphics.UI.FreeGame.GUI.GLFW 1960 0 0.0 0.0 0.0 0.0 | |
runInput Graphics.UI.FreeGame.GUI.GLFW 1961 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.GUI 1945 0 0.0 0.0 0.0 0.0 | |
main.run Main 1946 0 0.0 0.0 0.0 0.0 | |
mainloop Main 1947 0 0.0 0.0 0.0 0.0 | |
draw Player 966 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 967 0 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 968 0 0.0 0.0 0.0 0.0 | |
main.run Main 976 0 0.0 0.0 0.0 0.0 | |
mainloop Main 977 0 0.0 0.0 0.0 0.0 | |
update Key 978 0 0.0 0.0 0.0 0.0 | |
keyChar Graphics.UI.FreeGame.Base 979 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Internal.Finalizer 980 0 0.0 0.0 0.0 0.0 | |
fmap.\ Graphics.UI.FreeGame.Internal.Finalizer 981 0 0.0 0.0 0.0 0.0 | |
<*> Graphics.UI.FreeGame.Internal.Finalizer 982 0 0.0 0.0 0.0 0.0 | |
<*>.\ Graphics.UI.FreeGame.Internal.Finalizer 983 0 0.0 0.0 0.0 0.0 | |
<*>.\.\ Graphics.UI.FreeGame.Internal.Finalizer 984 0 0.0 0.0 0.0 0.0 | |
<*>.\.\.\ Graphics.UI.FreeGame.Internal.Finalizer 985 0 0.0 0.0 0.0 0.0 | |
runGame.\ Graphics.UI.FreeGame.GUI.GLFW 986 0 0.0 0.0 0.0 0.0 | |
runAction Graphics.UI.FreeGame.GUI.GLFW 987 0 0.0 0.0 0.0 0.0 | |
l.53:LiftUI,Input Graphics.UI.FreeGame.GUI.GLFW 988 0 0.0 0.0 0.0 0.0 | |
runInput Graphics.UI.FreeGame.GUI.GLFW 989 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.GUI 973 0 0.0 0.0 0.0 0.0 | |
main.run Main 974 0 0.0 0.0 0.0 0.0 | |
mainloop Main 975 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.GUI 831 8324884 2.6 6.6 3.4 6.6 | |
fmap Graphics.UI.FreeGame.Internal.Finalizer 1149 12424 0.0 0.0 0.0 0.0 | |
main.run Main 951 0 0.0 0.0 0.8 0.0 | |
mainloop Main 952 0 0.0 0.0 0.8 0.0 | |
draw Field 969 0 0.0 0.0 0.8 0.0 | |
drawBullet Field 2100 0 0.0 0.0 0.8 0.0 | |
rotateR Graphics.UI.FreeGame.Base 2104 0 0.0 0.0 0.7 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 2105 0 0.7 0.0 0.7 0.0 | |
translate Graphics.UI.FreeGame.Base 2101 0 0.0 0.0 0.1 0.0 | |
rotateR Graphics.UI.FreeGame.Base 2102 0 0.0 0.0 0.1 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 2103 0 0.1 0.0 0.1 0.0 | |
drawEnemy Field 1942 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 1943 0 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 1944 0 0.0 0.0 0.0 0.0 | |
update Key 953 0 0.0 0.0 0.0 0.0 | |
keyChar Graphics.UI.FreeGame.Base 954 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Internal.Finalizer 955 0 0.0 0.0 0.0 0.0 | |
fmap.\ Graphics.UI.FreeGame.Internal.Finalizer 956 0 0.0 0.0 0.0 0.0 | |
<*> Graphics.UI.FreeGame.Internal.Finalizer 957 0 0.0 0.0 0.0 0.0 | |
<*>.\ Graphics.UI.FreeGame.Internal.Finalizer 958 0 0.0 0.0 0.0 0.0 | |
<*>.\.\ Graphics.UI.FreeGame.Internal.Finalizer 959 0 0.0 0.0 0.0 0.0 | |
<*>.\.\.\ Graphics.UI.FreeGame.Internal.Finalizer 960 0 0.0 0.0 0.0 0.0 | |
runGame.\ Graphics.UI.FreeGame.GUI.GLFW 961 0 0.0 0.0 0.0 0.0 | |
runAction Graphics.UI.FreeGame.GUI.GLFW 962 0 0.0 0.0 0.0 0.0 | |
l.53:LiftUI,Input Graphics.UI.FreeGame.GUI.GLFW 963 0 0.0 0.0 0.0 0.0 | |
runInput Graphics.UI.FreeGame.GUI.GLFW 964 0 0.0 0.0 0.0 0.0 | |
update Key 753 0 0.0 0.0 0.0 0.0 | |
keyChar Graphics.UI.FreeGame.Base 787 0 0.0 0.0 0.0 0.0 | |
keySpecial Graphics.UI.FreeGame.Base 754 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.GUI 742 10871 0.0 0.0 0.0 0.0 | |
step Main 1843 0 0.0 0.0 0.0 0.0 | |
keySpecial Graphics.UI.FreeGame.Base 1844 0 0.0 0.0 0.0 0.0 | |
update Key 751 0 0.0 0.0 0.0 0.0 | |
keyChar Graphics.UI.FreeGame.Base 786 0 0.0 0.0 0.0 0.0 | |
keySpecial Graphics.UI.FreeGame.Base 752 0 0.0 0.0 0.0 0.0 | |
main.run Main 704 1553 0.0 0.0 31.9 58.8 | |
mainloop Main 705 1553 0.1 0.0 31.9 58.8 | |
text Graphics.UI.FreeGame.Text 1588 1553 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 1609 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 1612 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 1635 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.GUI 1636 0 0.0 0.0 0.0 0.0 | |
fromString Graphics.UI.FreeGame.Text 1597 1553 0.0 0.0 0.0 0.0 | |
fromString.\ Graphics.UI.FreeGame.Text 1599 5066 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Text 1605 5066 0.0 0.0 0.0 0.0 | |
runTextT Graphics.UI.FreeGame.Text 1590 1553 0.0 0.0 0.0 0.0 | |
runTextT.cond Graphics.UI.FreeGame.Text 2179 1531 0.0 0.0 0.0 0.0 | |
runTextT.y0 Graphics.UI.FreeGame.Text 1723 1553 0.0 0.0 0.0 0.0 | |
runTextT.(...) Graphics.UI.FreeGame.Text 1722 1553 0.0 0.0 0.0 0.0 | |
runTextT.x0 Graphics.UI.FreeGame.Text 1721 1553 0.0 0.0 0.0 0.0 | |
runTextT.go Graphics.UI.FreeGame.Text 1594 1553 0.0 0.0 0.0 0.0 | |
colored Graphics.UI.FreeGame.Base 1587 0 0.0 0.0 0.0 0.0 | |
colored Graphics.UI.FreeGame.Base 1632 0 0.0 0.0 0.0 0.0 | |
colored Graphics.UI.FreeGame.GUI 1633 0 0.0 0.0 0.0 0.0 | |
_Draw Graphics.UI.FreeGame.GUI 1634 1553 0.0 0.0 0.0 0.0 | |
text Graphics.UI.FreeGame.Text 1592 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 1610 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 1613 0 0.0 0.0 0.0 0.0 | |
_LiftUI Graphics.UI.FreeGame.Base 1626 1553 0.0 0.0 0.0 0.0 | |
fromString Graphics.UI.FreeGame.Text 1598 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Text 1604 1553 0.0 0.0 0.0 0.0 | |
fromString.\ Graphics.UI.FreeGame.Text 1600 0 0.0 0.0 0.0 0.0 | |
runTextT Graphics.UI.FreeGame.Text 1601 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\ Graphics.UI.FreeGame.Text 1607 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 1611 0 0.0 0.0 0.0 0.0 | |
runTextT.go Graphics.UI.FreeGame.Text 1602 0 0.0 0.0 0.0 0.0 | |
runTextT Graphics.UI.FreeGame.Text 1593 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\ Graphics.UI.FreeGame.Text 1603 1553 0.0 0.0 0.0 0.0 | |
charToBitmap Graphics.UI.FreeGame.Data.Font 1637 1553 0.0 0.0 0.0 0.0 | |
charToBitmap.siz Graphics.UI.FreeGame.Data.Font 1644 1553 0.0 0.0 0.0 0.0 | |
>>= Graphics.UI.FreeGame.Internal.Finalizer 1638 1553 0.0 0.0 0.0 0.0 | |
runTextT.go Graphics.UI.FreeGame.Text 1596 1553 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 1585 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 1628 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.GUI 1629 0 0.0 0.0 0.0 0.0 | |
_Draw Graphics.UI.FreeGame.GUI 1630 1553 0.0 0.0 0.0 0.0 | |
colored Graphics.UI.FreeGame.Base 1614 0 0.0 0.0 0.0 0.0 | |
text Graphics.UI.FreeGame.Text 1615 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 1616 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 1617 0 0.0 0.0 0.0 0.0 | |
_LiftUI Graphics.UI.FreeGame.Base 1624 1553 0.0 0.0 0.0 0.0 | |
mainloop.writeFPS Main 990 1553 0.0 0.0 0.0 0.0 | |
text Graphics.UI.FreeGame.Text 999 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 1096 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 1100 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 1136 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.GUI 1147 0 0.0 0.0 0.0 0.0 | |
fromString Graphics.UI.FreeGame.Text 1046 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Text 1091 1553 0.0 0.0 0.0 0.0 | |
update Key 1332 0 0.0 0.0 0.0 0.0 | |
keyChar Graphics.UI.FreeGame.Base 1333 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Internal.Finalizer 1334 0 0.0 0.0 0.0 0.0 | |
fmap.\ Graphics.UI.FreeGame.Internal.Finalizer 1335 0 0.0 0.0 0.0 0.0 | |
<*> Graphics.UI.FreeGame.Internal.Finalizer 1336 0 0.0 0.0 0.0 0.0 | |
<*>.\ Graphics.UI.FreeGame.Internal.Finalizer 1337 0 0.0 0.0 0.0 0.0 | |
<*>.\.\ Graphics.UI.FreeGame.Internal.Finalizer 1338 0 0.0 0.0 0.0 0.0 | |
<*>.\.\.\ Graphics.UI.FreeGame.Internal.Finalizer 1339 0 0.0 0.0 0.0 0.0 | |
runGame.\ Graphics.UI.FreeGame.GUI.GLFW 1340 0 0.0 0.0 0.0 0.0 | |
runAction Graphics.UI.FreeGame.GUI.GLFW 1341 0 0.0 0.0 0.0 0.0 | |
l.53:LiftUI,Input Graphics.UI.FreeGame.GUI.GLFW 1342 0 0.0 0.0 0.0 0.0 | |
runInput Graphics.UI.FreeGame.GUI.GLFW 1343 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.GUI 1344 0 0.0 0.0 0.0 0.0 | |
fromString.\ Graphics.UI.FreeGame.Text 1061 0 0.0 0.0 0.0 0.0 | |
runTextT Graphics.UI.FreeGame.Text 1075 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\ Graphics.UI.FreeGame.Text 1090 1553 0.0 0.0 0.0 0.0 | |
charToBitmap Graphics.UI.FreeGame.Data.Font 1156 1553 0.0 0.0 0.0 0.0 | |
finalizer Graphics.UI.FreeGame.Internal.Finalizer 1178 1 0.0 0.0 0.0 0.0 | |
charToBitmap.siz Graphics.UI.FreeGame.Data.Font 1168 1553 0.0 0.0 0.0 0.0 | |
charToBitmap.render Graphics.UI.FreeGame.Data.Font 1166 1 0.0 0.0 0.0 0.0 | |
makeStableBitmap Graphics.UI.FreeGame.Data.Bitmap 1177 1 0.0 0.0 0.0 0.0 | |
charToBitmap.render.pix Graphics.UI.FreeGame.Data.Font 1176 480 0.0 0.0 0.0 0.0 | |
charToBitmap.render.h Graphics.UI.FreeGame.Data.Font 1175 1 0.0 0.0 0.0 0.0 | |
charToBitmap.render.w Graphics.UI.FreeGame.Data.Font 1174 1 0.0 0.0 0.0 0.0 | |
runFreeType Graphics.UI.FreeGame.Data.Font 1167 3 0.0 0.0 0.0 0.0 | |
>>= Graphics.UI.FreeGame.Internal.Finalizer 1158 1553 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 1097 0 0.0 0.0 0.0 0.0 | |
runTextT.go Graphics.UI.FreeGame.Text 1076 1553 0.0 0.0 0.0 0.0 | |
runTextT.go.\ Graphics.UI.FreeGame.Text 1094 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 1098 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 1101 0 0.0 0.0 0.0 0.0 | |
colored Graphics.UI.FreeGame.Base 1102 0 0.0 0.0 0.0 0.0 | |
_LiftUI Graphics.UI.FreeGame.Base 1125 1553 0.0 0.0 0.0 0.0 | |
update Key 1077 0 0.0 0.0 0.0 0.0 | |
keyChar Graphics.UI.FreeGame.Base 1078 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Internal.Finalizer 1079 0 0.0 0.0 0.0 0.0 | |
fmap.\ Graphics.UI.FreeGame.Internal.Finalizer 1080 0 0.0 0.0 0.0 0.0 | |
<*> Graphics.UI.FreeGame.Internal.Finalizer 1081 0 0.0 0.0 0.0 0.0 | |
<*>.\ Graphics.UI.FreeGame.Internal.Finalizer 1082 0 0.0 0.0 0.0 0.0 | |
<*>.\.\ Graphics.UI.FreeGame.Internal.Finalizer 1083 0 0.0 0.0 0.0 0.0 | |
<*>.\.\.\ Graphics.UI.FreeGame.Internal.Finalizer 1084 0 0.0 0.0 0.0 0.0 | |
runGame.\ Graphics.UI.FreeGame.GUI.GLFW 1085 0 0.0 0.0 0.0 0.0 | |
runAction Graphics.UI.FreeGame.GUI.GLFW 1086 0 0.0 0.0 0.0 0.0 | |
l.53:LiftUI,Input Graphics.UI.FreeGame.GUI.GLFW 1087 0 0.0 0.0 0.0 0.0 | |
runInput Graphics.UI.FreeGame.GUI.GLFW 1088 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.GUI 1089 0 0.0 0.0 0.0 0.0 | |
update Key 1062 0 0.0 0.0 0.0 0.0 | |
keyChar Graphics.UI.FreeGame.Base 1063 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Internal.Finalizer 1064 0 0.0 0.0 0.0 0.0 | |
fmap.\ Graphics.UI.FreeGame.Internal.Finalizer 1065 0 0.0 0.0 0.0 0.0 | |
<*> Graphics.UI.FreeGame.Internal.Finalizer 1066 0 0.0 0.0 0.0 0.0 | |
<*>.\ Graphics.UI.FreeGame.Internal.Finalizer 1067 0 0.0 0.0 0.0 0.0 | |
<*>.\.\ Graphics.UI.FreeGame.Internal.Finalizer 1068 0 0.0 0.0 0.0 0.0 | |
<*>.\.\.\ Graphics.UI.FreeGame.Internal.Finalizer 1069 0 0.0 0.0 0.0 0.0 | |
runGame.\ Graphics.UI.FreeGame.GUI.GLFW 1070 0 0.0 0.0 0.0 0.0 | |
runAction Graphics.UI.FreeGame.GUI.GLFW 1071 0 0.0 0.0 0.0 0.0 | |
l.53:LiftUI,Input Graphics.UI.FreeGame.GUI.GLFW 1072 0 0.0 0.0 0.0 0.0 | |
runInput Graphics.UI.FreeGame.GUI.GLFW 1073 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.GUI 1074 0 0.0 0.0 0.0 0.0 | |
update Key 1048 0 0.0 0.0 0.0 0.0 | |
keyChar Graphics.UI.FreeGame.Base 1049 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Internal.Finalizer 1050 0 0.0 0.0 0.0 0.0 | |
fmap.\ Graphics.UI.FreeGame.Internal.Finalizer 1051 0 0.0 0.0 0.0 0.0 | |
<*> Graphics.UI.FreeGame.Internal.Finalizer 1052 0 0.0 0.0 0.0 0.0 | |
<*>.\ Graphics.UI.FreeGame.Internal.Finalizer 1053 0 0.0 0.0 0.0 0.0 | |
<*>.\.\ Graphics.UI.FreeGame.Internal.Finalizer 1054 0 0.0 0.0 0.0 0.0 | |
<*>.\.\.\ Graphics.UI.FreeGame.Internal.Finalizer 1055 0 0.0 0.0 0.0 0.0 | |
runGame.\ Graphics.UI.FreeGame.GUI.GLFW 1056 0 0.0 0.0 0.0 0.0 | |
runAction Graphics.UI.FreeGame.GUI.GLFW 1057 0 0.0 0.0 0.0 0.0 | |
l.53:LiftUI,Input Graphics.UI.FreeGame.GUI.GLFW 1058 0 0.0 0.0 0.0 0.0 | |
runInput Graphics.UI.FreeGame.GUI.GLFW 1059 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.GUI 1060 0 0.0 0.0 0.0 0.0 | |
runTextT Graphics.UI.FreeGame.Text 1000 1553 0.0 0.0 0.0 0.0 | |
runTextT.cond Graphics.UI.FreeGame.Text 1508 1553 0.0 0.0 0.0 0.0 | |
runTextT.y0 Graphics.UI.FreeGame.Text 1280 1553 0.0 0.0 0.0 0.0 | |
runTextT.(...) Graphics.UI.FreeGame.Text 1279 1553 0.0 0.0 0.0 0.0 | |
runTextT.x0 Graphics.UI.FreeGame.Text 1278 1553 0.0 0.0 0.0 0.0 | |
runTextT.go Graphics.UI.FreeGame.Text 1031 0 0.0 0.0 0.0 0.0 | |
update Key 1032 0 0.0 0.0 0.0 0.0 | |
keyChar Graphics.UI.FreeGame.Base 1033 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Internal.Finalizer 1034 0 0.0 0.0 0.0 0.0 | |
fmap.\ Graphics.UI.FreeGame.Internal.Finalizer 1035 0 0.0 0.0 0.0 0.0 | |
<*> Graphics.UI.FreeGame.Internal.Finalizer 1036 0 0.0 0.0 0.0 0.0 | |
<*>.\ Graphics.UI.FreeGame.Internal.Finalizer 1037 0 0.0 0.0 0.0 0.0 | |
<*>.\.\ Graphics.UI.FreeGame.Internal.Finalizer 1038 0 0.0 0.0 0.0 0.0 | |
<*>.\.\.\ Graphics.UI.FreeGame.Internal.Finalizer 1039 0 0.0 0.0 0.0 0.0 | |
runGame.\ Graphics.UI.FreeGame.GUI.GLFW 1040 0 0.0 0.0 0.0 0.0 | |
runAction Graphics.UI.FreeGame.GUI.GLFW 1041 0 0.0 0.0 0.0 0.0 | |
l.53:LiftUI,Input Graphics.UI.FreeGame.GUI.GLFW 1042 0 0.0 0.0 0.0 0.0 | |
runInput Graphics.UI.FreeGame.GUI.GLFW 1043 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.GUI 1044 0 0.0 0.0 0.0 0.0 | |
update Key 1018 0 0.0 0.0 0.0 0.0 | |
keyChar Graphics.UI.FreeGame.Base 1019 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Internal.Finalizer 1020 0 0.0 0.0 0.0 0.0 | |
fmap.\ Graphics.UI.FreeGame.Internal.Finalizer 1021 0 0.0 0.0 0.0 0.0 | |
<*> Graphics.UI.FreeGame.Internal.Finalizer 1022 0 0.0 0.0 0.0 0.0 | |
<*>.\ Graphics.UI.FreeGame.Internal.Finalizer 1023 0 0.0 0.0 0.0 0.0 | |
<*>.\.\ Graphics.UI.FreeGame.Internal.Finalizer 1024 0 0.0 0.0 0.0 0.0 | |
<*>.\.\.\ Graphics.UI.FreeGame.Internal.Finalizer 1025 0 0.0 0.0 0.0 0.0 | |
runGame.\ Graphics.UI.FreeGame.GUI.GLFW 1026 0 0.0 0.0 0.0 0.0 | |
runAction Graphics.UI.FreeGame.GUI.GLFW 1027 0 0.0 0.0 0.0 0.0 | |
l.53:LiftUI,Input Graphics.UI.FreeGame.GUI.GLFW 1028 0 0.0 0.0 0.0 0.0 | |
runInput Graphics.UI.FreeGame.GUI.GLFW 1029 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.GUI 1030 0 0.0 0.0 0.0 0.0 | |
colored Graphics.UI.FreeGame.Base 996 0 0.0 0.0 0.0 0.0 | |
colored Graphics.UI.FreeGame.Base 1133 0 0.0 0.0 0.0 0.0 | |
colored Graphics.UI.FreeGame.GUI 1134 0 0.0 0.0 0.0 0.0 | |
_Draw Graphics.UI.FreeGame.GUI 1135 1553 0.0 0.0 0.0 0.0 | |
update Key 1003 0 0.0 0.0 0.0 0.0 | |
keyChar Graphics.UI.FreeGame.Base 1004 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Internal.Finalizer 1005 0 0.0 0.0 0.0 0.0 | |
fmap.\ Graphics.UI.FreeGame.Internal.Finalizer 1006 0 0.0 0.0 0.0 0.0 | |
<*> Graphics.UI.FreeGame.Internal.Finalizer 1007 0 0.0 0.0 0.0 0.0 | |
<*>.\ Graphics.UI.FreeGame.Internal.Finalizer 1008 0 0.0 0.0 0.0 0.0 | |
<*>.\.\ Graphics.UI.FreeGame.Internal.Finalizer 1009 0 0.0 0.0 0.0 0.0 | |
<*>.\.\.\ Graphics.UI.FreeGame.Internal.Finalizer 1010 0 0.0 0.0 0.0 0.0 | |
runGame.\ Graphics.UI.FreeGame.GUI.GLFW 1011 0 0.0 0.0 0.0 0.0 | |
runAction Graphics.UI.FreeGame.GUI.GLFW 1012 0 0.0 0.0 0.0 0.0 | |
l.53:LiftUI,Input Graphics.UI.FreeGame.GUI.GLFW 1013 0 0.0 0.0 0.0 0.0 | |
runInput Graphics.UI.FreeGame.GUI.GLFW 1014 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.GUI 1015 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 994 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 1128 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.GUI 1129 0 0.0 0.0 0.0 0.0 | |
_Draw Graphics.UI.FreeGame.GUI 1130 1553 0.0 0.0 0.0 0.0 | |
text Graphics.UI.FreeGame.Text 1103 0 0.0 0.0 0.0 0.0 | |
fromString Graphics.UI.FreeGame.Text 1104 0 0.0 0.0 0.0 0.0 | |
fromString.\ Graphics.UI.FreeGame.Text 1105 0 0.0 0.0 0.0 0.0 | |
runTextT Graphics.UI.FreeGame.Text 1106 0 0.0 0.0 0.0 0.0 | |
runTextT.go Graphics.UI.FreeGame.Text 1107 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\ Graphics.UI.FreeGame.Text 1108 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 1109 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 1110 0 0.0 0.0 0.0 0.0 | |
colored Graphics.UI.FreeGame.Base 1111 0 0.0 0.0 0.0 0.0 | |
_LiftUI Graphics.UI.FreeGame.Base 1123 1553 0.0 0.0 0.0 0.0 | |
draw Field 802 1553 0.4 1.3 12.5 23.7 | |
drawBullet Field 2045 1184394 1.9 5.6 12.0 22.3 | |
drawBullet.img Field 2078 1184394 1.1 0.0 2.6 1.0 | |
unsafeIndex Object 2085 1184394 0.3 0.5 0.3 0.5 | |
inRange Object 2084 1184394 0.5 0.0 0.5 0.0 | |
unsafeIndex Object 2080 1184394 0.3 0.5 0.3 0.5 | |
inRange Object 2079 1184394 0.4 0.0 0.4 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 2050 0 0.4 1.4 1.1 3.1 | |
fromBitmap Graphics.UI.FreeGame.Base 2064 0 0.5 1.3 0.8 1.7 | |
fromBitmap Graphics.UI.FreeGame.GUI 2077 0 0.2 0.4 0.2 0.4 | |
rotateR Graphics.UI.FreeGame.Base 2047 1184394 1.3 1.4 3.6 6.7 | |
rotateR Graphics.UI.FreeGame.Base 2061 1184394 0.2 0.6 0.8 1.9 | |
rotateR Graphics.UI.FreeGame.Base 2069 0 0.4 0.7 0.6 1.3 | |
rotateD Graphics.UI.FreeGame.GUI 2071 0 0.2 0.6 0.2 0.6 | |
fromBitmap Graphics.UI.FreeGame.Base 2051 0 0.6 1.6 1.5 3.3 | |
rotateR Graphics.UI.FreeGame.Base 2062 0 0.1 0.0 0.9 1.8 | |
rotateR Graphics.UI.FreeGame.Base 2072 0 0.0 0.0 0.5 1.1 | |
rotateD Graphics.UI.FreeGame.GUI 2073 0 0.2 0.4 0.5 1.1 | |
_Draw Graphics.UI.FreeGame.GUI 2074 1184394 0.3 0.7 0.3 0.7 | |
_LiftUI Graphics.UI.FreeGame.Base 2063 1184394 0.3 0.7 0.3 0.7 | |
translate Graphics.UI.FreeGame.Base 2046 1184394 0.6 1.4 2.8 6.0 | |
translate Graphics.UI.FreeGame.Base 2058 1184394 0.3 0.6 0.6 1.2 | |
translate Graphics.UI.FreeGame.GUI 2065 0 0.3 0.6 0.3 0.6 | |
rotateR Graphics.UI.FreeGame.Base 2052 0 0.0 0.0 1.6 3.3 | |
fromBitmap Graphics.UI.FreeGame.Base 2053 0 0.5 1.6 1.6 3.3 | |
translate Graphics.UI.FreeGame.Base 2059 0 0.1 0.0 1.1 1.8 | |
translate Graphics.UI.FreeGame.GUI 2066 0 0.4 0.4 0.7 1.1 | |
_Draw Graphics.UI.FreeGame.GUI 2067 1184394 0.3 0.7 0.3 0.7 | |
_LiftUI Graphics.UI.FreeGame.Base 2060 1184394 0.4 0.7 0.4 0.7 | |
drawEnemy Field 1913 1543 0.0 0.0 0.0 0.0 | |
object Object 1931 0 0.0 0.0 0.0 0.0 | |
object Object 1935 0 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 1917 0 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 1926 0 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.GUI 1938 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 1914 1543 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 1922 1543 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.GUI 1927 0 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 1918 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 1923 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.GUI 1928 0 0.0 0.0 0.0 0.0 | |
_Draw Graphics.UI.FreeGame.GUI 1929 1543 0.0 0.0 0.0 0.0 | |
_LiftUI Graphics.UI.FreeGame.Base 1924 1543 0.0 0.0 0.0 0.0 | |
draw Player 805 1553 0.0 0.0 0.0 0.0 | |
object Object 834 0 0.0 0.0 0.0 0.0 | |
object Object 838 0 0.0 0.0 0.0 0.0 | |
chara Object 836 0 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 809 0 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 818 0 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.GUI 884 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 806 1553 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 814 1553 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.GUI 820 0 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 810 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 815 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.GUI 821 0 0.0 0.0 0.0 0.0 | |
_Draw Graphics.UI.FreeGame.GUI 822 1553 0.0 0.0 0.0 0.0 | |
_LiftUI Graphics.UI.FreeGame.Base 816 1553 0.0 0.0 0.0 0.0 | |
update Key 706 1553 0.0 0.0 19.3 35.0 | |
keyChar Graphics.UI.FreeGame.Base 762 0 0.0 0.0 19.3 35.0 | |
fmap Graphics.UI.FreeGame.Internal.Finalizer 763 0 0.0 0.0 19.3 35.0 | |
fmap.\ Graphics.UI.FreeGame.Internal.Finalizer 764 0 0.0 0.0 19.3 35.0 | |
<*> Graphics.UI.FreeGame.Internal.Finalizer 765 0 0.0 0.0 19.3 35.0 | |
<*>.\ Graphics.UI.FreeGame.Internal.Finalizer 766 0 0.0 0.0 19.3 35.0 | |
<*>.\.\ Graphics.UI.FreeGame.Internal.Finalizer 767 0 0.0 0.0 19.3 35.0 | |
<*>.\.\.\ Graphics.UI.FreeGame.Internal.Finalizer 768 0 0.0 0.0 19.3 35.0 | |
runGame.\ Graphics.UI.FreeGame.GUI.GLFW 769 0 0.1 1.3 19.3 35.0 | |
runAction Graphics.UI.FreeGame.GUI.GLFW 770 1195255 0.2 0.0 19.2 33.6 | |
l.55:Tick Graphics.UI.FreeGame.GUI.GLFW 1781 1553 0.0 0.0 1.8 0.0 | |
l.69:liftIO Graphics.UI.FreeGame.GUI.GLFW 1813 1553 1.1 0.0 1.1 0.0 | |
l.80:GLmatrixMode Graphics.UI.FreeGame.GUI.GLFW 1830 1553 0.0 0.0 0.0 0.0 | |
l.73:GLortho Graphics.UI.FreeGame.GUI.GLFW 1829 1553 0.0 0.0 0.0 0.0 | |
runAction.windowL Graphics.UI.FreeGame.GUI.GLFW 1828 1553 0.0 0.0 0.0 0.0 | |
runAction.ww Graphics.UI.FreeGame.GUI.GLFW 1827 1553 0.0 0.0 0.0 0.0 | |
runAction.ox Graphics.UI.FreeGame.GUI.GLFW 1826 1553 0.0 0.0 0.0 0.0 | |
runAction.windowT Graphics.UI.FreeGame.GUI.GLFW 1825 1553 0.0 0.0 0.0 0.0 | |
runAction.wh Graphics.UI.FreeGame.GUI.GLFW 1824 1553 0.0 0.0 0.0 0.0 | |
runAction.windowB Graphics.UI.FreeGame.GUI.GLFW 1823 1553 0.0 0.0 0.0 0.0 | |
runAction.windowR Graphics.UI.FreeGame.GUI.GLFW 1822 1553 0.0 0.0 0.0 0.0 | |
runAction.(...) Graphics.UI.FreeGame.GUI.GLFW 1820 1553 0.0 0.0 0.0 0.0 | |
_windowSize Graphics.UI.FreeGame.GUI 1821 1553 0.0 0.0 0.0 0.0 | |
runAction.oy Graphics.UI.FreeGame.GUI.GLFW 1819 1553 0.0 0.0 0.0 0.0 | |
runAction.(...) Graphics.UI.FreeGame.GUI.GLFW 1817 1553 0.0 0.0 0.0 0.0 | |
_windowOrigin Graphics.UI.FreeGame.GUI 1818 1553 0.0 0.0 0.0 0.0 | |
l.72:GLScale Graphics.UI.FreeGame.GUI.GLFW 1816 1553 0.0 0.0 0.0 0.0 | |
l.71:GLloadIdentity Graphics.UI.FreeGame.GUI.GLFW 1815 1553 0.0 0.0 0.0 0.0 | |
l.70:GLclear Graphics.UI.FreeGame.GUI.GLFW 1814 1553 0.0 0.0 0.0 0.0 | |
l.56:liftIO Graphics.UI.FreeGame.GUI.GLFW 1792 1553 0.7 0.0 0.7 0.0 | |
l.62:sleep Graphics.UI.FreeGame.GUI.GLFW 1798 1553 0.1 0.0 0.1 0.0 | |
_framePerSecond Graphics.UI.FreeGame.GUI 1799 1553 0.0 0.0 0.0 0.0 | |
l.61:refFrame Graphics.UI.FreeGame.GUI.GLFW 1797 1553 0.0 0.0 0.0 0.0 | |
l.60:getTime Graphics.UI.FreeGame.GUI.GLFW 1796 1553 0.0 0.0 0.0 0.0 | |
l.59:performGC Graphics.UI.FreeGame.GUI.GLFW 1795 1553 0.0 0.0 0.0 0.0 | |
l.58:swapBuffers Graphics.UI.FreeGame.GUI.GLFW 1794 1553 0.0 0.0 0.0 0.0 | |
l.57:GLmatrixMode Graphics.UI.FreeGame.GUI.GLFW 1793 1553 0.0 0.0 0.0 0.0 | |
>>= Graphics.UI.FreeGame.Internal.Finalizer 1782 4659 0.0 0.0 0.0 0.0 | |
l.49:LiftUI,Draw Graphics.UI.FreeGame.GUI.GLFW 824 1190596 0.2 0.7 6.6 11.5 | |
runPicture Graphics.UI.FreeGame.GUI.GLFW 830 3568692 6.1 9.1 6.4 10.8 | |
return Graphics.UI.FreeGame.Internal.Finalizer 939 1187490 0.0 0.0 0.0 0.0 | |
finalizer Graphics.UI.FreeGame.Internal.Finalizer 928 3 0.0 0.0 0.0 0.0 | |
installTexture Graphics.UI.FreeGame.GUI.GLFW 896 3 0.0 0.0 0.0 0.0 | |
installTexture.height Graphics.UI.FreeGame.GUI.GLFW 920 3 0.0 0.0 0.0 0.0 | |
installTexture.(...) Graphics.UI.FreeGame.GUI.GLFW 914 3 0.0 0.0 0.0 0.0 | |
bitmapSize Graphics.UI.FreeGame.Data.Bitmap 915 3 0.0 0.0 0.0 0.0 | |
bitmapSize.h Graphics.UI.FreeGame.Data.Bitmap 921 3 0.0 0.0 0.0 0.0 | |
bitmapSize.(...) Graphics.UI.FreeGame.Data.Bitmap 917 3 0.0 0.0 0.0 0.0 | |
bitmapSize.w Graphics.UI.FreeGame.Data.Bitmap 916 3 0.0 0.0 0.0 0.0 | |
installTexture.width Graphics.UI.FreeGame.GUI.GLFW 913 3 0.0 0.0 0.0 0.0 | |
installTexture.siz Graphics.UI.FreeGame.GUI.GLFW 912 3 0.0 0.0 0.0 0.0 | |
>>= Graphics.UI.FreeGame.Internal.Finalizer 897 3 0.0 0.0 0.0 0.0 | |
>>= Graphics.UI.FreeGame.Internal.Finalizer 867 3565586 0.0 0.0 0.0 0.0 | |
preservingMatrix' Graphics.UI.FreeGame.GUI.GLFW 845 2374990 0.3 1.7 0.3 1.7 | |
>>= Graphics.UI.FreeGame.Internal.Finalizer 846 4749980 0.0 0.0 0.0 0.0 | |
>>= Graphics.UI.FreeGame.Internal.Finalizer 825 1190596 0.0 0.0 0.0 0.0 | |
l.53:LiftUI,Input Graphics.UI.FreeGame.GUI.GLFW 776 3106 0.0 0.0 10.5 22.1 | |
runInput Graphics.UI.FreeGame.GUI.GLFW 780 3106 0.0 0.0 10.5 22.1 | |
mapSpecialKey Graphics.UI.FreeGame.GUI.GLFW 1840 1553 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.GUI 784 0 0.0 0.0 10.5 22.1 | |
update.keyFun Key 1858 1552 0.0 0.0 0.0 0.0 | |
update Field 1847 1552 0.0 0.0 9.5 20.1 | |
addPlayerBullet Field 1856 1552 0.0 0.0 0.0 0.0 | |
addEnemyBullet Field 1855 0 0.0 0.0 0.0 0.0 | |
addEnemyBullet.\ Field 1991 1542 0.0 0.0 0.0 0.0 | |
clearQ Field 1968 0 0.0 0.0 0.0 0.0 | |
updateField Field 1853 1552 0.6 1.1 9.5 20.0 | |
updateField.\ Field 2023 1184418 0.7 0.0 6.9 16.1 | |
normalBullet Barrage 2027 0 4.2 12.2 6.2 16.1 | |
fromPolar Global 2040 1184418 1.0 2.2 1.9 3.9 | |
fromPair Global 2042 0 0.3 0.4 0.3 0.4 | |
$* Global 2041 1184418 0.6 1.4 0.6 1.4 | |
counter.go.\ Object 2030 1184418 0.0 0.0 0.0 0.0 | |
pos.go.\ Object 2029 1184418 0.0 0.0 0.0 0.0 | |
barrage Barrage 2025 1184418 0.0 0.0 0.0 0.0 | |
updateField.\ Field 2016 1184418 1.4 2.7 1.9 2.7 | |
isInside Global 2018 0 0.3 0.0 0.5 0.0 | |
isInside.\ Global 2044 1184418 0.1 0.0 0.1 0.0 | |
toPair Global 2020 1184418 0.0 0.0 0.0 0.0 | |
isInside.\ Global 2019 1184418 0.1 0.0 0.1 0.0 | |
/= Object 1988 1542 0.0 0.0 0.0 0.0 | |
== Object 1987 1542 0.0 0.0 0.0 0.0 | |
updateField.\ Field 1966 1542 0.0 0.0 0.0 0.0 | |
normalEnemy Barrage 1970 1542 0.0 0.0 0.0 0.0 | |
barrage.danmaku Barrage 2003 1540 0.0 0.0 0.0 0.0 | |
barrage.danmaku.ang Barrage 2043 1540 0.0 0.0 0.0 0.0 | |
barrage.danmaku.posE Barrage 2031 1540 0.0 0.0 0.0 0.0 | |
object Object 2035 0 0.0 0.0 0.0 0.0 | |
object Object 2039 0 0.0 0.0 0.0 0.0 | |
barrage Barrage 2038 0 0.0 0.0 0.0 0.0 | |
barrage Barrage 2033 0 0.0 0.0 0.0 0.0 | |
initBullet Object 2024 1540 0.0 0.0 0.0 0.0 | |
if_ Barrage 2015 1540 0.0 0.0 0.0 0.0 | |
barrage.danmaku.cnt Barrage 2004 1540 0.0 0.0 0.0 0.0 | |
object Object 2010 0 0.0 0.0 0.0 0.0 | |
object Object 2014 0 0.0 0.0 0.0 0.0 | |
barrage Barrage 2013 0 0.0 0.0 0.0 0.0 | |
barrage Barrage 2008 0 0.0 0.0 0.0 0.0 | |
$* Global 1999 1 0.0 0.0 0.0 0.0 | |
moveMState Barrage 1997 1542 0.0 0.0 0.0 0.0 | |
counter.go.\ Object 1996 1543 0.0 0.0 0.0 0.0 | |
object Object 1983 0 0.0 0.0 0.0 0.0 | |
object Object 1985 0 0.0 0.0 0.0 0.0 | |
moveMState Barrage 1998 0 0.0 0.0 0.0 0.0 | |
pos.go.\ Object 1995 1542 0.0 0.0 0.0 0.0 | |
objectChara.go.\ Object 1986 3085 0.0 0.0 0.0 0.0 | |
normalEnemy.m Barrage 1972 1542 0.0 0.0 0.0 0.0 | |
checkStateMotion Barrage 1973 1542 0.0 0.0 0.0 0.0 | |
object Object 1976 0 0.0 0.0 0.0 0.0 | |
object Object 1979 0 0.0 0.0 0.0 0.0 | |
== Object 1971 3085 0.0 0.0 0.0 0.0 | |
barrage Barrage 1969 1542 0.0 0.0 0.0 0.0 | |
updateField.\ Field 1962 1542 0.0 0.0 0.0 0.0 | |
update Player 1865 1552 0.0 0.0 0.0 0.0 | |
updateCounter Player 1873 0 0.0 0.0 0.0 0.0 | |
counter.go.\ Object 1879 1552 0.0 0.0 0.0 0.0 | |
object Object 1876 0 0.0 0.0 0.0 0.0 | |
objectChara.go.\ Object 1877 1552 0.0 0.0 0.0 0.0 | |
updatePos Player 1866 1552 0.0 0.0 0.0 0.0 | |
updatePos.dir Player 1895 1552 0.0 0.0 0.0 0.0 | |
updatePos.dir.addTup Player 1898 6208 0.0 0.0 0.0 0.0 | |
bool Global 1899 6208 0.0 0.0 0.0 0.0 | |
$* Global 1894 1552 0.0 0.0 0.0 0.0 | |
clamp Player 1886 0 0.0 0.0 0.0 0.0 | |
clamp.edgeY Player 1906 0 0.0 0.0 0.0 0.0 | |
clamp.edgeY.\ Player 1909 1552 0.0 0.0 0.0 0.0 | |
bool Global 1910 1552 0.0 0.0 0.0 0.0 | |
clamp.edgeY.\ Player 1907 1552 0.0 0.0 0.0 0.0 | |
bool Global 1908 1552 0.0 0.0 0.0 0.0 | |
toPair Global 1901 1552 0.0 0.0 0.0 0.0 | |
toInt Global 1893 0 0.0 0.0 0.0 0.0 | |
clamp.edgeX Player 1890 0 0.0 0.0 0.0 0.0 | |
clamp.edgeX.\ Player 1903 1552 0.0 0.0 0.0 0.0 | |
bool Global 1904 1552 0.0 0.0 0.0 0.0 | |
clamp.edgeX.\ Player 1891 1552 0.0 0.0 0.0 0.0 | |
bool Global 1902 1552 0.0 0.0 0.0 0.0 | |
fromPair Global 1888 0 0.0 0.0 0.0 0.0 | |
toNum Global 1887 0 0.0 0.0 0.0 0.0 | |
pos.go.\ Object 1881 1552 0.0 0.0 0.0 0.0 | |
chara Object 1871 0 0.0 0.0 0.0 0.0 | |
object Object 1870 0 0.0 0.0 0.0 0.0 | |
pos.go.\ Object 1880 1552 0.0 0.0 0.0 0.0 | |
objectChara.go.\ Object 1878 3104 0.0 0.0 0.0 0.0 | |
collideP Field 1852 0 0.0 0.0 0.0 0.0 | |
bool Global 1884 1552 0.0 0.0 0.0 0.0 | |
collideP.pair Field 1883 1552 0.0 0.0 0.0 0.0 | |
collideP.pair.\ Field 1989 1542 0.0 0.0 0.0 0.0 | |
collideChara Field 1990 1542 0.0 0.0 0.0 0.0 | |
collideChara.bullet' Field 2001 1541 0.0 0.0 0.0 0.0 | |
collideChara.inDist Field 2002 1541 0.0 0.0 0.0 0.0 | |
hp.go.\ Object 1994 1542 0.0 0.0 0.0 0.0 | |
collideP.bullet' Field 1882 1552 0.0 0.0 0.0 0.0 | |
addEnemy Field 1849 0 0.0 0.0 0.0 0.0 | |
object Object 1860 0 0.0 0.0 0.0 0.0 | |
object Object 1864 0 0.0 0.0 0.0 0.0 | |
chara Object 1862 0 0.0 0.0 0.0 0.0 | |
addEnemy.maybeHead Field 1850 1552 0.0 0.0 0.0 0.0 | |
step Main 1778 0 0.0 0.0 0.0 0.0 | |
keySpecial Graphics.UI.FreeGame.Base 1832 0 0.0 0.0 0.0 0.0 | |
tick Graphics.UI.FreeGame.Base 1780 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 1618 0 0.0 0.0 0.0 0.0 | |
colored Graphics.UI.FreeGame.Base 1619 0 0.0 0.0 0.0 0.0 | |
text Graphics.UI.FreeGame.Text 1620 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 1621 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 1622 0 0.0 0.0 0.0 0.0 | |
mainloop.fps' Main 1552 1553 0.0 0.0 0.0 0.0 | |
mainloop.getFPS Main 1553 1553 0.0 0.0 0.0 0.0 | |
mainloop.writeFPS Main 991 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 1112 0 0.0 0.0 0.0 0.0 | |
text Graphics.UI.FreeGame.Text 1113 0 0.0 0.0 0.0 0.0 | |
fromString Graphics.UI.FreeGame.Text 1114 0 0.0 0.0 0.0 0.0 | |
fromString.\ Graphics.UI.FreeGame.Text 1115 0 0.0 0.0 0.0 0.0 | |
runTextT Graphics.UI.FreeGame.Text 1116 0 0.0 0.0 0.0 0.0 | |
runTextT.go Graphics.UI.FreeGame.Text 1117 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\ Graphics.UI.FreeGame.Text 1118 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 1119 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 1120 0 0.0 0.0 0.0 0.0 | |
colored Graphics.UI.FreeGame.Base 1121 0 0.0 0.0 0.0 0.0 | |
text Graphics.UI.FreeGame.Text 997 1553 0.0 0.0 0.0 0.0 | |
fromString Graphics.UI.FreeGame.Text 1045 1553 0.0 0.0 0.0 0.0 | |
fromString.\ Graphics.UI.FreeGame.Text 1047 8420 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Text 1092 8420 0.0 0.0 0.0 0.0 | |
runTextT Graphics.UI.FreeGame.Text 1001 0 0.0 0.0 0.0 0.0 | |
runTextT.go Graphics.UI.FreeGame.Text 1016 1553 0.0 0.0 0.0 0.0 | |
draw Field 803 0 0.3 0.8 0.9 1.9 | |
drawBullet Field 2054 0 0.0 0.0 0.5 1.1 | |
translate Graphics.UI.FreeGame.Base 2055 0 0.0 0.0 0.5 1.1 | |
rotateR Graphics.UI.FreeGame.Base 2056 0 0.0 0.0 0.5 1.1 | |
fromBitmap Graphics.UI.FreeGame.Base 2057 0 0.5 1.1 0.5 1.1 | |
drawEnemy Field 1919 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 1920 0 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 1921 0 0.0 0.0 0.0 0.0 | |
draw Player 811 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 812 0 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 813 0 0.0 0.0 0.0 0.0 | |
keySpecial Graphics.UI.FreeGame.Base 788 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.GUI 785 0 0.0 0.0 0.0 0.0 | |
step Main 1841 0 0.0 0.0 0.0 0.0 | |
keySpecial Graphics.UI.FreeGame.Base 1842 0 0.0 0.0 0.0 0.0 | |
>>= Graphics.UI.FreeGame.Internal.Finalizer 777 3106 0.0 0.0 0.0 0.0 | |
keySpecial Graphics.UI.FreeGame.Base 709 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Internal.Finalizer 710 0 0.0 0.0 0.0 0.0 | |
fmap.\ Graphics.UI.FreeGame.Internal.Finalizer 711 0 0.0 0.0 0.0 0.0 | |
<*> Graphics.UI.FreeGame.Internal.Finalizer 712 0 0.0 0.0 0.0 0.0 | |
<*>.\ Graphics.UI.FreeGame.Internal.Finalizer 713 0 0.0 0.0 0.0 0.0 | |
<*>.\.\ Graphics.UI.FreeGame.Internal.Finalizer 714 0 0.0 0.0 0.0 0.0 | |
<*>.\.\.\ Graphics.UI.FreeGame.Internal.Finalizer 715 0 0.0 0.0 0.0 0.0 | |
runGame.\ Graphics.UI.FreeGame.GUI.GLFW 716 0 0.0 0.0 0.0 0.0 | |
runAction Graphics.UI.FreeGame.GUI.GLFW 717 7765 0.0 0.0 0.0 0.0 | |
l.53:LiftUI,Input Graphics.UI.FreeGame.GUI.GLFW 724 7765 0.0 0.0 0.0 0.0 | |
runInput Graphics.UI.FreeGame.GUI.GLFW 741 7765 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.GUI 749 0 0.0 0.0 0.0 0.0 | |
update.keyFun Key 1900 6208 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.GUI 750 0 0.0 0.0 0.0 0.0 | |
mapSpecialKey Graphics.UI.FreeGame.GUI.GLFW 746 7765 0.0 0.0 0.0 0.0 | |
>>= Graphics.UI.FreeGame.Internal.Finalizer 725 7765 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Internal.Finalizer 626 41520 0.0 0.0 57.3 22.6 | |
fmap.\ Graphics.UI.FreeGame.Internal.Finalizer 627 53944 0.0 0.0 57.3 22.6 | |
embedIO Graphics.UI.FreeGame.Base 1152 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 1153 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.GUI 1154 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.GUI 1155 0 0.0 0.0 0.0 0.0 | |
<*> Graphics.UI.FreeGame.Internal.Finalizer 628 0 0.0 0.0 57.2 22.6 | |
<*>.\ Graphics.UI.FreeGame.Internal.Finalizer 629 0 0.0 0.0 57.2 22.6 | |
<*>.\.\ Graphics.UI.FreeGame.Internal.Finalizer 630 1 0.0 0.0 57.2 22.6 | |
<*>.\.\.\ Graphics.UI.FreeGame.Internal.Finalizer 631 1 0.0 0.0 57.2 22.6 | |
runGame.\ Graphics.UI.FreeGame.GUI.GLFW 636 1 0.0 0.0 57.2 22.6 | |
runAction Graphics.UI.FreeGame.GUI.GLFW 687 23866 0.0 0.0 56.7 19.8 | |
return Graphics.UI.FreeGame.Internal.Finalizer 2236 0 0.0 0.0 0.0 0.0 | |
return.\ Graphics.UI.FreeGame.Internal.Finalizer 2237 1 0.0 0.0 0.0 0.0 | |
runFinalizerT.\ Graphics.UI.FreeGame.Internal.Finalizer 2238 1 0.0 0.0 0.0 0.0 | |
l.55:Tick Graphics.UI.FreeGame.GUI.GLFW 1783 0 0.0 0.0 0.0 0.0 | |
l.67:windowIsOpen Graphics.UI.FreeGame.GUI.GLFW 1812 0 0.0 0.0 0.0 0.0 | |
>>= Graphics.UI.FreeGame.Internal.Finalizer 1784 0 0.0 0.0 0.0 0.0 | |
>>=.\ Graphics.UI.FreeGame.Internal.Finalizer 1785 4659 0.0 0.0 0.0 0.0 | |
>>=.\.\ Graphics.UI.FreeGame.Internal.Finalizer 1800 4659 0.0 0.0 0.0 0.0 | |
embedIO Graphics.UI.FreeGame.Base 1802 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 1803 0 0.0 0.0 0.0 0.0 | |
main.run Main 1804 0 0.0 0.0 0.0 0.0 | |
mainloop Main 1805 0 0.0 0.0 0.0 0.0 | |
update Key 1806 0 0.0 0.0 0.0 0.0 | |
keyChar Graphics.UI.FreeGame.Base 1807 0 0.0 0.0 0.0 0.0 | |
unFinalizerT Graphics.UI.FreeGame.Internal.Finalizer 1801 4659 0.0 0.0 0.0 0.0 | |
embedIO Graphics.UI.FreeGame.Base 1786 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 1787 0 0.0 0.0 0.0 0.0 | |
main.run Main 1788 0 0.0 0.0 0.0 0.0 | |
mainloop Main 1789 0 0.0 0.0 0.0 0.0 | |
update Key 1790 0 0.0 0.0 0.0 0.0 | |
keyChar Graphics.UI.FreeGame.Base 1791 0 0.0 0.0 0.0 0.0 | |
l.49:LiftUI,Draw Graphics.UI.FreeGame.GUI.GLFW 827 23866 0.1 0.0 56.6 19.6 | |
runPicture Graphics.UI.FreeGame.GUI.GLFW 853 85084 1.4 2.2 56.3 19.2 | |
>>=.\.\ Graphics.UI.FreeGame.Internal.Finalizer 1911 1187487 0.2 0.0 0.2 0.0 | |
unFinalizerT Graphics.UI.FreeGame.Internal.Finalizer 1912 1187487 0.0 0.0 0.0 0.0 | |
return Graphics.UI.FreeGame.Internal.Finalizer 940 2385370 0.1 0.0 2.4 2.9 | |
return.\ Graphics.UI.FreeGame.Internal.Finalizer 941 3559374 0.3 0.0 2.3 2.9 | |
>>= Graphics.UI.FreeGame.Internal.Finalizer 947 0 0.0 0.0 0.3 0.0 | |
>>=.\ Graphics.UI.FreeGame.Internal.Finalizer 948 0 0.1 0.0 0.3 0.0 | |
>>=.\.\ Graphics.UI.FreeGame.Internal.Finalizer 949 1187490 0.3 0.0 0.3 0.0 | |
embedIO Graphics.UI.FreeGame.Base 1138 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 1139 0 0.0 0.0 0.0 0.0 | |
main.run Main 1140 0 0.0 0.0 0.0 0.0 | |
mainloop Main 1141 0 0.0 0.0 0.0 0.0 | |
update Key 1142 0 0.0 0.0 0.0 0.0 | |
keyChar Graphics.UI.FreeGame.Base 1143 0 0.0 0.0 0.0 0.0 | |
unFinalizerT Graphics.UI.FreeGame.Internal.Finalizer 950 1187490 0.0 0.0 0.0 0.0 | |
preservingMatrix' Graphics.UI.FreeGame.GUI.GLFW 942 0 0.0 0.0 1.7 2.9 | |
>>= Graphics.UI.FreeGame.Internal.Finalizer 943 2371884 0.1 0.0 1.6 2.9 | |
>>=.\ Graphics.UI.FreeGame.Internal.Finalizer 944 2371884 0.6 0.5 1.5 2.9 | |
>>=.\.\ Graphics.UI.FreeGame.Internal.Finalizer 945 4743768 0.9 2.4 0.9 2.4 | |
unFinalizerT Graphics.UI.FreeGame.Internal.Finalizer 946 4743768 0.0 0.0 0.0 0.0 | |
finalizer Graphics.UI.FreeGame.Internal.Finalizer 935 14 0.0 0.0 0.0 0.0 | |
finalizer.\ Graphics.UI.FreeGame.Internal.Finalizer 936 3 0.0 0.0 0.0 0.0 | |
runFinalizerT.\ Graphics.UI.FreeGame.Internal.Finalizer 2239 3 0.0 0.0 0.0 0.0 | |
>>=.\.\ Graphics.UI.FreeGame.Internal.Finalizer 937 3 0.0 0.0 0.0 0.0 | |
unFinalizerT Graphics.UI.FreeGame.Internal.Finalizer 938 3 0.0 0.0 0.0 0.0 | |
installTexture Graphics.UI.FreeGame.GUI.GLFW 898 14 0.0 0.0 0.0 0.0 | |
installTexture.height Graphics.UI.FreeGame.GUI.GLFW 1298 14 0.0 0.0 0.0 0.0 | |
installTexture.(...) Graphics.UI.FreeGame.GUI.GLFW 1294 14 0.0 0.0 0.0 0.0 | |
bitmapSize Graphics.UI.FreeGame.Data.Bitmap 1295 14 0.0 0.0 0.0 0.0 | |
bitmapSize.h Graphics.UI.FreeGame.Data.Bitmap 1299 14 0.0 0.0 0.0 0.0 | |
bitmapSize.(...) Graphics.UI.FreeGame.Data.Bitmap 1297 14 0.0 0.0 0.0 0.0 | |
bitmapSize.w Graphics.UI.FreeGame.Data.Bitmap 1296 14 0.0 0.0 0.0 0.0 | |
installTexture.width Graphics.UI.FreeGame.GUI.GLFW 1293 14 0.0 0.0 0.0 0.0 | |
installTexture.siz Graphics.UI.FreeGame.GUI.GLFW 1292 14 0.0 0.0 0.0 0.0 | |
>>= Graphics.UI.FreeGame.Internal.Finalizer 899 29 0.0 0.0 0.0 0.0 | |
>>=.\ Graphics.UI.FreeGame.Internal.Finalizer 900 18 0.0 0.0 0.0 0.0 | |
l.53:LiftUI,Input Graphics.UI.FreeGame.GUI.GLFW 2260 0 0.0 0.0 0.0 0.0 | |
runInput Graphics.UI.FreeGame.GUI.GLFW 2261 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.GUI 2262 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.GUI 2263 0 0.0 0.0 0.0 0.0 | |
main.run Main 2264 0 0.0 0.0 0.0 0.0 | |
mainloop Main 2265 0 0.0 0.0 0.0 0.0 | |
mainloop.writeFPS Main 2266 0 0.0 0.0 0.0 0.0 | |
text Graphics.UI.FreeGame.Text 2267 0 0.0 0.0 0.0 0.0 | |
runTextT Graphics.UI.FreeGame.Text 2268 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\ Graphics.UI.FreeGame.Text 2269 0 0.0 0.0 0.0 0.0 | |
charToBitmap Graphics.UI.FreeGame.Data.Font 2270 0 0.0 0.0 0.0 0.0 | |
finalizer Graphics.UI.FreeGame.Internal.Finalizer 2271 0 0.0 0.0 0.0 0.0 | |
finalizer.\ Graphics.UI.FreeGame.Internal.Finalizer 2272 0 0.0 0.0 0.0 0.0 | |
runFinalizerT.\ Graphics.UI.FreeGame.Internal.Finalizer 2273 0 0.0 0.0 0.0 0.0 | |
embedIO Graphics.UI.FreeGame.Base 906 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 907 0 0.0 0.0 0.0 0.0 | |
main.run Main 908 0 0.0 0.0 0.0 0.0 | |
mainloop Main 909 0 0.0 0.0 0.0 0.0 | |
mainloop.writeFPS Main 2250 0 0.0 0.0 0.0 0.0 | |
text Graphics.UI.FreeGame.Text 2251 0 0.0 0.0 0.0 0.0 | |
fromString Graphics.UI.FreeGame.Text 2252 0 0.0 0.0 0.0 0.0 | |
fromString.\ Graphics.UI.FreeGame.Text 2253 0 0.0 0.0 0.0 0.0 | |
runTextT Graphics.UI.FreeGame.Text 2254 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\ Graphics.UI.FreeGame.Text 2255 0 0.0 0.0 0.0 0.0 | |
charToBitmap Graphics.UI.FreeGame.Data.Font 2256 0 0.0 0.0 0.0 0.0 | |
finalizer Graphics.UI.FreeGame.Internal.Finalizer 2257 0 0.0 0.0 0.0 0.0 | |
finalizer.\ Graphics.UI.FreeGame.Internal.Finalizer 2258 0 0.0 0.0 0.0 0.0 | |
runFinalizerT.\ Graphics.UI.FreeGame.Internal.Finalizer 2259 0 0.0 0.0 0.0 0.0 | |
update Key 910 0 0.0 0.0 0.0 0.0 | |
keyChar Graphics.UI.FreeGame.Base 911 0 0.0 0.0 0.0 0.0 | |
>>=.\.\ Graphics.UI.FreeGame.Internal.Finalizer 904 21 0.0 0.0 0.0 0.0 | |
embedIO Graphics.UI.FreeGame.Base 929 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 930 0 0.0 0.0 0.0 0.0 | |
main.run Main 931 0 0.0 0.0 0.0 0.0 | |
mainloop Main 932 0 0.0 0.0 0.0 0.0 | |
update Key 933 0 0.0 0.0 0.0 0.0 | |
keyChar Graphics.UI.FreeGame.Base 934 0 0.0 0.0 0.0 0.0 | |
drawTextureAt Graphics.UI.FreeGame.GUI.GLFW 926 3 0.0 0.0 0.0 0.0 | |
return Graphics.UI.FreeGame.Internal.Finalizer 924 3 0.0 0.0 0.0 0.0 | |
return.\ Graphics.UI.FreeGame.Internal.Finalizer 925 3 0.0 0.0 0.0 0.0 | |
finalizer Graphics.UI.FreeGame.Internal.Finalizer 922 3 0.0 0.0 0.0 0.0 | |
finalizer.\ Graphics.UI.FreeGame.Internal.Finalizer 923 3 0.0 0.0 0.0 0.0 | |
runFinalizerT.\ Graphics.UI.FreeGame.Internal.Finalizer 2240 3 0.0 0.0 0.0 0.0 | |
embedIO Graphics.UI.FreeGame.Base 2244 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 2245 0 0.0 0.0 0.0 0.0 | |
main.run Main 2246 0 0.0 0.0 0.0 0.0 | |
mainloop Main 2247 0 0.0 0.0 0.0 0.0 | |
update Key 2248 0 0.0 0.0 0.0 0.0 | |
keyChar Graphics.UI.FreeGame.Base 2249 0 0.0 0.0 0.0 0.0 | |
unFinalizerT Graphics.UI.FreeGame.Internal.Finalizer 905 21 0.0 0.0 0.0 0.0 | |
>>= Graphics.UI.FreeGame.Internal.Finalizer 874 1400696 0.3 0.0 50.5 11.7 | |
>>=.\ Graphics.UI.FreeGame.Internal.Finalizer 875 5074839 1.3 1.4 50.2 11.7 | |
l.53:LiftUI,Input Graphics.UI.FreeGame.GUI.GLFW 1423 0 0.0 0.0 0.0 0.0 | |
runInput Graphics.UI.FreeGame.GUI.GLFW 1424 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.GUI 1425 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.GUI 1426 0 0.0 0.0 0.0 0.0 | |
main.run Main 1429 0 0.0 0.0 0.0 0.0 | |
mainloop Main 1430 0 0.0 0.0 0.0 0.0 | |
mainloop.writeFPS Main 1431 0 0.0 0.0 0.0 0.0 | |
text Graphics.UI.FreeGame.Text 1432 0 0.0 0.0 0.0 0.0 | |
runTextT Graphics.UI.FreeGame.Text 1433 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\ Graphics.UI.FreeGame.Text 1434 0 0.0 0.0 0.0 0.0 | |
charToBitmap Graphics.UI.FreeGame.Data.Font 1435 0 0.0 0.0 0.0 0.0 | |
finalizer Graphics.UI.FreeGame.Internal.Finalizer 1444 0 0.0 0.0 0.0 0.0 | |
finalizer.\ Graphics.UI.FreeGame.Internal.Finalizer 1445 13 0.0 0.0 0.0 0.0 | |
runFinalizerT.\ Graphics.UI.FreeGame.Internal.Finalizer 2242 13 0.0 0.0 0.0 0.0 | |
>>=.\.\ Graphics.UI.FreeGame.Internal.Finalizer 1446 13 0.0 0.0 0.0 0.0 | |
unFinalizerT Graphics.UI.FreeGame.Internal.Finalizer 1447 13 0.0 0.0 0.0 0.0 | |
installTexture Graphics.UI.FreeGame.GUI.GLFW 1290 0 0.0 0.0 0.0 0.0 | |
preservingMatrix' Graphics.UI.FreeGame.GUI.GLFW 1186 0 0.0 0.0 0.0 0.0 | |
>>=.\.\ Graphics.UI.FreeGame.Internal.Finalizer 882 3893544 3.6 7.2 48.9 10.2 | |
drawTextureAt Graphics.UI.FreeGame.GUI.GLFW 1302 1200973 44.1 1.9 44.1 1.9 | |
finalizer Graphics.UI.FreeGame.Internal.Finalizer 1300 14 0.0 0.0 0.0 0.0 | |
finalizer.\ Graphics.UI.FreeGame.Internal.Finalizer 1301 28 0.0 0.0 0.0 0.0 | |
runFinalizerT.\ Graphics.UI.FreeGame.Internal.Finalizer 2241 28 0.0 0.0 0.0 0.0 | |
installTexture Graphics.UI.FreeGame.GUI.GLFW 1291 0 0.0 0.0 0.0 0.0 | |
preservingMatrix' Graphics.UI.FreeGame.GUI.GLFW 1276 0 0.0 0.0 0.0 0.0 | |
return Graphics.UI.FreeGame.Internal.Finalizer 1183 80930 0.0 0.0 0.4 0.9 | |
return.\ Graphics.UI.FreeGame.Internal.Finalizer 1184 94416 0.0 0.0 0.4 0.9 | |
l.53:LiftUI,Input Graphics.UI.FreeGame.GUI.GLFW 1448 0 0.0 0.0 0.2 0.4 | |
runInput Graphics.UI.FreeGame.GUI.GLFW 1449 0 0.0 0.0 0.2 0.4 | |
fmap Graphics.UI.FreeGame.GUI 1450 38277 0.0 0.0 0.2 0.4 | |
mainloop.writeFPS Main 1529 0 0.0 0.0 0.0 0.0 | |
text Graphics.UI.FreeGame.Text 1530 0 0.0 0.0 0.0 0.0 | |
runTextT Graphics.UI.FreeGame.Text 1562 0 0.0 0.0 0.0 0.0 | |
embedIO Graphics.UI.FreeGame.Base 1578 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 1579 0 0.0 0.0 0.0 0.0 | |
main.run Main 1580 0 0.0 0.0 0.0 0.0 | |
mainloop Main 1581 0 0.0 0.0 0.0 0.0 | |
update Key 1582 0 0.0 0.0 0.0 0.0 | |
keyChar Graphics.UI.FreeGame.Base 1583 0 0.0 0.0 0.0 0.0 | |
mainloop Main 1574 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\ Graphics.UI.FreeGame.Text 1568 1553 0.0 0.0 0.0 0.0 | |
runTextT.go Graphics.UI.FreeGame.Text 1563 0 0.0 0.0 0.0 0.0 | |
fromString Graphics.UI.FreeGame.Text 1531 0 0.0 0.0 0.0 0.0 | |
embedIO Graphics.UI.FreeGame.Base 1534 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 1535 0 0.0 0.0 0.0 0.0 | |
main.run Main 1536 0 0.0 0.0 0.0 0.0 | |
mainloop Main 1537 0 0.0 0.0 0.0 0.0 | |
update Key 1538 0 0.0 0.0 0.0 0.0 | |
keyChar Graphics.UI.FreeGame.Base 1539 0 0.0 0.0 0.0 0.0 | |
fromString.\ Graphics.UI.FreeGame.Text 1532 0 0.0 0.0 0.0 0.0 | |
runTextT Graphics.UI.FreeGame.Text 1557 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\ Graphics.UI.FreeGame.Text 1569 0 0.0 0.0 0.0 0.0 | |
embedIO Graphics.UI.FreeGame.Base 1570 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 1571 0 0.0 0.0 0.0 0.0 | |
main.run Main 1572 0 0.0 0.0 0.0 0.0 | |
mainloop Main 1573 0 0.0 0.0 0.0 0.0 | |
runTextT.go Graphics.UI.FreeGame.Text 1558 0 0.0 0.0 0.0 0.0 | |
embedIO Graphics.UI.FreeGame.Base 1564 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 1565 0 0.0 0.0 0.0 0.0 | |
main.run Main 1566 0 0.0 0.0 0.0 0.0 | |
mainloop Main 1567 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.GUI 1559 0 0.0 0.0 0.0 0.0 | |
main.run Main 1560 0 0.0 0.0 0.0 0.0 | |
mainloop Main 1561 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Text 1533 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.GUI 1554 0 0.0 0.0 0.0 0.0 | |
main.run Main 1555 0 0.0 0.0 0.0 0.0 | |
mainloop Main 1556 0 0.0 0.0 0.0 0.0 | |
embedIO Graphics.UI.FreeGame.Base 1540 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 1541 0 0.0 0.0 0.0 0.0 | |
main.run Main 1542 0 0.0 0.0 0.0 0.0 | |
mainloop Main 1543 0 0.0 0.0 0.0 0.0 | |
update Key 1544 0 0.0 0.0 0.0 0.0 | |
keyChar Graphics.UI.FreeGame.Base 1545 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.GUI 1451 90876 0.0 0.1 0.2 0.3 | |
translate Graphics.UI.FreeGame.Base 2137 0 0.0 0.0 0.0 0.0 | |
embedIO Graphics.UI.FreeGame.Base 2167 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 2168 0 0.0 0.0 0.0 0.0 | |
main.run Main 2169 0 0.0 0.0 0.0 0.0 | |
mainloop Main 2170 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 2138 5495 0.0 0.0 0.0 0.0 | |
main.run Main 2214 0 0.0 0.0 0.0 0.0 | |
mainloop Main 2215 0 0.0 0.0 0.0 0.0 | |
embedIO Graphics.UI.FreeGame.Base 2207 0 0.0 0.0 0.0 0.0 | |
main.run Main 1455 0 0.0 0.0 0.1 0.2 | |
mainloop Main 1456 0 0.0 0.0 0.1 0.2 | |
update Key 2212 0 0.0 0.0 0.0 0.0 | |
keyChar Graphics.UI.FreeGame.Base 2213 0 0.0 0.0 0.0 0.0 | |
colored Graphics.UI.FreeGame.Base 2208 0 0.0 0.0 0.0 0.0 | |
text Graphics.UI.FreeGame.Text 2209 0 0.0 0.0 0.0 0.0 | |
embedIO Graphics.UI.FreeGame.Base 2210 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 2211 0 0.0 0.0 0.0 0.0 | |
mainloop.writeFPS Main 1457 0 0.0 0.0 0.1 0.2 | |
colored Graphics.UI.FreeGame.Base 1486 0 0.0 0.0 0.0 0.0 | |
colored Graphics.UI.FreeGame.Base 1501 0 0.0 0.0 0.0 0.0 | |
colored Graphics.UI.FreeGame.GUI 1502 0 0.0 0.0 0.0 0.0 | |
_Draw Graphics.UI.FreeGame.GUI 1503 6867 0.0 0.0 0.0 0.0 | |
_LiftUI Graphics.UI.FreeGame.Base 1493 6867 0.0 0.0 0.0 0.0 | |
text Graphics.UI.FreeGame.Text 1458 0 0.0 0.0 0.1 0.2 | |
runTextT Graphics.UI.FreeGame.Text 1466 0 0.0 0.0 0.0 0.1 | |
runTextT.go Graphics.UI.FreeGame.Text 1471 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\ Graphics.UI.FreeGame.Text 1472 0 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 1473 0 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 1479 0 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 1500 0 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.GUI 1518 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 1499 6867 0.0 0.0 0.0 0.0 | |
runTextT.go.\ Graphics.UI.FreeGame.Text 1467 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\.offset Graphics.UI.FreeGame.Text 1517 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\.h Graphics.UI.FreeGame.Text 1515 6867 0.0 0.0 0.0 0.0 | |
runTextT.go.\.w Graphics.UI.FreeGame.Text 1512 6867 0.0 0.0 0.0 0.0 | |
runTextT.go.\.(...) Graphics.UI.FreeGame.Text 1510 6867 0.0 0.0 0.0 0.0 | |
bitmapSize Graphics.UI.FreeGame.Data.Bitmap 1511 6867 0.0 0.0 0.0 0.0 | |
bitmapSize.h Graphics.UI.FreeGame.Data.Bitmap 1516 6867 0.0 0.0 0.0 0.0 | |
bitmapSize.(...) Graphics.UI.FreeGame.Data.Bitmap 1514 6867 0.0 0.0 0.0 0.0 | |
bitmapSize.w Graphics.UI.FreeGame.Data.Bitmap 1513 6867 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 1468 0 0.0 0.0 0.0 0.0 | |
fromString Graphics.UI.FreeGame.Text 1459 0 0.0 0.0 0.1 0.1 | |
fromString.\ Graphics.UI.FreeGame.Text 1460 0 0.0 0.0 0.1 0.1 | |
runTextT Graphics.UI.FreeGame.Text 1461 0 0.0 0.0 0.1 0.1 | |
runTextT.go Graphics.UI.FreeGame.Text 1474 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\ Graphics.UI.FreeGame.Text 1475 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\.pen' Graphics.UI.FreeGame.Text 1550 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 1481 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 1482 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 1496 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.GUI 1505 0 0.0 0.0 0.0 0.0 | |
_Draw Graphics.UI.FreeGame.GUI 1506 6867 0.0 0.0 0.0 0.0 | |
_LiftUI Graphics.UI.FreeGame.Base 1497 6867 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 1476 0 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 1480 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 1498 6867 0.0 0.0 0.0 0.0 | |
runTextT.go.\ Graphics.UI.FreeGame.Text 1462 0 0.0 0.0 0.0 0.1 | |
runTextT.go.\.pen' Graphics.UI.FreeGame.Text 1549 5314 0.0 0.0 0.0 0.0 | |
runTextT.go Graphics.UI.FreeGame.Text 1551 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\.offset Graphics.UI.FreeGame.Text 1507 6867 0.0 0.0 0.0 0.0 | |
runTextT.go Graphics.UI.FreeGame.Text 1483 0 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 1478 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 1469 6867 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 1470 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 1495 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.GUI 1504 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 1494 6867 0.0 0.0 0.0 0.0 | |
runTextT.go Graphics.UI.FreeGame.Text 1519 0 0.0 0.0 0.0 0.0 | |
embedIO Graphics.UI.FreeGame.Base 1484 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 1485 0 0.0 0.0 0.0 0.0 | |
runTextT.go Graphics.UI.FreeGame.Text 1477 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 1463 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 1464 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 1465 0 0.0 0.0 0.0 0.0 | |
mainloop.writeFPS Main 1452 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 1453 0 0.0 0.0 0.0 0.0 | |
embedIO Graphics.UI.FreeGame.Base 1489 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 1490 0 0.0 0.0 0.0 0.0 | |
main.run Main 1491 0 0.0 0.0 0.0 0.0 | |
mainloop Main 1492 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 1454 12181 0.0 0.0 0.0 0.0 | |
main.run Main 1547 0 0.0 0.0 0.0 0.0 | |
mainloop Main 1548 0 0.0 0.0 0.0 0.0 | |
embedIO Graphics.UI.FreeGame.Base 1546 0 0.0 0.0 0.0 0.0 | |
embedIO Graphics.UI.FreeGame.Base 1187 0 0.0 0.0 0.2 0.5 | |
fmap Graphics.UI.FreeGame.Base 1188 50749 0.0 0.0 0.2 0.5 | |
main.run Main 1191 0 0.0 0.0 0.1 0.2 | |
mainloop Main 1192 0 0.0 0.0 0.1 0.2 | |
text Graphics.UI.FreeGame.Text 1670 0 0.0 0.0 0.0 0.1 | |
fromFinalizer Graphics.UI.FreeGame.Base 2127 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 2130 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 2133 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.GUI 2134 0 0.0 0.0 0.0 0.0 | |
fromString Graphics.UI.FreeGame.Text 1756 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Text 2126 3513 0.0 0.0 0.0 0.0 | |
fromString.\ Graphics.UI.FreeGame.Text 2123 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.GUI 2124 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.GUI 2125 0 0.0 0.0 0.0 0.0 | |
runTextT Graphics.UI.FreeGame.Text 1671 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\ Graphics.UI.FreeGame.Text 1761 5066 0.0 0.0 0.0 0.0 | |
charToBitmap Graphics.UI.FreeGame.Data.Font 2135 3513 0.0 0.0 0.0 0.0 | |
charToBitmap.siz Graphics.UI.FreeGame.Data.Font 2136 3513 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 2128 0 0.0 0.0 0.0 0.0 | |
runTextT.go Graphics.UI.FreeGame.Text 1672 3513 0.0 0.0 0.0 0.0 | |
runTextT.go.\ Graphics.UI.FreeGame.Text 1673 0 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 1674 0 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 1681 0 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 1706 0 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.GUI 1732 0 0.0 0.0 0.0 0.0 | |
colored Graphics.UI.FreeGame.Base 1655 0 0.0 0.0 0.0 0.1 | |
colored Graphics.UI.FreeGame.Base 1710 0 0.0 0.0 0.0 0.0 | |
colored Graphics.UI.FreeGame.GUI 1711 0 0.0 0.0 0.0 0.0 | |
_Draw Graphics.UI.FreeGame.GUI 1712 8579 0.0 0.0 0.0 0.0 | |
_LiftUI Graphics.UI.FreeGame.Base 1700 8579 0.0 0.0 0.0 0.0 | |
text Graphics.UI.FreeGame.Text 1656 0 0.0 0.0 0.0 0.0 | |
runTextT Graphics.UI.FreeGame.Text 1664 0 0.0 0.0 0.0 0.0 | |
runTextT.go Graphics.UI.FreeGame.Text 1675 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.GUI 1759 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.GUI 1760 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\ Graphics.UI.FreeGame.Text 1676 0 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 1677 0 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 1682 0 0.0 0.0 0.0 0.0 | |
fromString Graphics.UI.FreeGame.Text 1683 0 0.0 0.0 0.0 0.0 | |
fromString.\ Graphics.UI.FreeGame.Text 1684 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\ Graphics.UI.FreeGame.Text 1665 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 2129 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\.offset Graphics.UI.FreeGame.Text 1731 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\.h Graphics.UI.FreeGame.Text 1729 1553 0.0 0.0 0.0 0.0 | |
runTextT.go.\.w Graphics.UI.FreeGame.Text 1726 1553 0.0 0.0 0.0 0.0 | |
runTextT.go.\.(...) Graphics.UI.FreeGame.Text 1724 1553 0.0 0.0 0.0 0.0 | |
bitmapSize Graphics.UI.FreeGame.Data.Bitmap 1725 1553 0.0 0.0 0.0 0.0 | |
bitmapSize.h Graphics.UI.FreeGame.Data.Bitmap 1730 1553 0.0 0.0 0.0 0.0 | |
bitmapSize.(...) Graphics.UI.FreeGame.Data.Bitmap 1728 1553 0.0 0.0 0.0 0.0 | |
bitmapSize.w Graphics.UI.FreeGame.Data.Bitmap 1727 1553 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 1685 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 1686 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 1704 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.GUI 1716 0 0.0 0.0 0.0 0.0 | |
_Draw Graphics.UI.FreeGame.GUI 1717 1553 0.0 0.0 0.0 0.0 | |
fromString Graphics.UI.FreeGame.Text 1718 0 0.0 0.0 0.0 0.0 | |
fromString.\ Graphics.UI.FreeGame.Text 1719 0 0.0 0.0 0.0 0.0 | |
_LiftUI Graphics.UI.FreeGame.Base 1705 1553 0.0 0.0 0.0 0.0 | |
fromString Graphics.UI.FreeGame.Text 1714 0 0.0 0.0 0.0 0.0 | |
fromString.\ Graphics.UI.FreeGame.Text 1715 0 0.0 0.0 0.0 0.0 | |
fromString Graphics.UI.FreeGame.Text 1702 0 0.0 0.0 0.0 0.0 | |
fromString.\ Graphics.UI.FreeGame.Text 1703 0 0.0 0.0 0.0 0.0 | |
fromString Graphics.UI.FreeGame.Text 1659 0 0.0 0.0 0.0 0.0 | |
fromString.\ Graphics.UI.FreeGame.Text 1660 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Text 1755 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.GUI 1757 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.GUI 1758 0 0.0 0.0 0.0 0.0 | |
runTextT Graphics.UI.FreeGame.Text 1661 0 0.0 0.0 0.0 0.0 | |
runTextT.go Graphics.UI.FreeGame.Text 1678 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\ Graphics.UI.FreeGame.Text 1679 0 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 1680 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\ Graphics.UI.FreeGame.Text 1662 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\.pen' Graphics.UI.FreeGame.Text 2180 1531 0.0 0.0 0.0 0.0 | |
runTextT.go Graphics.UI.FreeGame.Text 2182 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\.offset Graphics.UI.FreeGame.Text 1720 1553 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 1666 1553 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 1668 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 1701 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.GUI 1713 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 1663 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 1657 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 1658 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 1650 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 1707 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.GUI 1708 0 0.0 0.0 0.0 0.0 | |
_Draw Graphics.UI.FreeGame.GUI 1709 8579 0.0 0.0 0.0 0.0 | |
_LiftUI Graphics.UI.FreeGame.Base 1699 8579 0.0 0.0 0.0 0.0 | |
colored Graphics.UI.FreeGame.Base 1651 0 0.0 0.0 0.0 0.0 | |
text Graphics.UI.FreeGame.Text 1652 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 1653 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 1654 0 0.0 0.0 0.0 0.0 | |
mainloop.writeFPS Main 1208 0 0.0 0.0 0.1 0.1 | |
colored Graphics.UI.FreeGame.Base 1245 0 0.0 0.0 0.0 0.0 | |
colored Graphics.UI.FreeGame.Base 1269 0 0.0 0.0 0.0 0.0 | |
colored Graphics.UI.FreeGame.GUI 1270 0 0.0 0.0 0.0 0.0 | |
_Draw Graphics.UI.FreeGame.GUI 1271 1553 0.0 0.0 0.0 0.0 | |
_LiftUI Graphics.UI.FreeGame.Base 1259 1553 0.0 0.0 0.0 0.0 | |
text Graphics.UI.FreeGame.Text 1219 0 0.0 0.0 0.0 0.0 | |
runTextT Graphics.UI.FreeGame.Text 1234 0 0.0 0.0 0.0 0.0 | |
runTextT.go Graphics.UI.FreeGame.Text 1235 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\ Graphics.UI.FreeGame.Text 1236 0 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 1237 0 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 1241 0 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 1265 0 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.GUI 1289 0 0.0 0.0 0.0 0.0 | |
fromString Graphics.UI.FreeGame.Text 1220 0 0.0 0.0 0.0 0.0 | |
fromString.\ Graphics.UI.FreeGame.Text 1221 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Text 1345 0 0.0 0.0 0.0 0.0 | |
runTextT Graphics.UI.FreeGame.Text 1222 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\ Graphics.UI.FreeGame.Text 1227 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\.h Graphics.UI.FreeGame.Text 1286 1553 0.0 0.0 0.0 0.0 | |
runTextT.go.\.w Graphics.UI.FreeGame.Text 1283 1553 0.0 0.0 0.0 0.0 | |
runTextT.go.\.(...) Graphics.UI.FreeGame.Text 1281 1553 0.0 0.0 0.0 0.0 | |
bitmapSize Graphics.UI.FreeGame.Data.Bitmap 1282 1553 0.0 0.0 0.0 0.0 | |
bitmapSize.h Graphics.UI.FreeGame.Data.Bitmap 1287 1553 0.0 0.0 0.0 0.0 | |
bitmapSize.(...) Graphics.UI.FreeGame.Data.Bitmap 1285 1553 0.0 0.0 0.0 0.0 | |
bitmapSize.w Graphics.UI.FreeGame.Data.Bitmap 1284 1553 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 1228 0 0.0 0.0 0.0 0.0 | |
runTextT.go Graphics.UI.FreeGame.Text 1223 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\ Graphics.UI.FreeGame.Text 1224 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\.pen' Graphics.UI.FreeGame.Text 1509 1553 0.0 0.0 0.0 0.0 | |
runTextT.go.\.offset Graphics.UI.FreeGame.Text 1277 1553 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 1238 0 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 1242 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 1243 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 1244 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 1262 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.GUI 1273 0 0.0 0.0 0.0 0.0 | |
_Draw Graphics.UI.FreeGame.GUI 1274 1553 0.0 0.0 0.0 0.0 | |
_LiftUI Graphics.UI.FreeGame.Base 1263 1553 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 1229 1553 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 1232 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 1261 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.GUI 1272 0 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 1239 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 1225 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 1226 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 1209 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 1266 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.GUI 1267 0 0.0 0.0 0.0 0.0 | |
_Draw Graphics.UI.FreeGame.GUI 1268 15287 0.0 0.0 0.0 0.0 | |
_LiftUI Graphics.UI.FreeGame.Base 1258 15287 0.0 0.0 0.0 0.0 | |
text Graphics.UI.FreeGame.Text 1210 0 0.0 0.0 0.0 0.0 | |
fromString Graphics.UI.FreeGame.Text 1211 0 0.0 0.0 0.0 0.0 | |
fromString.\ Graphics.UI.FreeGame.Text 1212 0 0.0 0.0 0.0 0.0 | |
runTextT Graphics.UI.FreeGame.Text 1213 0 0.0 0.0 0.0 0.0 | |
runTextT.go Graphics.UI.FreeGame.Text 1214 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\ Graphics.UI.FreeGame.Text 1215 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 1216 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 1217 0 0.0 0.0 0.0 0.0 | |
colored Graphics.UI.FreeGame.Base 1218 0 0.0 0.0 0.0 0.0 | |
update Key 1193 0 0.0 0.0 0.0 0.0 | |
keyChar Graphics.UI.FreeGame.Base 1194 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.GUI 1189 50749 0.0 0.0 0.1 0.2 | |
main.run Main 2139 0 0.0 0.0 0.0 0.1 | |
mainloop Main 2140 0 0.0 0.0 0.0 0.1 | |
text Graphics.UI.FreeGame.Text 2148 0 0.0 0.0 0.0 0.0 | |
runTextT Graphics.UI.FreeGame.Text 2149 0 0.0 0.0 0.0 0.0 | |
runTextT.go Graphics.UI.FreeGame.Text 2154 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\ Graphics.UI.FreeGame.Text 2155 0 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 2156 0 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 2162 0 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 2174 0 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.GUI 2191 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\ Graphics.UI.FreeGame.Text 2150 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\.h Graphics.UI.FreeGame.Text 2188 3513 0.0 0.0 0.0 0.0 | |
runTextT.go.\.w Graphics.UI.FreeGame.Text 2185 3513 0.0 0.0 0.0 0.0 | |
runTextT.go.\.(...) Graphics.UI.FreeGame.Text 2183 3513 0.0 0.0 0.0 0.0 | |
bitmapSize Graphics.UI.FreeGame.Data.Bitmap 2184 3513 0.0 0.0 0.0 0.0 | |
bitmapSize.h Graphics.UI.FreeGame.Data.Bitmap 2189 3513 0.0 0.0 0.0 0.0 | |
bitmapSize.(...) Graphics.UI.FreeGame.Data.Bitmap 2187 3513 0.0 0.0 0.0 0.0 | |
bitmapSize.w Graphics.UI.FreeGame.Data.Bitmap 2186 3513 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 2151 0 0.0 0.0 0.0 0.0 | |
colored Graphics.UI.FreeGame.Base 2141 0 0.0 0.0 0.0 0.1 | |
text Graphics.UI.FreeGame.Text 2142 0 0.0 0.0 0.0 0.1 | |
runTextT Graphics.UI.FreeGame.Text 2145 0 0.0 0.0 0.0 0.1 | |
runTextT.go Graphics.UI.FreeGame.Text 2157 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\ Graphics.UI.FreeGame.Text 2158 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\.pen' Graphics.UI.FreeGame.Text 2217 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 2164 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 2165 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 2172 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.GUI 2176 0 0.0 0.0 0.0 0.0 | |
_Draw Graphics.UI.FreeGame.GUI 2177 3513 0.0 0.0 0.0 0.0 | |
_LiftUI Graphics.UI.FreeGame.Base 2173 3513 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 2159 0 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 2163 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\ Graphics.UI.FreeGame.Text 2146 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\.pen' Graphics.UI.FreeGame.Text 2216 1982 0.0 0.0 0.0 0.0 | |
runTextT.go Graphics.UI.FreeGame.Text 2218 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\.offset Graphics.UI.FreeGame.Text 2178 3513 0.0 0.0 0.0 0.0 | |
runTextT.go Graphics.UI.FreeGame.Text 2166 0 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 2161 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 2152 3513 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 2153 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 2171 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.GUI 2175 0 0.0 0.0 0.0 0.0 | |
runTextT.go Graphics.UI.FreeGame.Text 2160 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 2147 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 2143 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 2144 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.GUI 1190 94720 0.0 0.1 0.0 0.1 | |
main.run Main 1306 0 0.0 0.0 0.0 0.0 | |
mainloop Main 1307 0 0.0 0.0 0.0 0.0 | |
text Graphics.UI.FreeGame.Text 2198 0 0.0 0.0 0.0 0.0 | |
fromString Graphics.UI.FreeGame.Text 2202 0 0.0 0.0 0.0 0.0 | |
fromString.\ Graphics.UI.FreeGame.Text 2203 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Text 2204 0 0.0 0.0 0.0 0.0 | |
colored Graphics.UI.FreeGame.Base 2205 0 0.0 0.0 0.0 0.0 | |
runTextT Graphics.UI.FreeGame.Text 2199 0 0.0 0.0 0.0 0.0 | |
runTextT.go Graphics.UI.FreeGame.Text 2201 0 0.0 0.0 0.0 0.0 | |
colored Graphics.UI.FreeGame.Base 2206 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\ Graphics.UI.FreeGame.Text 2200 0 0.0 0.0 0.0 0.0 | |
colored Graphics.UI.FreeGame.Base 1737 0 0.0 0.0 0.0 0.0 | |
text Graphics.UI.FreeGame.Text 1738 0 0.0 0.0 0.0 0.0 | |
runTextT Graphics.UI.FreeGame.Text 1745 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\ Graphics.UI.FreeGame.Text 2192 0 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 2195 0 0.0 0.0 0.0 0.0 | |
runTextT.go Graphics.UI.FreeGame.Text 2196 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 2193 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 2194 0 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 2197 0 0.0 0.0 0.0 0.0 | |
runTextT.go Graphics.UI.FreeGame.Text 1746 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\ Graphics.UI.FreeGame.Text 1747 0 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 1748 0 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 1749 0 0.0 0.0 0.0 0.0 | |
fromString Graphics.UI.FreeGame.Text 1739 0 0.0 0.0 0.0 0.0 | |
fromString.\ Graphics.UI.FreeGame.Text 1740 0 0.0 0.0 0.0 0.0 | |
runTextT Graphics.UI.FreeGame.Text 1741 0 0.0 0.0 0.0 0.0 | |
runTextT.go Graphics.UI.FreeGame.Text 1750 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\ Graphics.UI.FreeGame.Text 1751 0 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 1752 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\ Graphics.UI.FreeGame.Text 1742 0 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 1754 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 1743 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 1744 0 0.0 0.0 0.0 0.0 | |
runTextT.go Graphics.UI.FreeGame.Text 1753 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 1735 0 0.0 0.0 0.0 0.0 | |
colored Graphics.UI.FreeGame.Base 1736 0 0.0 0.0 0.0 0.0 | |
mainloop.writeFPS Main 1308 0 0.0 0.0 0.0 0.0 | |
colored Graphics.UI.FreeGame.Base 1403 0 0.0 0.0 0.0 0.0 | |
l.53:LiftUI,Input Graphics.UI.FreeGame.GUI.GLFW 1487 0 0.0 0.0 0.0 0.0 | |
runInput Graphics.UI.FreeGame.GUI.GLFW 1488 0 0.0 0.0 0.0 0.0 | |
text Graphics.UI.FreeGame.Text 1319 0 0.0 0.0 0.0 0.0 | |
fromString Graphics.UI.FreeGame.Text 1320 0 0.0 0.0 0.0 0.0 | |
fromString.\ Graphics.UI.FreeGame.Text 1321 0 0.0 0.0 0.0 0.0 | |
runTextT Graphics.UI.FreeGame.Text 1322 0 0.0 0.0 0.0 0.0 | |
runTextT.go Graphics.UI.FreeGame.Text 1323 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\ Graphics.UI.FreeGame.Text 1324 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 1329 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 1330 0 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 1331 0 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 1325 0 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 1326 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 1327 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 1328 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 1309 0 0.0 0.0 0.0 0.0 | |
text Graphics.UI.FreeGame.Text 1310 0 0.0 0.0 0.0 0.0 | |
fromString Graphics.UI.FreeGame.Text 1311 0 0.0 0.0 0.0 0.0 | |
fromString.\ Graphics.UI.FreeGame.Text 1312 0 0.0 0.0 0.0 0.0 | |
runTextT Graphics.UI.FreeGame.Text 1313 0 0.0 0.0 0.0 0.0 | |
runTextT.go Graphics.UI.FreeGame.Text 1314 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\ Graphics.UI.FreeGame.Text 1315 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 1316 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 1317 0 0.0 0.0 0.0 0.0 | |
colored Graphics.UI.FreeGame.Base 1318 0 0.0 0.0 0.0 0.0 | |
l.53:LiftUI,Input Graphics.UI.FreeGame.GUI.GLFW 1401 0 0.0 0.0 0.0 0.0 | |
runInput Graphics.UI.FreeGame.GUI.GLFW 1402 0 0.0 0.0 0.0 0.0 | |
preservingMatrix' Graphics.UI.FreeGame.GUI.GLFW 1185 0 0.0 0.0 0.0 0.0 | |
l.139:IM.lookup Graphics.UI.FreeGame.GUI.GLFW 895 1200976 0.7 0.2 0.7 0.2 | |
embedIO Graphics.UI.FreeGame.Base 889 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 890 0 0.0 0.0 0.0 0.0 | |
main.run Main 891 0 0.0 0.0 0.0 0.0 | |
mainloop Main 892 0 0.0 0.0 0.0 0.0 | |
update Key 893 0 0.0 0.0 0.0 0.0 | |
keyChar Graphics.UI.FreeGame.Base 894 0 0.0 0.0 0.0 0.0 | |
unFinalizerT Graphics.UI.FreeGame.Internal.Finalizer 883 3893544 0.0 0.0 0.0 0.0 | |
embedIO Graphics.UI.FreeGame.Base 876 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 877 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.GUI 1150 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.GUI 1151 0 0.0 0.0 0.0 0.0 | |
main.run Main 878 0 0.0 0.0 0.0 0.0 | |
mainloop Main 879 0 0.0 0.0 0.0 0.0 | |
colored Graphics.UI.FreeGame.Base 1639 0 0.0 0.0 0.0 0.0 | |
text Graphics.UI.FreeGame.Text 1640 0 0.0 0.0 0.0 0.0 | |
runTextT Graphics.UI.FreeGame.Text 1641 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\ Graphics.UI.FreeGame.Text 1642 0 0.0 0.0 0.0 0.0 | |
charToBitmap Graphics.UI.FreeGame.Data.Font 1643 0 0.0 0.0 0.0 0.0 | |
mainloop.writeFPS Main 1159 0 0.0 0.0 0.0 0.0 | |
text Graphics.UI.FreeGame.Text 1160 0 0.0 0.0 0.0 0.0 | |
fromString Graphics.UI.FreeGame.Text 1161 0 0.0 0.0 0.0 0.0 | |
fromString.\ Graphics.UI.FreeGame.Text 1162 0 0.0 0.0 0.0 0.0 | |
runTextT Graphics.UI.FreeGame.Text 1163 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\ Graphics.UI.FreeGame.Text 1164 0 0.0 0.0 0.0 0.0 | |
charToBitmap Graphics.UI.FreeGame.Data.Font 1165 0 0.0 0.0 0.0 0.0 | |
finalizer Graphics.UI.FreeGame.Internal.Finalizer 1179 0 0.0 0.0 0.0 0.0 | |
finalizer.\ Graphics.UI.FreeGame.Internal.Finalizer 1180 1 0.0 0.0 0.0 0.0 | |
runFinalizerT.\ Graphics.UI.FreeGame.Internal.Finalizer 2243 1 0.0 0.0 0.0 0.0 | |
>>=.\.\ Graphics.UI.FreeGame.Internal.Finalizer 1181 1 0.0 0.0 0.0 0.0 | |
unFinalizerT Graphics.UI.FreeGame.Internal.Finalizer 1182 1 0.0 0.0 0.0 0.0 | |
update Key 880 0 0.0 0.0 0.0 0.0 | |
keyChar Graphics.UI.FreeGame.Base 881 0 0.0 0.0 0.0 0.0 | |
preservingMatrix' Graphics.UI.FreeGame.GUI.GLFW 854 37352 0.5 1.2 1.7 2.4 | |
>>= Graphics.UI.FreeGame.Internal.Finalizer 855 74704 0.2 0.0 1.3 1.2 | |
>>=.\ Graphics.UI.FreeGame.Internal.Finalizer 856 4749980 0.7 1.2 1.1 1.2 | |
embedIO Graphics.UI.FreeGame.Base 868 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 869 0 0.0 0.0 0.0 0.0 | |
main.run Main 870 0 0.0 0.0 0.0 0.0 | |
mainloop Main 871 0 0.0 0.0 0.0 0.0 | |
update Key 872 0 0.0 0.0 0.0 0.0 | |
keyChar Graphics.UI.FreeGame.Base 873 0 0.0 0.0 0.0 0.0 | |
>>=.\.\ Graphics.UI.FreeGame.Internal.Finalizer 859 2374990 0.4 0.0 0.4 0.0 | |
embedIO Graphics.UI.FreeGame.Base 861 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 862 0 0.0 0.0 0.0 0.0 | |
main.run Main 863 0 0.0 0.0 0.0 0.0 | |
mainloop Main 864 0 0.0 0.0 0.0 0.0 | |
update Key 865 0 0.0 0.0 0.0 0.0 | |
keyChar Graphics.UI.FreeGame.Base 866 0 0.0 0.0 0.0 0.0 | |
unFinalizerT Graphics.UI.FreeGame.Internal.Finalizer 860 2374990 0.0 0.0 0.0 0.0 | |
>>= Graphics.UI.FreeGame.Internal.Finalizer 828 23866 0.0 0.0 0.2 0.4 | |
>>=.\ Graphics.UI.FreeGame.Internal.Finalizer 829 1190596 0.2 0.4 0.2 0.4 | |
embedIO Graphics.UI.FreeGame.Base 847 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 848 0 0.0 0.0 0.0 0.0 | |
main.run Main 849 0 0.0 0.0 0.0 0.0 | |
mainloop Main 850 0 0.0 0.0 0.0 0.0 | |
update Key 851 0 0.0 0.0 0.0 0.0 | |
keyChar Graphics.UI.FreeGame.Base 852 0 0.0 0.0 0.0 0.0 | |
l.53:LiftUI,Input Graphics.UI.FreeGame.GUI.GLFW 732 0 0.0 0.0 0.1 0.2 | |
runInput Graphics.UI.FreeGame.GUI.GLFW 1195 0 0.0 0.0 0.1 0.2 | |
fmap Graphics.UI.FreeGame.GUI 1196 19924 0.0 0.0 0.1 0.2 | |
translate Graphics.UI.FreeGame.Base 1645 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 1698 1553 0.0 0.0 0.0 0.0 | |
colored Graphics.UI.FreeGame.Base 1646 0 0.0 0.0 0.0 0.0 | |
text Graphics.UI.FreeGame.Text 1647 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 1648 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 1649 0 0.0 0.0 0.0 0.0 | |
l.49:LiftUI,Draw Graphics.UI.FreeGame.GUI.GLFW 1687 0 0.0 0.0 0.0 0.0 | |
runPicture Graphics.UI.FreeGame.GUI.GLFW 1688 0 0.0 0.0 0.0 0.0 | |
>>= Graphics.UI.FreeGame.Internal.Finalizer 1689 0 0.0 0.0 0.0 0.0 | |
>>=.\ Graphics.UI.FreeGame.Internal.Finalizer 1690 0 0.0 0.0 0.0 0.0 | |
>>=.\.\ Graphics.UI.FreeGame.Internal.Finalizer 1691 0 0.0 0.0 0.0 0.0 | |
return Graphics.UI.FreeGame.Internal.Finalizer 1692 0 0.0 0.0 0.0 0.0 | |
return.\ Graphics.UI.FreeGame.Internal.Finalizer 1693 0 0.0 0.0 0.0 0.0 | |
embedIO Graphics.UI.FreeGame.Base 1694 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 1695 0 0.0 0.0 0.0 0.0 | |
main.run Main 1696 0 0.0 0.0 0.0 0.0 | |
mainloop Main 1697 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.GUI 1275 35410 0.0 0.0 0.1 0.2 | |
translate Graphics.UI.FreeGame.Base 1733 0 0.0 0.0 0.0 0.0 | |
l.49:LiftUI,Draw Graphics.UI.FreeGame.GUI.GLFW 1762 0 0.0 0.0 0.0 0.0 | |
runPicture Graphics.UI.FreeGame.GUI.GLFW 1763 0 0.0 0.0 0.0 0.0 | |
>>= Graphics.UI.FreeGame.Internal.Finalizer 1764 0 0.0 0.0 0.0 0.0 | |
>>=.\ Graphics.UI.FreeGame.Internal.Finalizer 1765 0 0.0 0.0 0.0 0.0 | |
>>=.\.\ Graphics.UI.FreeGame.Internal.Finalizer 1766 0 0.0 0.0 0.0 0.0 | |
return Graphics.UI.FreeGame.Internal.Finalizer 1767 0 0.0 0.0 0.0 0.0 | |
return.\ Graphics.UI.FreeGame.Internal.Finalizer 1768 0 0.0 0.0 0.0 0.0 | |
embedIO Graphics.UI.FreeGame.Base 1769 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 1770 0 0.0 0.0 0.0 0.0 | |
main.run Main 2131 0 0.0 0.0 0.0 0.0 | |
mainloop Main 2132 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 1734 1531 0.0 0.0 0.0 0.0 | |
main.run Main 1370 0 0.0 0.0 0.1 0.1 | |
mainloop Main 1371 0 0.0 0.0 0.1 0.1 | |
update Key 1775 0 0.0 0.0 0.0 0.0 | |
keyChar Graphics.UI.FreeGame.Base 1776 0 0.0 0.0 0.0 0.0 | |
colored Graphics.UI.FreeGame.Base 1771 0 0.0 0.0 0.0 0.0 | |
text Graphics.UI.FreeGame.Text 1772 0 0.0 0.0 0.0 0.0 | |
embedIO Graphics.UI.FreeGame.Base 1773 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 1774 0 0.0 0.0 0.0 0.0 | |
mainloop.writeFPS Main 1372 0 0.0 0.0 0.1 0.1 | |
colored Graphics.UI.FreeGame.Base 1400 0 0.0 0.0 0.0 0.0 | |
colored Graphics.UI.FreeGame.Base 1418 0 0.0 0.0 0.0 0.0 | |
colored Graphics.UI.FreeGame.GUI 1419 0 0.0 0.0 0.0 0.0 | |
_Draw Graphics.UI.FreeGame.GUI 1420 6867 0.0 0.0 0.0 0.0 | |
_LiftUI Graphics.UI.FreeGame.Base 1415 6867 0.0 0.0 0.0 0.0 | |
text Graphics.UI.FreeGame.Text 1373 0 0.0 0.0 0.1 0.1 | |
fromFinalizer Graphics.UI.FreeGame.Base 1393 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 1396 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 1421 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.GUI 1422 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 1417 6867 0.0 0.0 0.0 0.0 | |
runTextT Graphics.UI.FreeGame.Text 1389 0 0.0 0.0 0.0 0.1 | |
runTextT.go Graphics.UI.FreeGame.Text 1522 6867 0.0 0.0 0.0 0.0 | |
runTextT.go.\ Graphics.UI.FreeGame.Text 1390 6867 0.0 0.0 0.0 0.1 | |
embedIO Graphics.UI.FreeGame.Base 1520 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 1521 0 0.0 0.0 0.0 0.0 | |
charToBitmap Graphics.UI.FreeGame.Data.Font 1427 6867 0.0 0.0 0.0 0.0 | |
finalizer Graphics.UI.FreeGame.Internal.Finalizer 1443 13 0.0 0.0 0.0 0.0 | |
charToBitmap.render Graphics.UI.FreeGame.Data.Font 1437 13 0.0 0.0 0.0 0.0 | |
makeStableBitmap Graphics.UI.FreeGame.Data.Bitmap 1442 13 0.0 0.0 0.0 0.0 | |
charToBitmap.render.pix Graphics.UI.FreeGame.Data.Font 1441 7588 0.0 0.0 0.0 0.0 | |
charToBitmap.render.h Graphics.UI.FreeGame.Data.Font 1440 13 0.0 0.0 0.0 0.0 | |
charToBitmap.render.w Graphics.UI.FreeGame.Data.Font 1439 13 0.0 0.0 0.0 0.0 | |
runFreeType Graphics.UI.FreeGame.Data.Font 1438 39 0.0 0.0 0.0 0.0 | |
charToBitmap.siz Graphics.UI.FreeGame.Data.Font 1436 6867 0.0 0.0 0.0 0.0 | |
>>= Graphics.UI.FreeGame.Internal.Finalizer 1428 6867 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 1394 0 0.0 0.0 0.0 0.0 | |
fromString Graphics.UI.FreeGame.Text 1374 0 0.0 0.0 0.0 0.0 | |
fromString.\ Graphics.UI.FreeGame.Text 1375 0 0.0 0.0 0.0 0.0 | |
runTextT Graphics.UI.FreeGame.Text 1376 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\ Graphics.UI.FreeGame.Text 1392 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 1395 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 1397 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 1416 6867 0.0 0.0 0.0 0.0 | |
embedIO Graphics.UI.FreeGame.Base 1398 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 1399 0 0.0 0.0 0.0 0.0 | |
runTextT.go Graphics.UI.FreeGame.Text 1377 0 0.0 0.0 0.0 0.0 | |
embedIO Graphics.UI.FreeGame.Base 1387 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 1388 0 0.0 0.0 0.0 0.0 | |
l.49:LiftUI,Draw Graphics.UI.FreeGame.GUI.GLFW 1378 0 0.0 0.0 0.0 0.0 | |
runPicture Graphics.UI.FreeGame.GUI.GLFW 1379 0 0.0 0.0 0.0 0.0 | |
>>= Graphics.UI.FreeGame.Internal.Finalizer 1380 0 0.0 0.0 0.0 0.0 | |
>>=.\ Graphics.UI.FreeGame.Internal.Finalizer 1381 0 0.0 0.0 0.0 0.0 | |
>>=.\.\ Graphics.UI.FreeGame.Internal.Finalizer 1382 0 0.0 0.0 0.0 0.0 | |
return Graphics.UI.FreeGame.Internal.Finalizer 1383 0 0.0 0.0 0.0 0.0 | |
return.\ Graphics.UI.FreeGame.Internal.Finalizer 1384 0 0.0 0.0 0.0 0.0 | |
embedIO Graphics.UI.FreeGame.Base 1385 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 1386 0 0.0 0.0 0.0 0.0 | |
mainloop.writeFPS Main 1303 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 1304 0 0.0 0.0 0.0 0.0 | |
l.49:LiftUI,Draw Graphics.UI.FreeGame.GUI.GLFW 1404 0 0.0 0.0 0.0 0.0 | |
runPicture Graphics.UI.FreeGame.GUI.GLFW 1405 0 0.0 0.0 0.0 0.0 | |
>>= Graphics.UI.FreeGame.Internal.Finalizer 1406 0 0.0 0.0 0.0 0.0 | |
>>=.\ Graphics.UI.FreeGame.Internal.Finalizer 1407 0 0.0 0.0 0.0 0.0 | |
>>=.\.\ Graphics.UI.FreeGame.Internal.Finalizer 1408 0 0.0 0.0 0.0 0.0 | |
return Graphics.UI.FreeGame.Internal.Finalizer 1409 0 0.0 0.0 0.0 0.0 | |
return.\ Graphics.UI.FreeGame.Internal.Finalizer 1410 0 0.0 0.0 0.0 0.0 | |
embedIO Graphics.UI.FreeGame.Base 1411 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 1412 0 0.0 0.0 0.0 0.0 | |
main.run Main 1413 0 0.0 0.0 0.0 0.0 | |
mainloop Main 1414 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 1305 1553 0.0 0.0 0.0 0.0 | |
mainloop.writeFPS Main 1197 0 0.0 0.0 0.0 0.0 | |
text Graphics.UI.FreeGame.Text 1346 0 0.0 0.0 0.0 0.0 | |
fromString Graphics.UI.FreeGame.Text 1347 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Text 1391 6867 0.0 0.0 0.0 0.0 | |
embedIO Graphics.UI.FreeGame.Base 1523 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 1524 0 0.0 0.0 0.0 0.0 | |
main.run Main 1525 0 0.0 0.0 0.0 0.0 | |
mainloop Main 1526 0 0.0 0.0 0.0 0.0 | |
update Key 1527 0 0.0 0.0 0.0 0.0 | |
keyChar Graphics.UI.FreeGame.Base 1528 0 0.0 0.0 0.0 0.0 | |
fromString.\ Graphics.UI.FreeGame.Text 1354 0 0.0 0.0 0.0 0.0 | |
l.49:LiftUI,Draw Graphics.UI.FreeGame.GUI.GLFW 1361 0 0.0 0.0 0.0 0.0 | |
runPicture Graphics.UI.FreeGame.GUI.GLFW 1362 0 0.0 0.0 0.0 0.0 | |
>>= Graphics.UI.FreeGame.Internal.Finalizer 1363 0 0.0 0.0 0.0 0.0 | |
>>=.\ Graphics.UI.FreeGame.Internal.Finalizer 1364 0 0.0 0.0 0.0 0.0 | |
>>=.\.\ Graphics.UI.FreeGame.Internal.Finalizer 1365 0 0.0 0.0 0.0 0.0 | |
return Graphics.UI.FreeGame.Internal.Finalizer 1366 0 0.0 0.0 0.0 0.0 | |
return.\ Graphics.UI.FreeGame.Internal.Finalizer 1367 0 0.0 0.0 0.0 0.0 | |
embedIO Graphics.UI.FreeGame.Base 1368 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 1369 0 0.0 0.0 0.0 0.0 | |
embedIO Graphics.UI.FreeGame.Base 1355 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 1356 0 0.0 0.0 0.0 0.0 | |
main.run Main 1357 0 0.0 0.0 0.0 0.0 | |
mainloop Main 1358 0 0.0 0.0 0.0 0.0 | |
update Key 1359 0 0.0 0.0 0.0 0.0 | |
keyChar Graphics.UI.FreeGame.Base 1360 0 0.0 0.0 0.0 0.0 | |
embedIO Graphics.UI.FreeGame.Base 1348 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 1349 0 0.0 0.0 0.0 0.0 | |
main.run Main 1350 0 0.0 0.0 0.0 0.0 | |
mainloop Main 1351 0 0.0 0.0 0.0 0.0 | |
update Key 1352 0 0.0 0.0 0.0 0.0 | |
keyChar Graphics.UI.FreeGame.Base 1353 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 1198 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 1257 1553 0.0 0.0 0.0 0.0 | |
text Graphics.UI.FreeGame.Text 1199 0 0.0 0.0 0.0 0.0 | |
fromString Graphics.UI.FreeGame.Text 1200 0 0.0 0.0 0.0 0.0 | |
fromString.\ Graphics.UI.FreeGame.Text 1201 0 0.0 0.0 0.0 0.0 | |
runTextT Graphics.UI.FreeGame.Text 1202 0 0.0 0.0 0.0 0.0 | |
runTextT.go Graphics.UI.FreeGame.Text 1203 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\ Graphics.UI.FreeGame.Text 1204 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 1205 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 1206 0 0.0 0.0 0.0 0.0 | |
colored Graphics.UI.FreeGame.Base 1207 0 0.0 0.0 0.0 0.0 | |
l.49:LiftUI,Draw Graphics.UI.FreeGame.GUI.GLFW 1246 0 0.0 0.0 0.0 0.0 | |
runPicture Graphics.UI.FreeGame.GUI.GLFW 1247 0 0.0 0.0 0.0 0.0 | |
>>= Graphics.UI.FreeGame.Internal.Finalizer 1248 0 0.0 0.0 0.0 0.0 | |
>>=.\ Graphics.UI.FreeGame.Internal.Finalizer 1249 0 0.0 0.0 0.0 0.0 | |
>>=.\.\ Graphics.UI.FreeGame.Internal.Finalizer 1250 0 0.0 0.0 0.0 0.0 | |
return Graphics.UI.FreeGame.Internal.Finalizer 1251 0 0.0 0.0 0.0 0.0 | |
return.\ Graphics.UI.FreeGame.Internal.Finalizer 1252 0 0.0 0.0 0.0 0.0 | |
embedIO Graphics.UI.FreeGame.Base 1253 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 1254 0 0.0 0.0 0.0 0.0 | |
main.run Main 1255 0 0.0 0.0 0.0 0.0 | |
mainloop Main 1256 0 0.0 0.0 0.0 0.0 | |
>>= Graphics.UI.FreeGame.Internal.Finalizer 733 0 0.0 0.0 0.0 0.0 | |
>>=.\ Graphics.UI.FreeGame.Internal.Finalizer 734 10871 0.0 0.0 0.0 0.0 | |
>>=.\.\ Graphics.UI.FreeGame.Internal.Finalizer 747 10871 0.0 0.0 0.0 0.0 | |
embedIO Graphics.UI.FreeGame.Base 755 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 756 0 0.0 0.0 0.0 0.0 | |
main.run Main 757 0 0.0 0.0 0.0 0.0 | |
mainloop Main 758 0 0.0 0.0 0.0 0.0 | |
update Key 759 0 0.0 0.0 0.0 0.0 | |
keyChar Graphics.UI.FreeGame.Base 778 0 0.0 0.0 0.0 0.0 | |
keySpecial Graphics.UI.FreeGame.Base 760 0 0.0 0.0 0.0 0.0 | |
unFinalizerT Graphics.UI.FreeGame.Internal.Finalizer 748 10871 0.0 0.0 0.0 0.0 | |
embedIO Graphics.UI.FreeGame.Base 735 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 736 0 0.0 0.0 0.0 0.0 | |
main.run Main 737 0 0.0 0.0 0.0 0.0 | |
mainloop Main 738 0 0.0 0.0 0.0 0.0 | |
update Key 739 0 0.0 0.0 0.0 0.0 | |
keyChar Graphics.UI.FreeGame.Base 779 0 0.0 0.0 0.0 0.0 | |
keySpecial Graphics.UI.FreeGame.Base 740 0 0.0 0.0 0.0 0.0 | |
l.50:EmbedIO Graphics.UI.FreeGame.GUI.GLFW 688 0 0.0 0.0 0.0 0.0 | |
>>= Graphics.UI.FreeGame.Internal.Finalizer 689 0 0.0 0.0 0.0 0.0 | |
>>=.\ Graphics.UI.FreeGame.Internal.Finalizer 690 1554 0.0 0.0 0.0 0.0 | |
>>=.\.\ Graphics.UI.FreeGame.Internal.Finalizer 694 1554 0.0 0.0 0.0 0.0 | |
embedIO Graphics.UI.FreeGame.Base 726 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 727 0 0.0 0.0 0.0 0.0 | |
main.run Main 728 0 0.0 0.0 0.0 0.0 | |
mainloop Main 729 0 0.0 0.0 0.0 0.0 | |
update Key 730 0 0.0 0.0 0.0 0.0 | |
keyChar Graphics.UI.FreeGame.Base 826 0 0.0 0.0 0.0 0.0 | |
keySpecial Graphics.UI.FreeGame.Base 731 0 0.0 0.0 0.0 0.0 | |
unFinalizerT Graphics.UI.FreeGame.Internal.Finalizer 695 1554 0.0 0.0 0.0 0.0 | |
embedIO Graphics.UI.FreeGame.Base 691 0 0.0 0.0 0.0 0.0 | |
initLoad Main 638 0 0.0 0.0 0.5 2.8 | |
loadBitmapFromFile Graphics.UI.FreeGame.Data.Bitmap 666 0 0.5 2.8 0.5 2.8 | |
makeStableBitmap Graphics.UI.FreeGame.Data.Bitmap 667 3 0.0 0.0 0.0 0.0 | |
loadFont Graphics.UI.FreeGame.Data.Font 656 0 0.0 0.0 0.0 0.0 | |
runFreeType Graphics.UI.FreeGame.Data.Font 658 1 0.0 0.0 0.0 0.0 | |
loadFont.\ Graphics.UI.FreeGame.Data.Font 657 1 0.0 0.0 0.0 0.0 | |
runFreeType Graphics.UI.FreeGame.Data.Font 659 0 0.0 0.0 0.0 0.0 | |
loadFont.\.\ Graphics.UI.FreeGame.Data.Font 660 1 0.0 0.0 0.0 0.0 | |
embedIO Graphics.UI.FreeGame.Base 640 0 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 642 4 0.0 0.0 0.0 0.0 | |
onBitmapWithHashable Graphics.UI.FreeGame.Data.Bitmap 887 2 0.0 0.0 0.0 0.0 | |
cropBitmap Graphics.UI.FreeGame.Data.Bitmap 886 2 0.0 0.0 0.0 0.0 | |
onBitmapWithHashable Graphics.UI.FreeGame.Data.Bitmap 888 0 0.0 0.0 0.0 0.0 | |
initLoad.\ Main 801 1 0.0 0.0 0.0 0.0 | |
initLoad.makeBulletImg Main 796 1 0.0 0.0 0.0 0.0 | |
initLoad.bulletImgRect Main 2086 1 0.0 0.0 0.0 0.0 | |
fromEnum Object 2094 1 0.0 0.0 0.0 0.0 | |
initLoad.bulletImgRect.color Main 2093 1 0.0 0.0 0.0 0.0 | |
initLoad.bulletImgRect.clip Main 2089 1 0.0 0.0 0.0 0.0 | |
onBitmapWithHashable Graphics.UI.FreeGame.Data.Bitmap 2091 1 0.0 0.0 0.0 0.0 | |
cropBitmap Graphics.UI.FreeGame.Data.Bitmap 2090 1 0.0 0.0 0.0 0.0 | |
onBitmapWithHashable Graphics.UI.FreeGame.Data.Bitmap 2092 0 0.0 0.0 0.0 0.0 | |
== Object 2087 8 0.0 0.0 0.0 0.0 | |
unsafeIndex Object 2082 1 0.0 0.0 0.0 0.0 | |
inRange Object 2081 1 0.0 0.0 0.0 0.0 | |
unsafeIndex Object 798 1 0.0 0.0 0.0 0.0 | |
inRange Object 797 1 0.0 0.0 0.0 0.0 | |
runAction Graphics.UI.FreeGame.GUI.GLFW 641 4 0.0 0.0 0.0 0.0 | |
l.50:EmbedIO Graphics.UI.FreeGame.GUI.GLFW 643 4 0.0 0.0 0.0 0.0 | |
>>= Graphics.UI.FreeGame.Internal.Finalizer 644 4 0.0 0.0 0.0 0.0 | |
>>= Graphics.UI.FreeGame.Internal.Finalizer 632 0 0.0 0.0 0.0 0.0 | |
>>=.\ Graphics.UI.FreeGame.Internal.Finalizer 633 4 0.0 0.0 0.0 0.0 | |
runGame.\ Graphics.UI.FreeGame.GUI.GLFW 650 0 0.0 0.0 0.0 0.0 | |
initLoad Main 651 0 0.0 0.0 0.0 0.0 | |
embedIO Graphics.UI.FreeGame.Base 652 0 0.0 0.0 0.0 0.0 | |
runAction Graphics.UI.FreeGame.GUI.GLFW 653 0 0.0 0.0 0.0 0.0 | |
l.50:EmbedIO Graphics.UI.FreeGame.GUI.GLFW 654 0 0.0 0.0 0.0 0.0 | |
>>=.\.\ Graphics.UI.FreeGame.Internal.Finalizer 634 5 0.0 0.0 0.0 0.0 | |
embedIO Graphics.UI.FreeGame.Base 686 0 0.0 0.0 0.0 0.0 | |
runGame.\ Graphics.UI.FreeGame.GUI.GLFW 645 0 0.0 0.0 0.0 0.0 | |
initLoad Main 646 0 0.0 0.0 0.0 0.0 | |
embedIO Graphics.UI.FreeGame.Base 647 0 0.0 0.0 0.0 0.0 | |
runAction Graphics.UI.FreeGame.GUI.GLFW 648 0 0.0 0.0 0.0 0.0 | |
l.50:EmbedIO Graphics.UI.FreeGame.GUI.GLFW 649 0 0.0 0.0 0.0 0.0 | |
unFinalizerT Graphics.UI.FreeGame.Internal.Finalizer 635 5 0.0 0.0 0.0 0.0 | |
launch.a Graphics.UI.FreeGame.GUI.GLFW 607 1 0.0 0.0 0.0 0.0 | |
launch.b Graphics.UI.FreeGame.GUI.GLFW 606 1 0.0 0.0 0.0 0.0 | |
launch.g Graphics.UI.FreeGame.GUI.GLFW 605 1 0.0 0.0 0.0 0.0 | |
launch.(...) Graphics.UI.FreeGame.GUI.GLFW 602 1 0.0 0.0 0.0 0.0 | |
launch.r Graphics.UI.FreeGame.GUI.GLFW 601 1 0.0 0.0 0.0 0.0 | |
launch Graphics.UI.FreeGame.GUI.GLFW 588 0 0.2 0.0 0.2 0.0 | |
liftIO Graphics.UI.FreeGame.Internal.Finalizer 621 0 0.0 0.0 0.0 0.0 | |
liftIO.\ Graphics.UI.FreeGame.Internal.Finalizer 622 2 0.0 0.0 0.0 0.0 | |
launch.wh Graphics.UI.FreeGame.GUI.GLFW 595 1 0.0 0.0 0.0 0.0 | |
launch.ww Graphics.UI.FreeGame.GUI.GLFW 589 1 0.0 0.0 0.0 0.0 | |
CAF Main 581 0 0.0 0.0 0.0 0.0 | |
keySpecial Graphics.UI.FreeGame.Base 1834 1 0.0 0.0 0.0 0.0 | |
step Main 1777 1 0.0 0.0 0.0 0.0 | |
keySpecial Graphics.UI.FreeGame.Base 1831 1 0.0 0.0 0.0 0.0 | |
keySpecial Graphics.UI.FreeGame.Base 1835 0 0.0 0.0 0.0 0.0 | |
keySpecial Graphics.UI.FreeGame.GUI 1838 0 0.0 0.0 0.0 0.0 | |
keySpecial Graphics.UI.FreeGame.GUI 1839 1 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 1833 1 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.GUI 1836 1 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.GUI 1837 1 0.0 0.0 0.0 0.0 | |
tick Graphics.UI.FreeGame.Base 1779 1 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 1264 1 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 1260 1 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 1240 1 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 1231 1 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 1126 1 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 1099 1 0.0 0.0 0.0 0.0 | |
initGameFrame Main 795 1 0.0 0.0 0.0 0.0 | |
mainloop Main 789 0 0.0 0.0 0.0 0.0 | |
text Graphics.UI.FreeGame.Text 1589 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 1608 1 0.0 0.0 0.0 0.0 | |
runTextT Graphics.UI.FreeGame.Text 1591 0 0.0 0.0 0.0 0.0 | |
runTextT.go Graphics.UI.FreeGame.Text 1595 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\ Graphics.UI.FreeGame.Text 1606 0 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 1669 1 0.0 0.0 0.0 0.0 | |
colored Graphics.UI.FreeGame.Base 1586 1 0.0 0.0 0.0 0.0 | |
colored Graphics.UI.FreeGame.Base 1625 1 0.0 0.0 0.0 0.0 | |
colored Graphics.UI.FreeGame.GUI 1631 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 1584 1 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 1623 1 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.GUI 1627 0 0.0 0.0 0.0 0.0 | |
mainloop.writeFPS Main 992 0 0.0 0.0 0.0 0.0 | |
text Graphics.UI.FreeGame.Text 998 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 1095 1 0.0 0.0 0.0 0.0 | |
runTextT Graphics.UI.FreeGame.Text 1002 0 0.0 0.0 0.0 0.0 | |
runTextT.go Graphics.UI.FreeGame.Text 1017 0 0.0 0.0 0.0 0.0 | |
runTextT.go.\ Graphics.UI.FreeGame.Text 1093 0 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 1233 1 0.0 0.0 0.0 0.0 | |
colored Graphics.UI.FreeGame.Base 995 1 0.0 0.0 0.0 0.0 | |
colored Graphics.UI.FreeGame.Base 1124 1 0.0 0.0 0.0 0.0 | |
colored Graphics.UI.FreeGame.GUI 1132 0 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 993 1 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.Base 1122 1 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.GUI 1127 0 0.0 0.0 0.0 0.0 | |
embedIO Graphics.UI.FreeGame.Base 790 1 0.0 0.0 0.0 0.0 | |
initLoad Main 637 1 0.0 0.0 0.0 0.0 | |
initLoad.makeBulletImg Main 799 0 0.0 0.0 0.0 0.0 | |
toEnum Object 2095 1 0.0 0.0 0.0 0.0 | |
toEnum Object 2088 1 0.0 0.0 0.0 0.0 | |
fromEnum Object 2083 2 0.0 0.0 0.0 0.0 | |
fromEnum Object 800 2 0.0 0.0 0.0 0.0 | |
loadBitmapFromFile Graphics.UI.FreeGame.Data.Bitmap 665 3 0.0 0.0 0.0 0.0 | |
loadFont Graphics.UI.FreeGame.Data.Font 655 1 0.0 0.0 0.0 0.0 | |
embedIO Graphics.UI.FreeGame.Base 639 4 0.0 0.0 0.0 0.0 | |
start Main 593 1 0.0 0.0 0.0 0.0 | |
main Main 582 1 0.0 0.0 0.0 0.0 | |
quit Graphics.UI.FreeGame.Base 2219 1 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 2234 1 0.0 0.0 0.0 0.0 | |
embedIO Graphics.UI.FreeGame.Base 668 1 0.0 0.0 0.0 0.0 | |
runGame Graphics.UI.FreeGame.GUI.GLFW 584 1 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Internal.Finalizer 615 1 0.0 0.0 0.0 0.0 | |
<*> Graphics.UI.FreeGame.Internal.Finalizer 612 1 0.0 0.0 0.0 0.0 | |
>>= Graphics.UI.FreeGame.Internal.Finalizer 609 1 0.0 0.0 0.0 0.0 | |
launch Graphics.UI.FreeGame.GUI.GLFW 585 1 0.0 0.0 0.0 0.0 | |
launch.(...) Graphics.UI.FreeGame.GUI.GLFW 603 0 0.0 0.0 0.0 0.0 | |
_clearColor Graphics.UI.FreeGame.GUI 604 1 0.0 0.0 0.0 0.0 | |
_windowTitle Graphics.UI.FreeGame.GUI 598 1 0.0 0.0 0.0 0.0 | |
_windowed Graphics.UI.FreeGame.GUI 597 1 0.0 0.0 0.0 0.0 | |
launch.(...) Graphics.UI.FreeGame.GUI.GLFW 591 1 0.0 0.0 0.0 0.0 | |
_windowSize Graphics.UI.FreeGame.GUI 592 1 0.0 0.0 0.0 0.0 | |
CAF Global 580 0 0.0 0.0 0.0 0.0 | |
isInside Global 2017 1 0.0 0.0 0.0 0.0 | |
toInt Global 1892 1 0.0 0.0 0.0 0.0 | |
fromPair Global 843 1 0.0 0.0 0.0 0.0 | |
toNum Global 841 1 0.0 0.0 0.0 0.0 | |
CAF Object 579 0 0.0 0.0 0.0 0.0 | |
initPlayer Object 839 1 0.0 0.0 0.0 0.0 | |
fromPair Global 844 0 0.0 0.0 0.0 0.0 | |
toNum Global 842 0 0.0 0.0 0.0 0.0 | |
initChara Object 840 1 0.0 0.0 0.0 0.0 | |
CAF Key 578 0 0.0 0.0 0.0 0.0 | |
initKeys Key 1857 1 0.0 0.0 0.0 0.0 | |
keyChar Graphics.UI.FreeGame.Base 772 1 0.0 0.0 0.0 0.0 | |
keySpecial Graphics.UI.FreeGame.Base 719 1 0.0 0.0 0.0 0.0 | |
update Key 707 0 0.0 0.0 0.0 0.0 | |
keyChar Graphics.UI.FreeGame.Base 761 1 0.0 0.0 0.0 0.0 | |
keyChar Graphics.UI.FreeGame.Base 773 0 0.0 0.0 0.0 0.0 | |
keyChar Graphics.UI.FreeGame.GUI 782 0 0.0 0.0 0.0 0.0 | |
keyChar Graphics.UI.FreeGame.GUI 783 1 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 771 1 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.GUI 774 1 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.GUI 781 1 0.0 0.0 0.0 0.0 | |
keySpecial Graphics.UI.FreeGame.Base 708 1 0.0 0.0 0.0 0.0 | |
keySpecial Graphics.UI.FreeGame.Base 720 0 0.0 0.0 0.0 0.0 | |
keySpecial Graphics.UI.FreeGame.GUI 744 0 0.0 0.0 0.0 0.0 | |
keySpecial Graphics.UI.FreeGame.GUI 745 5 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.Base 718 5 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.GUI 722 5 0.0 0.0 0.0 0.0 | |
fmap Graphics.UI.FreeGame.GUI 743 5 0.0 0.0 0.0 0.0 | |
CAF Field 577 0 0.0 0.0 0.0 0.0 | |
drawBullet Field 2048 0 0.0 0.0 0.0 0.0 | |
object Object 2075 1 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 2049 1 0.0 0.0 0.0 0.0 | |
collideChara Field 1992 0 0.0 0.0 0.0 0.0 | |
chara Object 1993 1 0.0 0.0 0.0 0.0 | |
clearQ Field 1967 1 0.0 0.0 0.0 0.0 | |
updateField Field 1963 0 0.0 0.0 0.0 0.0 | |
updateField.\ Field 2021 0 0.0 0.0 0.0 0.0 | |
object Object 2022 1 0.0 0.0 0.0 0.0 | |
updateField.\ Field 1964 0 0.0 0.0 0.0 0.0 | |
chara Object 1965 1 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 1925 1 0.0 0.0 0.0 0.0 | |
drawEnemy Field 1915 0 0.0 0.0 0.0 0.0 | |
object Object 1930 1 0.0 0.0 0.0 0.0 | |
object Object 1934 1 0.0 0.0 0.0 0.0 | |
chara Object 1932 1 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 1916 1 0.0 0.0 0.0 0.0 | |
addEnemyBullet Field 1854 1 0.0 0.0 0.0 0.0 | |
collideP Field 1851 1 0.0 0.0 0.0 0.0 | |
addEnemy Field 1848 1 0.0 0.0 0.0 0.0 | |
object Object 1859 1 0.0 0.0 0.0 0.0 | |
object Object 1863 1 0.0 0.0 0.0 0.0 | |
chara Object 1861 1 0.0 0.0 0.0 0.0 | |
initField Field 804 1 0.0 0.0 0.0 0.0 | |
fromPair Global 1937 0 0.0 0.0 0.0 0.0 | |
initEnemy Object 1933 1 0.0 0.0 0.0 0.0 | |
initChara Object 1936 1 0.0 0.0 0.0 0.0 | |
CAF Graphics.UI.FreeGame 576 0 0.0 0.0 0.0 0.0 | |
runGame Graphics.UI.FreeGame 583 1 0.0 0.0 0.0 0.0 | |
CAF Graphics.UI.FreeGame.GUI 575 0 0.0 0.0 0.0 0.0 | |
rotateD Graphics.UI.FreeGame.GUI 2076 1 0.0 0.0 0.0 0.0 | |
rotateD Graphics.UI.FreeGame.GUI 2070 1 0.0 0.0 0.0 0.0 | |
rotateR Graphics.UI.FreeGame.Base 2068 1 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.GUI 1148 1 0.0 0.0 0.0 0.0 | |
colored Graphics.UI.FreeGame.GUI 1144 1 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.GUI 1137 1 0.0 0.0 0.0 0.0 | |
colored Graphics.UI.FreeGame.GUI 1131 1 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.GUI 885 1 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.GUI 832 1 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.GUI 823 1 0.0 0.0 0.0 0.0 | |
translate Graphics.UI.FreeGame.GUI 819 1 0.0 0.0 0.0 0.0 | |
keyChar Graphics.UI.FreeGame.GUI 775 1 0.0 0.0 0.0 0.0 | |
keySpecial Graphics.UI.FreeGame.GUI 723 1 0.0 0.0 0.0 0.0 | |
def Graphics.UI.FreeGame.GUI 594 1 0.0 0.0 0.0 0.0 | |
CAF Graphics.UI.FreeGame.GUI.GLFW 574 0 0.0 0.0 0.0 0.0 | |
runAction Graphics.UI.FreeGame.GUI.GLFW 1808 0 0.0 0.0 0.0 0.0 | |
return Graphics.UI.FreeGame.Internal.Finalizer 2235 1 0.0 0.0 0.0 0.0 | |
l.55:Tick Graphics.UI.FreeGame.GUI.GLFW 1809 0 0.0 0.0 0.0 0.0 | |
l.67:windowIsOpen Graphics.UI.FreeGame.GUI.GLFW 1810 1 0.0 0.0 0.0 0.0 | |
liftIO Graphics.UI.FreeGame.Internal.Finalizer 1811 1 0.0 0.0 0.0 0.0 | |
runPicture Graphics.UI.FreeGame.GUI.GLFW 1145 0 0.0 0.0 0.0 0.0 | |
liftIO Graphics.UI.FreeGame.Internal.Finalizer 1146 1 0.0 0.0 0.0 0.0 | |
drawTextureAt Graphics.UI.FreeGame.GUI.GLFW 927 0 0.0 0.0 0.0 0.0 | |
installTexture Graphics.UI.FreeGame.GUI.GLFW 901 0 0.0 0.0 0.0 0.0 | |
liftIO Graphics.UI.FreeGame.Internal.Finalizer 902 1 0.0 0.0 0.0 0.0 | |
preservingMatrix' Graphics.UI.FreeGame.GUI.GLFW 857 0 0.0 0.0 0.0 0.0 | |
liftIO Graphics.UI.FreeGame.Internal.Finalizer 858 2 0.0 0.0 0.0 0.0 | |
runGame Graphics.UI.FreeGame.GUI.GLFW 599 0 0.0 0.0 0.0 0.0 | |
launch Graphics.UI.FreeGame.GUI.GLFW 600 0 0.0 0.0 0.0 0.0 | |
liftIO Graphics.UI.FreeGame.Internal.Finalizer 618 2 0.0 0.0 0.0 0.0 | |
CAF Graphics.UI.FreeGame.Base 572 0 0.0 0.0 0.0 0.0 | |
fromFinalizer Graphics.UI.FreeGame.Base 1157 1 0.0 0.0 0.0 0.0 | |
CAF Graphics.UI.FreeGame.Data.Bitmap 571 0 0.0 0.0 0.0 0.0 | |
cropBitmap Graphics.UI.FreeGame.Data.Bitmap 918 0 0.0 0.0 0.0 0.0 | |
onBitmapWithHashable Graphics.UI.FreeGame.Data.Bitmap 919 0 0.0 0.0 0.0 0.0 | |
CAF Graphics.UI.FreeGame.Data.Font 569 0 0.0 0.0 0.0 0.0 | |
resolutionDPI Graphics.UI.FreeGame.Data.Font 1171 1 0.0 0.0 0.0 0.0 | |
charToBitmap Graphics.UI.FreeGame.Data.Font 1169 0 0.0 0.0 0.0 0.0 | |
charToBitmap.render Graphics.UI.FreeGame.Data.Font 1172 0 0.0 0.0 0.0 0.0 | |
charToBitmap.render.dpi Graphics.UI.FreeGame.Data.Font 1173 1 0.0 0.0 0.0 0.0 | |
charToBitmap.siz Graphics.UI.FreeGame.Data.Font 1170 0 0.0 0.0 0.0 0.0 | |
freeType Graphics.UI.FreeGame.Data.Font 661 1 0.0 0.0 0.0 0.0 | |
runFreeType Graphics.UI.FreeGame.Data.Font 663 1 0.0 0.0 0.0 0.0 | |
freeType.\ Graphics.UI.FreeGame.Data.Font 662 1 0.0 0.0 0.0 0.0 | |
CAF Player 564 0 0.0 0.0 0.0 0.0 | |
clamp Player 1885 1 0.0 0.0 0.0 0.0 | |
clamp.edgeY Player 1905 1 0.0 0.0 0.0 0.0 | |
clamp.edgeX Player 1889 1 0.0 0.0 0.0 0.0 | |
updateCounter Player 1872 1 0.0 0.0 0.0 0.0 | |
object Object 1875 1 0.0 0.0 0.0 0.0 | |
chara Object 1874 1 0.0 0.0 0.0 0.0 | |
updatePos Player 1867 0 0.0 0.0 0.0 0.0 | |
updatePos.dir Player 1896 0 0.0 0.0 0.0 0.0 | |
fromPair Global 1897 0 0.0 0.0 0.0 0.0 | |
object Object 1869 2 0.0 0.0 0.0 0.0 | |
chara Object 1868 3 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 817 1 0.0 0.0 0.0 0.0 | |
draw Player 807 0 0.0 0.0 0.0 0.0 | |
object Object 833 1 0.0 0.0 0.0 0.0 | |
object Object 837 1 0.0 0.0 0.0 0.0 | |
chara Object 835 1 0.0 0.0 0.0 0.0 | |
fromBitmap Graphics.UI.FreeGame.Base 808 1 0.0 0.0 0.0 0.0 | |
CAF Barrage 563 0 0.0 0.0 0.0 0.0 | |
normalBullet Barrage 2026 1 0.0 0.0 0.0 0.0 | |
object Object 2028 3 0.0 0.0 0.0 0.0 | |
barrage Barrage 2005 0 0.0 0.0 0.0 0.0 | |
barrage.danmaku Barrage 2006 0 0.0 0.0 0.0 0.0 | |
barrage.danmaku.posE Barrage 2032 0 0.0 0.0 0.0 0.0 | |
object Object 2034 1 0.0 0.0 0.0 0.0 | |
object Object 2037 1 0.0 0.0 0.0 0.0 | |
chara Object 2036 1 0.0 0.0 0.0 0.0 | |
barrage.danmaku.cnt Barrage 2007 0 0.0 0.0 0.0 0.0 | |
object Object 2009 1 0.0 0.0 0.0 0.0 | |
object Object 2012 1 0.0 0.0 0.0 0.0 | |
chara Object 2011 1 0.0 0.0 0.0 0.0 | |
normalEnemy Barrage 1980 0 0.0 0.0 0.0 0.0 | |
fromPair Global 2000 0 0.0 0.0 0.0 0.0 | |
object Object 1981 3 0.0 0.0 0.0 0.0 | |
object Object 1984 3 0.0 0.0 0.0 0.0 | |
chara Object 1982 3 0.0 0.0 0.0 0.0 | |
checkStateMotion Barrage 1974 0 0.0 0.0 0.0 0.0 | |
object Object 1975 1 0.0 0.0 0.0 0.0 | |
object Object 1978 1 0.0 0.0 0.0 0.0 | |
chara Object 1977 1 0.0 0.0 0.0 0.0 | |
CAF Data.Hashable.Class 548 0 0.0 0.0 0.0 0.0 | |
CAF Graphics.Rendering.OpenGL.GL.LineSegments 502 0 0.0 0.0 0.0 0.0 | |
CAF Graphics.Rendering.OpenGL.GL.PerFragment 501 0 0.0 0.0 0.0 0.0 | |
CAF Graphics.Rendering.OpenGL.GL.VertexSpec 495 0 0.0 0.0 0.0 0.0 | |
CAF Codec.Picture.Repa 475 0 0.0 0.0 0.0 0.0 | |
CAF Data.Array.Repa.Eval.Gang 474 0 0.0 0.0 0.0 0.0 | |
CAF System.Random 463 0 0.0 0.0 0.0 0.0 | |
CAF Data.Time.Clock.POSIX 461 0 0.0 0.0 0.0 0.0 | |
CAF Data.Time.Clock.CTimeval 459 0 0.0 0.0 0.0 0.0 | |
CAF Codec.Picture.Png 453 0 0.0 0.0 0.0 0.0 | |
CAF Codec.Picture.Jpg 452 0 0.0 0.0 0.0 0.0 | |
CAF Codec.Picture.Png.Type 442 0 0.0 0.0 0.0 0.0 | |
CAF Codec.Compression.Zlib.Stream 437 0 0.0 0.0 0.0 0.0 | |
CAF System.IO.MMap 392 0 0.0 0.0 0.0 0.0 | |
CAF Graphics.Rendering.OpenGL.Raw.ARB.Compatibility.Functions 358 0 0.0 0.0 0.0 0.0 | |
CAF Graphics.Rendering.OpenGL.Raw.Core31.Functions 356 0 0.0 0.0 0.0 0.0 | |
CAF GHC.Conc.Signal 351 0 0.0 0.0 0.0 0.0 | |
CAF GHC.Conc.Sync 350 0 0.0 0.0 0.0 0.0 | |
CAF GHC.IO.Encoding 345 0 0.0 0.0 0.0 0.0 | |
CAF GHC.IO.Handle.FD 342 0 0.0 0.0 0.0 0.0 | |
CAF GHC.Int 340 0 0.0 0.0 0.0 0.0 | |
CAF System.CPUTime 332 0 0.0 0.0 0.0 0.0 | |
CAF Data.Fixed 316 0 0.0 0.0 0.0 0.0 | |
CAF GHC.IO.Encoding.Iconv 308 0 0.0 0.0 0.0 0.0 | |
CAF GHC.Integer.Logarithms.Internals 299 0 0.0 0.0 0.0 0.0 |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment