{-# LANGUAGE
    OverloadedStrings
  , FlexibleInstances
  , GeneralizedNewtypeDeriving
  #-}
module Clay.Mask
(
  Mask (mask)
, MaskComposite
, clear, copy
, sourceOver, sourceIn, sourceOut, sourceAtop
, destinationOver, destinationIn, destinationOut, destinationAtop
, xor
, maskComposite
, maskComposites
, maskPosition
, maskPositions
, maskSize
, maskSizes
, maskRepeat
, maskRepeats
, maskOrigin
, maskOrigins
, maskClip
, maskClips
, maskAttachment
, maskAttachments
, maskImage
, maskImages
)
where
import Clay.Background
import Clay.Common
import Clay.Property
import Clay.Stylesheet
pkey :: Val a => Prefixed -> a -> Css
pkey :: Prefixed -> a -> Css
pkey Prefixed
k = Prefixed -> a -> Css
forall a. Val a => Prefixed -> a -> Css
prefixed (Prefixed
browsers Prefixed -> Prefixed -> Prefixed
forall a. Semigroup a => a -> a -> a
<> Prefixed
k)
class Val a => Mask a where
  mask :: a -> Css
  mask = Prefixed -> a -> Css
forall a. Val a => Prefixed -> a -> Css
pkey Prefixed
"mask"
instance Mask a => Mask [a]
instance (Mask a, Mask b) => Mask (a, b)
instance Mask MaskComposite
instance Mask BackgroundPosition
instance Mask BackgroundSize
instance Mask BackgroundRepeat
instance Mask BackgroundOrigin
instance Mask BackgroundClip
instance Mask BackgroundAttachment
instance Mask BackgroundImage
newtype MaskComposite = MaskComposite Value
  deriving (MaskComposite -> Value
(MaskComposite -> Value) -> Val MaskComposite
forall a. (a -> Value) -> Val a
value :: MaskComposite -> Value
$cvalue :: MaskComposite -> Value
Val, Value -> MaskComposite
(Value -> MaskComposite) -> Other MaskComposite
forall a. (Value -> a) -> Other a
other :: Value -> MaskComposite
$cother :: Value -> MaskComposite
Other, MaskComposite
MaskComposite -> Inherit MaskComposite
forall a. a -> Inherit a
inherit :: MaskComposite
$cinherit :: MaskComposite
Inherit, MaskComposite
MaskComposite -> None MaskComposite
forall a. a -> None a
none :: MaskComposite
$cnone :: MaskComposite
None)
clear, copy
  , sourceOver, sourceIn, sourceOut, sourceAtop
  , destinationOver, destinationIn, destinationOut, destinationAtop
  , xor :: MaskComposite
clear :: MaskComposite
clear                = Value -> MaskComposite
forall a. Other a => Value -> a
other Value
"clear"
copy :: MaskComposite
copy                 = Value -> MaskComposite
forall a. Other a => Value -> a
other Value
"copy"
sourceOver :: MaskComposite
sourceOver           = Value -> MaskComposite
forall a. Other a => Value -> a
other Value
"source-over"
sourceIn :: MaskComposite
sourceIn             = Value -> MaskComposite
forall a. Other a => Value -> a
other Value
"source-in"
sourceOut :: MaskComposite
sourceOut            = Value -> MaskComposite
forall a. Other a => Value -> a
other Value
"source-out"
sourceAtop :: MaskComposite
sourceAtop           = Value -> MaskComposite
forall a. Other a => Value -> a
other Value
"source-atop"
destinationOver :: MaskComposite
destinationOver      = Value -> MaskComposite
forall a. Other a => Value -> a
other Value
"destination-over"
destinationIn :: MaskComposite
destinationIn        = Value -> MaskComposite
forall a. Other a => Value -> a
other Value
"destination-in"
destinationOut :: MaskComposite
destinationOut       = Value -> MaskComposite
forall a. Other a => Value -> a
other Value
"destination-out"
destinationAtop :: MaskComposite
destinationAtop      = Value -> MaskComposite
forall a. Other a => Value -> a
other Value
"destination-atop"
xor :: MaskComposite
xor                  = Value -> MaskComposite
forall a. Other a => Value -> a
other Value
"xor"
maskComposite :: MaskComposite -> Css
maskComposite :: MaskComposite -> Css
maskComposite = Prefixed -> MaskComposite -> Css
forall a. Val a => Prefixed -> a -> Css
pkey Prefixed
"mask-composite"
maskComposites :: [MaskComposite] -> Css
maskComposites :: [MaskComposite] -> Css
maskComposites = Prefixed -> [MaskComposite] -> Css
forall a. Val a => Prefixed -> a -> Css
pkey Prefixed
"mask-composite"
maskPosition :: BackgroundPosition -> Css
maskPosition :: BackgroundPosition -> Css
maskPosition = Prefixed -> BackgroundPosition -> Css
forall a. Val a => Prefixed -> a -> Css
pkey Prefixed
"mask-position"
maskPositions :: [BackgroundPosition] -> Css
maskPositions :: [BackgroundPosition] -> Css
maskPositions = Prefixed -> [BackgroundPosition] -> Css
forall a. Val a => Prefixed -> a -> Css
pkey Prefixed
"mask-position"
maskSize :: BackgroundSize -> Css
maskSize :: BackgroundSize -> Css
maskSize = Prefixed -> BackgroundSize -> Css
forall a. Val a => Prefixed -> a -> Css
pkey Prefixed
"mask-size"
maskSizes :: [BackgroundSize] -> Css
maskSizes :: [BackgroundSize] -> Css
maskSizes = Prefixed -> [BackgroundSize] -> Css
forall a. Val a => Prefixed -> a -> Css
pkey Prefixed
"mask-size"
maskRepeat :: BackgroundRepeat -> Css
maskRepeat :: BackgroundRepeat -> Css
maskRepeat = Prefixed -> BackgroundRepeat -> Css
forall a. Val a => Prefixed -> a -> Css
pkey Prefixed
"mask-repeat"
maskRepeats :: [BackgroundRepeat] -> Css
maskRepeats :: [BackgroundRepeat] -> Css
maskRepeats = Prefixed -> [BackgroundRepeat] -> Css
forall a. Val a => Prefixed -> a -> Css
pkey Prefixed
"mask-repeat"
maskImage :: BackgroundImage -> Css
maskImage :: BackgroundImage -> Css
maskImage = Prefixed -> BackgroundImage -> Css
forall a. Val a => Prefixed -> a -> Css
pkey Prefixed
"mask-image"
maskImages :: [BackgroundImage] -> Css
maskImages :: [BackgroundImage] -> Css
maskImages = Prefixed -> [BackgroundImage] -> Css
forall a. Val a => Prefixed -> a -> Css
pkey Prefixed
"mask-image"
maskOrigin :: BackgroundOrigin -> Css
maskOrigin :: BackgroundOrigin -> Css
maskOrigin = Prefixed -> BackgroundOrigin -> Css
forall a. Val a => Prefixed -> a -> Css
pkey Prefixed
"mask-origin"
maskOrigins :: [BackgroundOrigin] -> Css
maskOrigins :: [BackgroundOrigin] -> Css
maskOrigins = Prefixed -> [BackgroundOrigin] -> Css
forall a. Val a => Prefixed -> a -> Css
pkey Prefixed
"mask-origin"
maskClip :: BackgroundClip -> Css
maskClip :: BackgroundClip -> Css
maskClip = Prefixed -> BackgroundClip -> Css
forall a. Val a => Prefixed -> a -> Css
pkey Prefixed
"mask-clip"
maskClips :: [BackgroundClip] -> Css
maskClips :: [BackgroundClip] -> Css
maskClips = Prefixed -> [BackgroundClip] -> Css
forall a. Val a => Prefixed -> a -> Css
pkey Prefixed
"mask-clip"
maskAttachment :: BackgroundAttachment -> Css
maskAttachment :: BackgroundAttachment -> Css
maskAttachment = Prefixed -> BackgroundAttachment -> Css
forall a. Val a => Prefixed -> a -> Css
pkey Prefixed
"mask-attachment"
maskAttachments :: [BackgroundAttachment] -> Css
maskAttachments :: [BackgroundAttachment] -> Css
maskAttachments = Prefixed -> [BackgroundAttachment] -> Css
forall a. Val a => Prefixed -> a -> Css
pkey Prefixed
"mask-attachment"