metabrush/app/Main.hs

353 lines
10 KiB
Haskell
Raw Normal View History

2020-08-20 01:57:26 +00:00
{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE NegativeLiterals #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
2020-08-05 20:23:16 +00:00
2020-08-04 06:15:06 +00:00
module Main
( main )
where
2020-08-05 20:23:16 +00:00
-- base
2020-08-06 03:06:18 +00:00
import Control.Monad
( void )
2020-08-15 21:49:14 +00:00
import Data.Foldable
( for_ )
2020-08-05 20:23:16 +00:00
import Data.Int
( Int32 )
2020-08-10 14:38:27 +00:00
import Data.Word
( Word32 )
2020-08-05 20:23:16 +00:00
import System.Exit
( exitSuccess )
2020-08-10 14:38:27 +00:00
-- containers
2020-09-01 19:56:59 +00:00
import Data.Map.Strict
( Map )
import Data.Sequence
2020-08-19 21:34:43 +00:00
( Seq(..) )
import qualified Data.Sequence as Seq
( fromList )
2020-08-10 14:38:27 +00:00
2020-08-05 20:23:16 +00:00
-- directory
import qualified System.Directory as Directory
( canonicalizePath )
2020-08-04 06:15:06 +00:00
-- gi-cairo-connector
import qualified GI.Cairo.Render.Connector as Cairo
( renderWithContext )
-- gi-gdk
import qualified GI.Gdk as GDK
-- gi-gtk
import qualified GI.Gtk as GTK
2020-08-10 14:38:27 +00:00
-- stm
import qualified Control.Concurrent.STM.TVar as STM
2020-08-15 21:49:14 +00:00
( newTVarIO, readTVarIO )
2020-08-10 14:38:27 +00:00
2020-08-05 20:23:16 +00:00
-- text
import qualified Data.Text as Text
( pack )
2020-08-04 06:15:06 +00:00
-- MetaBrush
2020-08-19 21:34:43 +00:00
import Math.Bezier.Stroke
( StrokePoint(..) )
2020-08-10 14:38:27 +00:00
import Math.Vector2D
( Point2D(..) )
import MetaBrush.Asset.Brushes
( ellipse, rect )
2020-08-05 20:23:16 +00:00
import MetaBrush.Asset.Colours
2020-08-08 03:33:35 +00:00
( getColours )
2020-08-05 20:23:16 +00:00
import MetaBrush.Asset.Logo
( drawLogo )
2020-08-10 14:38:27 +00:00
import MetaBrush.Document
2020-09-01 19:56:59 +00:00
( Document(..), Stroke(..)
2020-08-20 01:57:26 +00:00
, FocusState(..)
, PointData(..), BrushPointData(..)
2020-08-15 21:49:14 +00:00
, currentDocument
2020-08-10 14:38:27 +00:00
)
2020-08-05 20:23:16 +00:00
import MetaBrush.Event
2020-08-16 22:09:16 +00:00
( HoldEvent, PartialPath
, handleEvents
)
2020-08-15 21:49:14 +00:00
import MetaBrush.Render.Document
( renderDocument )
import MetaBrush.UI.FileBar
( createFileBar )
import MetaBrush.UI.InfoBar
( createInfoBar )
2020-08-05 20:23:16 +00:00
import MetaBrush.UI.Menu
( createMenuBar )
import MetaBrush.UI.Panels
( createPanelBar )
import MetaBrush.UI.ToolBar
2020-08-13 22:47:10 +00:00
( Tool(..), Mode(..), createToolBar )
import MetaBrush.UI.Viewport
( Viewport(..), createViewport )
2020-08-16 22:09:16 +00:00
import MetaBrush.Unique
2020-09-01 19:56:59 +00:00
( newUniqueSupply
, Unique, unsafeUnique
, uniqueMapFromList
)
import MetaBrush.Util
( widgetAddClass, widgetAddClasses )
2020-08-05 20:23:16 +00:00
import qualified Paths_MetaBrush as Cabal
2020-08-04 06:15:06 +00:00
( getDataFileName )
--------------------------------------------------------------------------------
2020-09-01 19:56:59 +00:00
testDocuments :: Map Unique Document
testDocuments = uniqueMapFromList
[ Document
{ displayName = "Closed"
, mbFilePath = Nothing
, unsavedChanges = False
, viewportCenter = Point2D 50 50
, zoomFactor = 1
, documentUnique = unsafeUnique 0
, strokes = [ Stroke
{ strokeName = "Ellipse"
, strokeVisible = True
, strokeUnique = unsafeUnique 10
, strokePoints = ellipse 150 100 ( PointData Normal ( rect 30 6 $ BrushPointData Normal ) )
}
]
}
, Document
{ displayName = "Line"
, mbFilePath = Nothing
, unsavedChanges = True
, viewportCenter = Point2D 0 0
, zoomFactor = 1
, documentUnique = unsafeUnique 1
, strokes = [ Stroke
{ strokeName = "Line"
, strokeVisible = True
, strokeUnique = unsafeUnique 11
, strokePoints = linePts
}
]
}
, Document
{ displayName = "Short line"
, mbFilePath = Nothing
, unsavedChanges = False
, viewportCenter = Point2D 0 0
, zoomFactor = 1
, documentUnique = unsafeUnique 2
, strokes = [ Stroke
{ strokeName = "ShortLine"
, strokeVisible = True
, strokeUnique = unsafeUnique 12
, strokePoints = linePts2
}
]
}
]
where
linePts :: Seq ( StrokePoint PointData )
linePts = Seq.fromList
[ PathPoint ( Point2D 0 -100 ) ( PointData Normal ( ellipse 30 8 $ BrushPointData Normal ) )
, ControlPoint ( Point2D 0 -30 ) ( PointData Normal ( ellipse 25 6 $ BrushPointData Normal ) )
, ControlPoint ( Point2D 0 30 ) ( PointData Normal ( ellipse 15 6 $ BrushPointData Normal ) )
, PathPoint ( Point2D 0 100 ) ( PointData Normal ( ellipse 15 6 $ BrushPointData Normal ) )
, ControlPoint ( Point2D 0 150 ) ( PointData Normal ( ellipse 15 6 $ BrushPointData Normal ) )
, ControlPoint ( Point2D 0 200 ) ( PointData Normal ( ellipse 15 6 $ BrushPointData Normal ) )
, PathPoint ( Point2D 0 250 ) ( PointData Normal ( ellipse 10 1 $ BrushPointData Normal ) )
]
linePts2 :: Seq ( StrokePoint PointData )
linePts2 = Seq.fromList
[ PathPoint ( Point2D 0 -100 ) ( PointData Normal ( ellipse 20 8 $ BrushPointData Normal ) )
--, ControlPoint ( Point2D 0 0 ) ( PointData Normal ( ellipse 140 8 $ BrushPointData Normal ) )
, PathPoint ( Point2D 0 100 ) ( PointData Normal ( ellipse 20 8 $ BrushPointData Normal ) )
]
2020-08-10 14:38:27 +00:00
--------------------------------------------------------------------------------
2020-08-04 06:15:06 +00:00
main :: IO ()
main = do
2020-08-10 14:38:27 +00:00
---------------------------------------------------------
-- Initialise state
2020-08-16 22:09:16 +00:00
uniqueSupply <- newUniqueSupply
2020-09-01 19:56:59 +00:00
activeDocumentTVar <- STM.newTVarIO @( Maybe Unique ) Nothing
openDocumentsTVar <- STM.newTVarIO @( Map Unique Document ) testDocuments
2020-08-15 21:49:14 +00:00
mousePosTVar <- STM.newTVarIO @( Maybe ( Point2D Double ) ) Nothing
mouseHoldTVar <- STM.newTVarIO @( Maybe HoldEvent ) Nothing
pressedKeysTVar <- STM.newTVarIO @[ Word32 ] []
toolTVar <- STM.newTVarIO @Tool Selection
modeTVar <- STM.newTVarIO @Mode Path
2020-08-16 22:09:16 +00:00
partialPathTVar <- STM.newTVarIO @( Maybe PartialPath ) Nothing
2020-08-10 14:38:27 +00:00
2020-08-04 06:15:06 +00:00
---------------------------------------------------------
-- Initialise GTK
2020-08-06 03:06:18 +00:00
void $ GTK.init Nothing
2020-08-04 06:15:06 +00:00
Just screen <- GDK.screenGetDefault
2020-08-05 20:23:16 +00:00
themePath <- Text.pack <$> ( Directory.canonicalizePath =<< Cabal.getDataFileName "theme.css" )
2020-08-04 06:15:06 +00:00
cssProvider <- GTK.cssProviderNew
GTK.cssProviderLoadFromPath cssProvider themePath
GTK.styleContextAddProviderForScreen screen cssProvider 1000
window <- GTK.windowNew GTK.WindowTypeToplevel
windowWidgetPath <- GTK.widgetGetPath window
widgetAddClass window "window"
GTK.setWindowResizable window True
2020-08-10 14:38:27 +00:00
GTK.setWindowDecorated window False
2020-08-04 06:15:06 +00:00
GTK.setWindowTitle window "MetaBrush"
GTK.windowSetDefaultSize window 800 600
GTK.widgetAddEvents window
[ GDK.EventMaskKeyPressMask, GDK.EventMaskKeyReleaseMask ]
2020-08-04 06:15:06 +00:00
let
baseMinWidth, baseMinHeight :: Int32
2020-08-05 20:23:16 +00:00
baseMinWidth = 480
2020-08-04 06:15:06 +00:00
baseMinHeight = 240
windowGeometry <- GDK.newZeroGeometry
GDK.setGeometryMinWidth windowGeometry baseMinWidth
GDK.setGeometryMinHeight windowGeometry baseMinHeight
GTK.windowSetGeometryHints window ( Nothing @GTK.Widget )
( Just windowGeometry )
[ GDK.WindowHintsMinSize ]
2020-08-07 19:39:24 +00:00
iconPath <- Directory.canonicalizePath =<< Cabal.getDataFileName "icon.png"
GTK.windowSetIconFromFile window iconPath
2020-08-07 22:41:08 +00:00
colours <- getColours windowWidgetPath
2020-08-05 20:23:16 +00:00
2020-08-04 06:15:06 +00:00
---------------------------------------------------------
-- Create base UI elements
baseOverlay <- GTK.overlayNew
2020-08-05 20:23:16 +00:00
GTK.setContainerChild window baseOverlay
2020-08-04 06:15:06 +00:00
uiGrid <- GTK.gridNew
2020-08-05 20:23:16 +00:00
GTK.setContainerChild baseOverlay uiGrid
2020-08-04 06:15:06 +00:00
2020-08-08 13:53:06 +00:00
logo <- GTK.boxNew GTK.OrientationVertical 0
titleBar <- GTK.boxNew GTK.OrientationHorizontal 0
toolBar <- GTK.boxNew GTK.OrientationVertical 0
mainPane <- GTK.panedNew GTK.OrientationHorizontal
panelBox <- GTK.boxNew GTK.OrientationVertical 0
2020-08-04 06:15:06 +00:00
GTK.gridAttach uiGrid logo 0 0 1 2
2020-08-07 19:39:24 +00:00
GTK.gridAttach uiGrid titleBar 1 0 2 1
GTK.gridAttach uiGrid toolBar 0 2 2 1
GTK.gridAttach uiGrid mainPane 2 2 1 1
2020-08-05 21:30:36 +00:00
mainView <- GTK.boxNew GTK.OrientationVertical 0
2020-08-08 13:53:06 +00:00
GTK.panedPack1 mainPane mainView True False
GTK.panedPack2 mainPane panelBox False False
2020-08-05 21:30:36 +00:00
2020-08-06 00:45:20 +00:00
viewportGrid <- GTK.gridNew
infoBar <- GTK.boxNew GTK.OrientationHorizontal 0
2020-08-05 20:23:16 +00:00
---------------------------------------------------------
-- Background
widgetAddClass uiGrid "bg"
---------------------------------------------------------
2020-08-08 03:33:35 +00:00
-- Title bar
widgetAddClass titleBar "titleBar"
--------
2020-08-05 20:23:16 +00:00
-- Logo
widgetAddClass logo "logo"
logoArea <- GTK.drawingAreaNew
GTK.boxPackStart logo logoArea True True 0
2020-08-06 03:06:18 +00:00
void $ GTK.onWidgetDraw logoArea
2020-08-07 22:41:08 +00:00
$ Cairo.renderWithContext ( drawLogo colours )
2020-08-05 20:23:16 +00:00
2020-08-08 03:33:35 +00:00
------------
-- Menu bar
2020-08-05 20:23:16 +00:00
_ <- createMenuBar colours window titleBar
2020-08-07 19:39:24 +00:00
------------
-- Title
2020-08-07 19:39:24 +00:00
title <- GTK.labelNew ( Just "MetaBrush" )
widgetAddClasses title [ "text", "title", "plain" ]
GTK.boxSetCenterWidget titleBar ( Just title )
2020-08-07 19:39:24 +00:00
---------------------------------------------------------
-- Main viewport
2020-08-07 19:39:24 +00:00
2020-08-15 21:49:14 +00:00
Viewport { viewportDrawingArea } <- createViewport viewportGrid
-----------------
-- Viewport rendering
void $ GTK.onWidgetDraw viewportDrawingArea \ ctx -> do
-- Get the relevant document information
mbDoc <- currentDocument activeDocumentTVar openDocumentsTVar
for_ mbDoc \ doc -> do
2020-08-16 22:09:16 +00:00
mbMousePos <- STM.readTVarIO mousePosTVar
mbHoldEvent <- STM.readTVarIO mouseHoldTVar
mbPartialPath <- STM.readTVarIO partialPathTVar
2020-08-20 01:57:26 +00:00
mode <- STM.readTVarIO modeTVar
2020-08-15 21:49:14 +00:00
viewportWidth <- GTK.widgetGetAllocatedWidth viewportDrawingArea
viewportHeight <- GTK.widgetGetAllocatedHeight viewportDrawingArea
( `Cairo.renderWithContext` ctx ) $
2020-08-16 22:09:16 +00:00
renderDocument
2020-08-20 01:57:26 +00:00
colours mode ( viewportWidth, viewportHeight )
2020-08-16 22:09:16 +00:00
mbMousePos mbHoldEvent mbPartialPath
doc
2020-08-15 21:49:14 +00:00
pure True
2020-08-07 19:39:24 +00:00
2020-08-20 01:57:26 +00:00
---------------------------------------------------------
-- Tool bar
_ <- createToolBar toolTVar modeTVar colours viewportDrawingArea toolBar
---------------------------------------------------------
-- Info bar
2020-08-07 19:39:24 +00:00
infoBarElements <- createInfoBar colours infoBar
2020-08-06 03:06:18 +00:00
2020-08-10 14:38:27 +00:00
---------------------------------------------------------
-- File bar
2020-09-01 19:56:59 +00:00
fileBar <-
createFileBar
2020-09-01 19:56:59 +00:00
uniqueSupply activeDocumentTVar openDocumentsTVar
window title viewportDrawingArea infoBarElements
GTK.boxPackStart mainView fileBar False False 0
GTK.boxPackStart mainView viewportGrid True True 0
GTK.boxPackStart mainView infoBar False False 0
2020-08-10 14:38:27 +00:00
2020-08-05 20:23:16 +00:00
---------------------------------------------------------
-- Panels
createPanelBar panelBox
2020-08-05 20:23:16 +00:00
---------------------------------------------------------
2020-08-04 06:15:06 +00:00
-- Actions
handleEvents
2020-08-16 22:09:16 +00:00
uniqueSupply
2020-08-13 22:47:10 +00:00
activeDocumentTVar openDocumentsTVar
mousePosTVar mouseHoldTVar pressedKeysTVar
2020-08-16 22:09:16 +00:00
toolTVar modeTVar partialPathTVar
window viewportDrawingArea infoBarElements
2020-08-07 19:39:24 +00:00
2020-08-05 20:23:16 +00:00
---------------------------------------------------------
-- GTK main loop
2020-08-04 06:15:06 +00:00
GTK.widgetShowAll window
GTK.main
2020-08-05 20:23:16 +00:00
exitSuccess