metabrush/src/metabrushes/MetaBrush/Brush.hs

138 lines
4.1 KiB
Haskell
Raw Normal View History

2023-01-09 01:54:42 +00:00
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE UndecidableInstances #-}
module MetaBrush.Brush
2023-01-08 16:16:14 +00:00
( Brush(..), SomeBrush(..), BrushFunction
, 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(..)
)
-- 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 )
-- MetaBrush
2023-01-09 03:27:08 +00:00
import Math.Linear
import Math.Linear.Dual
( Diffy )
import Math.Bezier.Spline
( SplineType(Closed), SplinePts)
import MetaBrush.Records
2023-01-08 16:16:14 +00:00
import MetaBrush.Serialisable
--------------------------------------------------------------------------------
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-09 03:27:08 +00:00
type BrushFunction brushFields = WithParams brushFields ( SplinePts Closed )
2023-01-08 16:16:14 +00:00
type Brush :: [ Symbol ] -> Type
data Brush brushFields where
BrushData
:: forall brushFields
2023-01-08 16:16:14 +00:00
. ( KnownSymbols brushFields
, Representable ( ( Length brushFields) )
2023-01-09 03:27:08 +00:00
, Diffy ( ( Length brushFields) )
2023-01-08 16:16:14 +00:00
, Typeable brushFields )
=> { brushName :: !Text
, brushFunction :: BrushFunction brushFields
}
-> Brush brushFields
data SomeBrush where
SomeBrush
2023-01-08 16:16:14 +00:00
:: { someBrush :: !( Brush brushFields ) }
-> SomeBrush
instance Show ( Brush brushFields ) where
2022-12-11 01:33:34 +00:00
show ( BrushData { brushName } ) =
"BrushData\n\
\ { brushName = " <> Text.unpack brushName <> "\n\
\ }"
2022-12-11 01:33:34 +00:00
instance NFData ( Brush brushFields ) where
2022-12-11 01:33:34 +00:00
rnf ( BrushData { brushName } )
= rnf brushName
instance Eq ( Brush brushFields ) where
2022-12-11 01:33:34 +00:00
BrushData name1 _ == BrushData name2 _ = name1 == name2
instance Ord ( Brush brushFields ) where
2022-12-11 01:33:34 +00:00
compare ( BrushData name1 _ ) ( BrushData name2 _ ) = compare name1 name2
instance Hashable ( Brush brushFields ) where
2022-12-11 01:33:34 +00:00
hashWithSalt salt ( BrushData { brushName } ) =
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 )
, NFData ( Record pointFields )
, Interpolatable ( Record pointFields )
, Representable ( ( Length pointFields ) )
)
2023-01-08 16:16:14 +00:00
=> PointFields pointFields where { }
instance ( KnownSymbols pointFields, Typeable pointFields
, Serialisable ( Record pointFields )
, Show ( Record pointFields )
, NFData ( Record pointFields )
, Interpolatable ( Record pointFields )
, Representable ( ( Length pointFields ) )
)
=> PointFields pointFields where { }
-- | Assumes the input has no duplicates (doesn't check.)
provePointFields :: [ Text ] -> ( forall pointFields. PointFields pointFields => Proxy# pointFields -> r ) -> r
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 ] )
_ -> 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