module Graphics.UI.WXCore.Frame
        ( 
          frameCreateTopFrame
        , frameCreateDefault
        , frameSetTopFrame
        , frameDefaultStyle
        , frameCenter
        , frameCenterHorizontal
        , frameCenterVertical
          
        , windowGetRootParent
        , windowGetFrameParent
        , windowGetMousePosition
        , windowGetScreenPosition
        , windowChildren
          
        , dialogDefaultStyle
          
        , statusBarCreateFields
        ) where
import Data.Bits
import Foreign.Marshal.Array
import Graphics.UI.WXCore.WxcTypes
import Graphics.UI.WXCore.WxcDefs
import Graphics.UI.WXCore.WxcClassInfo
import Graphics.UI.WXCore.WxcClasses
import Graphics.UI.WXCore.WxcClassTypes
import Graphics.UI.WXCore.Types
frameDefaultStyle :: Int
frameDefaultStyle
  = wxDEFAULT_FRAME_STYLE .|. wxCLIP_CHILDREN 
dialogDefaultStyle :: Int
dialogDefaultStyle
  = wxCAPTION .|. wxSYSTEM_MENU .|. wxTAB_TRAVERSAL .|. wxCLOSE_BOX .|. wxCLIP_CHILDREN 
    
frameCreateTopFrame :: String -> IO (Frame ())
frameCreateTopFrame title
  = do frame <- frameCreateDefault title
       frameSetTopFrame frame
       return frame
frameSetTopFrame :: Frame a -> IO ()
frameSetTopFrame frame
  = wxcAppSetTopWindow frame
frameCreateDefault :: String -> IO (Frame ())
frameCreateDefault title
  = frameCreate objectNull idAny title rectNull frameDefaultStyle
frameCenter :: Frame a -> IO ()
frameCenter f 
  = frameCentre f wxBOTH
frameCenterHorizontal :: Frame a -> IO ()
frameCenterHorizontal f
  = frameCentre f wxHORIZONTAL
frameCenterVertical :: Frame a -> IO ()
frameCenterVertical f
  = frameCentre f wxVERTICAL
windowGetFrameParent :: Window a -> IO (Window ())
windowGetFrameParent w
  = if (instanceOf w classFrame || instanceOf w classDialog)
     then return (downcastWindow w)
     else do p <- windowGetParent w
             if (objectIsNull p)
              then return (downcastWindow w)
              else windowGetFrameParent p
windowGetRootParent :: Window a -> IO (Window ())
windowGetRootParent w
  = do p <- windowGetParent w
       if (objectIsNull p)
        then return (downcastWindow w)
        else windowGetRootParent p
       
windowGetMousePosition :: Window a -> IO Point
windowGetMousePosition w
  = do p <- wxcGetMousePosition
       windowScreenToClient2 w p
  
windowGetScreenPosition :: Window a -> IO Point
windowGetScreenPosition w
  = windowClientToScreen w pointZero
windowChildren :: Window a -> IO [Window ()]
windowChildren w
  = do count <- windowGetChildren w ptrNull 0
       if count <= 0
        then return []
        else withArray (replicate count ptrNull) $ \ptrs ->
             do windowGetChildren w ptrs count
                ps <- peekArray count ptrs
                return (map objectFromPtr ps)
statusBarCreateFields :: Frame a -> [Int] -> IO (StatusBar ())
statusBarCreateFields parent widths
  = do pst <- windowGetWindowStyleFlag parent
       let st = if (bitsSet wxRESIZE_BORDER pst) then wxST_SIZEGRIP else 0
       sb <- frameCreateStatusBar parent (length widths) st
       let len = length widths
       if (len <= 1)
        then return sb
        else do withArray (map toCInt widths) (\pwidths -> statusBarSetStatusWidths sb (length widths) pwidths)
                return sb