module Ribosome.Data.WindowView where
import Ribosome.Host.Class.Msgpack.Decode (MsgpackDecode)
import Ribosome.Host.Class.Msgpack.Encode (MsgpackEncode)
data WindowView =
WindowView {
WindowView -> Int
lnum :: Int,
WindowView -> Int
topline :: Int
}
deriving stock (WindowView -> WindowView -> Bool
(WindowView -> WindowView -> Bool)
-> (WindowView -> WindowView -> Bool) -> Eq WindowView
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WindowView -> WindowView -> Bool
$c/= :: WindowView -> WindowView -> Bool
== :: WindowView -> WindowView -> Bool
$c== :: WindowView -> WindowView -> Bool
Eq, Int -> WindowView -> ShowS
[WindowView] -> ShowS
WindowView -> String
(Int -> WindowView -> ShowS)
-> (WindowView -> String)
-> ([WindowView] -> ShowS)
-> Show WindowView
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WindowView] -> ShowS
$cshowList :: [WindowView] -> ShowS
show :: WindowView -> String
$cshow :: WindowView -> String
showsPrec :: Int -> WindowView -> ShowS
$cshowsPrec :: Int -> WindowView -> ShowS
Show, (forall x. WindowView -> Rep WindowView x)
-> (forall x. Rep WindowView x -> WindowView) -> Generic WindowView
forall x. Rep WindowView x -> WindowView
forall x. WindowView -> Rep WindowView x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep WindowView x -> WindowView
$cfrom :: forall x. WindowView -> Rep WindowView x
Generic)
deriving anyclass (WindowView -> Object
(WindowView -> Object) -> MsgpackEncode WindowView
forall a. (a -> Object) -> MsgpackEncode a
toMsgpack :: WindowView -> Object
$ctoMsgpack :: WindowView -> Object
MsgpackEncode, Object -> Either DecodeError WindowView
(Object -> Either DecodeError WindowView)
-> MsgpackDecode WindowView
forall a. (Object -> Either DecodeError a) -> MsgpackDecode a
fromMsgpack :: Object -> Either DecodeError WindowView
$cfromMsgpack :: Object -> Either DecodeError WindowView
MsgpackDecode)
data PartialWindowView =
PartialWindowView {
PartialWindowView -> Maybe Int
lnum :: Maybe Int,
PartialWindowView -> Maybe Int
topline :: Maybe Int
}
deriving stock (PartialWindowView -> PartialWindowView -> Bool
(PartialWindowView -> PartialWindowView -> Bool)
-> (PartialWindowView -> PartialWindowView -> Bool)
-> Eq PartialWindowView
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PartialWindowView -> PartialWindowView -> Bool
$c/= :: PartialWindowView -> PartialWindowView -> Bool
== :: PartialWindowView -> PartialWindowView -> Bool
$c== :: PartialWindowView -> PartialWindowView -> Bool
Eq, Int -> PartialWindowView -> ShowS
[PartialWindowView] -> ShowS
PartialWindowView -> String
(Int -> PartialWindowView -> ShowS)
-> (PartialWindowView -> String)
-> ([PartialWindowView] -> ShowS)
-> Show PartialWindowView
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PartialWindowView] -> ShowS
$cshowList :: [PartialWindowView] -> ShowS
show :: PartialWindowView -> String
$cshow :: PartialWindowView -> String
showsPrec :: Int -> PartialWindowView -> ShowS
$cshowsPrec :: Int -> PartialWindowView -> ShowS
Show, (forall x. PartialWindowView -> Rep PartialWindowView x)
-> (forall x. Rep PartialWindowView x -> PartialWindowView)
-> Generic PartialWindowView
forall x. Rep PartialWindowView x -> PartialWindowView
forall x. PartialWindowView -> Rep PartialWindowView x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PartialWindowView x -> PartialWindowView
$cfrom :: forall x. PartialWindowView -> Rep PartialWindowView x
Generic)
deriving anyclass (PartialWindowView -> Object
(PartialWindowView -> Object) -> MsgpackEncode PartialWindowView
forall a. (a -> Object) -> MsgpackEncode a
toMsgpack :: PartialWindowView -> Object
$ctoMsgpack :: PartialWindowView -> Object
MsgpackEncode, Object -> Either DecodeError PartialWindowView
(Object -> Either DecodeError PartialWindowView)
-> MsgpackDecode PartialWindowView
forall a. (Object -> Either DecodeError a) -> MsgpackDecode a
fromMsgpack :: Object -> Either DecodeError PartialWindowView
$cfromMsgpack :: Object -> Either DecodeError PartialWindowView
MsgpackDecode)
class AsPartialWindowView a where
asPartialWindowView :: a -> PartialWindowView
instance AsPartialWindowView WindowView where
asPartialWindowView :: WindowView -> PartialWindowView
asPartialWindowView (WindowView Int
l Int
t) =
Maybe Int -> Maybe Int -> PartialWindowView
PartialWindowView (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
l) (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
t)
instance AsPartialWindowView PartialWindowView where
asPartialWindowView :: PartialWindowView -> PartialWindowView
asPartialWindowView =
PartialWindowView -> PartialWindowView
forall a. a -> a
id