metabrush/src/metabrushes/MetaBrush/Brush.hs

180 lines
5.6 KiB
Haskell
Raw Normal View History

{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE QuantifiedConstraints #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE UndecidableInstances #-}
module MetaBrush.Brush
2023-01-13 22:10:06 +00:00
( WithParams(..)
, NamedBrush(..), SomeBrush(..), BrushFunction
2023-01-08 16:16:14 +00:00
, PointFields, provePointFields, duplicates
)
where
-- base
2023-01-08 16:16:14 +00:00
import Data.Kind
( Type, Constraint )
import Data.List
( nub )
import Data.Typeable
( Typeable )
import GHC.Exts
2023-01-08 16:16:14 +00:00
( Proxy#, proxy# )
import GHC.TypeLits
( Symbol, someSymbolVal
, SomeSymbol(..)
)
2024-08-28 23:46:50 +00:00
import GHC.TypeNats
( Nat )
-- deepseq
import Control.DeepSeq
2022-12-11 01:33:34 +00:00
( NFData(..) )
-- hashable
import Data.Hashable
( Hashable(..) )
-- text
import Data.Text
( Text )
import qualified Data.Text as Text
( unpack )
-- brush-strokes
import Calligraphy.Brushes
( Brush(..) )
2023-01-20 15:34:04 +00:00
import Math.Differentiable
( DiffInterp )
import Math.Interval
( 𝕀 )
import Math.Linear
-- MetaBrush
2024-05-21 17:40:22 +00:00
import qualified MetaBrush.Brush.Widget as Brush
( Widget )
import MetaBrush.Records
2023-01-13 22:10:06 +00:00
( KnownSymbols, Length, Record )
2023-01-08 16:16:14 +00:00
import MetaBrush.Serialisable
( Serialisable )
--------------------------------------------------------------------------------
-- | A brush, with default parameter values.
2024-08-28 23:46:50 +00:00
type WithParams :: Nat -> Type
data WithParams nbParams =
2023-01-13 22:10:06 +00:00
WithParams
2024-08-28 23:46:50 +00:00
{ defaultParams :: nbParams
, withParams :: Brush nbParams
2023-01-13 22:10:06 +00:00
}
--------------------------------------------------------------------------------
2022-12-11 01:33:34 +00:00
-- | A brush function: a function from a record of parameters to a closed spline.
2023-01-08 16:16:14 +00:00
type BrushFunction :: [ Symbol ] -> Type
2023-01-20 15:34:04 +00:00
type BrushFunction brushFields =
2024-08-28 23:46:50 +00:00
WithParams ( Length brushFields )
type NamedBrush :: [ Symbol ] -> Type
data NamedBrush brushFields where
NamedBrush
:: forall brushFields
2024-05-21 17:40:22 +00:00
. ( KnownSymbols brushFields
2023-01-20 15:34:04 +00:00
, Representable Double ( ( Length brushFields ) )
2024-08-28 23:46:50 +00:00
, DiffInterp 2 ( Length brushFields )
, DiffInterp 3 𝕀 ( Length brushFields )
, Show ( ( Length brushFields ) )
, NFData ( ( Length brushFields ) )
2023-01-13 22:10:06 +00:00
)
2023-01-08 16:16:14 +00:00
=> { brushName :: !Text
2024-05-21 17:40:22 +00:00
, brushFunction :: !( BrushFunction brushFields )
, brushWidget :: !( Brush.Widget brushFields )
2023-01-08 16:16:14 +00:00
}
-> NamedBrush brushFields
data SomeBrush where
SomeBrush
2024-05-21 17:40:22 +00:00
:: forall brushFields
. KnownSymbols brushFields
=> { someBrush :: !( NamedBrush brushFields ) }
-> SomeBrush
instance Show ( NamedBrush brushFields ) where
2024-09-27 23:32:03 +00:00
show ( NamedBrush { brushName } ) = Text.unpack brushName
instance NFData ( NamedBrush brushFields ) where
rnf ( NamedBrush { brushName } )
2022-12-11 01:33:34 +00:00
= rnf brushName
instance Eq ( NamedBrush brushFields ) where
2024-05-21 17:40:22 +00:00
NamedBrush { brushName = name1 } == NamedBrush { brushName = name2 }
= name1 == name2
instance Ord ( NamedBrush brushFields ) where
2024-05-21 17:40:22 +00:00
compare ( NamedBrush { brushName = name1 } ) ( NamedBrush { brushName = name2 } )
= compare name1 name2
instance Hashable ( NamedBrush brushFields ) where
hashWithSalt salt ( NamedBrush { brushName } ) =
2022-12-11 01:33:34 +00:00
hashWithSalt salt brushName
2023-01-08 16:16:14 +00:00
type PointFields :: [ Symbol ] -> Constraint
class ( KnownSymbols pointFields, Typeable pointFields
, Serialisable ( Record pointFields )
, Show ( Record pointFields )
2024-08-28 23:46:50 +00:00
, Show ( ( Length pointFields ) )
2023-01-08 16:16:14 +00:00
, NFData ( Record pointFields )
2023-01-20 15:34:04 +00:00
, Representable Double ( ( Length pointFields ) )
2024-08-28 23:46:50 +00:00
, RepDim ( ( Length pointFields ) ) ~ Length pointFields
, DiffInterp 2 ( Length pointFields )
, DiffInterp 3 𝕀 ( Length pointFields )
)
2023-01-08 16:16:14 +00:00
=> PointFields pointFields where { }
instance ( KnownSymbols pointFields, Typeable pointFields
, Serialisable ( Record pointFields )
, Show ( Record pointFields )
2024-08-28 23:46:50 +00:00
, Show ( ( Length pointFields ) )
2023-01-08 16:16:14 +00:00
, NFData ( Record pointFields )
2023-01-20 15:34:04 +00:00
, Representable Double ( ( Length pointFields ) )
2024-08-28 23:46:50 +00:00
, RepDim ( ( Length pointFields ) ) ~ Length pointFields
, DiffInterp 2 ( Length pointFields )
, DiffInterp 3 𝕀 ( Length pointFields )
2023-01-08 16:16:14 +00:00
)
=> PointFields pointFields where { }
-- | Assumes the input has no duplicates (doesn't check.)
2023-01-20 15:34:04 +00:00
provePointFields :: [ Text ]
-> ( forall pointFields. PointFields pointFields => Proxy# pointFields -> r )
-> r
2023-01-08 16:16:14 +00:00
provePointFields fieldNames k =
case fieldNames of
[]
-> k ( proxy# @'[] )
[ f1 ]
| SomeSymbol @f1 _ <- someSymbolVal ( Text.unpack f1 )
-> k ( proxy# @'[ f1 ] )
[ f1, f2 ]
| SomeSymbol @f1 _ <- someSymbolVal ( Text.unpack f1 )
, SomeSymbol @f2 _ <- someSymbolVal ( Text.unpack f2 )
-> k ( proxy# @'[ f1, f2 ] )
[ f1, f2, f3 ]
| SomeSymbol @f1 _ <- someSymbolVal ( Text.unpack f1 )
, SomeSymbol @f2 _ <- someSymbolVal ( Text.unpack f2 )
, SomeSymbol @f3 _ <- someSymbolVal ( Text.unpack f3 )
-> k ( proxy# @'[ f1, f2, f3 ] )
[ f1, f2, f3, f4 ]
| SomeSymbol @f1 _ <- someSymbolVal ( Text.unpack f1 )
, SomeSymbol @f2 _ <- someSymbolVal ( Text.unpack f2 )
, SomeSymbol @f3 _ <- someSymbolVal ( Text.unpack f3 )
, SomeSymbol @f4 _ <- someSymbolVal ( Text.unpack f4 )
-> k ( proxy# @'[ f1, f2, f3, f4 ] )
2023-01-08 16:16:14 +00:00
_ -> error $ "I haven't defined " ++ show ( length fieldNames )
{-# INLINE provePointFields #-}
duplicates :: [ Text ] -> [ Text ]
duplicates = nub . duplicatesAcc [] []
where
duplicatesAcc :: [ Text ] -> [ Text ] -> [ Text ] -> [ Text ]
duplicatesAcc _ dups [] = dups
duplicatesAcc seen dups ( k : kvs )
| k `elem` seen
= duplicatesAcc seen ( k : dups ) kvs
| otherwise
= duplicatesAcc ( k : seen ) dups kvs