{-# OPTIONS_GHC -fno-warn-unticked-promoted-constructors #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedLabels #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
module GI.Gtk.Declarative.Container.Patch (IsContainer(..), patchInContainer) where
import Control.Monad (forM_)
import Data.Int (Int32)
import Data.List (zip4)
import qualified GI.Gtk as Gtk
import GI.Gtk.Declarative.Bin
import GI.Gtk.Declarative.Container.Box
import GI.Gtk.Declarative.Markup
import GI.Gtk.Declarative.Patch
class IsContainer container child | container -> child where
appendChild
:: container
-> child event
-> Gtk.Widget
-> IO ()
replaceChild
:: container
-> child event
-> Int32
-> Gtk.Widget
-> Gtk.Widget
-> IO ()
patchInContainer
:: ( Gtk.IsWidget container
, Gtk.IsContainer container
, Patchable child
, IsContainer container child
)
=> container
-> [child e1]
-> [child e2]
-> IO ()
patchInContainer container os' ns' = do
cs <- Gtk.containerGetChildren container
let maxLength = maximum [length cs, length os', length ns']
indices = [0 .. pred (fromIntegral maxLength)]
forM_ (zip4 indices (padMaybes cs) (padMaybes os') (padMaybes ns')) $ \case
(i, Just w, Just old, Just new) -> case patch old new of
Modify modify -> modify w
Replace createWidget -> replaceChild container new i w =<< createWidget
Keep -> return ()
(i, Just w, Nothing, Just new) ->
replaceChild container new i w =<< create new
(_i, Nothing, _ , Just n ) -> create n >>= appendChild container n
(_i, Just w , Just _ , Nothing) -> Gtk.containerRemove container w
(_i, Nothing, Just _ , Nothing) -> return ()
(_i, Just w , Nothing, Nothing) -> Gtk.containerRemove container w
(_i, Nothing, Nothing, Nothing) -> return ()
Gtk.widgetQueueResize container
instance IsContainer Gtk.ListBox (Bin Gtk.ListBoxRow Widget) where
appendChild box _ widget' = Gtk.listBoxInsert box widget' (-1)
replaceChild box _ i old new = do
Gtk.containerRemove box old
Gtk.listBoxInsert box new i
Gtk.widgetShowAll box
instance IsContainer Gtk.Box BoxChild where
appendChild box BoxChild {..} widget' =
Gtk.boxPackStart box widget' expand fill padding
replaceChild box boxChild' i old new = do
Gtk.containerRemove box old
appendChild box boxChild' new
Gtk.boxReorderChild box new i
Gtk.widgetShowAll box
padMaybes :: [a] -> [Maybe a]
padMaybes xs = map Just xs ++ repeat Nothing