{-# LANGUAGE
      ForeignFunctionInterface
    , NamedFieldPuns
    , OverloadedStrings
    , CPP
#-}
module Graphics.UI.Webviewhs
  ( WindowParams(..)
  , WindowBackgroundColor(..)
  , WindowAlertDialogType(..)
  , Window
  , WithWindowLoopSetUp(..)
  , WithWindowLoopTearDown(..)
  , createWindowAndBlock
  , createWindow
  , setWindowTitle
  , setWindowFullscreen
  , setWindowBackgroundColor
  , withWindowLoop
  , iterateWindowLoop
  , runJavaScript'
#ifndef LIGHT
  , runJavaScript
  , injectCss
  , Graphics.UI.Webviewhs.log
#endif
  , injectCss'
  , openWindowAlertDialog
  , withWindowOpenDialog
  , withWindowSaveDialog
  , dispatchToMain
  , Graphics.UI.Webviewhs.log'
  , terminateWindowLoop
  , destroyWindow
  )
where
import Foreign.C
import Foreign.Ptr
import Foreign.Marshal.Alloc
import Control.Monad
import Control.Concurrent.MVar
import Data.Word
import Data.Text
#ifndef LIGHT
import qualified Data.Text.Lazy as DTL
import Language.Javascript.JMacro
import Data.Text.Format.Heavy
import Clay (Css, render)
#endif
type Window = Ptr
data WindowParams =
  WindowParams
    { windowParamsTitle      :: Text
    
    , windowParamsUri        :: Text
    , windowParamsWidth      :: Int
    , windowParamsHeight     :: Int
    , windowParamsResizable  :: Bool
    
    
    
    
    
    
    
    , windowParamsDebuggable :: Bool
    }
data CWindowParams =
  CWindowParams
    { cWindowParamsTitle      :: CString
    , cWindowParamsUri        :: CString
    , cWindowParamsWidth      :: CInt
    , cWindowParamsHeight     :: CInt
    , cWindowParamsResizable  :: CInt
    , cWindowParamsDebuggable :: CInt
    }
data WindowBackgroundColor =
  WindowBackgroundColor
    { windowBackgroundColorRed   :: Word8
    , windowBackgroundColorGreen :: Word8
    , windowBackgroundColorBlue  :: Word8
    , windowBackgroundColorAlpha :: Word8
    }
data  WindowAlertDialogType =
      WindowAlertDialogTypeInfo
    | WindowAlertDialogTypeWarning
    | WindowAlertDialogTypeError
newtype WithWindowLoopSetUp    a = WithWindowLoopSetUp    (Window a -> IO ())
newtype WithWindowLoopTearDown a = WithWindowLoopTearDown (Window a -> IO ())
windowDialogTypeAlert :: CInt
windowDialogTypeAlert = 2
foreign import ccall "webview-ffi.h c_create_window_and_block"
    c_create_window_and_block
      ::  CString
      ->  CString
      ->  CInt
      ->  CInt
      ->  CInt
      ->  CInt
      ->  IO ()
foreign import ccall "webview-ffi.h c_create_window"
  c_create_window
      ::  CString
      ->  CString
      ->  CInt
      ->  CInt
      ->  CInt
      ->  CInt
      ->  FunPtr (Window a -> CString -> IO ())
      ->  IO (Window a)
foreign import ccall "webview-ffi.h c_set_window_title"
  c_set_window_title
      ::  Window a
      ->  CString
      ->  IO ()
foreign import ccall "webview-ffi.h c_set_window_fullscreen"
  c_set_window_fullscreen
      ::  Window a
      ->  CInt
      ->  IO ()
foreign import ccall "webview-ffi.h c_set_window_background_color"
  c_set_window_background_color
      ::  Window a
      ->  CUChar
      ->  CUChar
      ->  CUChar
      ->  CUChar
      ->  IO ()
foreign import ccall "webview-ffi.h c_iterate_window"
  c_iterate_window
      ::  Window a
      ->  CInt
      ->  IO CInt
foreign import ccall "webview-ffi.h c_run_javascript"
  c_run_javascript
      ::  Window a
      ->  CString
      ->  IO CInt
foreign import ccall "webview-ffi.h c_inject_css"
  c_inject_css
      ::  Window a
      ->  CString
      ->  IO CInt
foreign import ccall "webview-ffi.h c_open_window_dialog"
  c_open_window_dialog
      ::  Window a
      ->  CInt    
      ->  CInt    
      ->  CString 
      ->  CString 
      ->  CString 
      ->  CUInt   
      ->  IO ()
foreign import ccall safe "webview-ffi.h c_dispatch_to_main"
  c_dispatch_to_main
      ::  Window a
      ->  FunPtr (Window a -> Ptr () -> IO () )
      ->  Ptr ()
      ->  IO ()
foreign import ccall "webview-ffi.h c_log"
  c_log
      ::  CString
      ->  IO ()
foreign import ccall "webview-ffi.h c_terminate_window_loop"
  c_terminate_window_loop
      ::  Window a
      ->  IO ()
foreign import ccall "webview-ffi.h c_destroy_window"
  c_destroy_window
      ::  Window a
      ->  IO ()
foreign import ccall "wrapper"
  makeDispatchCallback
      ::  (Window a -> Ptr () -> IO ())
      ->  IO (FunPtr (Window a -> Ptr () -> IO ()))
foreign import ccall "wrapper"
  makeCallback
      ::  (Window a -> CString -> IO ())
      ->  IO (FunPtr (Window a -> CString -> IO ()))
createWindowAndBlock
  ::  WindowParams
  ->  IO ()
createWindowAndBlock
  windowParams
  = do
  CWindowParams
    { cWindowParamsTitle
    , cWindowParamsUri
    , cWindowParamsWidth
    , cWindowParamsHeight
    , cWindowParamsResizable
    , cWindowParamsDebuggable
    } <- windowParamsToC windowParams
  c_create_window_and_block
    cWindowParamsTitle
    cWindowParamsUri
    cWindowParamsWidth
    cWindowParamsHeight
    cWindowParamsResizable
    cWindowParamsDebuggable
  free cWindowParamsTitle
  free cWindowParamsUri
createWindow
  ::  WindowParams
  ->  (Window a -> Text -> IO ()) 
                                  
  ->  IO (Either Text (Window a))
createWindow
  windowParams
  callback
  = do
  CWindowParams
    { cWindowParamsTitle
    , cWindowParamsUri
    , cWindowParamsWidth
    , cWindowParamsHeight
    , cWindowParamsResizable
    , cWindowParamsDebuggable
    } <- windowParamsToC windowParams
  let callback' window cString = do
        string <- peekCString cString
        callback window (Data.Text.pack string)
  funPtr <- makeCallback callback'
  result <-
    c_create_window
      cWindowParamsTitle
      cWindowParamsUri
      cWindowParamsWidth
      cWindowParamsHeight
      cWindowParamsResizable
      cWindowParamsDebuggable
      funPtr
  if result == nullPtr
    then do
      free cWindowParamsTitle
      free cWindowParamsUri
      freeHaskellFunPtr funPtr
      return $ Left "[WEBVIEWHS:ERROR] Could not create window."
    else do
      free cWindowParamsTitle
      free cWindowParamsUri
      return $ Right result
setWindowTitle
  ::  Window a
  ->  Text
  ->  IO ()
setWindowTitle
  window
  newTitle
  = do
  newTitle' <- newCString $ Data.Text.unpack newTitle
  c_set_window_title window newTitle'
  free newTitle'
setWindowFullscreen
  ::  Window a
  ->  Bool
  ->  IO ()
setWindowFullscreen
  window
  fullscreen
  = do
  let fullscreen' = if fullscreen then 1 else 0
  c_set_window_fullscreen window fullscreen'
setWindowBackgroundColor
  ::  Window a
  ->  WindowBackgroundColor
  ->  IO ()
setWindowBackgroundColor
  window
  WindowBackgroundColor
    { windowBackgroundColorRed
    , windowBackgroundColorGreen
    , windowBackgroundColorBlue
    , windowBackgroundColorAlpha
    }
  = do
  let red'   = fromIntegral windowBackgroundColorRed   :: CUChar
  let green' = fromIntegral windowBackgroundColorGreen :: CUChar
  let blue'  = fromIntegral windowBackgroundColorBlue  :: CUChar
  let alpha' = fromIntegral windowBackgroundColorAlpha :: CUChar
  c_set_window_background_color window red' green' blue' alpha'
iterateWindowLoop
  ::  Window a
  ->  Bool 
           
  ->  IO Bool
iterateWindowLoop
  window
  block
  = do
  result <-
    c_iterate_window
      window
      (if block then 1 else 0)
  return (result == 0)
runJavaScript'
  ::  Window a
  ->  Text
  ->  IO Bool 
runJavaScript'
  window
  javaScript
  = do
  javaScript' <- newCString $ Data.Text.unpack javaScript
  result      <- c_run_javascript window javaScript'
  free javaScript'
  return (result /= -1)
injectCss'
  ::  Window a
  ->  Text
  ->  IO Bool 
injectCss'
  window
  css
  = do
  css'   <- newCString $ Data.Text.unpack css
  result <- c_inject_css window css'
  free css'
  return (result /= -1)
openWindowAlertDialog
  ::  Window a
  ->  WindowAlertDialogType
  ->  Text 
  ->  Text 
  ->  IO ()
openWindowAlertDialog
  window
  windowAlertDialogType
  primaryMessage
  secondaryMessage
  = do
  primaryMessage'   <- newCString $ Data.Text.unpack primaryMessage
  secondaryMessage' <- newCString $ Data.Text.unpack secondaryMessage
  result            <- newCString ""
  c_open_window_dialog
    window
    windowDialogTypeAlert
    (dialogType windowAlertDialogType)
    primaryMessage'
    secondaryMessage'
    result
    0
  free primaryMessage'
  free secondaryMessage'
  free result
  where
    dialogType :: WindowAlertDialogType -> CInt
    dialogType WindowAlertDialogTypeInfo    = 2
    dialogType WindowAlertDialogTypeWarning = 4
    dialogType WindowAlertDialogTypeError   = 6
withWindowOpenDialog
  ::  Window a
  ->  Text 
  ->  Bool 
           
  ->  (Text -> IO ()) 
  ->  IO ()
withWindowOpenDialog
  window
  title
  =
  withWindowFileDialog
    window
    title
    True
withWindowSaveDialog
  ::  Window a
  ->  Text 
  ->  (Text -> IO ()) 
  ->  IO ()
withWindowSaveDialog
  window
  title
  =
  withWindowFileDialog
    window
    title
    False
    False
withWindowFileDialog
  ::  Window a
  ->  Text
  ->  Bool
  ->  Bool
  ->  (Text -> IO ())
  ->  IO ()
withWindowFileDialog
  window
  title
  open
  disableOpeningFiles
  callback
  = do
  title'          <- newCString $ Data.Text.unpack title
  message'        <- newCString ""
  let bufferSize  = 1024
  let bufferSize' = fromIntegral bufferSize :: CUInt
  result          <- callocBytes bufferSize
  c_open_window_dialog
    window
    (if open then 0 else 1)
    (if disableOpeningFiles then 1 else 0)
    title'
    message'
    result
    bufferSize'
  free title'
  free message'
  result' <- peekCString result
  callback $ Data.Text.pack result'
  free result
dispatchToMain
  ::  Window a
  ->  (Window a -> IO ())
  ->  IO ()
dispatchToMain
  window
  callback
  = do
  mvar                    <- newEmptyMVar
  let callback' window' _ = do
        callback window'
        putMVar mvar (1 :: Int)
  funPtr                  <- makeDispatchCallback callback'
  let nullPtr'            = nullPtr
  c_dispatch_to_main window funPtr nullPtr'
  _ <- takeMVar mvar
  freeHaskellFunPtr funPtr
  return ()
log'
  ::  Text
  ->  IO ()
log'
  entry
  = do
  entry' <- newCString $ Data.Text.unpack entry
  c_log entry'
  free entry'
  return ()
terminateWindowLoop
  ::  Window a
  ->  IO ()
terminateWindowLoop = c_terminate_window_loop
destroyWindow
  ::  Window a
  ->  IO ()
destroyWindow = c_destroy_window
withWindowLoop
  ::  WindowParams
  ->  (Window a -> Text -> IO ()) 
                                  
                                  
  ->  WithWindowLoopSetUp    a    
                                  
                                  
                                  
                                  
  ->  WithWindowLoopTearDown a    
                                  
                                  
                                  
                                  
                                  
                                  
  ->  (Window a -> IO Bool)       
                                  
  ->  IO ()
withWindowLoop
  windowParams
  callback
  (WithWindowLoopSetUp setUp)
  (WithWindowLoopTearDown tearDown)
  iteration
  = do
  eitherWindow   <- createWindow windowParams callback
  case eitherWindow of
    Left  e      -> putStrLn $ Data.Text.unpack e
    Right window -> do
      setUp               window
      loop                window iteration
      tearDown            window
      terminateWindowLoop window
      destroyWindow       window
  where
    loop :: Window a -> (Window a -> IO Bool) -> IO ()
    loop window iteration' = do
      continue        <- iteration'        window
      shouldContinue  <- iterateWindowLoop window False
      when (continue && shouldContinue) $
        loop window iteration'
#ifndef LIGHT
runJavaScript
  ::  (JsToDoc js, JMacro js)
  =>  Window a
  ->  js
  ->  IO Bool 
runJavaScript
  window
  javaScript
  = do
  let javaScript' = Data.Text.pack $ show $ renderJs javaScript
  runJavaScript' window javaScript'
injectCss
  ::  Window a
  ->  Clay.Css
  ->  IO Bool 
injectCss
  window
  css
  =
  injectCss'
    window $
      DTL.toStrict $
        Clay.render css
log
  ::  VarContainer vars
  =>  Format
  ->  vars
  ->  IO ()
log
  fmt
  vars
  = do
  let entry = format fmt vars
  log' $ DTL.toStrict entry
#endif
windowParamsToC
  ::  WindowParams
  ->  IO CWindowParams
windowParamsToC
  WindowParams
    { windowParamsTitle
    , windowParamsUri
    , windowParamsWidth
    , windowParamsHeight
    , windowParamsResizable
    , windowParamsDebuggable
    }
  = do
  title          <- newCString $ Data.Text.unpack windowParamsTitle
  uri            <- newCString $ Data.Text.unpack windowParamsUri
  let width      = fromIntegral windowParamsWidth  :: CInt
  let height     = fromIntegral windowParamsHeight :: CInt
  let resizable  = if windowParamsResizable then 1 else 0
  let debuggable = if windowParamsDebuggable then 1 else 0
  return
    CWindowParams
      { cWindowParamsTitle      = title
      , cWindowParamsUri        = uri
      , cWindowParamsWidth      = width
      , cWindowParamsHeight     = height
      , cWindowParamsResizable  = resizable
      , cWindowParamsDebuggable = debuggable
      }