resolve merge conflict
This commit is contained in:
commit
63ff896642
3 changed files with 19 additions and 20 deletions
|
@ -1,7 +1,6 @@
|
||||||
module Main where
|
module Main where
|
||||||
|
|
||||||
import Control.Monad (when)
|
import Control.Monad (when)
|
||||||
import Data.Maybe (fromMaybe)
|
|
||||||
import Data.Monoid ((<>))
|
import Data.Monoid ((<>))
|
||||||
import System.Exit (exitSuccess)
|
import System.Exit (exitSuccess)
|
||||||
import System.IO (readFile, writeFile)
|
import System.IO (readFile, writeFile)
|
||||||
|
@ -75,7 +74,7 @@ main :: IO ()
|
||||||
main = do
|
main = do
|
||||||
(Opts hd ml hs) <- execParser fullopts -- get CLI opts/args
|
(Opts hd ml hs) <- execParser fullopts -- get CLI opts/args
|
||||||
when hs (getHighScore >>= printM >> exitSuccess) -- show high score and exit
|
when hs (getHighScore >>= printM >> exitSuccess) -- show high score and exit
|
||||||
l <- fromMaybe pickLevel (return <$> ml) -- pick level prompt if necessary
|
l <- maybe pickLevel return ml -- pick level prompt if necessary
|
||||||
g <- playGame l (hdOptStr hd) -- play game
|
g <- playGame l (hdOptStr hd) -- play game
|
||||||
handleEndGame (_score g) -- save & print score
|
handleEndGame (_score g) -- save & print score
|
||||||
|
|
||||||
|
|
|
@ -143,8 +143,8 @@ rotateRaw b@(Block s o@(V2 xo yo) cs)
|
||||||
s == I && V2 xo (yo + 1) `elem` cs = rotateWith clockwise
|
s == I && V2 xo (yo + 1) `elem` cs = rotateWith clockwise
|
||||||
| otherwise = rotateWith counterclockwise
|
| otherwise = rotateWith counterclockwise
|
||||||
where
|
where
|
||||||
clockwise = (+ o) . (cwperp) . (subtract o)
|
clockwise = (+ o) . cwperp . subtract o
|
||||||
counterclockwise = (+ o) . LV.perp . (subtract o)
|
counterclockwise = (+ o) . LV.perp . subtract o
|
||||||
rotateWith dir = b & extra %~ fmap dir
|
rotateWith dir = b & extra %~ fmap dir
|
||||||
cwperp (V2 x y) = V2 y (-x)
|
cwperp (V2 x y) = V2 y (-x)
|
||||||
|
|
||||||
|
@ -160,7 +160,7 @@ coords b = b ^. origin : b ^. extra
|
||||||
bagFourTetriminoEach :: Seq.Seq Tetrimino -> IO (Tetrimino, Seq.Seq Tetrimino)
|
bagFourTetriminoEach :: Seq.Seq Tetrimino -> IO (Tetrimino, Seq.Seq Tetrimino)
|
||||||
bagFourTetriminoEach (t :<| ts) = pure (t, ts)
|
bagFourTetriminoEach (t :<| ts) = pure (t, ts)
|
||||||
bagFourTetriminoEach Empty =
|
bagFourTetriminoEach Empty =
|
||||||
bagFourTetriminoEach <=< shuffle . Seq.fromList . take 28 $ cycle [(I) ..]
|
bagFourTetriminoEach <=< shuffle . Seq.fromList . take 28 $ cycle [I ..]
|
||||||
|
|
||||||
-- | Initialize a game with a given level
|
-- | Initialize a game with a given level
|
||||||
initGame :: Int -> IO Game
|
initGame :: Int -> IO Game
|
||||||
|
@ -205,7 +205,7 @@ clearFullRows = do
|
||||||
modifying board $ M.filterWithKey $ \(V2 _ y) _ -> y `notElem` fullRows
|
modifying board $ M.filterWithKey $ \(V2 _ y) _ -> y `notElem` fullRows
|
||||||
-- Shift cells above full rows
|
-- Shift cells above full rows
|
||||||
modifying board $ M.mapKeysMonotonic $ over _y $ \y ->
|
modifying board $ M.mapKeysMonotonic $ over _y $ \y ->
|
||||||
y - (length $ filter (< y) fullRows)
|
y - length (filter (< y) fullRows)
|
||||||
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)
|
||||||
|
@ -260,8 +260,8 @@ blockStopped g = isStopped (g ^. board) (g ^. block)
|
||||||
isStopped :: Board -> Block -> Bool
|
isStopped :: Board -> Block -> Bool
|
||||||
isStopped brd = any stopped . coords
|
isStopped brd = any stopped . coords
|
||||||
where
|
where
|
||||||
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 :: Tetris ()
|
||||||
hardDrop = hardDroppedBlock >>= assign block
|
hardDrop = hardDroppedBlock >>= assign block
|
||||||
|
@ -277,8 +277,8 @@ hardDroppedBlock = do
|
||||||
, xo == x
|
, xo == x
|
||||||
, yo < y
|
, yo < y
|
||||||
]
|
]
|
||||||
minY = minimum $ (view _y) <$> blockCoords
|
minY = minimum $ view _y <$> blockCoords
|
||||||
dist = minimum $ (subtract 1) <$> (minY : diffs)
|
dist = minimum $ subtract 1 <$> (minY : diffs)
|
||||||
translateBy dist Down <$> use block
|
translateBy dist Down <$> use block
|
||||||
|
|
||||||
-- | Freeze current block
|
-- | Freeze current block
|
||||||
|
@ -326,7 +326,7 @@ shuffle xs
|
||||||
| null xs = mempty
|
| null xs = mempty
|
||||||
| otherwise = do
|
| otherwise = do
|
||||||
randomPosition <- getStdRandom (randomR (0, length xs - 1))
|
randomPosition <- getStdRandom (randomR (0, length xs - 1))
|
||||||
let (left, (y :<| ys)) = Seq.splitAt randomPosition xs
|
let (left, y :<| ys) = Seq.splitAt randomPosition xs
|
||||||
fmap (y <|) (shuffle $ left >< ys)
|
fmap (y <|) (shuffle $ left >< ys)
|
||||||
|
|
||||||
v2 :: (a, a) -> V2 a
|
v2 :: (a, a) -> V2 a
|
||||||
|
|
|
@ -163,7 +163,7 @@ drawGrid ui =
|
||||||
$ mconcat
|
$ mconcat
|
||||||
[ drawBlockCell NormalBlock <$> ui ^. (game . board)
|
[ drawBlockCell NormalBlock <$> ui ^. (game . board)
|
||||||
, blockMap NormalBlock (ui ^. (game . block))
|
, blockMap NormalBlock (ui ^. (game . block))
|
||||||
, case (ui ^. preview) of
|
, case ui ^. preview of
|
||||||
Nothing -> M.empty
|
Nothing -> M.empty
|
||||||
Just s -> blockMap (HardDropBlock s) (evalTetris hardDroppedBlock (ui ^. game))
|
Just s -> blockMap (HardDropBlock s) (evalTetris hardDroppedBlock (ui ^. game))
|
||||||
, emptyCellMap
|
, emptyCellMap
|
||||||
|
@ -174,7 +174,7 @@ drawGrid ui =
|
||||||
|
|
||||||
emptyCellMap :: Map Coord (Widget Name)
|
emptyCellMap :: Map Coord (Widget Name)
|
||||||
emptyCellMap = M.fromList
|
emptyCellMap = M.fromList
|
||||||
[ ((V2 x y), emptyGridCellW) | x <- [1 .. boardWidth], y <- [1 .. boardHeight] ]
|
[ (V2 x y, emptyGridCellW) | x <- [1 .. boardWidth], y <- [1 .. boardHeight] ]
|
||||||
|
|
||||||
emptyGridCellW :: Widget Name
|
emptyGridCellW :: Widget Name
|
||||||
emptyGridCellW = withAttr emptyAttr cw
|
emptyGridCellW = withAttr emptyAttr cw
|
||||||
|
@ -222,7 +222,7 @@ drawStats g =
|
||||||
]
|
]
|
||||||
|
|
||||||
drawStat :: String -> Int -> Widget Name
|
drawStat :: String -> Int -> Widget Name
|
||||||
drawStat s n = padLeftRight 1 $ str s <+> (padLeft Max $ str $ show n)
|
drawStat s n = padLeftRight 1 $ str s <+> padLeft Max (str $ show n)
|
||||||
|
|
||||||
drawLeaderBoard :: Game -> Widget Name
|
drawLeaderBoard :: Game -> Widget Name
|
||||||
drawLeaderBoard _ = emptyWidget
|
drawLeaderBoard _ = emptyWidget
|
||||||
|
@ -231,8 +231,8 @@ drawInfo :: Game -> Widget Name
|
||||||
drawInfo g = hLimit 18 -- size of next piece box
|
drawInfo g = hLimit 18 -- size of next piece box
|
||||||
$ vBox
|
$ vBox
|
||||||
[ drawNextShape (g ^. nextShape)
|
[ drawNextShape (g ^. nextShape)
|
||||||
, padTop (Pad 1) $ drawHelp
|
, padTop (Pad 1) drawHelp
|
||||||
, padTop (Pad 1) $ drawGameOver g
|
, padTop (Pad 1) (drawGameOver g)
|
||||||
]
|
]
|
||||||
|
|
||||||
drawNextShape :: Tetrimino -> Widget Name
|
drawNextShape :: Tetrimino -> Widget Name
|
||||||
|
@ -258,7 +258,7 @@ drawHelp =
|
||||||
$ padTopBottom 1
|
$ padTopBottom 1
|
||||||
$ vBox
|
$ vBox
|
||||||
$ map (uncurry drawKeyInfo)
|
$ map (uncurry drawKeyInfo)
|
||||||
$ [ ("Left" , "h, ←")
|
[ ("Left" , "h, ←")
|
||||||
, ("Right" , "l, →")
|
, ("Right" , "l, →")
|
||||||
, ("Down" , "j, ↓")
|
, ("Down" , "j, ↓")
|
||||||
, ("Rotate" , "k, ↑")
|
, ("Rotate" , "k, ↑")
|
||||||
|
@ -270,12 +270,12 @@ drawHelp =
|
||||||
|
|
||||||
drawKeyInfo :: String -> String -> Widget Name
|
drawKeyInfo :: String -> String -> Widget Name
|
||||||
drawKeyInfo action keys =
|
drawKeyInfo action keys =
|
||||||
(padRight Max $ padLeft (Pad 1) $ str action)
|
padRight Max (padLeft (Pad 1) $ str action)
|
||||||
<+> (padLeft Max $ padRight (Pad 1) $ str keys)
|
<+> padLeft Max (padRight (Pad 1) $ str keys)
|
||||||
|
|
||||||
drawGameOver :: Game -> Widget Name
|
drawGameOver :: Game -> Widget Name
|
||||||
drawGameOver g =
|
drawGameOver g =
|
||||||
if (isGameOver g)
|
if isGameOver g
|
||||||
then padLeftRight 4 $ withAttr gameOverAttr $ str "GAME OVER"
|
then padLeftRight 4 $ withAttr gameOverAttr $ str "GAME OVER"
|
||||||
else emptyWidget
|
else emptyWidget
|
||||||
|
|
||||||
|
|
Loading…
Add table
Reference in a new issue