{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase       #-}
{-# LANGUAGE RecordWildCards  #-}
module GI.Gtk.Declarative.App.Simple
  ( App(..)
  , AppView
  , Transition(..)
  , run
  , runLoop
  )
where
import           Control.Concurrent
import qualified Control.Concurrent.Async       as Async
import           Control.Exception              (Exception, throw)
import           Control.Monad
import           Data.Typeable
import qualified GI.Gdk                         as Gdk
import qualified GI.GLib.Constants              as GLib
import qualified GI.Gtk                         as Gtk
import           GI.Gtk.Declarative
import           GI.Gtk.Declarative.Bin
import           GI.Gtk.Declarative.EventSource
import           GI.Gtk.Declarative.State
import           Pipes
import           Pipes.Concurrent
data App window state event =
  App
    { update       :: state -> event -> Transition state event
    
    
    
    , view         :: state -> AppView window event
    
    
    , inputs       :: [Producer event IO ()]
    
    , initialState :: state
    
    }
type AppView window event = Bin window Widget event
data Transition state event =
  
  
  Transition state (IO (Maybe event))
  
  | Exit
data GtkMainExitedException =
  GtkMainExitedException String deriving (Typeable, Show)
instance Exception GtkMainExitedException
run
  :: (Typeable event, BinChild window Widget)
  => App window state event      
  -> IO state
run app = do
  void $ Gtk.init Nothing
  Async.withAsync (runLoop app <* Gtk.mainQuit) $ \lastState -> do
    Gtk.main
    Async.poll lastState >>= \case
      Nothing -> throw $
        GtkMainExitedException "gtk's main loop exited unexpectedly"
      Just (Right state) -> return state
      Just (Left exception) -> throw exception
runLoop :: (Typeable event, BinChild window Widget) => App window state event -> IO state
runLoop App {..} = do
  let firstMarkup = view initialState
  events                  <- newChan
  (firstState, subscription) <- do
    firstState <- runUI (create firstMarkup)
    runUI (Gtk.widgetShowAll =<< someStateWidget firstState)
    sub <- subscribe firstMarkup firstState (publishEvent events)
    return (firstState, sub)
  void . forkIO $ runEffect
    (mergeProducers inputs >-> publishInputEvents events)
  loop firstState firstMarkup events subscription initialState
  where
    loop oldState oldMarkup events oldSubscription oldModel = do
      event <- readChan events
      case update oldModel event of
        Transition newModel action -> do
          let newMarkup = view newModel
          (newState, sub) <-
            case patch oldState oldMarkup newMarkup of
              Modify ma -> runUI $ do
                cancel oldSubscription
                newState <- ma
                sub <- subscribe newMarkup newState (publishEvent events)
                return (newState, sub)
              Replace createNew -> runUI $ do
                Gtk.widgetDestroy =<< someStateWidget oldState
                cancel oldSubscription
                newState <- createNew
                Gtk.widgetShowAll =<< someStateWidget newState
                sub <- subscribe newMarkup newState (publishEvent events)
                return (newState, sub)
              Keep -> return (oldState, oldSubscription)
          
          
          
          
          
          void . forkIO $ action >>= maybe (return ()) (writeChan events)
          
          loop newState newMarkup events sub newModel
        Exit -> return oldModel
publishEvent :: Chan event -> event -> IO ()
publishEvent mvar = void . writeChan mvar
mergeProducers :: [Producer a IO ()] -> Producer a IO ()
mergeProducers producers = do
  (output, input) <- liftIO $ spawn unbounded
  _               <- liftIO $ mapM (fork output) producers
  fromInput input
 where
  fork :: Output a -> Producer a IO () -> IO ()
  fork output producer = void $ forkIO $ do
    runEffect $ producer >-> toOutput output
    performGC
publishInputEvents :: Chan event -> Consumer event IO ()
publishInputEvents events = forever (await >>= liftIO . writeChan events)
runUI :: IO a -> IO a
runUI ma = do
  r <- newEmptyMVar
  runUI_ (ma >>= putMVar r)
  takeMVar r
runUI_ :: IO () -> IO ()
runUI_ ma =
  void . Gdk.threadsAddIdle GLib.PRIORITY_DEFAULT $ do
    ma
    return False