{-# LANGUAGE OverloadedStrings #-}
module Miso.Lynx.Element.ScrollView.Event
(
onScroll
, onScrollToUpper
, onScrollToLower
, onScrollEnd
, onContentSizeChanged
, scrollDecoder
, ScrollEvent (..)
, scrollViewEvents
) where
import qualified Data.Map as M
import Data.Aeson (withObject, (.:), (.:?), (.!=))
import Miso.Types (Attribute)
import Miso.Event
import Miso.String (MisoString)
scrollViewEvents :: Events
scrollViewEvents :: Events
scrollViewEvents
= [(MisoString, Capture)] -> Events
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList
[ (MisoString
"scroll", Capture
False)
, (MisoString
"scrolltoupper", Capture
False)
, (MisoString
"scrolltolower", Capture
False)
, (MisoString
"scrollend", Capture
False)
, (MisoString
"contentsizechanged", Capture
False)
]
scrollDecoder :: Decoder ScrollEvent
scrollDecoder :: Decoder ScrollEvent
scrollDecoder = [MisoString
"detail"] [MisoString]
-> (Value -> Parser ScrollEvent) -> Decoder ScrollEvent
forall a. [MisoString] -> (Value -> Parser a) -> Decoder a
`at` do
String
-> (Object -> Parser ScrollEvent) -> Value -> Parser ScrollEvent
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"ScrollEvent" ((Object -> Parser ScrollEvent) -> Value -> Parser ScrollEvent)
-> (Object -> Parser ScrollEvent) -> Value -> Parser ScrollEvent
forall a b. (a -> b) -> a -> b
$ \Object
o ->
MisoString
-> Double
-> Double
-> Double
-> Double
-> Double
-> Double
-> ScrollEvent
ScrollEvent
(MisoString
-> Double
-> Double
-> Double
-> Double
-> Double
-> Double
-> ScrollEvent)
-> Parser MisoString
-> Parser
(Double
-> Double -> Double -> Double -> Double -> Double -> ScrollEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser MisoString
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type"
Parser
(Double
-> Double -> Double -> Double -> Double -> Double -> ScrollEvent)
-> Parser Double
-> Parser
(Double -> Double -> Double -> Double -> Double -> ScrollEvent)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Double)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"deltaX" Parser (Maybe Double) -> Double -> Parser Double
forall a. Parser (Maybe a) -> a -> Parser a
.!= Double
0
Parser
(Double -> Double -> Double -> Double -> Double -> ScrollEvent)
-> Parser Double
-> Parser (Double -> Double -> Double -> Double -> ScrollEvent)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Double)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"deltaY" Parser (Maybe Double) -> Double -> Parser Double
forall a. Parser (Maybe a) -> a -> Parser a
.!= Double
0
Parser (Double -> Double -> Double -> Double -> ScrollEvent)
-> Parser Double
-> Parser (Double -> Double -> Double -> ScrollEvent)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Double)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"scrollLeft" Parser (Maybe Double) -> Double -> Parser Double
forall a. Parser (Maybe a) -> a -> Parser a
.!= Double
0
Parser (Double -> Double -> Double -> ScrollEvent)
-> Parser Double -> Parser (Double -> Double -> ScrollEvent)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Double)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"scrollTop" Parser (Maybe Double) -> Double -> Parser Double
forall a. Parser (Maybe a) -> a -> Parser a
.!= Double
0
Parser (Double -> Double -> ScrollEvent)
-> Parser Double -> Parser (Double -> ScrollEvent)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Double)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"scrollHeight" Parser (Maybe Double) -> Double -> Parser Double
forall a. Parser (Maybe a) -> a -> Parser a
.!= Double
0
Parser (Double -> ScrollEvent)
-> Parser Double -> Parser ScrollEvent
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Double)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"scrollWidth" Parser (Maybe Double) -> Double -> Parser Double
forall a. Parser (Maybe a) -> a -> Parser a
.!= Double
0
data ScrollEvent
= ScrollEvent
{ ScrollEvent -> MisoString
scrollType :: MisoString
, ScrollEvent -> Double
deltaX, ScrollEvent -> Double
deltaY :: Double
, ScrollEvent -> Double
scrollLeft, ScrollEvent -> Double
scrollTop, ScrollEvent -> Double
scrollHeight, ScrollEvent -> Double
scrollWidth :: Double
} deriving (Int -> ScrollEvent -> ShowS
[ScrollEvent] -> ShowS
ScrollEvent -> String
(Int -> ScrollEvent -> ShowS)
-> (ScrollEvent -> String)
-> ([ScrollEvent] -> ShowS)
-> Show ScrollEvent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ScrollEvent -> ShowS
showsPrec :: Int -> ScrollEvent -> ShowS
$cshow :: ScrollEvent -> String
show :: ScrollEvent -> String
$cshowList :: [ScrollEvent] -> ShowS
showList :: [ScrollEvent] -> ShowS
Show, ScrollEvent -> ScrollEvent -> Capture
(ScrollEvent -> ScrollEvent -> Capture)
-> (ScrollEvent -> ScrollEvent -> Capture) -> Eq ScrollEvent
forall a. (a -> a -> Capture) -> (a -> a -> Capture) -> Eq a
$c== :: ScrollEvent -> ScrollEvent -> Capture
== :: ScrollEvent -> ScrollEvent -> Capture
$c/= :: ScrollEvent -> ScrollEvent -> Capture
/= :: ScrollEvent -> ScrollEvent -> Capture
Eq)
onScroll :: (ScrollEvent -> action) -> Attribute action
onScroll :: forall action. (ScrollEvent -> action) -> Attribute action
onScroll ScrollEvent -> action
action = MisoString
-> Decoder ScrollEvent
-> (ScrollEvent -> DOMRef -> action)
-> Attribute action
forall r action.
MisoString
-> Decoder r -> (r -> DOMRef -> action) -> Attribute action
on MisoString
"scroll" Decoder ScrollEvent
scrollDecoder (\ScrollEvent
x DOMRef
_ -> ScrollEvent -> action
action ScrollEvent
x)
onScrollToUpper :: (ScrollEvent -> action) -> Attribute action
onScrollToUpper :: forall action. (ScrollEvent -> action) -> Attribute action
onScrollToUpper ScrollEvent -> action
action = MisoString
-> Decoder ScrollEvent
-> (ScrollEvent -> DOMRef -> action)
-> Attribute action
forall r action.
MisoString
-> Decoder r -> (r -> DOMRef -> action) -> Attribute action
on MisoString
"scrolltoupper" Decoder ScrollEvent
scrollDecoder (\ScrollEvent
x DOMRef
_ -> ScrollEvent -> action
action ScrollEvent
x)
onScrollToLower :: (ScrollEvent -> action) -> Attribute action
onScrollToLower :: forall action. (ScrollEvent -> action) -> Attribute action
onScrollToLower ScrollEvent -> action
action = MisoString
-> Decoder ScrollEvent
-> (ScrollEvent -> DOMRef -> action)
-> Attribute action
forall r action.
MisoString
-> Decoder r -> (r -> DOMRef -> action) -> Attribute action
on MisoString
"scrolltolower" Decoder ScrollEvent
scrollDecoder (\ScrollEvent
x DOMRef
_ -> ScrollEvent -> action
action ScrollEvent
x)
onScrollEnd :: (ScrollEvent -> action) -> Attribute action
onScrollEnd :: forall action. (ScrollEvent -> action) -> Attribute action
onScrollEnd ScrollEvent -> action
action = MisoString
-> Decoder ScrollEvent
-> (ScrollEvent -> DOMRef -> action)
-> Attribute action
forall r action.
MisoString
-> Decoder r -> (r -> DOMRef -> action) -> Attribute action
on MisoString
"scrollend" Decoder ScrollEvent
scrollDecoder (\ScrollEvent
x DOMRef
_ -> ScrollEvent -> action
action ScrollEvent
x)
onContentSizeChanged :: (ScrollEvent -> action) -> Attribute action
onContentSizeChanged :: forall action. (ScrollEvent -> action) -> Attribute action
onContentSizeChanged ScrollEvent -> action
action = MisoString
-> Decoder ScrollEvent
-> (ScrollEvent -> DOMRef -> action)
-> Attribute action
forall r action.
MisoString
-> Decoder r -> (r -> DOMRef -> action) -> Attribute action
on MisoString
"contentsizechanged" Decoder ScrollEvent
scrollDecoder (\ScrollEvent
x DOMRef
_ -> ScrollEvent -> action
action ScrollEvent
x)