metabrush/src/metabrushes/MetaBrush/Document.hs

442 lines
13 KiB
Haskell
Raw Normal View History

2023-01-09 01:54:42 +00:00
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE UndecidableInstances #-}
2021-02-24 21:45:08 +00:00
module MetaBrush.Document
( AABB(..), mkAABB
2020-09-10 16:43:42 +00:00
, Document(..), DocumentContent(..)
, emptyDocument
2021-04-26 15:18:48 +00:00
, Stroke(..), StrokeHierarchy(..), visibleStrokes
, StrokeSpline, _strokeSpline, overStrokeSpline
2020-11-12 17:34:46 +00:00
, PointData(..), BrushPointData(..), DiffPointData(..)
, FocusState(..), Hoverable(..), HoverContext(..)
, Guide(..), Ruler(..)
2020-11-12 17:34:46 +00:00
, _selection, _coords, coords
, addGuide, selectedGuide
)
where
2020-08-04 06:15:06 +00:00
2020-09-01 19:56:59 +00:00
-- base
2021-02-24 21:45:08 +00:00
import Control.Monad.ST
( RealWorld )
2020-11-12 17:34:46 +00:00
import Data.Coerce
( coerce )
import Data.Functor.Identity
( Identity(..) )
import Data.Semigroup
( Arg(..), Min(..), ArgMin )
2023-01-08 16:16:14 +00:00
import Data.Typeable
( Typeable )
2020-09-01 19:56:59 +00:00
import GHC.Generics
2020-11-12 17:34:46 +00:00
( Generic, Generic1 )
2023-01-08 16:16:14 +00:00
import GHC.TypeLits
( Symbol )
2020-09-01 19:56:59 +00:00
-- acts
import Data.Act
2020-11-12 17:34:46 +00:00
( Act(..), Torsor(..) )
-- containers
import Data.Map.Strict
( Map )
import qualified Data.Map.Strict as Map
2020-11-12 17:34:46 +00:00
( empty, insert )
2021-04-26 12:34:34 +00:00
import Data.Sequence
2021-04-26 15:18:48 +00:00
( Seq(..) )
2021-04-26 12:34:34 +00:00
import qualified Data.Sequence as Seq
2021-04-26 15:18:48 +00:00
( empty, singleton )
2020-09-10 16:43:42 +00:00
-- deepseq
import Control.DeepSeq
2020-11-12 17:34:46 +00:00
( NFData(..), NFData1, deepseq )
2020-09-10 16:43:42 +00:00
2020-08-19 21:34:43 +00:00
-- generic-lens
import Data.Generics.Product.Fields
( field' )
2020-11-12 17:34:46 +00:00
-- groups
import Data.Group
( Group(..) )
2020-08-19 21:34:43 +00:00
-- lens
import Control.Lens
2020-11-12 17:34:46 +00:00
( Lens'
, set, view, over
)
2020-08-19 21:34:43 +00:00
-- stm
import Control.Concurrent.STM
( STM )
2020-08-10 14:38:27 +00:00
-- text
import Data.Text
( Text )
2020-11-12 17:34:46 +00:00
-- transformers
import Control.Monad.Trans.Reader
( ReaderT, runReaderT )
2020-08-10 14:38:27 +00:00
-- MetaBrush
2020-11-12 17:34:46 +00:00
import Math.Bezier.Spline
( Spline(..), KnownSplineType )
2020-08-19 21:34:43 +00:00
import Math.Bezier.Stroke
2020-11-12 17:34:46 +00:00
( CachedStroke )
import Math.Module
2020-11-12 17:34:46 +00:00
( Module
( origin, (^+^), (^-^), (*^) )
, Inner((^.^))
, squaredNorm, quadrance
)
2023-01-08 16:16:14 +00:00
import Math.Linear
( Point2D(..), Vector2D(..) )
import MetaBrush.Brush
2023-01-08 16:16:14 +00:00
( Brush, PointFields )
import MetaBrush.Records
2020-08-16 22:09:16 +00:00
import MetaBrush.Unique
( UniqueSupply, Unique, freshUnique )
2020-08-10 14:38:27 +00:00
2020-08-04 06:15:06 +00:00
--------------------------------------------------------------------------------
2020-08-10 14:38:27 +00:00
data AABB
= AABB
{ topLeft, botRight :: !( Point2D Double ) }
2020-09-10 16:43:42 +00:00
deriving stock ( Show, Generic )
deriving anyclass NFData
2020-08-10 14:38:27 +00:00
mkAABB :: Point2D Double -> Point2D Double -> AABB
mkAABB ( Point2D x1 y1 ) ( Point2D x2 y2 ) = AABB ( Point2D xmin ymin ) ( Point2D xmax ymax )
where
( xmin, xmax )
| x1 > x2 = ( x2, x1 )
| otherwise = ( x1, x2 )
( ymin, ymax )
| y1 > y2 = ( y2, y1 )
| otherwise = ( y1, y2 )
2020-09-10 16:43:42 +00:00
-- | Document, together with some extra metadata.
2020-08-04 06:15:06 +00:00
data Document
= Document
2020-09-10 16:43:42 +00:00
{ displayName :: !Text
, mbFilePath :: !( Maybe FilePath )
, viewportCenter :: !( Point2D Double )
, zoomFactor :: !Double
, documentUnique :: Unique
, documentContent :: !DocumentContent
}
deriving stock ( Show, Generic )
deriving anyclass NFData
2020-11-12 17:34:46 +00:00
-- | Main content of document (data which we kept track of throughout history).
2020-09-10 16:43:42 +00:00
data DocumentContent
= Content
{ unsavedChanges :: !Bool
, latestChange :: !Text
, guides :: !( Map Unique Guide )
2021-04-26 15:18:48 +00:00
, strokes :: !( Seq StrokeHierarchy )
2020-09-10 16:43:42 +00:00
}
deriving stock ( Show, Generic )
deriving anyclass NFData
2020-08-10 14:38:27 +00:00
2021-04-26 15:18:48 +00:00
-- | Hierarchy for groups of strokes.
data StrokeHierarchy
= StrokeGroup
2021-04-26 15:18:48 +00:00
{ groupName :: !Text
, groupVisible :: !Bool
, groupContents :: !( Seq StrokeHierarchy )
}
| StrokeLeaf
{ strokeLeaf :: !Stroke }
deriving stock ( Show, Generic )
deriving anyclass NFData
visibleStrokes :: StrokeHierarchy -> Seq Stroke
visibleStrokes ( StrokeGroup { groupVisible, groupContents } )
| groupVisible
= foldMap visibleStrokes groupContents
| otherwise
= Empty
visibleStrokes ( StrokeLeaf { strokeLeaf } )
| strokeVisible strokeLeaf
= Seq.singleton strokeLeaf
| otherwise
= Empty
2021-02-25 00:08:13 +00:00
type StrokeSpline clo brushParams =
Spline clo ( CachedStroke RealWorld ) ( PointData brushParams )
2020-11-12 17:34:46 +00:00
data Stroke where
Stroke
2023-01-08 16:16:14 +00:00
:: forall clo pointParams ( pointFields :: [ Symbol ] ) ( brushFields :: [ Symbol ] )
. ( KnownSplineType clo
, pointParams ~ Record pointFields
, PointFields pointFields, Typeable pointFields
2020-11-12 17:34:46 +00:00
)
=>
{ strokeName :: !Text
, strokeVisible :: !Bool
, strokeUnique :: Unique
, strokeBrush :: !( Maybe ( Brush brushFields ) )
, strokeSpline :: !( StrokeSpline clo pointParams )
2020-11-12 17:34:46 +00:00
}
-> Stroke
deriving stock instance Show Stroke
instance NFData Stroke where
2021-04-25 23:17:27 +00:00
rnf ( Stroke { strokeName, strokeVisible, strokeUnique, strokeBrush, strokeSpline } )
2020-11-12 17:34:46 +00:00
= deepseq strokeSpline
2021-04-25 23:17:27 +00:00
. deepseq strokeBrush
2020-11-12 17:34:46 +00:00
. deepseq strokeUnique
. deepseq strokeVisible
$ rnf strokeName
_strokeSpline
:: forall f
. Functor f
2023-01-08 16:16:14 +00:00
=> ( forall clo pointParams ( pointFields :: [ Symbol ] )
2020-11-12 17:34:46 +00:00
. ( KnownSplineType clo
2023-01-08 16:16:14 +00:00
, pointParams ~ Record pointFields
, PointFields pointFields
2020-11-12 17:34:46 +00:00
)
=> StrokeSpline clo pointParams
-> f ( StrokeSpline clo pointParams )
)
-> Stroke -> f Stroke
_strokeSpline f ( Stroke { strokeSpline = oldStrokeSpline, .. } )
= ( \ newSpline -> Stroke { strokeSpline = newSpline, .. } ) <$> f oldStrokeSpline
overStrokeSpline
2023-01-08 16:16:14 +00:00
:: ( forall clo pointParams ( pointFields :: [ Symbol ] )
2020-11-12 17:34:46 +00:00
. ( KnownSplineType clo
2023-01-08 16:16:14 +00:00
, pointParams ~ Record pointFields
, PointFields pointFields
2020-11-12 17:34:46 +00:00
)
=> StrokeSpline clo pointParams
-> StrokeSpline clo pointParams
)
-> Stroke -> Stroke
overStrokeSpline f = coerce ( _strokeSpline @Identity ( coerce . f ) )
data PointData params
2020-08-19 21:34:43 +00:00
= PointData
2020-11-12 17:34:46 +00:00
{ pointCoords :: !( Point2D Double )
, pointState :: FocusState
, brushParams :: !params
2020-08-13 17:05:19 +00:00
}
deriving stock ( Show, Generic )
2020-09-10 16:43:42 +00:00
deriving anyclass NFData
2022-02-13 16:30:54 +00:00
instance Act (Vector2D Double) (PointData params) where
v ( dat@( PointData { pointCoords = p } ) ) =
dat { pointCoords = v p }
2020-08-20 01:57:26 +00:00
data BrushPointData
= BrushPointData
{ brushPointState :: FocusState }
deriving stock ( Show, Generic )
2020-09-10 16:43:42 +00:00
deriving anyclass NFData
2020-08-20 01:57:26 +00:00
2020-08-13 17:05:19 +00:00
data FocusState
= Normal
| Hover
| Selected
2020-09-10 16:43:42 +00:00
deriving stock ( Show, Eq, Generic )
deriving anyclass NFData
instance Semigroup FocusState where
Selected <> _ = Selected
Normal <> s = s
_ <> Selected = Selected
s <> Normal = s
_ <> _ = Hover
instance Monoid FocusState where
mempty = Normal
2020-09-01 19:56:59 +00:00
emptyDocument :: Text -> Unique -> Document
emptyDocument docName unique =
Document
2020-09-10 16:43:42 +00:00
{ displayName = docName
, mbFilePath = Nothing
, viewportCenter = Point2D 0 0
, zoomFactor = 1
, documentUnique = unique
, documentContent =
Content
{ unsavedChanges = False
, latestChange = "New document"
2021-04-26 12:34:34 +00:00
, strokes = Seq.empty
2020-09-10 16:43:42 +00:00
, guides = Map.empty
}
2020-09-01 19:56:59 +00:00
}
--------------------------------------------------------------------------------
data HoverContext
= MouseHover !( Point2D Double )
| RectangleHover !AABB
2020-09-10 16:43:42 +00:00
deriving stock ( Show, Generic )
deriving anyclass NFData
instance Act ( Vector2D Double ) HoverContext where
v MouseHover p = MouseHover ( v p )
v RectangleHover ( AABB p1 p2 ) = RectangleHover ( AABB ( v p1 ) ( v p2 ) )
instance Act ( Vector2D Double ) ( Maybe HoverContext ) where
() v = fmap ( v )
class Hoverable a where
hovered :: Maybe HoverContext -> Double -> a -> FocusState
instance Hoverable ( Point2D Double ) where
hovered Nothing _ _ = Normal
hovered ( Just ( MouseHover p ) ) zoom q
| quadrance @( Vector2D Double ) p q * zoom ^ ( 2 :: Int ) < 16
= Hover
| otherwise
= Normal
hovered ( Just ( RectangleHover ( AABB ( Point2D x1 y1 ) ( Point2D x2 y2 ) ) ) ) _ ( Point2D x y )
| x >= x1 && x <= x2 && y >= y1 && y <= y2
= Hover
| otherwise
= Normal
2020-11-12 17:34:46 +00:00
class HasSelection pt where
_selection :: Lens' pt FocusState
instance HasSelection ( PointData brushParams ) where
_selection = field' @"pointState"
instance HasSelection BrushPointData where
_selection = field' @"brushPointState"
_coords :: Lens' ( PointData brushParams ) ( Point2D Double )
_coords = field' @"pointCoords"
coords :: PointData brushParams -> Point2D Double
coords = view _coords
data FocusDifference
= DifferentFocus
| SameFocus
deriving stock ( Show, Generic )
deriving anyclass NFData
instance Semigroup FocusDifference where
SameFocus <> SameFocus = SameFocus
_ <> _ = DifferentFocus
instance Monoid FocusDifference where
mempty = SameFocus
instance Group FocusDifference where
invert = id
data DiffPointData diffBrushParams
= DiffPointData
{ diffVector :: !( Vector2D Double )
, diffParams :: !diffBrushParams
, diffState :: !FocusDifference
}
deriving stock ( Show, Generic, Generic1, Functor, Foldable, Traversable )
deriving anyclass ( NFData, NFData1 )
instance Module Double diffBrushParams => Semigroup ( DiffPointData diffBrushParams ) where
DiffPointData v1 p1 s1 <> DiffPointData v2 p2 s2 =
DiffPointData ( v1 <> v2 ) ( p1 ^+^ p2 ) ( s1 <> s2 )
instance Module Double diffBrushParams => Monoid ( DiffPointData diffBrushParams ) where
mempty = DiffPointData mempty origin mempty
instance Module Double diffBrushParams => Group ( DiffPointData diffBrushParams ) where
invert ( DiffPointData v1 p1 s1 ) =
2023-01-08 16:16:14 +00:00
DiffPointData ( invert v1 ) ( -1 *^ p1 ) ( invert s1 )
2020-11-12 17:34:46 +00:00
instance ( Module Double diffBrushParams, Act diffBrushParams brushParams )
=> Act ( DiffPointData diffBrushParams ) ( PointData brushParams ) where
() ( DiffPointData { diffVector = dp, diffParams = db, diffState = focusDiff } )
= over _coords ( dp )
. over ( field' @"brushParams" ) ( db )
. ( case focusDiff of { SameFocus -> id; DifferentFocus -> set ( field' @"pointState" ) Normal } )
instance ( Module Double diffBrushParams, Torsor diffBrushParams brushParams )
=> Torsor ( DiffPointData diffBrushParams ) ( PointData brushParams ) where
( PointData { pointCoords = p1, brushParams = b1, pointState = s1 } ) <-- ( PointData { pointCoords = p2, brushParams = b2, pointState = s2 } ) =
DiffPointData
{ diffVector = p1 <-- p2
, diffParams = b1 <-- b2
, diffState = if s1 == s2 then SameFocus else DifferentFocus
}
instance Module Double brushParams => Module Double ( DiffPointData brushParams ) where
origin = mempty
(^+^) = (<>)
x ^-^ y = x <> invert y
d *^ DiffPointData v1 p1 s1 = DiffPointData ( d *^ v1 ) ( d *^ p1 ) s1
--------------------------------------------------------------------------------
-- Guides.
data Guide
= Guide
{ guidePoint :: !( Point2D Double ) -- ^ point on the guide line
, guideNormal :: !( Vector2D Double ) -- ^ /normalised/ normal vector of the guide
, guideFocus :: !FocusState
, guideUnique :: Unique
}
2020-09-10 16:43:42 +00:00
deriving stock ( Show, Generic )
deriving anyclass NFData
data Ruler
= RulerCorner
| LeftRuler
| TopRuler
deriving stock Show
-- | Try to select a guide at the given document coordinates.
selectedGuide :: Point2D Double -> Document -> Maybe Guide
2020-09-10 16:43:42 +00:00
selectedGuide c ( Document { zoomFactor, documentContent = Content { guides } } ) =
\case { Min ( Arg _ g ) -> g } <$> foldMap ( selectGuide_maybe c zoomFactor ) guides
selectGuide_maybe :: Point2D Double -> Double -> Guide -> Maybe ( ArgMin Double Guide )
selectGuide_maybe c zoom guide@( Guide { guidePoint = p, guideNormal = n } )
| sqDist * zoom ^ ( 2 :: Int ) < 4
= Just ( Min ( Arg sqDist guide ) )
| otherwise
= Nothing
where
t :: Double
t = ( c --> p ) ^.^ n
sqDist :: Double
sqDist = t ^ ( 2 :: Int ) / squaredNorm n
-- | Add new guide after a mouse drag from a ruler area.
addGuide :: UniqueSupply -> Ruler -> Point2D Double -> Document -> STM Document
2020-11-12 17:34:46 +00:00
addGuide uniqueSupply ruler p doc = ( `runReaderT` uniqueSupply ) $ ( field' @"documentContent" . field' @"guides" ) insertNewGuides doc
where
2020-11-12 17:34:46 +00:00
insertNewGuides :: Map Unique Guide -> ReaderT UniqueSupply STM ( Map Unique Guide )
insertNewGuides gs = case ruler of
RulerCorner
-> do
2020-11-12 17:34:46 +00:00
uniq1 <- freshUnique
uniq2 <- freshUnique
let
guide1, guide2 :: Guide
guide1 = Guide { guidePoint = p, guideNormal = Vector2D 0 1, guideFocus = Normal, guideUnique = uniq1 }
guide2 = Guide { guidePoint = p, guideNormal = Vector2D 1 0, guideFocus = Normal, guideUnique = uniq2 }
pure ( Map.insert uniq2 guide2 . Map.insert uniq1 guide1 $ gs )
TopRuler
-> do
2020-11-12 17:34:46 +00:00
uniq1 <- freshUnique
let
guide1 :: Guide
guide1 = Guide { guidePoint = p, guideNormal = Vector2D 0 1, guideFocus = Normal, guideUnique = uniq1 }
pure ( Map.insert uniq1 guide1 gs )
LeftRuler
-> do
2020-11-12 17:34:46 +00:00
uniq2 <- freshUnique
let
guide2 :: Guide
guide2 = Guide { guidePoint = p, guideNormal = Vector2D 1 0, guideFocus = Normal, guideUnique = uniq2 }
pure ( Map.insert uniq2 guide2 gs )
instance Hoverable Guide where
hovered ( Just ( MouseHover c ) ) zoom guide
| Just _ <- selectGuide_maybe c zoom guide
= Hover
| otherwise
= Normal
hovered _ _ _ = Normal