Skip to content

Commit

Permalink
format
Browse files Browse the repository at this point in the history
  • Loading branch information
wavewave committed Jun 25, 2023
1 parent b55610a commit 75a66a4
Showing 1 changed file with 21 additions and 19 deletions.
40 changes: 21 additions & 19 deletions grid/app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,15 +6,15 @@ module Main where
import Data.Foldable (for_)
import Data.GI.Base (AttrOp ((:=)), after, get, new, on)
import Data.GI.Gtk.Threading (postGUIASync)
import Data.IORef (newIORef, modifyIORef', readIORef)
import Data.IORef (modifyIORef', newIORef, readIORef)
import Data.Maybe (fromMaybe)
import Data.Text (Text)
import Data.Text qualified as T
import Data.Time.Clock (
diffUTCTime,
getCurrentTime,
nominalDiffTimeToSeconds,
)
import Data.Time.Clock
( diffUTCTime,
getCurrentTime,
nominalDiffTimeToSeconds,
)
import Data.Traversable (for)
import GI.Cairo.Render qualified as R
import GI.Cairo.Render.Connector as RC
Expand All @@ -29,8 +29,8 @@ data ViewPort = ViewPort (Double, Double) (Double, Double)
deriving (Show)

data GridState = GridState
{ gridViewPort :: ViewPort
, gridTempViewPort :: Maybe ViewPort
{ gridViewPort :: ViewPort,
gridTempViewPort :: Maybe ViewPort
}
deriving (Show)

Expand Down Expand Up @@ -60,7 +60,7 @@ gridInViewPort (ViewPort (x0, y0) (x1, y1)) = (xs, ys)

textPosInViewPort :: ViewPort -> [(Double, Double)]
textPosInViewPort (ViewPort (x0, y0) (x1, y1)) =
[ (x, y) | x <- xs, y <- ys ]
[(x, y) | x <- xs, y <- ys]
where
u0, u1 :: Int
u0 = floor ((x0 - 120) / 512.0)
Expand Down Expand Up @@ -130,7 +130,7 @@ drawTextMultiline ::
[Text] ->
R.Render ()
drawTextMultiline (ctxt, desc) (x, y) msgs = do
for_ (zip [y, y + 12 .. ] msgs) $ \(y', msg) ->
for_ (zip [y, y + 12 ..] msgs) $ \(y', msg) ->
drawTextLine (ctxt, desc) (x, y') msg

myText ::
Expand All @@ -141,7 +141,7 @@ myText (pangoCtxt, descSans, descMono) vp = do
let xys = textPosInViewPort vp
for_ xys $ \(x, y) -> do
drawTextMultiline (pangoCtxt, descSans) (x, y) (T.lines loremIpsum)
drawTextMultiline (pangoCtxt, descMono) (x, y+120) (T.lines loremIpsum)
drawTextMultiline (pangoCtxt, descMono) (x, y + 120) (T.lines loremIpsum)

myDraw ::
(P.Context, P.FontDescription, P.FontDescription) ->
Expand Down Expand Up @@ -197,11 +197,13 @@ main = do
drawingArea <- new Gtk.DrawingArea []
#addEvents
drawingArea
[ Gdk.EventMaskScrollMask
, Gdk.EventMaskTouchpadGestureMask
[ Gdk.EventMaskScrollMask,
Gdk.EventMaskTouchpadGestureMask
]
_ <- drawingArea `on` #draw $
RC.renderWithContext $ do
_ <- drawingArea
`on` #draw
$ RC.renderWithContext
$ do
start <- R.liftIO $ getCurrentTime
s <- R.liftIO $ readIORef ref
-- R.liftIO $ print s
Expand Down Expand Up @@ -230,8 +232,8 @@ main = do
scale = (cx1 - cx0) / (vx1 - vx0)
vp' = transformScroll dir scale (dx, dy) vp
in s
{ gridViewPort = vp'
, gridTempViewPort = Nothing
{ gridViewPort = vp',
gridTempViewPort = Nothing
}
postGUIASync (#queueDraw drawingArea)
pure True
Expand All @@ -258,8 +260,8 @@ main = do
let vp = gridViewPort s
mtvp = gridTempViewPort s
in s
{ gridViewPort = fromMaybe vp mtvp
, gridTempViewPort = Nothing
{ gridViewPort = fromMaybe vp mtvp,
gridTempViewPort = Nothing
}
postGUIASync (#queueDraw drawingArea)
#setPropagationPhase gzoom Gtk.PropagationPhaseBubble
Expand Down

0 comments on commit 75a66a4

Please sign in to comment.