2020-09-02 02:52:08 +00:00
|
|
|
|
{-# LANGUAGE BlockArguments #-}
|
2020-09-05 00:56:59 +00:00
|
|
|
|
{-# LANGUAGE ConstraintKinds #-}
|
2020-09-02 02:52:08 +00:00
|
|
|
|
{-# LANGUAGE DerivingStrategies #-}
|
2020-09-05 00:56:59 +00:00
|
|
|
|
{-# LANGUAGE FlexibleContexts #-}
|
|
|
|
|
{-# LANGUAGE LambdaCase #-}
|
2020-09-04 18:54:48 +00:00
|
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
|
|
|
|
{-# LANGUAGE RecordWildCards #-}
|
2020-09-02 02:52:08 +00:00
|
|
|
|
{-# LANGUAGE NamedFieldPuns #-}
|
2020-09-05 00:56:59 +00:00
|
|
|
|
{-# LANGUAGE TypeApplications #-}
|
2020-09-02 02:52:08 +00:00
|
|
|
|
|
|
|
|
|
module MetaBrush.Context
|
|
|
|
|
( UIElements(..), Variables(..)
|
2020-09-02 13:58:00 +00:00
|
|
|
|
, LR(..), Modifier(..), modifierKey, modifierType
|
2020-09-05 22:35:00 +00:00
|
|
|
|
, HoldAction(..), GuideAction(..), PartialPath(..)
|
2020-09-05 00:56:59 +00:00
|
|
|
|
, currentDocument, withCurrentDocument
|
|
|
|
|
, PureDocModification(..), DocModification(..)
|
|
|
|
|
, modifyingCurrentDocument
|
2020-09-04 18:54:48 +00:00
|
|
|
|
, updateTitle
|
2020-09-02 02:52:08 +00:00
|
|
|
|
)
|
|
|
|
|
where
|
|
|
|
|
|
|
|
|
|
-- base
|
|
|
|
|
import Data.Foldable
|
2020-09-04 18:54:48 +00:00
|
|
|
|
( for_, sequenceA_ )
|
2020-09-02 02:52:08 +00:00
|
|
|
|
import Data.Word
|
|
|
|
|
( Word32 )
|
|
|
|
|
|
|
|
|
|
-- containers
|
|
|
|
|
import Data.Set
|
|
|
|
|
( Set )
|
|
|
|
|
import Data.Map.Strict
|
|
|
|
|
( Map )
|
|
|
|
|
import qualified Data.Map.Strict as Map
|
2020-09-05 00:56:59 +00:00
|
|
|
|
( insert, lookup, delete )
|
2020-09-02 02:52:08 +00:00
|
|
|
|
|
|
|
|
|
-- gi-gtk
|
|
|
|
|
import qualified GI.Gdk as GDK
|
|
|
|
|
|
|
|
|
|
-- gi-gtk
|
|
|
|
|
import qualified GI.Gtk as GTK
|
|
|
|
|
|
2020-09-05 00:56:59 +00:00
|
|
|
|
-- lens
|
|
|
|
|
import Control.Lens.Fold
|
|
|
|
|
( Fold, forOf_, sequenceAOf_ )
|
|
|
|
|
|
2020-09-02 02:52:08 +00:00
|
|
|
|
-- stm
|
|
|
|
|
import Control.Concurrent.STM
|
|
|
|
|
( STM )
|
2020-09-04 18:54:48 +00:00
|
|
|
|
import qualified Control.Concurrent.STM as STM
|
|
|
|
|
( atomically )
|
2020-09-02 02:52:08 +00:00
|
|
|
|
import qualified Control.Concurrent.STM.TVar as STM
|
2020-09-05 00:56:59 +00:00
|
|
|
|
( TVar, readTVar, readTVar, modifyTVar' )
|
2020-09-02 02:52:08 +00:00
|
|
|
|
|
2020-09-04 18:54:48 +00:00
|
|
|
|
-- text
|
|
|
|
|
import Data.Text
|
|
|
|
|
( Text )
|
|
|
|
|
|
2020-09-05 00:56:59 +00:00
|
|
|
|
-- transformers
|
|
|
|
|
import Control.Monad.Trans.Class
|
|
|
|
|
( lift )
|
|
|
|
|
import Control.Monad.Trans.Maybe
|
|
|
|
|
( MaybeT(..) )
|
|
|
|
|
|
2020-09-02 02:52:08 +00:00
|
|
|
|
-- MetaBrush
|
|
|
|
|
import Math.Vector2D
|
|
|
|
|
( Point2D )
|
2020-09-04 20:28:31 +00:00
|
|
|
|
import MetaBrush.Asset.Colours
|
|
|
|
|
( Colours )
|
2020-09-02 02:52:08 +00:00
|
|
|
|
import MetaBrush.Document
|
2020-09-04 18:54:48 +00:00
|
|
|
|
( Document(..) )
|
2020-09-02 02:52:08 +00:00
|
|
|
|
import MetaBrush.Document.Draw
|
|
|
|
|
( DrawAnchor )
|
|
|
|
|
import {-# SOURCE #-} MetaBrush.UI.FileBar
|
2020-09-05 00:56:59 +00:00
|
|
|
|
( FileBar, removeFileTab )
|
2020-09-02 02:52:08 +00:00
|
|
|
|
import {-# SOURCE #-} MetaBrush.UI.InfoBar
|
2020-09-05 00:56:59 +00:00
|
|
|
|
( InfoBar, updateInfoBar )
|
2020-09-02 02:52:08 +00:00
|
|
|
|
import MetaBrush.UI.ToolBar
|
|
|
|
|
( Tool, Mode )
|
2020-09-05 22:35:00 +00:00
|
|
|
|
import MetaBrush.UI.Viewport
|
|
|
|
|
( Viewport(..), Ruler(..) )
|
2020-09-02 02:52:08 +00:00
|
|
|
|
import MetaBrush.Unique
|
|
|
|
|
( UniqueSupply, Unique )
|
|
|
|
|
import MetaBrush.Util
|
|
|
|
|
( (>>?=) )
|
|
|
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
|
|
|
|
|
|
data UIElements
|
|
|
|
|
= UIElements
|
2020-09-05 22:35:00 +00:00
|
|
|
|
{ window :: !GTK.Window
|
|
|
|
|
, title :: !GTK.Label
|
|
|
|
|
, titleBar :: !GTK.Box
|
|
|
|
|
, fileBar :: !FileBar
|
|
|
|
|
, viewport :: !Viewport
|
|
|
|
|
, infoBar :: !InfoBar
|
|
|
|
|
, colours :: !Colours
|
2020-09-02 02:52:08 +00:00
|
|
|
|
}
|
|
|
|
|
|
|
|
|
|
data Variables
|
|
|
|
|
= Variables
|
|
|
|
|
{ uniqueSupply :: !UniqueSupply
|
|
|
|
|
, activeDocumentTVar :: !( STM.TVar ( Maybe Unique ) )
|
|
|
|
|
, openDocumentsTVar :: !( STM.TVar ( Map Unique Document ) )
|
|
|
|
|
, mousePosTVar :: !( STM.TVar ( Maybe ( Point2D Double ) ) )
|
|
|
|
|
, mouseHoldTVar :: !( STM.TVar ( Maybe HoldAction ) )
|
|
|
|
|
, modifiersTVar :: !( STM.TVar ( Set Modifier ) )
|
|
|
|
|
, toolTVar :: !( STM.TVar Tool )
|
|
|
|
|
, modeTVar :: !( STM.TVar Mode )
|
|
|
|
|
, partialPathTVar :: !( STM.TVar ( Maybe PartialPath ) )
|
2020-09-04 18:54:48 +00:00
|
|
|
|
, fileBarTabsTVar :: !( STM.TVar ( Map Unique GTK.Box ) )
|
2020-09-06 03:32:03 +00:00
|
|
|
|
, showGuidesTVar :: !( STM.TVar Bool )
|
2020-09-02 02:52:08 +00:00
|
|
|
|
}
|
|
|
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
|
|
|
|
|
|
data LR = L | R
|
|
|
|
|
deriving stock ( Show, Eq, Ord )
|
|
|
|
|
|
|
|
|
|
data Modifier
|
|
|
|
|
= Control LR
|
|
|
|
|
| Alt LR
|
|
|
|
|
| Shift LR
|
|
|
|
|
deriving stock ( Show, Eq, Ord )
|
|
|
|
|
|
|
|
|
|
modifierKey :: Word32 -> Maybe Modifier
|
|
|
|
|
modifierKey GDK.KEY_Control_L = Just ( Control L )
|
|
|
|
|
modifierKey GDK.KEY_Control_R = Just ( Control R )
|
|
|
|
|
modifierKey GDK.KEY_Shift_L = Just ( Shift L )
|
|
|
|
|
modifierKey GDK.KEY_Shift_R = Just ( Shift R )
|
|
|
|
|
modifierKey GDK.KEY_Alt_L = Just ( Alt L )
|
|
|
|
|
modifierKey GDK.KEY_Alt_R = Just ( Alt R )
|
|
|
|
|
modifierKey _ = Nothing
|
|
|
|
|
|
2020-09-02 13:58:00 +00:00
|
|
|
|
modifierType :: Modifier -> GDK.ModifierType
|
|
|
|
|
modifierType ( Control _ ) = GDK.ModifierTypeControlMask
|
|
|
|
|
modifierType ( Alt _ ) = GDK.ModifierTypeMod1Mask
|
|
|
|
|
modifierType ( Shift _ ) = GDK.ModifierTypeShiftMask
|
|
|
|
|
|
2020-09-05 22:35:00 +00:00
|
|
|
|
|
|
|
|
|
data GuideAction
|
|
|
|
|
= CreateGuide !Ruler
|
|
|
|
|
| MoveGuide !Unique
|
|
|
|
|
deriving stock Show
|
|
|
|
|
|
2020-09-02 02:52:08 +00:00
|
|
|
|
-- | Keep track of a mouse hold action:
|
|
|
|
|
--
|
|
|
|
|
-- - start a rectangular selection,
|
|
|
|
|
-- - move objects by dragging,
|
2020-09-05 22:35:00 +00:00
|
|
|
|
-- - drawing a control point,
|
|
|
|
|
-- - create/modify a guide.
|
2020-09-02 02:52:08 +00:00
|
|
|
|
data HoldAction
|
|
|
|
|
= SelectionHold { holdStartPos :: !( Point2D Double ) }
|
|
|
|
|
| DragMoveHold { holdStartPos :: !( Point2D Double ) }
|
|
|
|
|
| DrawHold { holdStartPos :: !( Point2D Double ) }
|
2020-09-05 22:35:00 +00:00
|
|
|
|
| GuideAction { holdStartPos :: !( Point2D Double )
|
|
|
|
|
, guideAction :: !GuideAction
|
|
|
|
|
}
|
2020-09-02 02:52:08 +00:00
|
|
|
|
deriving stock Show
|
|
|
|
|
|
|
|
|
|
-- | Keep track of a path that is in the middle of being drawn.
|
|
|
|
|
data PartialPath
|
|
|
|
|
= PartialPath
|
|
|
|
|
{ partialStartPos :: !( Point2D Double )
|
|
|
|
|
, partialControlPoint :: !( Maybe ( Point2D Double ) )
|
|
|
|
|
, partialPathAnchor :: !DrawAnchor
|
|
|
|
|
, firstPoint :: !Bool
|
|
|
|
|
}
|
|
|
|
|
deriving stock Show
|
|
|
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
|
|
|
|
|
|
-- | Read the currently active document from the stateful variables.
|
|
|
|
|
currentDocument :: Variables -> STM ( Maybe Document )
|
|
|
|
|
currentDocument ( Variables { activeDocumentTVar, openDocumentsTVar } )
|
|
|
|
|
= STM.readTVar activeDocumentTVar
|
|
|
|
|
>>?= ( \ unique -> Map.lookup unique <$> STM.readTVar openDocumentsTVar )
|
|
|
|
|
|
|
|
|
|
-- | Do something with the currently active document.
|
|
|
|
|
--
|
|
|
|
|
-- Does nothing if no document is currently active.
|
|
|
|
|
withCurrentDocument :: Variables -> ( Document -> STM a ) -> STM ( Maybe a )
|
|
|
|
|
withCurrentDocument vars f = traverse f =<< currentDocument vars
|
|
|
|
|
|
2020-09-05 00:56:59 +00:00
|
|
|
|
data PureDocModification
|
|
|
|
|
= Don'tModifyDoc
|
|
|
|
|
| UpdateDocTo ( Maybe Document )
|
|
|
|
|
|
|
|
|
|
data DocModification
|
|
|
|
|
= Don'tModifyDocAndThen { postModifAction :: IO () }
|
|
|
|
|
| UpdateDocToAndThen
|
|
|
|
|
{ modifDocument :: ( Maybe Document )
|
|
|
|
|
, postModifAction :: IO ()
|
|
|
|
|
}
|
|
|
|
|
|
|
|
|
|
class DocumentModification modif where
|
|
|
|
|
docFold :: Fold modif ( Maybe Document )
|
|
|
|
|
actionFold :: Fold modif ( IO () )
|
|
|
|
|
|
|
|
|
|
instance DocumentModification PureDocModification where
|
|
|
|
|
docFold _ Don'tModifyDoc = pure Don'tModifyDoc
|
|
|
|
|
docFold f ( UpdateDocTo mbDoc ) = UpdateDocTo <$> ( f mbDoc )
|
|
|
|
|
actionFold _ a = pure a
|
|
|
|
|
|
|
|
|
|
instance DocumentModification DocModification where
|
|
|
|
|
docFold _ don't@( Don'tModifyDocAndThen {} ) = pure don't
|
|
|
|
|
docFold f ( UpdateDocToAndThen mbDoc action ) = ( \ mbDoc' -> UpdateDocToAndThen mbDoc' action ) <$> f mbDoc
|
|
|
|
|
actionFold f modif = ( \ action' -> modif { postModifAction = action' } ) <$> f ( postModifAction modif )
|
|
|
|
|
|
2020-09-02 02:52:08 +00:00
|
|
|
|
-- | Modify the currently active document.
|
|
|
|
|
--
|
|
|
|
|
-- Does nothing if no document is currently active.
|
2020-09-05 00:56:59 +00:00
|
|
|
|
modifyingCurrentDocument :: DocumentModification modif => UIElements -> Variables -> ( Document -> STM modif ) -> IO ()
|
2020-09-05 22:35:00 +00:00
|
|
|
|
modifyingCurrentDocument ( UIElements { viewport = Viewport {..}, .. } ) vars@( Variables {..} ) f = do
|
2020-09-05 00:56:59 +00:00
|
|
|
|
mbAction <- STM.atomically . runMaybeT $ do
|
|
|
|
|
unique <- MaybeT ( STM.readTVar activeDocumentTVar )
|
|
|
|
|
oldDoc <- MaybeT ( Map.lookup unique <$> STM.readTVar openDocumentsTVar )
|
|
|
|
|
modif <- lift ( f oldDoc )
|
|
|
|
|
forOf_ docFold modif \case
|
|
|
|
|
Nothing
|
|
|
|
|
-> lift ( STM.modifyTVar' openDocumentsTVar ( Map.delete unique ) )
|
|
|
|
|
Just newDoc
|
|
|
|
|
-> lift ( STM.modifyTVar' openDocumentsTVar ( Map.insert unique newDoc ) )
|
|
|
|
|
mbActiveTab <- lift ( Map.lookup unique <$> STM.readTVar fileBarTabsTVar )
|
|
|
|
|
pure
|
|
|
|
|
do
|
|
|
|
|
forOf_ docFold modif \ mbNewDoc -> do
|
|
|
|
|
case mbNewDoc of
|
|
|
|
|
Nothing -> do
|
|
|
|
|
removeFileTab vars ( documentUnique oldDoc )
|
|
|
|
|
updateTitle window title Nothing
|
|
|
|
|
updateInfoBar viewportDrawingArea infoBar vars
|
|
|
|
|
Just ( Document { displayName, unsavedChanges } ) -> do
|
|
|
|
|
updateTitle window title ( Just ( displayName, unsavedChanges ) )
|
|
|
|
|
GTK.widgetQueueDraw viewportDrawingArea
|
2020-09-05 22:35:00 +00:00
|
|
|
|
for_ [ rulerCornerDrawingArea, topRulerDrawingArea, leftRulerDrawingArea ] \ drawingArea -> do
|
|
|
|
|
GTK.widgetQueueDraw drawingArea
|
2020-09-05 00:56:59 +00:00
|
|
|
|
for_ mbActiveTab GTK.widgetQueueDraw
|
|
|
|
|
sequenceAOf_ actionFold modif
|
|
|
|
|
sequenceA_ mbAction
|
2020-09-04 18:54:48 +00:00
|
|
|
|
|
|
|
|
|
updateTitle :: GTK.Window -> GTK.Label -> Maybe ( Text, Bool ) -> IO ()
|
|
|
|
|
updateTitle window title mbTitleText = do
|
|
|
|
|
GTK.labelSetText title titleText
|
|
|
|
|
GTK.setWindowTitle window titleText
|
|
|
|
|
where
|
|
|
|
|
titleText :: Text
|
|
|
|
|
titleText = case mbTitleText of
|
|
|
|
|
Nothing -> "MetaBrush"
|
|
|
|
|
Just ( name, hasUnsavedChanges )
|
|
|
|
|
| hasUnsavedChanges
|
|
|
|
|
-> "● " <> name <> " – MetaBrush"
|
|
|
|
|
| otherwise
|
|
|
|
|
-> name <> " – MetaBrush"
|