1 -- This file is part of Intricacy
2 -- Copyright (C) 2013 Martin Bays <mbays@sdf.org>
4 -- This program is free software: you can redistribute it and/or modify
5 -- it under the terms of version 3 of the GNU General Public License as
6 -- published by the Free Software Foundation, or any later version.
8 -- You should have received a copy of the GNU General Public License
9 -- along with this program. If not, see http://www.gnu.org/licenses/.
12 {-# LANGUAGE FlexibleContexts #-}
13 {-# LANGUAGE LambdaCase #-}
14 {-# LANGUAGE TupleSections #-}
18 import Control
.Applicative
20 import Control
.Concurrent
.STM
22 import Control
.Monad
.State
23 import Control
.Monad
.Trans
.Maybe
24 import Control
.Monad
.Trans
.Reader
26 import Data
.Function
(on
)
29 import qualified Data
.Map
as Map
32 import Data
.Time
.Clock
(getCurrentTime
)
34 import Graphics
.UI
.SDL
hiding (flip)
35 import qualified Graphics
.UI
.SDL
as SDL
36 import qualified Graphics
.UI
.SDL
.TTF
as TTF
37 import System
.FilePath
38 --import Debug.Trace (traceShow)
41 import Graphics
.UI
.SDL
.Mixer
42 import System
.Random
(randomRIO)
61 data UIState
= UIState
64 , gsSurface
:: Maybe Surface
65 , bgSurface
:: Maybe Surface
66 , cachedGlyphs
:: CachedGlyphs
67 , lastDrawArgs
:: Maybe DrawArgs
68 , miniLocks
:: Map Lock Surface
69 , registeredSelectables
:: Map HexVec Selectable
70 , contextButtons
:: [ButtonGroup
]
71 , uiOptions
:: UIOptions
72 , settingBinding
:: Maybe Command
73 , uiKeyBindings
:: Map InputMode KeyBindings
74 , dispFont
:: Maybe TTF
.Font
75 , dispFontSmall
:: Maybe TTF
.Font
76 , lastFrameTicks
:: Word32
77 , paintTileIndex
:: Int
78 , leftButtonDown
:: Maybe HexVec
79 , middleButtonDown
:: Maybe HexVec
80 , rightButtonDown
:: Maybe HexVec
81 , mousePos
:: (HexVec
,Bool)
82 , message
:: Maybe (Pixel
, String)
83 , hoverStr
:: Maybe String
84 , dispCentre
:: HexPos
85 , dispLastCol
:: PieceColouring
87 , nextAnimFrameAt
:: Maybe Word32
90 , sounds
:: Map
String [Chunk
]
93 deriving (Eq
, Ord
, Show)
94 type UIM
= StateT UIState
IO
95 nullUIState
= UIState
0 0 Nothing Nothing emptyCachedGlyphs Nothing Map
.empty Map
.empty []
96 defaultUIOptions Nothing Map
.empty Nothing Nothing
0 0 Nothing Nothing Nothing
97 (zero
,False) Nothing Nothing
(PHS zero
) Map
.empty 0 Nothing
50
102 data UIOptions
= UIOptions
103 { useFiveColouring
:: Bool
104 , showBlocks
:: ShowBlocks
105 , whsButtons
:: Maybe WrHoSel
106 , useBackground
:: Bool
108 , showButtonText
:: Bool
110 , uiAnimTime
:: Word32
111 , shortUiAnimTime
:: Word32
113 deriving (Eq
, Ord
, Show, Read)
114 defaultUIOptions
= UIOptions
False ShowBlocksBlocking Nothing
True False True True 100 20
116 modifyUIOptions
:: (UIOptions
-> UIOptions
) -> UIM
()
117 modifyUIOptions f
= modify
$ \s
-> s
{ uiOptions
= f
$ uiOptions s
}
119 renderToMain
:: RenderM a
-> UIM a
121 surf
<- liftIO getVideoSurface
122 renderToMainWithSurf surf m
123 renderToMainWithSurf
:: Surface
-> RenderM a
-> UIM a
124 renderToMainWithSurf surf m
= do
125 (scrCentre
, size
) <- getGeom
126 centre
<- gets dispCentre
127 mfont
<- gets dispFont
128 bgsurf
<- gets bgSurface
129 cgs
<- gets cachedGlyphs
130 (a
,cgs
') <- liftIO
$ runRenderM m cgs
$ RenderContext surf bgsurf centre scrCentre zero size mfont
131 modify
$ \s
-> s
{ cachedGlyphs
= cgs
' }
136 surface
<- liftIO getVideoSurface
137 liftIO
$ SDL
.flip surface
141 last <- gets lastFrameTicks
142 let next = last + 1000 `
div`
30
143 now
<- liftIO getTicks
144 -- liftIO $ print now
146 liftIO
$ delay
(next - now
)
147 modify
$ \ds
-> ds
{ lastFrameTicks
= now
}
150 data Button
= Button
{ buttonPos
:: HexVec
, buttonCmd
:: Command
, buttonHelp
:: [ButtonHelp
] }
151 deriving (Eq
, Ord
, Show)
152 type ButtonGroup
= ([Button
],(Int,Int))
153 type ButtonHelp
= (String, HexVec
)
154 singleButton
:: HexVec
-> Command
-> Int -> [ButtonHelp
] -> ButtonGroup
155 singleButton pos cmd col helps
= ([Button pos cmd helps
], (col
,0))
156 getButtons
:: InputMode
-> UIM
[ ButtonGroup
]
158 mwhs
<- gets
$ whsButtons
. uiOptions
159 cntxtButtons
<- gets contextButtons
160 return $ cntxtButtons
++ global
++ case mode
of
162 singleButton
(tl
+^hv
+^neg hw
) CmdTest
1 [("test", hu
+^neg hw
)]
163 , singleButton
(tl
+^neg hw
) CmdPlay
2 [("play", hu
+^neg hw
)]
165 , singleButton
(br
+^
2*^hu
) CmdWriteState
2 [("save", hu
+^neg hw
)] ]
167 ++ [ ([Button
(paintButtonStart
+^ hu
+^ i
*^hv
) (paintTileCmds
!!i
) []
168 | i
<- take (length paintTiles
) [0..] ],(5,0)) ]
169 IMPlay
-> whsBGs mwhs mode
170 IMReplay
-> [ markButtonGroup
]
172 [ singleButton serverPos CmdSetServer
0 [("server",7*^neg hu
)]
173 , singleButton
(serverPos
+^hw
) CmdToggleCacheOnly
0 [("offline",hv
+^
7*^neg hu
),("mode",hw
+^
5*^neg hu
)]
174 , singleButton
(codenamePos
+^
2*^neg hu
) (CmdSelCodename Nothing
) 2 [("code",hv
+^
5*^neg hu
),("name",hw
+^
5*^neg hu
)]
175 , singleButton
(serverPos
+^
2*^neg hv
+^
2*^hw
) CmdInitiation
3 [("initi",hu
+^neg hw
),("ation",hu
+^neg hv
)]
180 global
= if mode `
elem`
[IMTextInput
,IMImpatience
] then [] else
181 [ singleButton br CmdQuit
0 [("quit",hu
+^neg hw
)]
182 , singleButton
(tr
+^
3*^hv
+^
3*^hu
) CmdHelp
3 [("help",hu
+^neg hw
)] ]
183 whsBGs
:: Maybe WrHoSel
-> InputMode
-> [ ButtonGroup
]
184 whsBGs Nothing _
= []
185 whsBGs
(Just whs
) mode
=
186 let edit
= mode
== IMEdit
187 in [ ( [ Button bl
(if edit
then CmdSelect
else CmdWait
) [] ], (0,0))
188 , ( [ Button
(bl
+^dir
) (CmdDir whs dir
)
189 (if dir
==hu
then [("move",hu
+^neg hw
),(if edit
then "piece" else whsStr whs
,hu
+^neg hv
)] else [])
190 | dir
<- hexDirs
], (5,0) )
192 ([( [ Button
(bl
+^
((-2)*^hv
))
194 [("turn",hu
+^neg hw
),("cw",hu
+^neg hv
)]
195 , Button
(bl
+^
((-2)*^hw
))
197 [("turn",hu
+^neg hw
),("ccw",hu
+^neg hv
)]
198 ], (5,0) ) | whs
/= WHSWrench
]) ++
199 ([( [ Button
(bl
+^
(2*^hv
)+^hw
+^neg hu
) (CmdTile HookTile
) [("select",hu
+^neg hw
),("hook",hu
+^neg hv
)]
200 , Button
(bl
+^
(2*^hv
)+^neg hu
) (CmdTile
$ WrenchTile zero
) [("select",hu
+^neg hw
),("wrench",hu
+^neg hv
)]
201 ], (2,0) ) | whs
== WHSSelected
&& mode
/= IMEdit
])
207 markButtonGroup
= ([Button
(tl
+^hw
) CmdMark
[("set",hu
+^neg hw
),("mark",hu
+^neg hv
)]
208 , Button
(tl
+^hw
+^hv
) CmdJumpMark
[("jump",hu
+^neg hw
),("mark",hu
+^neg hv
)]
209 , Button
(tl
+^hw
+^
2*^hv
) CmdReset
[("jump",hu
+^neg hw
),("start",hu
+^neg hv
)]],(0,1))
213 data AccessedInfo
= AccessedSolved | AccessedPublic | AccessedReadNotes | AccessedUndeclared
214 deriving (Eq
, Ord
, Show)
218 | SelInitLock HexVec
Bool
220 | SelLockUnset
Bool ActiveLock
221 | SelSelectedCodeName Codename
223 | SelRelScoreComponent
224 | SelScoreLock
(Maybe Codename
) (Maybe AccessedReason
) ActiveLock
225 | SelUndeclared Undeclared
226 | SelReadNote NoteInfo
228 | SelSolution NoteInfo
229 | SelAccessed Codename
231 | SelSecured NoteInfo
232 | SelOldLock LockSpec
234 | SelAccessedInfo AccessedInfo
240 deriving (Eq
, Ord
, Show)
242 registerSelectable
:: HexVec
-> Int -> Selectable
-> UIM
()
243 registerSelectable v r s
=
244 modify
$ \ds
-> ds
{registeredSelectables
= foldr (
245 (`Map
.insert` s
) . (v
+^
)) (registeredSelectables ds
) (hexDisc r
)}
246 registerButtonGroup
:: ButtonGroup
-> UIM
()
247 registerButtonGroup g
= modify
$ \ds
-> ds
{contextButtons
= g
:contextButtons ds
}
248 registerButton
:: HexVec
-> Command
-> Int -> [ButtonHelp
] -> UIM
()
249 registerButton pos cmd col helps
= registerButtonGroup
$ singleButton pos cmd col helps
250 clearSelectables
,clearButtons
:: UIM
()
251 clearSelectables
= modify
$ \ds
-> ds
{registeredSelectables
= Map
.empty}
252 clearButtons
= modify
$ \ds
-> ds
{contextButtons
= []}
254 registerUndoButtons
:: Bool -> UIM
()
255 registerUndoButtons noRedo
= do
256 registerButton
(periphery
2+^hu
) CmdUndo
0 [("undo",hu
+^neg hw
)]
257 unless noRedo
$ registerButton
(periphery
2+^hu
+^neg hv
) CmdRedo
2 [("redo",hu
+^neg hw
)]
259 commandOfSelectable IMInit
(SelTut _
) _
= Just
. CmdSolveInit
$ Just zero
260 commandOfSelectable IMInit
(SelInitLock v _
) _
= Just
. CmdSolveInit
$ Just v
261 commandOfSelectable IMMeta SelOurLock _
= Just CmdEdit
262 commandOfSelectable IMMeta
(SelLock
(ActiveLock _ i
)) False = Just
$ CmdSolve
(Just i
)
263 commandOfSelectable IMMeta
(SelLock
(ActiveLock _ i
)) True = Just
$ CmdPlaceLock
(Just i
)
264 commandOfSelectable IMMeta
(SelScoreLock Nothing _
(ActiveLock _ i
)) False = Just
$ CmdSolve
(Just i
)
265 commandOfSelectable IMMeta
(SelScoreLock Nothing _
(ActiveLock _ i
)) True = Just
$ CmdPlaceLock
(Just i
)
266 commandOfSelectable IMMeta
(SelScoreLock
(Just _
) _ _
) _
= Just CmdHome
267 commandOfSelectable IMMeta
(SelLockUnset
True (ActiveLock _ i
)) _
= Just
$ CmdPlaceLock
(Just i
)
268 commandOfSelectable IMMeta
(SelSelectedCodeName _
) False = Just
$ CmdSelCodename Nothing
269 commandOfSelectable IMMeta
(SelSelectedCodeName _
) True = Just CmdHome
270 commandOfSelectable IMMeta
(SelUndeclared undecl
) _
= Just
$ CmdDeclare
$ Just undecl
271 commandOfSelectable IMMeta
(SelReadNote note
) False = Just
$ CmdSelCodename
$ Just
$ noteAuthor note
272 commandOfSelectable IMMeta
(SelReadNote note
) True = Just
$ CmdViewSolution
$ Just note
273 commandOfSelectable IMMeta
(SelSolution note
) False = Just
$ CmdSelCodename
$ Just
$ noteAuthor note
274 commandOfSelectable IMMeta
(SelSolution note
) True = Just
$ CmdViewSolution
$ Just note
275 commandOfSelectable IMMeta
(SelAccessed name
) _
= Just
$ CmdSelCodename
$ Just name
276 commandOfSelectable IMMeta
(SelRandom name
) _
= Just
$ CmdSelCodename
$ Just name
277 commandOfSelectable IMMeta
(SelSecured note
) False = Just
$ CmdSelCodename
$ Just
$ lockOwner
$ noteOn note
278 commandOfSelectable IMMeta
(SelSecured note
) True = Just
$ CmdViewSolution
$ Just note
279 commandOfSelectable IMMeta
(SelOldLock ls
) _
= Just
$ CmdPlayLockSpec
$ Just ls
280 commandOfSelectable IMMeta SelLockPath _
= Just CmdSelectLock
281 commandOfSelectable IMTextInput
(SelLock
(ActiveLock _ i
)) _
= Just
$ CmdInputSelLock i
282 commandOfSelectable IMTextInput
(SelScoreLock _ _
(ActiveLock _ i
)) _
= Just
$ CmdInputSelLock i
283 commandOfSelectable IMTextInput
(SelLockUnset _
(ActiveLock _ i
)) _
= Just
$ CmdInputSelLock i
284 commandOfSelectable IMTextInput
(SelReadNote note
) _
= Just
$ CmdInputCodename
$ noteAuthor note
285 commandOfSelectable IMTextInput
(SelSolution note
) _
= Just
$ CmdInputCodename
$ noteAuthor note
286 commandOfSelectable IMTextInput
(SelSecured note
) _
= Just
$ CmdInputCodename
$ lockOwner
$ noteOn note
287 commandOfSelectable IMTextInput
(SelRandom name
) _
= Just
$ CmdInputCodename name
288 commandOfSelectable IMTextInput
(SelUndeclared undecl
) _
= Just
$ CmdInputSelUndecl undecl
289 commandOfSelectable _ _ _
= Nothing
291 helpOfSelectable
(SelTut
False) = Just
"Enter tutorials"
292 helpOfSelectable
(SelTut
True) = Just
"Revisit tutorials"
293 helpOfSelectable
(SelInitLock _
False) = Just
"Attempt lock"
294 helpOfSelectable
(SelInitLock _
True) = Just
"Revisit solved lock"
295 helpOfSelectable SelOurLock
= Just
297 helpOfSelectable
(SelSelectedCodeName name
) = Just
$
298 "Currently viewing player "++name
++"."
299 helpOfSelectable SelRelScore
= Just
300 "The extent to which you are held in higher esteem than this player."
301 helpOfSelectable SelRelScoreComponent
= Just
302 "Contribution to total relative esteem."
303 helpOfSelectable
(SelLock
(ActiveLock name i
)) = Just
$
304 name
++"'s lock "++[lockIndexChar i
]++"."
305 helpOfSelectable
(SelLockUnset
True _
) = Just
307 helpOfSelectable
(SelLockUnset
False _
) = Just
308 "An empty lock slot."
309 helpOfSelectable
(SelUndeclared _
) = Just
310 "Declare your solution to a lock by securing a note on it behind a lock of your own."
311 helpOfSelectable
(SelRandom _
) = Just
312 "Random set of players. Colours show relative esteem, bright red (-3) to bright green (+3)."
313 helpOfSelectable
(SelScoreLock
(Just name
) Nothing _
) = Just
$
314 "Your lock. "++name
++" can not not unlock it."
315 helpOfSelectable
(SelScoreLock
(Just name
) (Just AccessedPrivy
) _
) = Just
$
316 "Your lock. "++name
++" can unlock it: -1 to relative esteem."
317 helpOfSelectable
(SelScoreLock
(Just name
) (Just AccessedPub
) _
) = Just
318 "Your lock. Its secrets have been publically revealed: -1 to relative esteem."
319 helpOfSelectable
(SelScoreLock
(Just name
) (Just AccessedEmpty
) _
) = Just
$
320 "Your empty lock slot. "++name
++" can unlock all your locks: -1 to relative esteem."
321 helpOfSelectable
(SelScoreLock Nothing Nothing
(ActiveLock name _
)) = Just
$
322 name
++"'s lock. You can not unlock it."
323 helpOfSelectable
(SelScoreLock Nothing
(Just AccessedPrivy
) (ActiveLock name _
)) = Just
$
324 name
++"'s lock. You can unlock it: +1 to relative esteem."
325 helpOfSelectable
(SelScoreLock Nothing
(Just AccessedPub
) (ActiveLock name _
)) = Just
$
326 name
++"'s lock. Its secrets have been publically revealed: +1 to relative esteem."
327 helpOfSelectable
(SelScoreLock Nothing
(Just AccessedEmpty
) (ActiveLock name _
)) = Just
$
328 name
++"'s empty lock slot. You can unlock all "++name
++"'s locks: +1 to relative esteem."
329 helpOfSelectable
(SelReadNote note
) = Just
$
330 "You have read "++noteAuthor note
++"'s note on this lock."
331 helpOfSelectable SelReadNoteSlot
= Just
332 "Reading three notes on this lock would suffice to reveal its secrets."
333 helpOfSelectable
(SelSecured note
) = let ActiveLock owner idx
= noteOn note
in
334 Just
$ "Secured note on "++owner
++"'s lock "++[lockIndexChar idx
]++"."
335 helpOfSelectable
(SelSolution note
) = Just
$ case noteBehind note
of
336 Just
(ActiveLock owner idx
) -> owner
++
337 " has secured their note on this lock behind their lock " ++ [lockIndexChar idx
] ++ "."
338 Nothing
-> noteAuthor note
++ "'s note on this lock is public knowledge."
339 helpOfSelectable
(SelAccessed name
) = Just
$
340 name
++ " did not pick this lock, but learnt how to unlock it by reading three notes on it."
341 helpOfSelectable SelPublicLock
= Just
342 "Notes behind retired or public locks are public; a lock with three public notes on it is public."
343 helpOfSelectable
(SelAccessedInfo meth
) = Just
$ case meth
of
344 AccessedSolved
-> "You picked this lock and declared your solution, so may read any notes it secures."
345 AccessedPublic
-> "The secrets of this lock have been publically revealed."
346 AccessedUndeclared
-> "You have picked this lock, but are yet to declare your solution."
348 "Having read three notes on others' solutions to this lock, you have unravelled its secrets."
349 helpOfSelectable
(SelOldLock ls
) = Just
$
350 "Retired lock #"++show ls
++". Any notes which were secured by the lock are now public knowledge."
351 helpOfSelectable SelLockPath
= Just
352 "Select a lock by its name. The names you give your locks are not revealed to others."
353 helpOfSelectable SelPrivyHeader
= Just
354 "Notes on this lock declared by players who picked the lock."
355 helpOfSelectable SelNotesHeader
= Just
356 "Notes secured by this lock. These notes are read by everyone who can unlock the lock."
357 helpOfSelectable
(SelToolWrench
False) = Just
"The wrench, one of your lockpicking tools. Click and drag to move."
358 helpOfSelectable
(SelToolWrench
True) = Just
"The wrench, currently in motion. It will keep moving until it is blocked."
359 helpOfSelectable SelToolHook
= Just
"The hook, one of your lockpicking tools. Click and drag to move, use mousewheel to turn."
361 cmdAtMousePos pos
@(mPos
,central
) im selMode
= do
362 buttons
<- concatMap fst <$> getButtons im
363 sels
<- gets registeredSelectables
364 return $ listToMaybe $
366 | button
<- buttons
, mPos
== buttonPos button
, central
]
367 ++ maybe [] (\isRight
->
369 | Just sel
<- [Map
.lookup mPos sels
]
370 , Just cmd
<- [ commandOfSelectable im sel isRight
] ])
373 helpAtMousePos
:: (HexVec
, Bool) -> InputMode
-> UIM
(Maybe [Char])
374 helpAtMousePos
(mPos
,_
) _
=
375 gets
$ (helpOfSelectable
<=< Map
.lookup mPos
) . registeredSelectables
378 data UIOptButton a
= UIOptButton
{ getUIOpt
:: UIOptions
->a
, setUIOpt
:: a
->UIOptions
->UIOptions
,
379 uiOptVals
:: [a
], uiOptPos
:: HexVec
, uiOptGlyph
:: a
->Glyph
, uiOptDescr
:: a
->String,
380 uiOptModes
:: [InputMode
], onSet
:: Maybe (a
-> UIM
()) }
382 -- non-uniform type, so can't use a list...
383 uiOB1
= UIOptButton useFiveColouring
(\v o
-> o
{useFiveColouring
=v
}) [True,False]
384 (periphery
0 +^
3 *^ hu
+^ neg hv
) UseFiveColourButton
385 (\v -> if v
then "Adjacent pieces get different colours" else
386 "Pieces are coloured according to type")
387 [IMPlay
, IMReplay
, IMEdit
] Nothing
388 uiOB2
= UIOptButton showBlocks
(\v o
-> o
{showBlocks
=v
}) [ShowBlocksBlocking
,ShowBlocksAll
,ShowBlocksNone
]
389 (periphery
0 +^
2 *^ hu
+^
2 *^ neg hv
) ShowBlocksButton
391 ShowBlocksBlocking
-> "Blocking forces are annotated"
392 ShowBlocksAll
-> "Blocked and blocking forces are annotated"
393 ShowBlocksNone
-> "Blockage annotations disabled")
394 [IMPlay
, IMReplay
] Nothing
395 uiOB3
= UIOptButton whsButtons
(\v o
-> o
{whsButtons
=v
}) [Nothing
, Just WHSSelected
, Just WHSWrench
, Just WHSHook
]
396 (periphery
3 +^
3 *^ hv
) WhsButtonsButton
398 Nothing
-> "Click to show (and rebind) keyboard control buttons."
399 Just whs
-> "Showing buttons for controlling " ++ case whs
of
400 WHSSelected
-> "selected piece; right-click to rebind"
401 WHSWrench
-> "wrench; right-click to rebind"
402 WHSHook
-> "hook; right-click to rebind")
403 [IMPlay
, IMEdit
] Nothing
404 uiOB4
= UIOptButton showButtonText
(\v o
-> o
{showButtonText
=v
}) [True,False]
405 (periphery
0 +^
2 *^ hu
+^
3 *^ hv
) ShowButtonTextButton
406 (\v -> if v
then "Help text enabled" else
407 "Help text disabled")
408 [IMPlay
, IMEdit
, IMReplay
, IMMeta
, IMInit
] Nothing
409 uiOB5
= UIOptButton fullscreen
(\v o
-> o
{fullscreen
=v
}) [True,False]
410 (periphery
0 +^
4 *^ hu
+^
2 *^ hv
) FullscreenButton
411 (\v -> if v
then "Fullscreen mode active" else "Windowed mode active")
412 [IMPlay
, IMEdit
, IMReplay
, IMMeta
, IMInit
] (Just
$ const $ initVideo
0 0)
413 uiOB6
= UIOptButton useSounds
(\v o
-> o
{useSounds
=v
}) [True,False]
414 (periphery
0 +^
4 *^ hu
+^ hv
) UseSoundsButton
415 (\v -> if v
then "Sound effects enabled" else
416 "Sound effects disabled")
417 [IMPlay
, IMEdit
, IMReplay
] Nothing
419 drawUIOptionButtons
:: InputMode
-> UIM
()
420 drawUIOptionButtons mode
= do
421 drawUIOptionButton mode uiOB1
422 drawUIOptionButton mode uiOB2
423 drawUIOptionButton mode uiOB3
424 drawUIOptionButton mode uiOB4
425 drawUIOptionButton mode uiOB5
427 drawUIOptionButton mode uiOB6
429 drawUIOptionButton im b
= when (im `
elem` uiOptModes b
) $ do
430 value <- gets
$ getUIOpt b
. uiOptions
431 renderToMain
$ mapM_ (\g
-> drawAtRel g
(uiOptPos b
))
432 [HollowGlyph
$ obscure purple
, uiOptGlyph b
value]
433 describeUIOptionButton
:: UIOptButton a
-> MaybeT UIM
String
434 describeUIOptionButton b
= do
435 value <- gets
$ getUIOpt b
. uiOptions
436 return $ uiOptDescr b
value
437 -- XXX: hand-hacking lenses...
438 toggleUIOption
(UIOptButton getopt setopt vals _ _ _ _ monSet
) = do
439 value <- gets
$ getopt
. uiOptions
440 let value' = cycle vals
!! max 0 (1 + fromMaybe 0 (elemIndex value vals
))
441 modifyUIOptions
$ setopt
value'
444 Just onSet
-> onSet
value'
446 readUIConfigFile
:: UIM
()
447 readUIConfigFile
= do
448 path
<- liftIO
$ confFilePath
"SDLUI.conf"
449 mOpts
<- liftIO
$ readReadFile path
451 Just opts
-> modify
$ \s
-> s
{uiOptions
= opts
}
453 writeUIConfigFile
:: UIM
()
454 writeUIConfigFile
= do
455 path
<- liftIO
$ confFilePath
"SDLUI.conf"
456 opts
<- gets uiOptions
458 liftIO
$ writeFile path
$ show opts
460 readBindings
:: UIM
()
462 path
<- liftIO
$ confFilePath
"bindings"
463 mbdgs
<- liftIO
$ readReadFile path
465 Just bdgs
-> modify
$ \s
-> s
{uiKeyBindings
= bdgs
}
467 writeBindings
:: UIM
()
469 path
<- liftIO
$ confFilePath
"bindings"
470 bdgs
<- gets uiKeyBindings
472 liftIO
$ writeFile path
$ show bdgs
474 getBindings
:: InputMode
-> UIM
[(Char, Command
)]
475 getBindings mode
= do
476 uibdgs
<- gets
(Map
.findWithDefault
[] mode
. uiKeyBindings
)
477 return $ uibdgs
++ bindings mode
479 paintTiles
:: [ Maybe Tile
]
482 , Just
$ ArmTile zero
False
483 , Just
$ PivotTile zero
484 , Just
$ SpringTile Relaxed zero
485 , Just
$ BlockTile
[]
489 paintTileCmds
= map (maybe CmdDelete CmdTile
) paintTiles
491 getEffPaintTileIndex
:: UIM
Int
492 getEffPaintTileIndex
= do
493 mods
<- liftIO getModState
494 if any (`
elem` mods
) [KeyModLeftCtrl
, KeyModRightCtrl
]
495 then return $ length paintTiles
- 1
496 else gets paintTileIndex
498 paintButtonStart
:: HexVec
499 paintButtonStart
= periphery
0 +^
(- length paintTiles `
div`
2)*^hv
501 drawPaintButtons
:: UIM
()
502 drawPaintButtons
= do
503 pti
<- getEffPaintTileIndex
504 renderToMain
$ sequence_ [
506 let gl
= case paintTiles
!!i
of
507 Nothing
-> HollowInnerGlyph
$ dim purple
508 Just t
-> TileGlyph t
$ dim purple
510 when selected
$ drawAtRel cursorGlyph pos
511 | i
<- take (length paintTiles
) [0..]
512 , let pos
= paintButtonStart
+^ i
*^hv
513 , let selected
= i
== pti
516 periphery
0 = ((3*maxlocksize
)`
div`
2)*^hu
+^
((3*maxlocksize
)`
div`
4)*^hv
517 periphery n
= rotate n
$ periphery
0
518 -- ^ XXX only peripheries 0,2,3,5 are guaranteed to be on-screen!
519 --messageLineStart = (maxlocksize+1)*^hw
520 messageLineCentre
= ((maxlocksize
+1)`
div`
2)*^hw
+^
((maxlocksize
+1+1)`
div`
2)*^neg hv
522 -- XXX HACK: the n=8 line is crowded
523 titlePos n
= titlePos
' $ if n
== 8 then 9 else n
524 where titlePos
' n
= n
*^hv
+^
(n`
div`
2)*^hu
526 screenWidthHexes
,screenHeightHexes
:: Int
527 screenWidthHexes
= 32
528 screenHeightHexes
= 26
529 getGeom
:: UIM
(SVec
, Int)
533 let scrCentre
= SVec
(w`
div`
2) (h`
div`
2)
534 -- |size is the greatest integer such that
535 -- and [2*size*screenWidthHexes < width
536 -- , 3*ysize size*screenHeightHexes < height]
537 -- where ysize size = round $ fi size / sqrt 3
538 -- Minimum allowed size is 2 (get segfaults on SDL_FreeSurface with 1).
539 let size
= max 2 $ min ((w
-1)`
div`
(2*screenWidthHexes
))
540 (floor $ sqrt 3 * (0.5 + fi
((h
-1)`
div`
(3*screenHeightHexes
))))
541 return (scrCentre
, size
)
543 data DrawArgs
= DrawArgs
[PieceIdx
] Bool [Alert
] GameState UIOptions
544 deriving (Eq
, Ord
, Show)
546 drawMainGameState
:: [PieceIdx
] -> Bool -> [Alert
] -> GameState
-> UIM
()
547 drawMainGameState highlight colourFixed alerts st
= do
548 uiopts
<- gets uiOptions
549 drawMainGameState
' $ DrawArgs highlight colourFixed alerts st uiopts
551 drawMainGameState
' :: DrawArgs
-> UIM
()
552 drawMainGameState
' args
@(DrawArgs highlight colourFixed alerts st uiopts
) = do
553 lastArgs
<- gets lastDrawArgs
554 when (case lastArgs
of
556 Just
(DrawArgs _ _ lastAlerts lastSt _
) ->
557 lastAlerts
/= alerts || lastSt
/= st
) $
558 modify
$ \ds
-> ds
{ animFrame
= 0, nextAnimFrameAt
= Nothing
}
560 lastAnimFrame
<- gets animFrame
561 now
<- liftIO getTicks
562 anim
<- gets
(maybe False (<now
) . nextAnimFrameAt
)
564 modify
$ \ds
-> ds
{ animFrame
= lastAnimFrame
+1, nextAnimFrameAt
= Nothing
}
565 animFrameToDraw
<- gets animFrame
566 void
$ if lastArgs
== Just args
&& lastAnimFrame
== animFrameToDraw
568 vidSurf
<- liftIO getVideoSurface
569 gsSurf
<- gets
(fromJust . gsSurface
)
570 liftIO
$ blitSurface gsSurf Nothing vidSurf Nothing
572 modify
$ \ds
-> ds
{ lastDrawArgs
= Just args
}
574 -- split the alerts at intermediate states, and associate alerts
575 -- to the right states:
576 let (globalAlerts
,transitoryAlerts
) = partition isGlobalAlert alerts
577 splitAlerts frameAs
(AlertIntermediateState st
' : as) =
578 (frameAs
,st
',True) : splitAlerts
[] as
579 splitAlerts frameAs
(a
:as) =
580 splitAlerts
(a
:frameAs
) as
581 splitAlerts frameAs
[] = [(frameAs
,st
,False)]
582 isGlobalAlert
(AlertAppliedForce _
) = False
583 isGlobalAlert
(AlertIntermediateState _
) = False
584 isGlobalAlert _
= True
585 let animAlertedStates
= nub $
586 let ass
= splitAlerts
[] transitoryAlerts
587 in if last ass
== ([],st
,False) then ass
else ass
++ [([],st
,False)]
588 let frames
= length animAlertedStates
589 let (drawAlerts
',drawSt
,isIntermediate
) = animAlertedStates
!! animFrameToDraw
590 let drawAlerts
= drawAlerts
' ++ globalAlerts
591 -- let drawAlerts = takeWhile (/= AlertIntermediateState drawSt) alerts
592 nextIsSet
<- gets
(isJust . nextAnimFrameAt
)
593 when (not nextIsSet
&& frames
> animFrameToDraw
+1) $ do
594 time
<- gets
((if isIntermediate
then uiAnimTime
else shortUiAnimTime
) . uiOptions
)
595 modify
$ \ds
-> ds
{ nextAnimFrameAt
= Just
$ now
+ time
}
597 let board
= stateBoard drawSt
598 lastCol
<- gets dispLastCol
599 let coloured
= colouredPieces colourFixed drawSt
600 let colouring
= if useFiveColouring uiopts
601 then boardColouring drawSt coloured lastCol
602 else pieceTypeColouring drawSt coloured
603 modify
$ \ds
-> ds
{ dispLastCol
= colouring
}
604 gsSurf
<- gets
(fromJust . gsSurface
)
605 renderToMainWithSurf gsSurf
$ do
606 let tileGlyphs
= ownedTileGlyph colouring highlight
<$> board
608 applyAlert
(AlertAppliedForce f
@(Torque idx tdir
)) =
609 let poss
= case getpp drawSt idx
of
610 PlacedPiece pos
(Pivot arms
) -> pos
: map (+^pos
) arms
611 PlacedPiece pos
(Hook arm _
) -> [arm
+^pos
]
613 rotateGlyph
(TileGlyph
(ArmTile dir _
) col
) =
614 ArmGlyph
(-tdir
) dir col
615 rotateGlyph
(TileGlyph
(PivotTile dir
) col
) =
616 PivotGlyph
(-tdir
) dir col
617 in flip (foldr . Map
.adjust
$ rotateGlyph
) poss
618 applyAlert
(AlertAppliedForce f
@(Push idx dir
)) =
619 displaceFootprint
. displaceSprings
621 displace
= DisplacedGlyph
$ neg dir
622 displaceSpringGlyph isRoot
(TileGlyph
(SpringTile extn sdir
) col
) =
623 displaceSpringGlyph isRoot
$ SpringGlyph zero zero extn sdir col
624 displaceSpringGlyph isRoot
(SpringGlyph rdisp edisp extn sdir col
)
625 | isRoot
= SpringGlyph
(neg dir
) edisp extn sdir col
626 |
otherwise = SpringGlyph rdisp
(neg dir
) extn sdir col
627 displaceSpringGlyph _ glyph
= glyph
629 flip (foldr . Map
.adjust
$ displace
) $
630 plPieceFootprint
$ getpp drawSt idx
632 displaceSpring isRoot c
@(Connection root end
(Spring sdir _
))
633 | dir `
elem`
[sdir
,neg sdir
] =
634 Map
.adjust
(displaceSpringGlyph isRoot
) $
636 then sdir
+^ locusPos drawSt root
637 else neg sdir
+^ locusPos drawSt end
639 flip (foldr . Map
.adjust
$ displace
) $
640 connectionFootPrint drawSt c
642 displaceSpring _ _
= id
645 flip (foldr $ displaceSpring
True) (springsRootAtIdx drawSt idx
) .
646 flip (foldr $ displaceSpring
False) (springsEndAtIdx drawSt idx
)
649 applyAlerts
= flip (foldr applyAlert
) drawAlerts
652 sequence_ [ drawAt glyph pos |
653 (pos
,glyph
) <- Map
.toList
$ applyAlerts tileGlyphs
656 when (showBlocks uiopts
/= ShowBlocksNone
) $ sequence_
657 $ [drawBlocked drawSt colouring
False force |
658 showBlocks uiopts
== ShowBlocksAll
,
659 AlertBlockedForce force
<- drawAlerts
]
660 ++ [ drawBlocked drawSt colouring
True force
661 | AlertBlockingForce force
<- drawAlerts
]
662 -- ++ [ drawBlocked drawSt colouring True force |
663 -- AlertResistedForce force <- drawAlerts ]
664 ++ [ drawAt CollisionMarker pos
665 | AlertCollision pos
<- drawAlerts
]
666 -- ++ [ drawApplied drawSt colouring force
667 -- | AlertAppliedForce force <- drawAlerts ]
668 vidSurf
<- liftIO getVideoSurface
669 liftIO
$ blitSurface gsSurf Nothing vidSurf Nothing
671 playAlertSounds
:: GameState
-> [Alert
] -> UIM
()
673 playAlertSounds st alerts
= do
674 use
<- useSounds
<$> gets uiOptions
675 when use
$ mapM_ (maybe (return ()) playSound
. alertSound
) alerts
677 alertSound
(AlertBlockedForce force
) =
678 let PlacedPiece _ piece
= getpp st
$ forceIdx force
680 Wrench _
-> Just
"wrenchblocked"
681 Hook _ _
-> if isPush force
then Just
"hookblocked" else Just
"hookarmblocked"
683 alertSound
(AlertDivertedWrench _
) = Just
"wrenchscrape"
684 alertSound
(AlertAppliedForce
(Torque idx _
))
685 | isPivot
.placedPiece
.getpp st
$ idx
= Just
"pivot"
686 | isTool
.placedPiece
.getpp st
$ idx
= Just
"toolmove"
687 alertSound
(AlertAppliedForce
(Push idx dir
))
688 | isBall
.placedPiece
.getpp st
$ idx
= Just
"ballmove"
689 | isTool
.placedPiece
.getpp st
$ idx
= Just
"toolmove"
691 (align
,newLen
) <- listToMaybe [(align
,newLen
)
692 | c
@(Connection
(startIdx
,_
) (endIdx
,_
) (Spring outDir natLen
)) <- connections st
693 , let align
= (if outDir
== dir
then 1 else if outDir
== neg dir
then -1 else 0)
694 * (if idx
== startIdx
then 1 else if idx
== endIdx
then -1 else 0)
696 , let newLen
= connectionLength st c
]
697 return $ "spring" ++ (if align
== 1 then "contract" else "extend")
698 ++ show (min newLen
12)
699 alertSound AlertUnlocked
= Just
"unlocked"
700 alertSound _
= Nothing
701 playSound
:: String -> UIM
()
702 playSound sound
= void
.runMaybeT
$ do
703 ss
<- MaybeT
$ Map
.lookup sound
<$> gets sounds
705 liftIO
$ randFromList ss
>>= \(Just s
) -> void
$ tryPlayChannel
(-1) s
0
706 randFromList
:: [a
] -> IO (Maybe a
)
707 randFromList
[] = return Nothing
708 randFromList
as = (Just
.(as!!)) <$> randomRIO (0,length as - 1)
710 playAlertSounds _ _
= return ()
714 drawMiniLock
:: Lock
-> HexVec
-> UIM
()
715 drawMiniLock lock v
= do
716 surface
<- gets miniLocks
>>= maybe new
return . Map
.lookup lock
717 renderToMain
$ blitAt surface v
722 let minisize
= size `
div`
ceiling (lockSize lock
% miniLocksize
)
723 let width
= size
*2*(miniLocksize
*2+1)
724 let height
= ceiling $ fi size
* sqrt 3 * fi
(miniLocksize
*2+1+1)
725 surf
<- liftIO
$ createRGBSurface
[] width height
16 0 0 0 0
726 liftIO
$ setColorKey surf
[SrcColorKey
,RLEAccel
] $ Pixel
0
727 uiopts
<- gets uiOptions
728 let st
= snd $ reframe lock
729 coloured
= colouredPieces
False st
730 colouring
= if useFiveColouring uiopts
731 then boardColouring st coloured Map
.empty
732 else pieceTypeColouring st coloured
733 draw
= sequence_ [ drawAt glyph pos |
734 (pos
,glyph
) <- Map
.toList
$ ownedTileGlyph colouring
[] <$> stateBoard st
]
735 liftIO
$ runRenderM draw emptyCachedGlyphs
$
736 RenderContext surf Nothing
(PHS zero
) (SVec
(width`
div`
2) (height`
div`
2)) zero minisize Nothing
738 modify
$ \ds
-> ds
{ miniLocks
= Map
.insert lock surf
$ miniLocks ds
}
741 -- | TODO: do this more cleverly
743 (>=50).Map
.size
<$> gets miniLocks
>>? clearMiniLocks
744 clearMiniLocks
= modify
$ \ds
-> ds
{ miniLocks
= Map
.empty}
746 drawEmptyMiniLock v
=
747 renderToMain
$ recentreAt v
$ rescaleRender
6 $ drawAtRel
(HollowInnerGlyph
$ dim white
) zero
749 getBindingStr
:: InputMode
-> UIM
(Command
-> String)
750 getBindingStr mode
= do
751 setting
<- gets settingBinding
752 uibdgs
<- gets
(Map
.findWithDefault
[] mode
. uiKeyBindings
)
754 if Just cmd
== setting
then "??"
755 else maybe "" showKey
$ findBinding
(uibdgs
++ bindings mode
) cmd
)
757 drawButtons
:: InputMode
-> UIM
()
758 drawButtons mode
= do
759 buttons
<- getButtons mode
760 bindingStr
<- getBindingStr mode
761 showBT
<- gets
(showButtonText
. uiOptions
)
762 smallFont
<- gets dispFontSmall
763 renderToMain
$ sequence_ $ concat [ [ do
764 drawAtRel
(ButtonGlyph col
) v
765 (if length bdg
> 2 then withFont smallFont
else id) $
766 renderStrColAt buttonTextCol bdg v
768 withFont smallFont
$ recentreAt v
$ rescaleRender
(1/4) $
769 sequence_ [ renderStrColAtLeft white s dv |
(s
,dv
) <- helps
]
770 |
(i
,(v
,bdg
,helps
)) <- enumerate
$ map (\b->(buttonPos b
, bindingStr
$ buttonCmd b
, buttonHelp b
)) buttonGroup
771 , let col
= dim
$ colourWheel
(base
+inc
*i
) ]
772 |
(buttonGroup
,(base
,inc
)) <- buttons
774 where enumerate
= zip [0..]
777 initMisc
= void
$ enableUnicode
True >> enableKeyRepeat
250 30 >> setCaption
"intricacy" "intricacy"
779 initVideo
:: Int -> Int -> UIM
()
781 liftIO
$ (((w
,h
)==(0,0) &&) . (InitVideo `
elem`
) <$> wasInit
[InitVideo
]) >>?
782 -- reset video so that passing (0,0) to setVideoMode sets to
783 -- current screen res rather than current window size
784 (quitSubSystem
[InitVideo
] >> initSubSystem
[InitVideo
] >> initMisc
)
786 fs
<- gets
(fullscreen
. uiOptions
)
788 (w
',h
') <- if fs ||
(w
,h
)/=(0,0) then return (w
,h
) else
790 -- use smaller dimensions than the screen's, to work around a bug
791 -- seen on mac, whereby a resizable window created with
792 -- (w,h)=(0,0), or even with the (w,h) given by getHardwareDimensions
793 -- after creating such a window, is reported to be larger than it
796 (w
',h
') <- getHardwareDimensions
797 return (4*w
'`
div`
5,4*h
'`
div`
5)
799 getHardwareDimensions
801 setVideoMode w
' h
' 0 $ if fs
then [Fullscreen
] else [Resizable
]
803 (w
',h
') <- liftIO getSurfaceDimensions
805 modify
$ \ds
-> ds
{ scrWidth
= w
' }
806 modify
$ \ds
-> ds
{ scrHeight
= h
' }
807 gssurf
<- liftIO
$ createRGBSurface
[] w
' h
' 16 0 0 0 0
808 modify
$ \ds
-> ds
{ gsSurface
= Just gssurf
, lastDrawArgs
= Nothing
}
811 let fontfn
= "VeraMoBd.ttf"
812 fontpath
<- liftIO
$ getDataPath fontfn
813 font
<- liftIO
$ TTF
.tryOpenFont fontpath size
814 smallFont
<- liftIO
$ TTF
.tryOpenFont fontpath
(2*size`
div`
3)
815 modify
$ \ds
-> ds
{ dispFont
= font
, dispFontSmall
= smallFont
}
817 useBG
<- gets
$ useBackground
. uiOptions
818 mbg
<- if useBG
then do
819 bgsurf
<- liftIO
$ createRGBSurface
[] w
' h
' 16 0 0 0 0
820 renderToMainWithSurf bgsurf
$ drawBasicBG
$ 2*max screenWidthHexes screenHeightHexes`
div`
3
823 modify
$ \ds
-> ds
{ bgSurface
= mbg
}
827 when (isNothing font
) $ liftIO
$ do
828 now
<- getCurrentTime
829 let text
= show now
++ ": Warning: font file not found at "++fontpath
++".\n"
831 appendFile "intricacy-warnings.log" text
834 getHardwareDimensions
= (videoInfoWidth
&&& videoInfoHeight
) <$> getVideoInfo
835 getSurfaceDimensions
= (surfaceGetWidth
&&& surfaceGetHeight
) <$> getVideoSurface
841 initialised
<- liftIO
$ tryOpenAudio defaultFrequency AudioS16Sys
1 1024
842 unless initialised
$ liftIO
$ do
843 now
<- getCurrentTime
844 let text
= show now
++ ": Warning: audio failed to initialise.\n"
846 appendFile "intricacy-warnings.log" text
847 -- liftIO $ querySpec >>= print
848 liftIO
$ allocateChannels
16
849 let seqWhileJust
(m
:ms
) = m
>>= \ret
-> case ret
of
851 Just a
-> (a
:) <$> seqWhileJust ms
852 soundsdir
<- liftIO
$ getDataPath
"sounds"
853 sounds
<- sequence [ do
854 chunks
<- liftIO
$ seqWhileJust
856 chunk
<- msum $ map (MaybeT
. tryLoadWAV
) paths
857 liftIO
$ volumeChunk chunk vol
860 , let paths
= [soundsdir
++ [pathSeparator
] ++ sound
++
861 "-" ++ (if n
< 10 then ('0':) else id) (show n
) ++ ext
862 | ext
<- [".ogg", ".wav"] ]
863 , let vol
= case sound
of
869 return (sound
,chunks
)
870 | sound
<- ["hookblocked","hookarmblocked","wrenchblocked","wrenchscrape","pivot","unlocked","ballmove","toolmove"]
871 ++ ["spring" ++ d
++ show l | d
<- ["extend","contract"], l
<- [1..12]] ]
872 -- liftIO $ print sounds
873 modify
$ \s
-> s
{ sounds
= Map
.fromList sounds
}
875 initAudio
= return ()
886 drawMsgLine
= void
.runMaybeT
$ do
888 [ MaybeT
$ gets message
889 , (dimWhiteCol
,) <$> MaybeT
(gets hoverStr
)
892 renderToMain
$ blankRow messageLineCentre
893 smallFont
<- gets dispFontSmall
895 (if length str
> screenWidthHexes
* 3 then withFont smallFont
else id) $
896 renderStrColAtCentre col str messageLineCentre
898 setMsgLineNoRefresh col str
= do
899 modify
$ \s
-> s
{ message
= Just
(col
,str
) }
901 setMsgLine col str
= setMsgLineNoRefresh col str
>> refresh
904 clearMsg
= modify
$ \s
-> s
{ message
= Nothing
}
906 drawTitle
(Just
(title
,n
)) = renderToMain
$ renderStrColAtCentre messageCol title
(titlePos n
)
907 drawTitle Nothing
= return ()
909 say
= setMsgLine messageCol
910 sayError
= setMsgLine errorCol
912 miniLockPos
= (-9)*^hw
+^ hu
913 lockLinePos
= 4*^hu
+^ miniLockPos
914 serverPos
= 12*^hv
+^
7*^neg hu
915 serverWaitPos
= serverPos
+^ hw
+^ neg hu
916 randomNamesPos
= 9*^hv
+^
2*^ neg hu
917 codenamePos
= (-6)*^hw
+^
6*^hv
918 undeclsPos
= 13*^neg hu
919 accessedOursPos
= 2*^hw
+^ codenamePos
920 locksPos
= hw
+^neg hv
921 retiredPos
= locksPos
+^
11*^hu
+^ neg hv
922 interactButtonsPos
= 9*^neg hu
+^
8*^hw
923 scoresPos
= codenamePos
+^
5*^hu
+^
2*^neg hv