{-# LANGUAGE
OverloadedStrings
, FlexibleInstances
, GeneralizedNewtypeDeriving
#-}
module Clay.Background
(
Background (background)
, backgroundColor
, BackgroundPosition
, backgroundPosition
, backgroundPositions
, placed
, positioned
, BackgroundSize
, backgroundSize
, backgroundSizes
, contain, cover
, by
, BackgroundRepeat
, backgroundRepeat
, backgroundRepeats
, repeat, space, round, noRepeat
, xyRepeat
, repeatX, repeatY
, BackgroundOrigin
, backgroundOrigin
, backgroundOrigins
, origin
, BackgroundClip
, backgroundClip
, backgroundClips
, boxClip
, BackgroundAttachment
, backgroundAttachment
, backgroundAttachments
, attachFixed, attachScroll
, BackgroundImage
, backgroundImage
, backgroundImages
, url
, Side
, sideTop
, sideLeft
, sideRight
, sideBottom
, sideCenter
, sideMiddle
, Direction
, straight
, angular
, Location
, Loc
, Val
, location
)
where
import Data.Text (Text)
import Data.Monoid
import Prelude hiding (repeat, round)
import Clay.Box
import Clay.Color
import Clay.Common
import Clay.Property
import Clay.Stylesheet
import Clay.Size
class Val a => Background a where
background :: a -> Css
background = Key a -> a -> Css
forall a. Val a => Key a -> a -> Css
key Key a
"background"
instance Background a => Background [a]
instance (Background a, Background b) => Background (a, b)
instance Background Color
instance Background BackgroundPosition
instance Background BackgroundSize
instance Background BackgroundRepeat
instance Background BackgroundOrigin
instance Background BackgroundClip
instance Background BackgroundAttachment
instance Background BackgroundImage
backgroundColor :: Color -> Css
backgroundColor :: Color -> Css
backgroundColor = Key Color -> Color -> Css
forall a. Val a => Key a -> a -> Css
key Key Color
"background-color"
newtype BackgroundPosition = BackgroundPosition Value
deriving (BackgroundPosition -> Value
(BackgroundPosition -> Value) -> Val BackgroundPosition
forall a. (a -> Value) -> Val a
value :: BackgroundPosition -> Value
$cvalue :: BackgroundPosition -> Value
Val, Value -> BackgroundPosition
(Value -> BackgroundPosition) -> Other BackgroundPosition
forall a. (Value -> a) -> Other a
other :: Value -> BackgroundPosition
$cother :: Value -> BackgroundPosition
Other, BackgroundPosition
BackgroundPosition -> Inherit BackgroundPosition
forall a. a -> Inherit a
inherit :: BackgroundPosition
$cinherit :: BackgroundPosition
Inherit)
placed :: Side -> Side -> BackgroundPosition
placed :: Side -> Side -> BackgroundPosition
placed Side
a Side
b = Value -> BackgroundPosition
BackgroundPosition ((Side, Side) -> Value
forall a. Val a => a -> Value
value (Side
a, Side
b))
positioned :: Size a -> Size a -> BackgroundPosition
positioned :: Size a -> Size a -> BackgroundPosition
positioned Size a
a Size a
b = Value -> BackgroundPosition
BackgroundPosition ((Size a, Size a) -> Value
forall a. Val a => a -> Value
value (Size a
a, Size a
b))
backgroundPosition :: BackgroundPosition -> Css
backgroundPosition :: BackgroundPosition -> Css
backgroundPosition = Key BackgroundPosition -> BackgroundPosition -> Css
forall a. Val a => Key a -> a -> Css
key Key BackgroundPosition
"background-position"
backgroundPositions :: [BackgroundPosition] -> Css
backgroundPositions :: [BackgroundPosition] -> Css
backgroundPositions = Key [BackgroundPosition] -> [BackgroundPosition] -> Css
forall a. Val a => Key a -> a -> Css
key Key [BackgroundPosition]
"background-position"
newtype BackgroundSize = BackgroundSize Value
deriving (BackgroundSize -> Value
(BackgroundSize -> Value) -> Val BackgroundSize
forall a. (a -> Value) -> Val a
value :: BackgroundSize -> Value
$cvalue :: BackgroundSize -> Value
Val, Value -> BackgroundSize
(Value -> BackgroundSize) -> Other BackgroundSize
forall a. (Value -> a) -> Other a
other :: Value -> BackgroundSize
$cother :: Value -> BackgroundSize
Other, BackgroundSize
BackgroundSize -> Inherit BackgroundSize
forall a. a -> Inherit a
inherit :: BackgroundSize
$cinherit :: BackgroundSize
Inherit)
instance Auto BackgroundSize where auto :: BackgroundSize
auto = Size Any
forall a. Auto a => a
auto Size Any -> Size Any -> BackgroundSize
forall a b. Size a -> Size b -> BackgroundSize
`by` Size Any
forall a. Auto a => a
auto
contain, cover :: BackgroundSize
contain :: BackgroundSize
contain = Value -> BackgroundSize
BackgroundSize Value
"contain"
cover :: BackgroundSize
cover = Value -> BackgroundSize
BackgroundSize Value
"cover"
by :: Size a -> Size b -> BackgroundSize
by :: Size a -> Size b -> BackgroundSize
by Size a
a Size b
b = Value -> BackgroundSize
BackgroundSize ((Size a, Size b) -> Value
forall a. Val a => a -> Value
value (Size a
a, Size b
b))
backgroundSize :: BackgroundSize -> Css
backgroundSize :: BackgroundSize -> Css
backgroundSize = Key BackgroundSize -> BackgroundSize -> Css
forall a. Val a => Key a -> a -> Css
key Key BackgroundSize
"background-size"
backgroundSizes :: [BackgroundSize] -> Css
backgroundSizes :: [BackgroundSize] -> Css
backgroundSizes = Key [BackgroundSize] -> [BackgroundSize] -> Css
forall a. Val a => Key a -> a -> Css
key Key [BackgroundSize]
"background-size"
newtype BackgroundRepeat = BackgroundRepeat Value
deriving (BackgroundRepeat -> Value
(BackgroundRepeat -> Value) -> Val BackgroundRepeat
forall a. (a -> Value) -> Val a
value :: BackgroundRepeat -> Value
$cvalue :: BackgroundRepeat -> Value
Val, Value -> BackgroundRepeat
(Value -> BackgroundRepeat) -> Other BackgroundRepeat
forall a. (Value -> a) -> Other a
other :: Value -> BackgroundRepeat
$cother :: Value -> BackgroundRepeat
Other, BackgroundRepeat
BackgroundRepeat -> Inherit BackgroundRepeat
forall a. a -> Inherit a
inherit :: BackgroundRepeat
$cinherit :: BackgroundRepeat
Inherit, BackgroundRepeat
BackgroundRepeat -> None BackgroundRepeat
forall a. a -> None a
none :: BackgroundRepeat
$cnone :: BackgroundRepeat
None)
repeat, space, round, noRepeat :: BackgroundRepeat
repeat :: BackgroundRepeat
repeat = Value -> BackgroundRepeat
BackgroundRepeat Value
"repeat"
space :: BackgroundRepeat
space = Value -> BackgroundRepeat
BackgroundRepeat Value
"space"
round :: BackgroundRepeat
round = Value -> BackgroundRepeat
BackgroundRepeat Value
"round"
noRepeat :: BackgroundRepeat
noRepeat = Value -> BackgroundRepeat
BackgroundRepeat Value
"no-repeat"
xyRepeat :: BackgroundRepeat -> BackgroundRepeat -> BackgroundRepeat
xyRepeat :: BackgroundRepeat -> BackgroundRepeat -> BackgroundRepeat
xyRepeat BackgroundRepeat
a BackgroundRepeat
b = Value -> BackgroundRepeat
BackgroundRepeat ((BackgroundRepeat, BackgroundRepeat) -> Value
forall a. Val a => a -> Value
value (BackgroundRepeat
a, BackgroundRepeat
b))
repeatX, repeatY :: BackgroundRepeat
repeatX :: BackgroundRepeat
repeatX = BackgroundRepeat -> BackgroundRepeat -> BackgroundRepeat
xyRepeat BackgroundRepeat
repeat BackgroundRepeat
noRepeat
repeatY :: BackgroundRepeat
repeatY = BackgroundRepeat -> BackgroundRepeat -> BackgroundRepeat
xyRepeat BackgroundRepeat
noRepeat BackgroundRepeat
repeat
backgroundRepeat :: BackgroundRepeat -> Css
backgroundRepeat :: BackgroundRepeat -> Css
backgroundRepeat = Key BackgroundRepeat -> BackgroundRepeat -> Css
forall a. Val a => Key a -> a -> Css
key Key BackgroundRepeat
"background-repeat"
backgroundRepeats :: [BackgroundRepeat] -> Css
backgroundRepeats :: [BackgroundRepeat] -> Css
backgroundRepeats = Key [BackgroundRepeat] -> [BackgroundRepeat] -> Css
forall a. Val a => Key a -> a -> Css
key Key [BackgroundRepeat]
"background-repeat"
newtype BackgroundImage = BackgroundImage Value
deriving (BackgroundImage -> Value
(BackgroundImage -> Value) -> Val BackgroundImage
forall a. (a -> Value) -> Val a
value :: BackgroundImage -> Value
$cvalue :: BackgroundImage -> Value
Val, Value -> BackgroundImage
(Value -> BackgroundImage) -> Other BackgroundImage
forall a. (Value -> a) -> Other a
other :: Value -> BackgroundImage
$cother :: Value -> BackgroundImage
Other, BackgroundImage
BackgroundImage -> Inherit BackgroundImage
forall a. a -> Inherit a
inherit :: BackgroundImage
$cinherit :: BackgroundImage
Inherit, BackgroundImage
BackgroundImage -> None BackgroundImage
forall a. a -> None a
none :: BackgroundImage
$cnone :: BackgroundImage
None)
url :: Text -> BackgroundImage
url :: Text -> BackgroundImage
url Text
u = Value -> BackgroundImage
BackgroundImage (Text -> Value
forall a. Val a => a -> Value
value (Text
"url(\"" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
u Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\")"))
backgroundImage :: BackgroundImage -> Css
backgroundImage :: BackgroundImage -> Css
backgroundImage = Key BackgroundImage -> BackgroundImage -> Css
forall a. Val a => Key a -> a -> Css
key Key BackgroundImage
"background-image"
backgroundImages :: [BackgroundImage] -> Css
backgroundImages :: [BackgroundImage] -> Css
backgroundImages = Key [BackgroundImage] -> [BackgroundImage] -> Css
forall a. Val a => Key a -> a -> Css
key Key [BackgroundImage]
"background-image"
newtype BackgroundOrigin = BackgroundOrigin Value
deriving (BackgroundOrigin -> Value
(BackgroundOrigin -> Value) -> Val BackgroundOrigin
forall a. (a -> Value) -> Val a
value :: BackgroundOrigin -> Value
$cvalue :: BackgroundOrigin -> Value
Val, Value -> BackgroundOrigin
(Value -> BackgroundOrigin) -> Other BackgroundOrigin
forall a. (Value -> a) -> Other a
other :: Value -> BackgroundOrigin
$cother :: Value -> BackgroundOrigin
Other, BackgroundOrigin
BackgroundOrigin -> Inherit BackgroundOrigin
forall a. a -> Inherit a
inherit :: BackgroundOrigin
$cinherit :: BackgroundOrigin
Inherit)
origin :: BoxType -> BackgroundOrigin
origin :: BoxType -> BackgroundOrigin
origin BoxType
b = Value -> BackgroundOrigin
BackgroundOrigin (BoxType -> Value
forall a. Val a => a -> Value
value BoxType
b)
backgroundOrigin :: BackgroundOrigin -> Css
backgroundOrigin :: BackgroundOrigin -> Css
backgroundOrigin = Key BackgroundOrigin -> BackgroundOrigin -> Css
forall a. Val a => Key a -> a -> Css
key Key BackgroundOrigin
"background-origin"
backgroundOrigins :: [BackgroundOrigin] -> Css
backgroundOrigins :: [BackgroundOrigin] -> Css
backgroundOrigins = Key [BackgroundOrigin] -> [BackgroundOrigin] -> Css
forall a. Val a => Key a -> a -> Css
key Key [BackgroundOrigin]
"background-origin"
newtype BackgroundClip = BackgroundClip Value
deriving (BackgroundClip -> Value
(BackgroundClip -> Value) -> Val BackgroundClip
forall a. (a -> Value) -> Val a
value :: BackgroundClip -> Value
$cvalue :: BackgroundClip -> Value
Val, Value -> BackgroundClip
(Value -> BackgroundClip) -> Other BackgroundClip
forall a. (Value -> a) -> Other a
other :: Value -> BackgroundClip
$cother :: Value -> BackgroundClip
Other, BackgroundClip
BackgroundClip -> Inherit BackgroundClip
forall a. a -> Inherit a
inherit :: BackgroundClip
$cinherit :: BackgroundClip
Inherit)
boxClip :: BoxType -> BackgroundClip
boxClip :: BoxType -> BackgroundClip
boxClip BoxType
b = Value -> BackgroundClip
BackgroundClip (BoxType -> Value
forall a. Val a => a -> Value
value BoxType
b)
backgroundClip :: BackgroundClip -> Css
backgroundClip :: BackgroundClip -> Css
backgroundClip = Key BackgroundClip -> BackgroundClip -> Css
forall a. Val a => Key a -> a -> Css
key Key BackgroundClip
"background-clip"
backgroundClips :: [BackgroundClip] -> Css
backgroundClips :: [BackgroundClip] -> Css
backgroundClips = Key [BackgroundClip] -> [BackgroundClip] -> Css
forall a. Val a => Key a -> a -> Css
key Key [BackgroundClip]
"background-clip"
newtype BackgroundAttachment = BackgroundAttachment Value
deriving (Value -> BackgroundAttachment
(Value -> BackgroundAttachment) -> Other BackgroundAttachment
forall a. (Value -> a) -> Other a
other :: Value -> BackgroundAttachment
$cother :: Value -> BackgroundAttachment
Other, BackgroundAttachment -> Value
(BackgroundAttachment -> Value) -> Val BackgroundAttachment
forall a. (a -> Value) -> Val a
value :: BackgroundAttachment -> Value
$cvalue :: BackgroundAttachment -> Value
Val, BackgroundAttachment
BackgroundAttachment -> Inherit BackgroundAttachment
forall a. a -> Inherit a
inherit :: BackgroundAttachment
$cinherit :: BackgroundAttachment
Inherit)
attachFixed, attachScroll :: BackgroundAttachment
attachFixed :: BackgroundAttachment
attachFixed = Value -> BackgroundAttachment
BackgroundAttachment Value
"fixed"
attachScroll :: BackgroundAttachment
attachScroll = Value -> BackgroundAttachment
BackgroundAttachment Value
"scroll"
backgroundAttachment :: BackgroundAttachment -> Css
backgroundAttachment :: BackgroundAttachment -> Css
backgroundAttachment = Key BackgroundAttachment -> BackgroundAttachment -> Css
forall a. Val a => Key a -> a -> Css
key Key BackgroundAttachment
"background-attachment"
backgroundAttachments :: [BackgroundAttachment] -> Css
backgroundAttachments :: [BackgroundAttachment] -> Css
backgroundAttachments = Key [BackgroundAttachment] -> [BackgroundAttachment] -> Css
forall a. Val a => Key a -> a -> Css
key Key [BackgroundAttachment]
"background-attachment"
newtype Side = Side Value
deriving (Side -> Value
(Side -> Value) -> Val Side
forall a. (a -> Value) -> Val a
value :: Side -> Value
$cvalue :: Side -> Value
Val, Value -> Side
(Value -> Side) -> Other Side
forall a. (Value -> a) -> Other a
other :: Value -> Side
$cother :: Value -> Side
Other, Side
Side -> Inherit Side
forall a. a -> Inherit a
inherit :: Side
$cinherit :: Side
Inherit)
sideTop, sideLeft, sideRight, sideBottom, sideCenter, sideMiddle :: Side
sideTop :: Side
sideTop = Value -> Side
Side Value
"top"
sideLeft :: Side
sideLeft = Value -> Side
Side Value
"left"
sideRight :: Side
sideRight = Value -> Side
Side Value
"right"
sideBottom :: Side
sideBottom = Value -> Side
Side Value
"bottom"
sideCenter :: Side
sideCenter = Value -> Side
Side Value
"center"
sideMiddle :: Side
sideMiddle = Value -> Side
Side Value
"middle"
newtype Direction = Direction Value
deriving (Direction -> Value
(Direction -> Value) -> Val Direction
forall a. (a -> Value) -> Val a
value :: Direction -> Value
$cvalue :: Direction -> Value
Val, Value -> Direction
(Value -> Direction) -> Other Direction
forall a. (Value -> a) -> Other a
other :: Value -> Direction
$cother :: Value -> Direction
Other)
straight :: Side -> Direction
straight :: Side -> Direction
straight Side
a = Value -> Direction
Direction (Side -> Value
forall a. Val a => a -> Value
value Side
a)
angular :: Angle a -> Direction
angular :: Angle a -> Direction
angular Angle a
a = Value -> Direction
Direction (Angle a -> Value
forall a. Val a => a -> Value
value Angle a
a)
newtype Location = Location Value
deriving (Location -> Value
(Location -> Value) -> Val Location
forall a. (a -> Value) -> Val a
value :: Location -> Value
$cvalue :: Location -> Value
Val, Value -> Location
(Value -> Location) -> Other Location
forall a. (Value -> a) -> Other a
other :: Value -> Location
$cother :: Value -> Location
Other)
class Val a => Loc a where
location :: a -> Location
location = Value -> Location
Location (Value -> Location) -> (a -> Value) -> a -> Location
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Value
forall a. Val a => a -> Value
value
instance Loc Side
instance Loc (Size a)
instance (Loc a, Loc b) => Loc (a, b)