{-# Language MultiParamTypeClasses, BangPatterns, TemplateHaskell #-}
module Client.State.Window
(
Window(..)
, winName
, winMessages
, winUnread
, winTotal
, winMention
, winMarker
, winHideMeta
, winHidden
, winActivityFilter
, WindowLines(..)
, WindowLine(..)
, wlSummary
, wlText
, wlPrefix
, wlImage
, wlFullImage
, wlImportance
, wlTimestamp
, ActivityFilter(..)
, WindowLineImportance(..)
, activityFilterStrings
, applyActivityFilter
, readActivityFilter
, emptyWindow
, addToWindow
, windowSeen
, windowActivate
, windowDeactivate
, windowClear
, PackedTime
, packZonedTime
, unpackUTCTime
, unpackTimeOfDay
) where
import Client.Image.PackedImage (Image', imageText)
import Client.Message (IrcSummary)
import Control.Lens (Lens', view, to, from, non, set, makeLenses, Each(..), Getter)
import Control.Monad ((<$!>))
import Data.Bits ((.|.), (.&.), shiftL, shiftR)
import Data.Text.Lazy (Text)
import Data.Time
import Data.Word (Word64)
import Data.List (elemIndex)
data WindowLine = WindowLine
{ WindowLine -> IrcSummary
_wlSummary :: !IrcSummary
, WindowLine -> Image'
_wlPrefix :: !Image'
, WindowLine -> Image'
_wlImage :: !Image'
, WindowLine -> Image'
_wlFullImage :: !Image'
, WindowLine -> WindowLineImportance
_wlImportance :: !WindowLineImportance
, WindowLine -> PackedTime
_wlTimestamp :: {-# UNPACK #-} !PackedTime
}
newtype PackedTime = PackedTime Word64
data WindowLines
= {-# UNPACK #-} !WindowLine :- WindowLines
| Nil
data Window = Window
{ Window -> Char
_winName' :: !Char
, Window -> WindowLines
_winMessages :: !WindowLines
, Window -> Maybe Int
_winMarker :: !(Maybe Int)
, Window -> Int
_winUnread :: !Int
, Window -> Int
_winTotal :: !Int
, Window -> WindowLineImportance
_winMention :: !WindowLineImportance
, Window -> Bool
_winHideMeta :: !Bool
, Window -> Bool
_winHidden :: !Bool
, Window -> ActivityFilter
_winActivityFilter :: !ActivityFilter
}
data ActivityLevel = NoActivity | NormalActivity | HighActivity
deriving (ActivityLevel -> ActivityLevel -> Bool
(ActivityLevel -> ActivityLevel -> Bool)
-> (ActivityLevel -> ActivityLevel -> Bool) -> Eq ActivityLevel
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ActivityLevel -> ActivityLevel -> Bool
== :: ActivityLevel -> ActivityLevel -> Bool
$c/= :: ActivityLevel -> ActivityLevel -> Bool
/= :: ActivityLevel -> ActivityLevel -> Bool
Eq, Eq ActivityLevel
Eq ActivityLevel =>
(ActivityLevel -> ActivityLevel -> Ordering)
-> (ActivityLevel -> ActivityLevel -> Bool)
-> (ActivityLevel -> ActivityLevel -> Bool)
-> (ActivityLevel -> ActivityLevel -> Bool)
-> (ActivityLevel -> ActivityLevel -> Bool)
-> (ActivityLevel -> ActivityLevel -> ActivityLevel)
-> (ActivityLevel -> ActivityLevel -> ActivityLevel)
-> Ord ActivityLevel
ActivityLevel -> ActivityLevel -> Bool
ActivityLevel -> ActivityLevel -> Ordering
ActivityLevel -> ActivityLevel -> ActivityLevel
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ActivityLevel -> ActivityLevel -> Ordering
compare :: ActivityLevel -> ActivityLevel -> Ordering
$c< :: ActivityLevel -> ActivityLevel -> Bool
< :: ActivityLevel -> ActivityLevel -> Bool
$c<= :: ActivityLevel -> ActivityLevel -> Bool
<= :: ActivityLevel -> ActivityLevel -> Bool
$c> :: ActivityLevel -> ActivityLevel -> Bool
> :: ActivityLevel -> ActivityLevel -> Bool
$c>= :: ActivityLevel -> ActivityLevel -> Bool
>= :: ActivityLevel -> ActivityLevel -> Bool
$cmax :: ActivityLevel -> ActivityLevel -> ActivityLevel
max :: ActivityLevel -> ActivityLevel -> ActivityLevel
$cmin :: ActivityLevel -> ActivityLevel -> ActivityLevel
min :: ActivityLevel -> ActivityLevel -> ActivityLevel
Ord, ReadPrec [ActivityLevel]
ReadPrec ActivityLevel
Int -> ReadS ActivityLevel
ReadS [ActivityLevel]
(Int -> ReadS ActivityLevel)
-> ReadS [ActivityLevel]
-> ReadPrec ActivityLevel
-> ReadPrec [ActivityLevel]
-> Read ActivityLevel
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ActivityLevel
readsPrec :: Int -> ReadS ActivityLevel
$creadList :: ReadS [ActivityLevel]
readList :: ReadS [ActivityLevel]
$creadPrec :: ReadPrec ActivityLevel
readPrec :: ReadPrec ActivityLevel
$creadListPrec :: ReadPrec [ActivityLevel]
readListPrec :: ReadPrec [ActivityLevel]
Read, Int -> ActivityLevel -> ShowS
[ActivityLevel] -> ShowS
ActivityLevel -> String
(Int -> ActivityLevel -> ShowS)
-> (ActivityLevel -> String)
-> ([ActivityLevel] -> ShowS)
-> Show ActivityLevel
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ActivityLevel -> ShowS
showsPrec :: Int -> ActivityLevel -> ShowS
$cshow :: ActivityLevel -> String
show :: ActivityLevel -> String
$cshowList :: [ActivityLevel] -> ShowS
showList :: [ActivityLevel] -> ShowS
Show)
data WindowLineImportance
= WLBoring
| WLNormal
| WLImportant
deriving (WindowLineImportance -> WindowLineImportance -> Bool
(WindowLineImportance -> WindowLineImportance -> Bool)
-> (WindowLineImportance -> WindowLineImportance -> Bool)
-> Eq WindowLineImportance
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: WindowLineImportance -> WindowLineImportance -> Bool
== :: WindowLineImportance -> WindowLineImportance -> Bool
$c/= :: WindowLineImportance -> WindowLineImportance -> Bool
/= :: WindowLineImportance -> WindowLineImportance -> Bool
Eq, Eq WindowLineImportance
Eq WindowLineImportance =>
(WindowLineImportance -> WindowLineImportance -> Ordering)
-> (WindowLineImportance -> WindowLineImportance -> Bool)
-> (WindowLineImportance -> WindowLineImportance -> Bool)
-> (WindowLineImportance -> WindowLineImportance -> Bool)
-> (WindowLineImportance -> WindowLineImportance -> Bool)
-> (WindowLineImportance
-> WindowLineImportance -> WindowLineImportance)
-> (WindowLineImportance
-> WindowLineImportance -> WindowLineImportance)
-> Ord WindowLineImportance
WindowLineImportance -> WindowLineImportance -> Bool
WindowLineImportance -> WindowLineImportance -> Ordering
WindowLineImportance
-> WindowLineImportance -> WindowLineImportance
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: WindowLineImportance -> WindowLineImportance -> Ordering
compare :: WindowLineImportance -> WindowLineImportance -> Ordering
$c< :: WindowLineImportance -> WindowLineImportance -> Bool
< :: WindowLineImportance -> WindowLineImportance -> Bool
$c<= :: WindowLineImportance -> WindowLineImportance -> Bool
<= :: WindowLineImportance -> WindowLineImportance -> Bool
$c> :: WindowLineImportance -> WindowLineImportance -> Bool
> :: WindowLineImportance -> WindowLineImportance -> Bool
$c>= :: WindowLineImportance -> WindowLineImportance -> Bool
>= :: WindowLineImportance -> WindowLineImportance -> Bool
$cmax :: WindowLineImportance
-> WindowLineImportance -> WindowLineImportance
max :: WindowLineImportance
-> WindowLineImportance -> WindowLineImportance
$cmin :: WindowLineImportance
-> WindowLineImportance -> WindowLineImportance
min :: WindowLineImportance
-> WindowLineImportance -> WindowLineImportance
Ord, Int -> WindowLineImportance -> ShowS
[WindowLineImportance] -> ShowS
WindowLineImportance -> String
(Int -> WindowLineImportance -> ShowS)
-> (WindowLineImportance -> String)
-> ([WindowLineImportance] -> ShowS)
-> Show WindowLineImportance
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> WindowLineImportance -> ShowS
showsPrec :: Int -> WindowLineImportance -> ShowS
$cshow :: WindowLineImportance -> String
show :: WindowLineImportance -> String
$cshowList :: [WindowLineImportance] -> ShowS
showList :: [WindowLineImportance] -> ShowS
Show, ReadPrec [WindowLineImportance]
ReadPrec WindowLineImportance
Int -> ReadS WindowLineImportance
ReadS [WindowLineImportance]
(Int -> ReadS WindowLineImportance)
-> ReadS [WindowLineImportance]
-> ReadPrec WindowLineImportance
-> ReadPrec [WindowLineImportance]
-> Read WindowLineImportance
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS WindowLineImportance
readsPrec :: Int -> ReadS WindowLineImportance
$creadList :: ReadS [WindowLineImportance]
readList :: ReadS [WindowLineImportance]
$creadPrec :: ReadPrec WindowLineImportance
readPrec :: ReadPrec WindowLineImportance
$creadListPrec :: ReadPrec [WindowLineImportance]
readListPrec :: ReadPrec [WindowLineImportance]
Read, Int -> WindowLineImportance
WindowLineImportance -> Int
WindowLineImportance -> [WindowLineImportance]
WindowLineImportance -> WindowLineImportance
WindowLineImportance
-> WindowLineImportance -> [WindowLineImportance]
WindowLineImportance
-> WindowLineImportance
-> WindowLineImportance
-> [WindowLineImportance]
(WindowLineImportance -> WindowLineImportance)
-> (WindowLineImportance -> WindowLineImportance)
-> (Int -> WindowLineImportance)
-> (WindowLineImportance -> Int)
-> (WindowLineImportance -> [WindowLineImportance])
-> (WindowLineImportance
-> WindowLineImportance -> [WindowLineImportance])
-> (WindowLineImportance
-> WindowLineImportance -> [WindowLineImportance])
-> (WindowLineImportance
-> WindowLineImportance
-> WindowLineImportance
-> [WindowLineImportance])
-> Enum WindowLineImportance
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: WindowLineImportance -> WindowLineImportance
succ :: WindowLineImportance -> WindowLineImportance
$cpred :: WindowLineImportance -> WindowLineImportance
pred :: WindowLineImportance -> WindowLineImportance
$ctoEnum :: Int -> WindowLineImportance
toEnum :: Int -> WindowLineImportance
$cfromEnum :: WindowLineImportance -> Int
fromEnum :: WindowLineImportance -> Int
$cenumFrom :: WindowLineImportance -> [WindowLineImportance]
enumFrom :: WindowLineImportance -> [WindowLineImportance]
$cenumFromThen :: WindowLineImportance
-> WindowLineImportance -> [WindowLineImportance]
enumFromThen :: WindowLineImportance
-> WindowLineImportance -> [WindowLineImportance]
$cenumFromTo :: WindowLineImportance
-> WindowLineImportance -> [WindowLineImportance]
enumFromTo :: WindowLineImportance
-> WindowLineImportance -> [WindowLineImportance]
$cenumFromThenTo :: WindowLineImportance
-> WindowLineImportance
-> WindowLineImportance
-> [WindowLineImportance]
enumFromThenTo :: WindowLineImportance
-> WindowLineImportance
-> WindowLineImportance
-> [WindowLineImportance]
Enum)
data ActivityFilter
= AFSilent
| AFQuieter
| AFQuiet
| AFImpOnly
| AFLoud
| AFLouder
deriving (ActivityFilter -> ActivityFilter -> Bool
(ActivityFilter -> ActivityFilter -> Bool)
-> (ActivityFilter -> ActivityFilter -> Bool) -> Eq ActivityFilter
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ActivityFilter -> ActivityFilter -> Bool
== :: ActivityFilter -> ActivityFilter -> Bool
$c/= :: ActivityFilter -> ActivityFilter -> Bool
/= :: ActivityFilter -> ActivityFilter -> Bool
Eq, Eq ActivityFilter
Eq ActivityFilter =>
(ActivityFilter -> ActivityFilter -> Ordering)
-> (ActivityFilter -> ActivityFilter -> Bool)
-> (ActivityFilter -> ActivityFilter -> Bool)
-> (ActivityFilter -> ActivityFilter -> Bool)
-> (ActivityFilter -> ActivityFilter -> Bool)
-> (ActivityFilter -> ActivityFilter -> ActivityFilter)
-> (ActivityFilter -> ActivityFilter -> ActivityFilter)
-> Ord ActivityFilter
ActivityFilter -> ActivityFilter -> Bool
ActivityFilter -> ActivityFilter -> Ordering
ActivityFilter -> ActivityFilter -> ActivityFilter
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ActivityFilter -> ActivityFilter -> Ordering
compare :: ActivityFilter -> ActivityFilter -> Ordering
$c< :: ActivityFilter -> ActivityFilter -> Bool
< :: ActivityFilter -> ActivityFilter -> Bool
$c<= :: ActivityFilter -> ActivityFilter -> Bool
<= :: ActivityFilter -> ActivityFilter -> Bool
$c> :: ActivityFilter -> ActivityFilter -> Bool
> :: ActivityFilter -> ActivityFilter -> Bool
$c>= :: ActivityFilter -> ActivityFilter -> Bool
>= :: ActivityFilter -> ActivityFilter -> Bool
$cmax :: ActivityFilter -> ActivityFilter -> ActivityFilter
max :: ActivityFilter -> ActivityFilter -> ActivityFilter
$cmin :: ActivityFilter -> ActivityFilter -> ActivityFilter
min :: ActivityFilter -> ActivityFilter -> ActivityFilter
Ord, Int -> ActivityFilter
ActivityFilter -> Int
ActivityFilter -> [ActivityFilter]
ActivityFilter -> ActivityFilter
ActivityFilter -> ActivityFilter -> [ActivityFilter]
ActivityFilter
-> ActivityFilter -> ActivityFilter -> [ActivityFilter]
(ActivityFilter -> ActivityFilter)
-> (ActivityFilter -> ActivityFilter)
-> (Int -> ActivityFilter)
-> (ActivityFilter -> Int)
-> (ActivityFilter -> [ActivityFilter])
-> (ActivityFilter -> ActivityFilter -> [ActivityFilter])
-> (ActivityFilter -> ActivityFilter -> [ActivityFilter])
-> (ActivityFilter
-> ActivityFilter -> ActivityFilter -> [ActivityFilter])
-> Enum ActivityFilter
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: ActivityFilter -> ActivityFilter
succ :: ActivityFilter -> ActivityFilter
$cpred :: ActivityFilter -> ActivityFilter
pred :: ActivityFilter -> ActivityFilter
$ctoEnum :: Int -> ActivityFilter
toEnum :: Int -> ActivityFilter
$cfromEnum :: ActivityFilter -> Int
fromEnum :: ActivityFilter -> Int
$cenumFrom :: ActivityFilter -> [ActivityFilter]
enumFrom :: ActivityFilter -> [ActivityFilter]
$cenumFromThen :: ActivityFilter -> ActivityFilter -> [ActivityFilter]
enumFromThen :: ActivityFilter -> ActivityFilter -> [ActivityFilter]
$cenumFromTo :: ActivityFilter -> ActivityFilter -> [ActivityFilter]
enumFromTo :: ActivityFilter -> ActivityFilter -> [ActivityFilter]
$cenumFromThenTo :: ActivityFilter
-> ActivityFilter -> ActivityFilter -> [ActivityFilter]
enumFromThenTo :: ActivityFilter
-> ActivityFilter -> ActivityFilter -> [ActivityFilter]
Enum)
activityFilterStrings :: [String]
activityFilterStrings :: [String]
activityFilterStrings = [String
"silent", String
"quieter", String
"quiet", String
"imponly", String
"loud", String
"louder"]
applyActivityFilter :: ActivityFilter -> WindowLineImportance -> WindowLineImportance
applyActivityFilter :: ActivityFilter -> WindowLineImportance -> WindowLineImportance
applyActivityFilter ActivityFilter
AFSilent WindowLineImportance
_ = WindowLineImportance
WLBoring
applyActivityFilter ActivityFilter
AFQuieter WindowLineImportance
WLNormal = WindowLineImportance
WLBoring
applyActivityFilter ActivityFilter
AFQuieter WindowLineImportance
WLImportant = WindowLineImportance
WLNormal
applyActivityFilter ActivityFilter
AFImpOnly WindowLineImportance
WLNormal = WindowLineImportance
WLBoring
applyActivityFilter ActivityFilter
AFQuiet WindowLineImportance
WLImportant = WindowLineImportance
WLNormal
applyActivityFilter ActivityFilter
AFLouder WindowLineImportance
WLNormal = WindowLineImportance
WLImportant
applyActivityFilter ActivityFilter
_ WindowLineImportance
etc = WindowLineImportance
etc
instance Show ActivityFilter where
show :: ActivityFilter -> String
show ActivityFilter
af = [String]
activityFilterStrings [String] -> Int -> String
forall a. HasCallStack => [a] -> Int -> a
!! ActivityFilter -> Int
forall a. Enum a => a -> Int
fromEnum ActivityFilter
af
readActivityFilter :: String -> Maybe ActivityFilter
readActivityFilter :: String -> Maybe ActivityFilter
readActivityFilter String
s = Int -> ActivityFilter
forall a. Enum a => Int -> a
toEnum (Int -> ActivityFilter) -> Maybe Int -> Maybe ActivityFilter
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> [String] -> Maybe Int
forall a. Eq a => a -> [a] -> Maybe Int
elemIndex String
s [String]
activityFilterStrings
makeLenses ''Window
makeLenses ''WindowLine
winName :: Lens' Window (Maybe Char)
winName :: Lens' Window (Maybe Char)
winName = (Char -> f Char) -> Window -> f Window
Lens' Window Char
winName' ((Char -> f Char) -> Window -> f Window)
-> ((Maybe Char -> f (Maybe Char)) -> Char -> f Char)
-> (Maybe Char -> f (Maybe Char))
-> Window
-> f Window
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AnIso (Maybe Char) (Maybe Char) Char Char
-> Iso Char Char (Maybe Char) (Maybe Char)
forall s t a b. AnIso s t a b -> Iso b a t s
from (Char -> Iso' (Maybe Char) Char
forall a. Eq a => a -> Iso' (Maybe a) a
non Char
'\0')
wlText :: Getter WindowLine Text
wlText :: Getter WindowLine Text
wlText = (Image' -> f Image') -> WindowLine -> f WindowLine
Lens' WindowLine Image'
wlFullImage ((Image' -> f Image') -> WindowLine -> f WindowLine)
-> ((Text -> f Text) -> Image' -> f Image')
-> (Text -> f Text)
-> WindowLine
-> f WindowLine
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Image' -> Text) -> (Text -> f Text) -> Image' -> f Image'
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to Image' -> Text
imageText
emptyWindow :: Window
emptyWindow :: Window
emptyWindow = Window
{ _winName' :: Char
_winName' = Char
'\0'
, _winMessages :: WindowLines
_winMessages = WindowLines
Nil
, _winMarker :: Maybe Int
_winMarker = Maybe Int
forall a. Maybe a
Nothing
, _winUnread :: Int
_winUnread = Int
0
, _winTotal :: Int
_winTotal = Int
0
, _winMention :: WindowLineImportance
_winMention = WindowLineImportance
WLBoring
, _winHideMeta :: Bool
_winHideMeta = Bool
False
, _winHidden :: Bool
_winHidden = Bool
False
, _winActivityFilter :: ActivityFilter
_winActivityFilter = ActivityFilter
AFLoud
}
windowClear :: Window -> Window
windowClear :: Window -> Window
windowClear Window
w = Window
w
{ _winMessages = Nil
, _winMarker = Nothing
, _winUnread = 0
, _winTotal = 0
, _winMention = WLBoring
}
addToWindow :: WindowLine -> Window -> (Window, Bool)
addToWindow :: WindowLine -> Window -> (Window, Bool)
addToWindow !WindowLine
msg !Window
win = (Window
win', Bool
nowImportant)
where
win' :: Window
win' = Window
win
{ _winMessages = msg :- view winMessages win
, _winTotal = view winTotal win + 1
, _winMarker = (+1) <$!> view winMarker win
, _winUnread = if msgImportance == WLBoring
then view winUnread win
else view winUnread win + 1
, _winMention = max oldMention msgImportance
, _winHideMeta = view winHideMeta win
}
oldMention :: WindowLineImportance
oldMention = Getting WindowLineImportance Window WindowLineImportance
-> Window -> WindowLineImportance
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting WindowLineImportance Window WindowLineImportance
Lens' Window WindowLineImportance
winMention Window
win
nowImportant :: Bool
nowImportant = WindowLineImportance
oldMention WindowLineImportance -> WindowLineImportance -> Bool
forall a. Ord a => a -> a -> Bool
< WindowLineImportance
WLImportant Bool -> Bool -> Bool
&& WindowLineImportance
msgImportance WindowLineImportance -> WindowLineImportance -> Bool
forall a. Ord a => a -> a -> Bool
>= WindowLineImportance
WLImportant
msgImportance :: WindowLineImportance
msgImportance = ActivityFilter -> WindowLineImportance -> WindowLineImportance
applyActivityFilter (Getting ActivityFilter Window ActivityFilter
-> Window -> ActivityFilter
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting ActivityFilter Window ActivityFilter
Lens' Window ActivityFilter
winActivityFilter Window
win) (Getting WindowLineImportance WindowLine WindowLineImportance
-> WindowLine -> WindowLineImportance
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting WindowLineImportance WindowLine WindowLineImportance
Lens' WindowLine WindowLineImportance
wlImportance WindowLine
msg)
windowSeen :: Window -> Window
windowSeen :: Window -> Window
windowSeen = ASetter Window Window Int Int -> Int -> Window -> Window
forall s t a b. ASetter s t a b -> b -> s -> t
set ASetter Window Window Int Int
Lens' Window Int
winUnread Int
0
(Window -> Window) -> (Window -> Window) -> Window -> Window
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ASetter Window Window WindowLineImportance WindowLineImportance
-> WindowLineImportance -> Window -> Window
forall s t a b. ASetter s t a b -> b -> s -> t
set ASetter Window Window WindowLineImportance WindowLineImportance
Lens' Window WindowLineImportance
winMention WindowLineImportance
WLBoring
windowActivate :: Window -> Window
windowActivate :: Window -> Window
windowActivate Window
win
| Getting Int Window Int -> Window -> Int
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Int Window Int
Lens' Window Int
winUnread Window
win Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 = ASetter Window Window (Maybe Int) (Maybe Int)
-> Maybe Int -> Window -> Window
forall s t a b. ASetter s t a b -> b -> s -> t
set ASetter Window Window (Maybe Int) (Maybe Int)
Lens' Window (Maybe Int)
winMarker Maybe Int
forall a. Maybe a
Nothing Window
win
| Bool
otherwise = Window
win
windowDeactivate :: Window -> Window
windowDeactivate :: Window -> Window
windowDeactivate = ASetter Window Window (Maybe Int) (Maybe Int)
-> Maybe Int -> Window -> Window
forall s t a b. ASetter s t a b -> b -> s -> t
set ASetter Window Window (Maybe Int) (Maybe Int)
Lens' Window (Maybe Int)
winMarker (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
0)
instance Each WindowLines WindowLines WindowLine WindowLine where
each :: Traversal WindowLines WindowLines WindowLine WindowLine
each WindowLine -> f WindowLine
_ WindowLines
Nil = WindowLines -> f WindowLines
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure WindowLines
Nil
each WindowLine -> f WindowLine
f (WindowLine
x :- WindowLines
xs) = WindowLine -> WindowLines -> WindowLines
(:-) (WindowLine -> WindowLines -> WindowLines)
-> f WindowLine -> f (WindowLines -> WindowLines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> WindowLine -> f WindowLine
f WindowLine
x f (WindowLines -> WindowLines) -> f WindowLines -> f WindowLines
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (WindowLine -> f WindowLine) -> WindowLines -> f WindowLines
forall s t a b. Each s t a b => Traversal s t a b
Traversal WindowLines WindowLines WindowLine WindowLine
each WindowLine -> f WindowLine
f WindowLines
xs
field :: Num a => PackedTime -> Int -> Int -> a
field :: forall a. Num a => PackedTime -> Int -> Int -> a
field (PackedTime Word64
x) Int
off Int
sz = Word64 -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Word64
x Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
`shiftR` Int
off) Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.&. (Word64
2Word64 -> Int -> Word64
forall a b. (Num a, Integral b) => a -> b -> a
^Int
szWord64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
-Word64
1))
{-# INLINE field #-}
packField :: Int -> Int -> Word64
packField :: Int -> Int -> Word64
packField Int
off Int
val = Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
val Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
`shiftL` Int
off
packZonedTime :: ZonedTime -> PackedTime
packZonedTime :: ZonedTime -> PackedTime
packZonedTime (ZonedTime (LocalTime (ModifiedJulianDay Integer
d) (TimeOfDay Int
h Int
m Pico
s)) TimeZone
z)
= Word64 -> PackedTime
PackedTime
(Word64 -> PackedTime) -> Word64 -> PackedTime
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Word64
packField Int
17 Int
h Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.|.
Int -> Int -> Word64
packField Int
11 Int
m Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.|.
Int -> Int -> Word64
packField Int
5 (Pico -> Int
forall b. Integral b => Pico -> b
forall a b. (RealFrac a, Integral b) => a -> b
floor Pico
s) Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.|.
Int -> Int -> Word64
packField Int
22 (Integer -> Int
forall a. Num a => Integer -> a
fromInteger Integer
d) Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.|.
Int -> Int -> Word64
packField Int
0 (TimeZone -> Int
timeZoneMinutes TimeZone
z Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
60 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
12)
unpackTimeOfDay :: PackedTime -> TimeOfDay
unpackTimeOfDay :: PackedTime -> TimeOfDay
unpackTimeOfDay !PackedTime
x = Int -> Int -> Pico -> TimeOfDay
TimeOfDay Int
h Int
m Pico
s
where
h :: Int
h = PackedTime -> Int -> Int -> Int
forall a. Num a => PackedTime -> Int -> Int -> a
field PackedTime
x Int
17 Int
5
m :: Int
m = PackedTime -> Int -> Int -> Int
forall a. Num a => PackedTime -> Int -> Int -> a
field PackedTime
x Int
11 Int
6
s :: Pico
s = PackedTime -> Int -> Int -> Pico
forall a. Num a => PackedTime -> Int -> Int -> a
field PackedTime
x Int
5 Int
6
unpackLocalTime :: PackedTime -> LocalTime
unpackLocalTime :: PackedTime -> LocalTime
unpackLocalTime !PackedTime
x = Day -> TimeOfDay -> LocalTime
LocalTime Day
d TimeOfDay
t
where
d :: Day
d = Integer -> Day
ModifiedJulianDay (PackedTime -> Int -> Int -> Integer
forall a. Num a => PackedTime -> Int -> Int -> a
field PackedTime
x Int
22 Int
42)
t :: TimeOfDay
t = PackedTime -> TimeOfDay
unpackTimeOfDay PackedTime
x
unpackUTCTime :: PackedTime -> UTCTime
unpackUTCTime :: PackedTime -> UTCTime
unpackUTCTime = ZonedTime -> UTCTime
zonedTimeToUTC (ZonedTime -> UTCTime)
-> (PackedTime -> ZonedTime) -> PackedTime -> UTCTime
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PackedTime -> ZonedTime
unpackZonedTime
unpackZonedTime :: PackedTime -> ZonedTime
unpackZonedTime :: PackedTime -> ZonedTime
unpackZonedTime !PackedTime
x = LocalTime -> TimeZone -> ZonedTime
ZonedTime LocalTime
t TimeZone
z
where
z :: TimeZone
z = Int -> TimeZone
minutesToTimeZone ((PackedTime -> Int -> Int -> Int
forall a. Num a => PackedTime -> Int -> Int -> a
field PackedTime
x Int
0 Int
5 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
12) Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
60)
t :: LocalTime
t = PackedTime -> LocalTime
unpackLocalTime PackedTime
x