Skip to content

Commit 330d8c3

Browse files
jsjs
js
authored and
js
committed
Added some temporary graphics for battle, can now make menu choices
1 parent e9bad35 commit 330d8c3

10 files changed

+49
-7
lines changed

Animation.hs

+21-1
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
module Animation where
22

33
import Graphics.UI.SDL as SDL
4+
import Graphics.UI.SDL.TTF as TTF
45

56
import Data.Word
67
import Data.Tiled
@@ -46,11 +47,30 @@ drawWalkingMode gs = do
4647
blitAnimations ((animation (player gs)) : animations gs) s (cameraPos gs)
4748
SDL.flip s
4849

50+
drawLabels :: [String] -> Position -> Surface -> Font -> IO()
51+
drawLabels [] _ _ _ = return ()
52+
drawLabels (x:xs) pos s fnt = do
53+
title <- renderTextSolid fnt x (Color 20 0 0)
54+
blitSurface title Nothing s (Just (Rect (floor $ xVal pos) (floor $ yVal pos) 200 200))
55+
drawLabels xs (Position ((xVal pos)) ((yVal pos) + 30)) s fnt
56+
57+
drawMenu :: GameState -> Surface -> IO ()
58+
drawMenu gs s = do
59+
let menu' = menu gs
60+
let pos' = menuPos menu'
61+
let gx' = gx gs
62+
blitSurface (menubg gx') Nothing s (Just (Rect (floor $ xVal pos') (floor $ yVal pos') 20 20 ))
63+
blitSurface (menumarker gx') Nothing s (Just (Rect (floor $ xVal pos') ((floor $ yVal pos') + 10 +(choice menu') *30) 20 20 ))
64+
drawLabels (labels menu') (Position (((xVal pos') +10.0)) (((yVal pos') + 10.0))) s (fnt gs)
65+
66+
return ()
67+
4968
drawFight :: GameState -> IO ()
5069
drawFight gs = do
5170
s <- getVideoSurface
5271
blitSurface (fightbg $ gx gs) Nothing s Nothing
53-
72+
blitSurface (enemyfire $ gx gs) Nothing s (Just (Rect 200 100 0 0))
73+
drawMenu gs s
5474
SDL.flip s
5575

5676
drawGamestate :: GameState -> IO ()

Event.hs

+3
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,7 @@ module Event where
22

33
import Graphics.UI.SDL as SDL
44
import Model
5+
import Logics
56

67
getEvents :: IO Event -> [Event] -> IO [Event]
78
getEvents pEvent es = do
@@ -22,6 +23,8 @@ handleFightEvent x gs =
2223
case x of
2324
KeyDown (Keysym SDLK_ESCAPE _ _) -> gs {gameActive = False}
2425
KeyDown (Keysym SDLK_a _ _ ) -> gs { gameMode = Model.AfterFight }
26+
KeyDown (Keysym SDLK_DOWN _ _ ) -> gs { menu = (menu gs) { choice = ((choice $ menu gs) + 1 ) `mod` (length $ labels $ menu gs) } }
27+
KeyDown (Keysym SDLK_RETURN _ _ ) -> activateMenuOption gs
2528
_ -> gs
2629

2730
handleWalkingEvent :: Event -> GameState -> GameState

Logics.hs

+4
Original file line numberDiff line numberDiff line change
@@ -58,3 +58,7 @@ updateGamestate gs t dt
5858
player' = updatePlayer (player gs) t dt
5959
cameraPos' = updateCamera (cameraPos gs) (playerPos $ player gs) (fromIntegral $ mapWidth $ currentMap gs) (fromIntegral $ mapHeight $ currentMap gs)
6060
gameMode' = checkForFight gs t
61+
62+
activateMenuOption :: GameState -> GameState
63+
activateMenuOption gs
64+
| otherwise = gs

Model.hs

+14-2
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
module Model where
22

33
import Graphics.UI.SDL as SDL
4+
import Graphics.UI.SDL.TTF as TTF
45

56
import Data.Word
67
import Data.Tiled
@@ -21,7 +22,16 @@ data Mode = Walking | Fight | AfterFight
2122

2223
data Graphics = Graphics {
2324
tileSurface :: Surface,
24-
fightbg :: Surface
25+
fightbg :: Surface,
26+
menumarker :: Surface,
27+
menubg :: Surface,
28+
enemyfire :: Surface
29+
}
30+
31+
data Menu = Menu {
32+
choice :: Int,
33+
labels :: [String],
34+
menuPos :: Position
2535
}
2636

2737
data GameState = GameState{
@@ -34,7 +44,9 @@ data GameState = GameState{
3444
gameMode :: Mode,
3545
rng :: StdGen,
3646
nextFight :: Int,
37-
gx :: Graphics
47+
gx :: Graphics,
48+
menu :: Menu,
49+
fnt :: Font
3850
}
3951

4052
data Animation = Animation {

enemyfire.png

972 Bytes
Loading

fight.png

61.6 KB
Loading

main.hs

+7-4
Original file line numberDiff line numberDiff line change
@@ -26,20 +26,23 @@ main = do
2626

2727
tiledMap <- Data.Tiled.loadMapFile "map.tmx"
2828
tileSurface <- SDLi.load (iSource $ head $ tsImages $ head $ mapTilesets tiledMap)
29-
--let image = head $ mapTilesets m
3029

3130
rng <- getStdGen
3231

3332
fnt <- openFont "font.ttf" 30
3433
sheet <- SDLi.load "playerWalkDown.png"
3534
bg <- SDLi.load "menubg.bmp"
3635
fightbg <- SDLi.load "fight.png"
36+
menumarker <- SDLi.load "menumarker.png"
37+
menubg <- SDLi.load "menubg.png"
38+
enemyfire <- SDLi.load "enemyfire.png"
3739

3840
t0 <- getTicks
3941

4042
let player = Player Down Stop (Position 300 300) (Animation sheet 26 4 250 t0 0 (Position 0 0))
41-
let gx = Graphics tileSurface fightbg
42-
let gs = (GameState True [] t0 player tiledMap (Position 32 32) Model.Walking rng 0 gx)
43+
let gx = Graphics tileSurface fightbg menumarker menubg enemyfire
44+
let menu = Menu 0 ["Attack", "Run"] (Position 0 340)
45+
let gs = (GameState True [] t0 player tiledMap (Position 32 32) Model.Walking rng 0 gx menu fnt)
4346
let gs' = setUpNextFight gs ( fromIntegral (t0+1000) )
4447

4548
gameLoop gs' t0
@@ -53,7 +56,7 @@ gameLoop gs lastTick = do
5356
let gs' = updateGamestate (handleEvents events gs) t (t - lastTick)
5457

5558
drawGamestate gs'
56-
putStrLn $ show $ gameMode gs
59+
--putStrLn $ show $ gameMode gs
5760
if gameActive gs'
5861
then gameLoop gs' t
5962
else return ()

menubg.bmp

1.83 MB
Binary file not shown.

menubg.png

5.05 KB
Loading

menumarker.png

864 Bytes
Loading

0 commit comments

Comments
 (0)