mirror of
https://gitlab.com/sheaf/metabrush.git
synced 2024-11-05 23:03:38 +00:00
use Seq for strokes
This commit is contained in:
parent
e1c5d266eb
commit
a5fdce1133
|
@ -174,6 +174,7 @@ runApplication application = do
|
||||||
testDocuments = fmap newHistory $ uniqueMapFromList
|
testDocuments = fmap newHistory $ uniqueMapFromList
|
||||||
[ emptyDocument "Test" docUnique
|
[ emptyDocument "Test" docUnique
|
||||||
& ( field' @"documentContent" . field' @"strokes" ) .~
|
& ( field' @"documentContent" . field' @"strokes" ) .~
|
||||||
|
( Seq.fromList
|
||||||
[ Stroke
|
[ Stroke
|
||||||
{ strokeName = "Stroke 1"
|
{ strokeName = "Stroke 1"
|
||||||
, strokeVisible = True
|
, strokeVisible = True
|
||||||
|
@ -190,6 +191,7 @@ runApplication application = do
|
||||||
}
|
}
|
||||||
}
|
}
|
||||||
]
|
]
|
||||||
|
)
|
||||||
]
|
]
|
||||||
where
|
where
|
||||||
mkPoint :: Point2D Double -> Double -> PointData ( Super.Rec '[ "r" SuperRecord.:= Double ] )
|
mkPoint :: Point2D Double -> Double -> PointData ( Super.Rec '[ "r" SuperRecord.:= Double ] )
|
||||||
|
|
|
@ -56,6 +56,10 @@ import Data.Map.Strict
|
||||||
( Map )
|
( Map )
|
||||||
import qualified Data.Map.Strict as Map
|
import qualified Data.Map.Strict as Map
|
||||||
( empty, insert )
|
( empty, insert )
|
||||||
|
import Data.Sequence
|
||||||
|
( Seq )
|
||||||
|
import qualified Data.Sequence as Seq
|
||||||
|
( empty )
|
||||||
|
|
||||||
-- deepseq
|
-- deepseq
|
||||||
import Control.DeepSeq
|
import Control.DeepSeq
|
||||||
|
@ -154,7 +158,7 @@ data DocumentContent
|
||||||
{ unsavedChanges :: !Bool
|
{ unsavedChanges :: !Bool
|
||||||
, latestChange :: !Text
|
, latestChange :: !Text
|
||||||
, guides :: !( Map Unique Guide )
|
, guides :: !( Map Unique Guide )
|
||||||
, strokes :: ![ Stroke ]
|
, strokes :: !( Seq Stroke )
|
||||||
}
|
}
|
||||||
deriving stock ( Show, Generic )
|
deriving stock ( Show, Generic )
|
||||||
deriving anyclass NFData
|
deriving anyclass NFData
|
||||||
|
@ -262,7 +266,7 @@ emptyDocument docName unique =
|
||||||
Content
|
Content
|
||||||
{ unsavedChanges = False
|
{ unsavedChanges = False
|
||||||
, latestChange = "New document"
|
, latestChange = "New document"
|
||||||
, strokes = []
|
, strokes = Seq.empty
|
||||||
, guides = Map.empty
|
, guides = Map.empty
|
||||||
}
|
}
|
||||||
}
|
}
|
||||||
|
|
|
@ -18,8 +18,6 @@ module MetaBrush.Document.Draw
|
||||||
-- base
|
-- base
|
||||||
import Data.Functor
|
import Data.Functor
|
||||||
( ($>) )
|
( ($>) )
|
||||||
import Data.Maybe
|
|
||||||
( listToMaybe )
|
|
||||||
|
|
||||||
-- acts
|
-- acts
|
||||||
import Data.Act
|
import Data.Act
|
||||||
|
@ -28,6 +26,8 @@ import Data.Act
|
||||||
-- containers
|
-- containers
|
||||||
import Data.Sequence
|
import Data.Sequence
|
||||||
( Seq(..) )
|
( Seq(..) )
|
||||||
|
import qualified Data.Sequence as Seq
|
||||||
|
( filter, lookup )
|
||||||
|
|
||||||
-- deepseq
|
-- deepseq
|
||||||
import Control.DeepSeq
|
import Control.DeepSeq
|
||||||
|
@ -144,7 +144,7 @@ getOrCreateDrawAnchor uniqueSupply c doc@( Document { zoomFactor } ) =
|
||||||
newDoc' :: Document
|
newDoc' :: Document
|
||||||
newDoc'
|
newDoc'
|
||||||
= over ( field' @"documentContent" . field' @"strokes" )
|
= over ( field' @"documentContent" . field' @"strokes" )
|
||||||
( newStroke : )
|
( newStroke :<| )
|
||||||
newDoc
|
newDoc
|
||||||
pure ( newDoc', AnchorAtEnd uniq, c, Nothing )
|
pure ( newDoc', AnchorAtEnd uniq, c, Nothing )
|
||||||
where
|
where
|
||||||
|
@ -244,7 +244,7 @@ withAnchorBrushData
|
||||||
)
|
)
|
||||||
-> r
|
-> r
|
||||||
withAnchorBrushData anchor ( Document { documentContent = Content { strokes } } ) f =
|
withAnchorBrushData anchor ( Document { documentContent = Content { strokes } } ) f =
|
||||||
splineAnchor . listToMaybe $ filter ( \ Stroke { strokeUnique } -> strokeUnique == anchorStrokeUnique anchor ) strokes
|
splineAnchor . Seq.lookup 0 $ Seq.filter ( \ Stroke { strokeUnique } -> strokeUnique == anchorStrokeUnique anchor ) strokes
|
||||||
where
|
where
|
||||||
splineAnchor :: Maybe Stroke -> r
|
splineAnchor :: Maybe Stroke -> r
|
||||||
splineAnchor ( Just ( Stroke { strokeSpline = strokeSpline :: StrokeSpline clo pointData, strokeBrush } ) )
|
splineAnchor ( Just ( Stroke { strokeSpline = strokeSpline :: StrokeSpline clo pointData, strokeBrush } ) )
|
||||||
|
|
|
@ -128,6 +128,8 @@ import MetaBrush.MetaParameter.Interpolation
|
||||||
( Interpolatable(Diff) )
|
( Interpolatable(Diff) )
|
||||||
import MetaBrush.Unique
|
import MetaBrush.Unique
|
||||||
( Unique )
|
( Unique )
|
||||||
|
import MetaBrush.Util
|
||||||
|
( traverseMaybe )
|
||||||
|
|
||||||
--------------------------------------------------------------------------------
|
--------------------------------------------------------------------------------
|
||||||
|
|
||||||
|
@ -504,7 +506,7 @@ deleteSelected :: Document -> ( Document, UpdateInfo )
|
||||||
deleteSelected doc =
|
deleteSelected doc =
|
||||||
( `runState` mempty ) $
|
( `runState` mempty ) $
|
||||||
( field' @"documentContent" . field' @"strokes" )
|
( field' @"documentContent" . field' @"strokes" )
|
||||||
( fmap catMaybes . traverse updateStroke )
|
( traverseMaybe updateStroke )
|
||||||
doc
|
doc
|
||||||
|
|
||||||
where
|
where
|
||||||
|
|
|
@ -714,7 +714,7 @@ decodeGuide uniqueSupply = do
|
||||||
encodeDocumentContent :: Applicative f => JSON.Encoder f DocumentContent
|
encodeDocumentContent :: Applicative f => JSON.Encoder f DocumentContent
|
||||||
encodeDocumentContent = JSON.Encoder.mapLikeObj \ ( Content { guides, strokes } ) ->
|
encodeDocumentContent = JSON.Encoder.mapLikeObj \ ( Content { guides, strokes } ) ->
|
||||||
JSON.Encoder.atKey' "guides" ( encodeUniqueMap encodeGuide ) guides
|
JSON.Encoder.atKey' "guides" ( encodeUniqueMap encodeGuide ) guides
|
||||||
. JSON.Encoder.atKey' "strokes" ( JSON.Encoder.list encodeStroke ) strokes
|
. JSON.Encoder.atKey' "strokes" ( encodeSequence encodeStroke ) strokes
|
||||||
|
|
||||||
decodeDocumentContent :: MonadIO m => UniqueSupply -> JSON.Decoder m DocumentContent
|
decodeDocumentContent :: MonadIO m => UniqueSupply -> JSON.Decoder m DocumentContent
|
||||||
decodeDocumentContent uniqueSupply = do
|
decodeDocumentContent uniqueSupply = do
|
||||||
|
@ -723,7 +723,7 @@ decodeDocumentContent uniqueSupply = do
|
||||||
unsavedChanges = False
|
unsavedChanges = False
|
||||||
latestChange :: Text
|
latestChange :: Text
|
||||||
latestChange = "Load document"
|
latestChange = "Load document"
|
||||||
strokes <- JSON.Decoder.atKey "strokes" ( JSON.Decoder.list ( decodeStroke uniqueSupply ) )
|
strokes <- JSON.Decoder.atKey "strokes" ( decodeSequence ( decodeStroke uniqueSupply ) )
|
||||||
guides <- JSON.Decoder.atKey "guides" ( decodeUniqueMap ( decodeGuide uniqueSupply ) )
|
guides <- JSON.Decoder.atKey "guides" ( decodeUniqueMap ( decodeGuide uniqueSupply ) )
|
||||||
pure ( Content { unsavedChanges, latestChange, strokes, guides } )
|
pure ( Content { unsavedChanges, latestChange, strokes, guides } )
|
||||||
|
|
||||||
|
|
|
@ -138,7 +138,7 @@ import MetaBrush.UI.ToolBar
|
||||||
import MetaBrush.Unique
|
import MetaBrush.Unique
|
||||||
( unsafeUnique )
|
( unsafeUnique )
|
||||||
import MetaBrush.Util
|
import MetaBrush.Util
|
||||||
( withRGBA )
|
( traverseMaybe, withRGBA )
|
||||||
|
|
||||||
--------------------------------------------------------------------------------
|
--------------------------------------------------------------------------------
|
||||||
|
|
||||||
|
@ -178,7 +178,7 @@ getDocumentRender
|
||||||
|
|
||||||
let
|
let
|
||||||
-- Get any modifications from in-flight user actions (e.g. in the middle of dragging something).
|
-- Get any modifications from in-flight user actions (e.g. in the middle of dragging something).
|
||||||
modifiedStrokes :: [ Stroke ]
|
modifiedStrokes :: Seq Stroke
|
||||||
modifiedStrokes = case mode of
|
modifiedStrokes = case mode of
|
||||||
PathMode
|
PathMode
|
||||||
| Just ( DragMoveHold { holdStartPos = p0, dragAction } ) <- mbHoldEvent
|
| Just ( DragMoveHold { holdStartPos = p0, dragAction } ) <- mbHoldEvent
|
||||||
|
@ -230,10 +230,10 @@ getDocumentRender
|
||||||
, strokeName = "Preview stroke (temporary)"
|
, strokeName = "Preview stroke (temporary)"
|
||||||
, strokeBrush = mbBrush
|
, strokeBrush = mbBrush
|
||||||
}
|
}
|
||||||
-> previewStroke : strokes content
|
-> previewStroke :<| strokes content
|
||||||
_ -> strokes content
|
_ -> strokes content
|
||||||
|
|
||||||
strokesRenderData <- sequenceA $ mapMaybe ( strokeRenderData fitParams ) modifiedStrokes
|
strokesRenderData <- traverseMaybe ( sequenceA . strokeRenderData fitParams ) modifiedStrokes
|
||||||
|
|
||||||
let
|
let
|
||||||
renderSelectionRect :: Cairo.Render ()
|
renderSelectionRect :: Cairo.Render ()
|
||||||
|
|
|
@ -1,6 +1,7 @@
|
||||||
{-# LANGUAGE BlockArguments #-}
|
{-# LANGUAGE BlockArguments #-}
|
||||||
{-# LANGUAGE ConstraintKinds #-}
|
{-# LANGUAGE ConstraintKinds #-}
|
||||||
{-# LANGUAGE GADTs #-}
|
{-# LANGUAGE GADTs #-}
|
||||||
|
{-# LANGUAGE LambdaCase #-}
|
||||||
{-# LANGUAGE MonoLocalBinds #-}
|
{-# LANGUAGE MonoLocalBinds #-}
|
||||||
{-# LANGUAGE ScopedTypeVariables #-}
|
{-# LANGUAGE ScopedTypeVariables #-}
|
||||||
{-# LANGUAGE TypeApplications #-}
|
{-# LANGUAGE TypeApplications #-}
|
||||||
|
@ -9,6 +10,7 @@ module MetaBrush.Util
|
||||||
( withRGBA, showRGBA
|
( withRGBA, showRGBA
|
||||||
, widgetAddClasses, widgetAddClass
|
, widgetAddClasses, widgetAddClass
|
||||||
, (>=?=>), (>>?=)
|
, (>=?=>), (>>?=)
|
||||||
|
, traverseMaybe
|
||||||
, Exists(..)
|
, Exists(..)
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
@ -23,6 +25,10 @@ import Data.Foldable
|
||||||
import GHC.Stack
|
import GHC.Stack
|
||||||
( HasCallStack )
|
( HasCallStack )
|
||||||
|
|
||||||
|
-- containers
|
||||||
|
import Data.Sequence
|
||||||
|
( Seq(..) )
|
||||||
|
|
||||||
-- gi-gdk
|
-- gi-gdk
|
||||||
import qualified GI.Gdk as GDK
|
import qualified GI.Gdk as GDK
|
||||||
|
|
||||||
|
@ -73,5 +79,11 @@ infixl 1 >>?=
|
||||||
|
|
||||||
--------------------------------------------------------------------------------
|
--------------------------------------------------------------------------------
|
||||||
|
|
||||||
|
traverseMaybe :: Applicative f => ( a -> f ( Maybe b ) ) -> Seq a -> f ( Seq b )
|
||||||
|
traverseMaybe _ Empty = pure Empty
|
||||||
|
traverseMaybe f ( a :<| as ) = ( \ case { Nothing -> id; Just b -> ( b :<| ) } ) <$> f a <*> traverseMaybe f as
|
||||||
|
|
||||||
|
--------------------------------------------------------------------------------
|
||||||
|
|
||||||
data Exists c where
|
data Exists c where
|
||||||
Exists :: c a => a -> Exists c
|
Exists :: c a => a -> Exists c
|
||||||
|
|
Loading…
Reference in a new issue