Refactor
This commit is contained in:
		
							parent
							
								
									bcd6b38978
								
							
						
					
					
						commit
						e8c6c804c5
					
				
					 3 changed files with 37 additions and 57 deletions
				
			
		| 
						 | 
					@ -1,3 +1,4 @@
 | 
				
			||||||
 | 
					{-# LANGUAGE FlexibleContexts #-}
 | 
				
			||||||
{-# LANGUAGE FlexibleInstances #-}
 | 
					{-# LANGUAGE FlexibleInstances #-}
 | 
				
			||||||
{-# LANGUAGE LambdaCase #-}
 | 
					{-# LANGUAGE LambdaCase #-}
 | 
				
			||||||
{-# LANGUAGE RankNTypes #-}
 | 
					{-# LANGUAGE RankNTypes #-}
 | 
				
			||||||
| 
						 | 
					@ -11,7 +12,6 @@ module Tetris
 | 
				
			||||||
  , rotate
 | 
					  , rotate
 | 
				
			||||||
  , hardDrop
 | 
					  , hardDrop
 | 
				
			||||||
  -- Game state handlers
 | 
					  -- Game state handlers
 | 
				
			||||||
  , execTetris
 | 
					 | 
				
			||||||
  , evalTetris
 | 
					  , evalTetris
 | 
				
			||||||
  -- Game state queries
 | 
					  -- Game state queries
 | 
				
			||||||
  , isGameOver
 | 
					  , isGameOver
 | 
				
			||||||
| 
						 | 
					@ -33,9 +33,10 @@ module Tetris
 | 
				
			||||||
import Prelude hiding (Left, Right)
 | 
					import Prelude hiding (Left, Right)
 | 
				
			||||||
import Control.Applicative ((<|>))
 | 
					import Control.Applicative ((<|>))
 | 
				
			||||||
import Control.Monad (forM_, mfilter, when, (<=<))
 | 
					import Control.Monad (forM_, mfilter, when, (<=<))
 | 
				
			||||||
import Control.Monad.IO.Class (MonadIO(..), liftIO)
 | 
					 | 
				
			||||||
 | 
					
 | 
				
			||||||
import Control.Monad.Trans.State (StateT(..), gets, evalStateT, execStateT)
 | 
					import Control.Monad.IO.Class (MonadIO(..), liftIO)
 | 
				
			||||||
 | 
					import Control.Monad.State.Class (MonadState, gets)
 | 
				
			||||||
 | 
					import Control.Monad.Trans.State (evalStateT)
 | 
				
			||||||
import Data.Map (Map)
 | 
					import Data.Map (Map)
 | 
				
			||||||
import qualified Data.Map as M
 | 
					import qualified Data.Map as M
 | 
				
			||||||
import Data.Sequence (Seq(..), (><))
 | 
					import Data.Sequence (Seq(..), (><))
 | 
				
			||||||
| 
						 | 
					@ -44,6 +45,7 @@ import Control.Lens hiding (Empty)
 | 
				
			||||||
import Linear.V2 (V2(..), _y)
 | 
					import Linear.V2 (V2(..), _y)
 | 
				
			||||||
import qualified Linear.V2 as LV
 | 
					import qualified Linear.V2 as LV
 | 
				
			||||||
import System.Random (getStdRandom, randomR)
 | 
					import System.Random (getStdRandom, randomR)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- Types and instances
 | 
					-- Types and instances
 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- | Tetris shape types
 | 
					-- | Tetris shape types
 | 
				
			||||||
| 
						 | 
					@ -83,14 +85,10 @@ data Game = Game
 | 
				
			||||||
  } deriving (Eq, Show)
 | 
					  } deriving (Eq, Show)
 | 
				
			||||||
makeLenses ''Game
 | 
					makeLenses ''Game
 | 
				
			||||||
 | 
					
 | 
				
			||||||
type TetrisT = StateT Game
 | 
					 | 
				
			||||||
type Tetris a = forall m. (Monad m) => TetrisT m a
 | 
					 | 
				
			||||||
 | 
					 | 
				
			||||||
evalTetris :: Tetris a -> Game -> a
 | 
					evalTetris :: Tetris a -> Game -> a
 | 
				
			||||||
evalTetris m = runIdentity . evalStateT m
 | 
					evalTetris m = runIdentity . evalStateT m
 | 
				
			||||||
 | 
					
 | 
				
			||||||
execTetris :: Tetris a -> Game -> Game
 | 
					type Tetris a = forall m. MonadState Game m => m a
 | 
				
			||||||
execTetris m = runIdentity . execStateT m
 | 
					 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- Translate class for direct translations, without concern for boundaries
 | 
					-- Translate class for direct translations, without concern for boundaries
 | 
				
			||||||
-- 'shift' concerns safe translations with boundaries
 | 
					-- 'shift' concerns safe translations with boundaries
 | 
				
			||||||
| 
						 | 
					@ -181,7 +179,7 @@ isGameOver :: Game -> Bool
 | 
				
			||||||
isGameOver g = blockStopped g && g ^. (block . origin) == startOrigin
 | 
					isGameOver g = blockStopped g && g ^. (block . origin) == startOrigin
 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- | The main game execution, this is executed at each discrete time step
 | 
					-- | The main game execution, this is executed at each discrete time step
 | 
				
			||||||
timeStep :: MonadIO m => TetrisT m ()
 | 
					timeStep :: (MonadIO m, MonadState Game m) => m ()
 | 
				
			||||||
timeStep = do
 | 
					timeStep = do
 | 
				
			||||||
  gets blockStopped >>= \case
 | 
					  gets blockStopped >>= \case
 | 
				
			||||||
    False -> gravitate
 | 
					    False -> gravitate
 | 
				
			||||||
| 
						 | 
					@ -193,11 +191,11 @@ timeStep = do
 | 
				
			||||||
      nextBlock
 | 
					      nextBlock
 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- | Gravitate current block, i.e. shift down
 | 
					-- | Gravitate current block, i.e. shift down
 | 
				
			||||||
gravitate :: Tetris ()
 | 
					gravitate :: MonadState Game m => m ()
 | 
				
			||||||
gravitate = shift Down
 | 
					gravitate = shift Down
 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- | If necessary: clear full rows and return the count
 | 
					-- | If necessary: clear full rows and return the count
 | 
				
			||||||
clearFullRows :: Tetris Int
 | 
					clearFullRows :: MonadState Game m => m Int
 | 
				
			||||||
clearFullRows = do
 | 
					clearFullRows = do
 | 
				
			||||||
  brd <- use board
 | 
					  brd <- use board
 | 
				
			||||||
  let rowSize r = length $ M.filterWithKey (\(V2 _ y) _ -> r == y) brd
 | 
					  let rowSize r = length $ M.filterWithKey (\(V2 _ y) _ -> r == y) brd
 | 
				
			||||||
| 
						 | 
					@ -210,7 +208,7 @@ clearFullRows = do
 | 
				
			||||||
  return $ length fullRows
 | 
					  return $ length fullRows
 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- | Empties row on 0, otherwise appends value (just keeps consecutive information)
 | 
					-- | Empties row on 0, otherwise appends value (just keeps consecutive information)
 | 
				
			||||||
addToRowClears :: Int -> Tetris ()
 | 
					addToRowClears :: MonadState Game m => Int -> m ()
 | 
				
			||||||
addToRowClears 0 = rowClears .= mempty
 | 
					addToRowClears 0 = rowClears .= mempty
 | 
				
			||||||
addToRowClears n = rowClears %= (|> n)
 | 
					addToRowClears n = rowClears %= (|> n)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
| 
						 | 
					@ -220,7 +218,7 @@ addToRowClears n = rowClears %= (|> n)
 | 
				
			||||||
-- Note I'm keeping rowClears as a sequence in case I want to award
 | 
					-- Note I'm keeping rowClears as a sequence in case I want to award
 | 
				
			||||||
-- more points for back to back clears, right now the scoring is more simple,
 | 
					-- more points for back to back clears, right now the scoring is more simple,
 | 
				
			||||||
-- but you do get more points for more rows cleared at once.
 | 
					-- but you do get more points for more rows cleared at once.
 | 
				
			||||||
updateScore :: Tetris ()
 | 
					updateScore :: MonadState Game m => m ()
 | 
				
			||||||
updateScore = do
 | 
					updateScore = do
 | 
				
			||||||
  multiplier <- (1 +) <$> use level
 | 
					  multiplier <- (1 +) <$> use level
 | 
				
			||||||
  clears <- latestOrZero <$> use rowClears
 | 
					  clears <- latestOrZero <$> use rowClears
 | 
				
			||||||
| 
						 | 
					@ -240,7 +238,7 @@ updateScore = do
 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- | Handle counterclockwise block rotation (if possible)
 | 
					-- | Handle counterclockwise block rotation (if possible)
 | 
				
			||||||
-- Allows wallkicks: http://tetris.wikia.com/wiki/TGM_rotation
 | 
					-- Allows wallkicks: http://tetris.wikia.com/wiki/TGM_rotation
 | 
				
			||||||
rotate :: Tetris ()
 | 
					rotate :: MonadState Game m => m ()
 | 
				
			||||||
rotate = do
 | 
					rotate = do
 | 
				
			||||||
  blk <- use block
 | 
					  blk <- use block
 | 
				
			||||||
  brd <- use board
 | 
					  brd <- use board
 | 
				
			||||||
| 
						 | 
					@ -264,10 +262,10 @@ isStopped brd = any stopped . coords
 | 
				
			||||||
  stopped = (||) <$> atBottom <*> (`M.member` brd) . translate Down
 | 
					  stopped = (||) <$> atBottom <*> (`M.member` brd) . translate Down
 | 
				
			||||||
  atBottom = (== 1) . view _y
 | 
					  atBottom = (== 1) . view _y
 | 
				
			||||||
 | 
					
 | 
				
			||||||
hardDrop :: Tetris ()
 | 
					hardDrop :: MonadState Game m => m ()
 | 
				
			||||||
hardDrop = hardDroppedBlock >>= assign block
 | 
					hardDrop = hardDroppedBlock >>= assign block
 | 
				
			||||||
 | 
					
 | 
				
			||||||
hardDroppedBlock :: Tetris Block
 | 
					hardDroppedBlock :: MonadState Game m => m Block
 | 
				
			||||||
hardDroppedBlock = do
 | 
					hardDroppedBlock = do
 | 
				
			||||||
  boardCoords <- M.keys <$> use board
 | 
					  boardCoords <- M.keys <$> use board
 | 
				
			||||||
  blockCoords <- coords <$> use block
 | 
					  blockCoords <- coords <$> use block
 | 
				
			||||||
| 
						 | 
					@ -283,13 +281,13 @@ hardDroppedBlock = do
 | 
				
			||||||
  translateBy dist Down <$> use block
 | 
					  translateBy dist Down <$> use block
 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- | Freeze current block
 | 
					-- | Freeze current block
 | 
				
			||||||
freezeBlock :: Tetris ()
 | 
					freezeBlock :: MonadState Game m => m ()
 | 
				
			||||||
freezeBlock = do
 | 
					freezeBlock = do
 | 
				
			||||||
  blk <- use block
 | 
					  blk <- use block
 | 
				
			||||||
  modifying board $ M.union $ M.fromList [ (c, _shape blk) | c <- coords blk ]
 | 
					  modifying board $ M.union $ M.fromList [ (c, _shape blk) | c <- coords blk ]
 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- | Replace block with next block
 | 
					-- | Replace block with next block
 | 
				
			||||||
nextBlock :: MonadIO m => TetrisT m ()
 | 
					nextBlock :: (MonadIO m, MonadState Game m) => m ()
 | 
				
			||||||
nextBlock = do
 | 
					nextBlock = do
 | 
				
			||||||
  bag <- use nextShapeBag
 | 
					  bag <- use nextShapeBag
 | 
				
			||||||
  (t, ts) <- liftIO $ bagFourTetriminoEach bag
 | 
					  (t, ts) <- liftIO $ bagFourTetriminoEach bag
 | 
				
			||||||
| 
						 | 
					@ -298,7 +296,7 @@ nextBlock = do
 | 
				
			||||||
  nextShapeBag .= ts
 | 
					  nextShapeBag .= ts
 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- | Try to shift current block; if shifting not possible, leave block where it is
 | 
					-- | Try to shift current block; if shifting not possible, leave block where it is
 | 
				
			||||||
shift :: Direction -> Tetris ()
 | 
					shift :: MonadState Game m => Direction -> m ()
 | 
				
			||||||
shift dir = do
 | 
					shift dir = do
 | 
				
			||||||
  brd <- use board
 | 
					  brd <- use board
 | 
				
			||||||
  blk <- use block
 | 
					  blk <- use block
 | 
				
			||||||
| 
						 | 
					
 | 
				
			||||||
| 
						 | 
					@ -1,3 +1,4 @@
 | 
				
			||||||
 | 
					{-# LANGUAGE FlexibleContexts #-}
 | 
				
			||||||
{-# LANGUAGE OverloadedStrings #-}
 | 
					{-# LANGUAGE OverloadedStrings #-}
 | 
				
			||||||
{-# LANGUAGE RankNTypes #-}
 | 
					{-# LANGUAGE RankNTypes #-}
 | 
				
			||||||
{-# LANGUAGE TemplateHaskell #-}
 | 
					{-# LANGUAGE TemplateHaskell #-}
 | 
				
			||||||
| 
						 | 
					@ -7,9 +8,7 @@ module UI.Game
 | 
				
			||||||
  ) where
 | 
					  ) where
 | 
				
			||||||
 | 
					
 | 
				
			||||||
import Control.Concurrent (threadDelay, forkIO)
 | 
					import Control.Concurrent (threadDelay, forkIO)
 | 
				
			||||||
import Control.Monad (void, forever, when, unless)
 | 
					import Control.Monad (void, forever)
 | 
				
			||||||
import Control.Monad.IO.Class (liftIO)
 | 
					 | 
				
			||||||
import Control.Monad.Trans.State (execStateT)
 | 
					 | 
				
			||||||
import Prelude hiding (Left, Right)
 | 
					import Prelude hiding (Left, Right)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
import Brick hiding (Down)
 | 
					import Brick hiding (Down)
 | 
				
			||||||
| 
						 | 
					@ -18,6 +17,8 @@ import qualified Brick.Widgets.Border as B
 | 
				
			||||||
import qualified Brick.Widgets.Border.Style as BS
 | 
					import qualified Brick.Widgets.Border.Style as BS
 | 
				
			||||||
import qualified Brick.Widgets.Center as C
 | 
					import qualified Brick.Widgets.Center as C
 | 
				
			||||||
import Control.Lens hiding (preview, op, zoom)
 | 
					import Control.Lens hiding (preview, op, zoom)
 | 
				
			||||||
 | 
					import Control.Monad.Extra (orM, unlessM)
 | 
				
			||||||
 | 
					import Control.Monad.IO.Class (liftIO)
 | 
				
			||||||
import qualified Graphics.Vty as V
 | 
					import qualified Graphics.Vty as V
 | 
				
			||||||
import qualified Graphics.Vty.CrossPlatform
 | 
					import qualified Graphics.Vty.CrossPlatform
 | 
				
			||||||
import qualified Graphics.Vty.Config
 | 
					import qualified Graphics.Vty.Config
 | 
				
			||||||
| 
						 | 
					@ -84,7 +85,9 @@ levelToDelay n = floor $ 400000 * (0.85 :: Double) ^ (2 * n)
 | 
				
			||||||
-- Handling events
 | 
					-- Handling events
 | 
				
			||||||
 | 
					
 | 
				
			||||||
handleEvent :: BrickEvent Name Tick -> EventM Name UI ()
 | 
					handleEvent :: BrickEvent Name Tick -> EventM Name UI ()
 | 
				
			||||||
handleEvent (AppEvent Tick                      ) = handleTick
 | 
					handleEvent (VtyEvent (V.EvKey (V.KChar 'r') [])) = restart
 | 
				
			||||||
 | 
					handleEvent (VtyEvent (V.EvKey (V.KChar 'q') [])) = halt
 | 
				
			||||||
 | 
					handleEvent (VtyEvent (V.EvKey V.KEsc        [])) = halt
 | 
				
			||||||
handleEvent (VtyEvent (V.EvKey V.KRight      [])) = exec (shift Right)
 | 
					handleEvent (VtyEvent (V.EvKey V.KRight      [])) = exec (shift Right)
 | 
				
			||||||
handleEvent (VtyEvent (V.EvKey V.KLeft       [])) = exec (shift Left)
 | 
					handleEvent (VtyEvent (V.EvKey V.KLeft       [])) = exec (shift Left)
 | 
				
			||||||
handleEvent (VtyEvent (V.EvKey V.KDown       [])) = exec (shift Down)
 | 
					handleEvent (VtyEvent (V.EvKey V.KDown       [])) = exec (shift Down)
 | 
				
			||||||
| 
						 | 
					@ -94,53 +97,31 @@ handleEvent (VtyEvent (V.EvKey (V.KChar 'j') [])) = exec (shift Down)
 | 
				
			||||||
handleEvent (VtyEvent (V.EvKey V.KUp         [])) = exec rotate
 | 
					handleEvent (VtyEvent (V.EvKey V.KUp         [])) = exec rotate
 | 
				
			||||||
handleEvent (VtyEvent (V.EvKey (V.KChar 'k') [])) = exec rotate
 | 
					handleEvent (VtyEvent (V.EvKey (V.KChar 'k') [])) = exec rotate
 | 
				
			||||||
handleEvent (VtyEvent (V.EvKey (V.KChar ' ') [])) =
 | 
					handleEvent (VtyEvent (V.EvKey (V.KChar ' ') [])) =
 | 
				
			||||||
  guarded
 | 
					  unlessM (orM [use paused, use (game . to isGameOver)]) $ do
 | 
				
			||||||
    (not . view paused)
 | 
					    zoom game hardDrop
 | 
				
			||||||
    (over game (execTetris hardDrop) . set locked True)
 | 
					    assign locked True
 | 
				
			||||||
handleEvent (VtyEvent (V.EvKey (V.KChar 'p') [])) =
 | 
					handleEvent (VtyEvent (V.EvKey (V.KChar 'p') [])) =
 | 
				
			||||||
  guarded
 | 
					  unlessM (orM [use locked, use (game . to isGameOver)]) $ do
 | 
				
			||||||
    (not . view locked)
 | 
					    modifying paused not
 | 
				
			||||||
    (over paused not)
 | 
					handleEvent (AppEvent Tick                      ) =
 | 
				
			||||||
handleEvent (VtyEvent (V.EvKey (V.KChar 'r') [])) = restart
 | 
					  unlessM (orM [use paused, use (game . to isGameOver)]) $ do
 | 
				
			||||||
handleEvent (VtyEvent (V.EvKey (V.KChar 'q') [])) = halt
 | 
					    zoom game timeStep
 | 
				
			||||||
handleEvent (VtyEvent (V.EvKey V.KEsc        [])) = halt
 | 
					    assign locked False
 | 
				
			||||||
handleEvent _ = pure ()
 | 
					handleEvent _ = pure ()
 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- | This common execution function is used for all game user input except hard
 | 
					-- | This common execution function is used for all game user input except hard
 | 
				
			||||||
-- drop and pause. If paused or locked (from hard drop) do nothing, else
 | 
					-- drop and pause. If paused or locked (from hard drop) do nothing, else
 | 
				
			||||||
-- execute the state computation.
 | 
					-- execute the state computation.
 | 
				
			||||||
exec :: Tetris () -> EventM Name UI ()
 | 
					exec :: Tetris () -> EventM Name UI ()
 | 
				
			||||||
exec op =
 | 
					exec = unlessM (orM [use paused, use locked, use (game . to isGameOver)]) . zoom game
 | 
				
			||||||
  guarded
 | 
					 | 
				
			||||||
    (not . \ui -> ui ^. paused || ui ^. locked)
 | 
					 | 
				
			||||||
    (game %~ execTetris op)
 | 
					 | 
				
			||||||
 | 
					 | 
				
			||||||
-- | This base execution function takes a predicate and only issues UI
 | 
					 | 
				
			||||||
-- modification when predicate passes and game is not over.
 | 
					 | 
				
			||||||
guarded :: (UI -> Bool) -> (UI -> UI) -> EventM Name UI ()
 | 
					 | 
				
			||||||
guarded p f = do
 | 
					 | 
				
			||||||
  ui <- get
 | 
					 | 
				
			||||||
  when (p ui && not (ui ^. game . to isGameOver)) $
 | 
					 | 
				
			||||||
    modify f
 | 
					 | 
				
			||||||
 | 
					 | 
				
			||||||
-- | Handles time steps, does nothing if game is over or paused
 | 
					 | 
				
			||||||
handleTick :: EventM Name UI ()
 | 
					 | 
				
			||||||
handleTick = do
 | 
					 | 
				
			||||||
  ui <- get
 | 
					 | 
				
			||||||
  unless (ui ^. paused || ui ^. game . to isGameOver) $ do
 | 
					 | 
				
			||||||
    -- awkward, should just mutate the inner state
 | 
					 | 
				
			||||||
    --zoom game timeStep
 | 
					 | 
				
			||||||
    g' <- execStateT timeStep $ ui ^. game
 | 
					 | 
				
			||||||
    game .= g'
 | 
					 | 
				
			||||||
    locked .= False
 | 
					 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- | Restart game at the same level
 | 
					-- | Restart game at the same level
 | 
				
			||||||
restart :: EventM Name UI ()
 | 
					restart :: EventM Name UI ()
 | 
				
			||||||
restart = do
 | 
					restart = do
 | 
				
			||||||
  lvl <- use $ game . level
 | 
					  lvl <- use $ game . level
 | 
				
			||||||
  g <- liftIO $ initGame lvl
 | 
					  g <- liftIO $ initGame lvl
 | 
				
			||||||
  game .= g
 | 
					  assign game g
 | 
				
			||||||
  locked .= False
 | 
					  assign locked False
 | 
				
			||||||
 | 
					
 | 
				
			||||||
-- Drawing
 | 
					-- Drawing
 | 
				
			||||||
 | 
					
 | 
				
			||||||
| 
						 | 
					
 | 
				
			||||||
| 
						 | 
					@ -19,6 +19,7 @@ library
 | 
				
			||||||
  build-depends:       base >= 4.7 && < 5
 | 
					  build-depends:       base >= 4.7 && < 5
 | 
				
			||||||
                     , brick
 | 
					                     , brick
 | 
				
			||||||
                     , containers
 | 
					                     , containers
 | 
				
			||||||
 | 
					                     , extra
 | 
				
			||||||
                     , lens
 | 
					                     , lens
 | 
				
			||||||
                     , linear
 | 
					                     , linear
 | 
				
			||||||
                     , mtl
 | 
					                     , mtl
 | 
				
			||||||
| 
						 | 
					
 | 
				
			||||||
		Loading…
	
	Add table
		Add a link
		
	
		Reference in a new issue