-- Author:     Andy Stewart <lazycat.manatee@gmail.com>
-- Maintainer: Andy Stewart <lazycat.manatee@gmail.com>
-- 
-- Copyright (C) 2010 Andy Stewart, all rights reserved.
-- 
-- This program is free software: you can redistribute it and/or modify
-- it under the terms of the GNU General Public License as published by
-- the Free Software Foundation, either version 3 of the License, or
-- any later version.
-- 
-- This program is distributed in the hope that it will be useful,
-- but WITHOUT ANY WARRANTY; without even the implied warranty of
-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
-- GNU General Public License for more details.
-- 
-- You should have received a copy of the GNU General Public License
-- along with this program.  If not, see <http://www.gnu.org/licenses/>.

module Manatee.UI.UIFrame where

import Graphics.UI.Gtk hiding (Statusbar, statusbarNew)
import Manatee.Types
import Manatee.Toolkit.Gtk.Gtk
import Manatee.Toolkit.Gtk.Notebook
import Manatee.Toolkit.Widget.Interactivebar
import Manatee.Toolkit.Widget.NotebookTab
import Manatee.Toolkit.Widget.Outputbar
import Manatee.Toolkit.Widget.Statusbar

-- | Stick ui frame to notebook.
uiFrameStick :: NotebookClass notebook => notebook -> Maybe UIFrame -> IO UIFrame
uiFrameStick notebook frame = do
  -- Create or clone ui frame.
  uiFrame <- case frame of
              Just f  -> uiFrameClone f
              Nothing -> uiFrameNew

  -- Stick uiFrame in notebook.
  let notebookTab = uiFrameNotebookTab uiFrame
  notebookAppendPageTab_ notebook (uiFrameBox uiFrame) (ntBox notebookTab)
  notebookSetTabReorderable notebook (uiFrameBox uiFrame) False -- disable reorder tab use DND action
  notebookTabStart notebookTab  -- start spinner animation

  return uiFrame

-- | Create 'UIFrame'.
uiFrameNew :: IO UIFrame
uiFrameNew = do
  -- Create box.
  box <- vBoxNew False 0

  -- Interactivebar.
  interactivebar <- interactivebarNew

  -- Body frame.
  frame <- frameNewWithShadowType Nothing
  boxPackStart box frame PackGrow 0 

  -- Outputbar.
  outputbar <- outputbarNew
  
  -- Statusbar.
  statusbar <- statusbarNew box

  -- Notebook tab. 
  notebookTab <- notebookTabNew Nothing Nothing

  return $ UIFrame box interactivebar frame outputbar statusbar notebookTab

-- | Clone UIFrame.
uiFrameClone :: UIFrame -> IO UIFrame  
uiFrameClone oldUIFrame = do
  -- Create box.
  box <- vBoxNew False 0

  -- Clone interactivebar.
  interactivebar <- interactivebarClone box (uiFrameInteractivebar oldUIFrame)

  -- Body frame.
  frame <- frameNewWithShadowType Nothing
  boxPackStart box frame PackGrow 0 

  -- Outputbar.
  outputbar <- outputbarNew
  
  -- Clone statusbar.
  statusbar <- statusbarClone box (uiFrameStatusbar oldUIFrame)

  -- Notebook tab. 
  notebookTab <- notebookTabNew Nothing Nothing

  return $ UIFrame box interactivebar frame outputbar statusbar notebookTab

-- | Show interactivebar.
uiFrameShowInteractivebar :: UIFrame -> IO ()  
uiFrameShowInteractivebar uiFrame = 
  interactivebarShow (uiFrameBox uiFrame) 
                     (uiFrameInteractivebar uiFrame) 

-- | Hide interactivebar.
uiFrameHideInteractivebar :: UIFrame -> IO ()  
uiFrameHideInteractivebar uiFrame = 
  interactivebarExit (uiFrameBox uiFrame) 
                     (uiFrameInteractivebar uiFrame) 

-- | Is focus on interactivebar.
uiFrameIsFocusInteractivebar :: UIFrame -> IO Bool  
uiFrameIsFocusInteractivebar = 
  widgetGetIsFocus . interactivebarEntry . uiFrameInteractivebar

-- | Show outputbar.
uiFrameShowOutputbar :: UIFrame -> String -> IO ()
uiFrameShowOutputbar uiFrame =
    outputbarShow (uiFrameBox uiFrame) 
                  (uiFrameOutputbar uiFrame) 

-- | Update statusbar.
uiFrameUpdateStatusbar :: UIFrame -> String -> String -> IO ()
uiFrameUpdateStatusbar uiFrame = 
    statusbarInfoItemUpdate (uiFrameStatusbar uiFrame) 

-- | Update statusbar.
uiFrameUpdateProgress :: UIFrame -> Double -> IO ()
uiFrameUpdateProgress uiFrame = 
    statusbarProgressUpdate (uiFrameStatusbar uiFrame)