resolve merge conflict
This commit is contained in:
		
						commit
						63ff896642
					
				
					 3 changed files with 19 additions and 20 deletions
				
			
		| 
						 | 
				
			
			@ -143,8 +143,8 @@ rotateRaw b@(Block s o@(V2 xo yo) cs)
 | 
			
		|||
    s == I && V2 xo (yo + 1) `elem` cs = rotateWith clockwise
 | 
			
		||||
  | otherwise                          = rotateWith counterclockwise
 | 
			
		||||
 where
 | 
			
		||||
  clockwise        = (+ o) . (cwperp) . (subtract o)
 | 
			
		||||
  counterclockwise = (+ o) . LV.perp . (subtract o)
 | 
			
		||||
  clockwise        = (+ o) . cwperp . subtract o
 | 
			
		||||
  counterclockwise = (+ o) . LV.perp . subtract o
 | 
			
		||||
  rotateWith dir = b & extra %~ fmap dir
 | 
			
		||||
  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 (t :<| ts) = pure (t, ts)
 | 
			
		||||
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
 | 
			
		||||
initGame :: Int -> IO Game
 | 
			
		||||
| 
						 | 
				
			
			@ -205,7 +205,7 @@ clearFullRows = do
 | 
			
		|||
  modifying board $ M.filterWithKey $ \(V2 _ y) _ -> y `notElem` fullRows
 | 
			
		||||
  -- Shift cells above full rows
 | 
			
		||||
  modifying board $ M.mapKeysMonotonic $ over _y $ \y ->
 | 
			
		||||
    y - (length $ filter (< y) fullRows)
 | 
			
		||||
    y - length (filter (< y) fullRows)
 | 
			
		||||
  return $ length fullRows
 | 
			
		||||
 | 
			
		||||
-- | 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 brd = any stopped . coords
 | 
			
		||||
 where
 | 
			
		||||
  stopped = (||) <$> atBottom <*> (`M.member` brd) . (translate Down)
 | 
			
		||||
  atBottom = (== 1) . (view _y)
 | 
			
		||||
  stopped = (||) <$> atBottom <*> (`M.member` brd) . translate Down
 | 
			
		||||
  atBottom = (== 1) . view _y
 | 
			
		||||
 | 
			
		||||
hardDrop :: Tetris ()
 | 
			
		||||
hardDrop = hardDroppedBlock >>= assign block
 | 
			
		||||
| 
						 | 
				
			
			@ -277,8 +277,8 @@ hardDroppedBlock = do
 | 
			
		|||
        , xo == x
 | 
			
		||||
        , yo < y
 | 
			
		||||
        ]
 | 
			
		||||
      minY = minimum $ (view _y) <$> blockCoords
 | 
			
		||||
      dist = minimum $ (subtract 1) <$> (minY : diffs)
 | 
			
		||||
      minY = minimum $ view _y <$> blockCoords
 | 
			
		||||
      dist = minimum $ subtract 1 <$> (minY : diffs)
 | 
			
		||||
  translateBy dist Down <$> use block
 | 
			
		||||
 | 
			
		||||
-- | Freeze current block
 | 
			
		||||
| 
						 | 
				
			
			@ -326,7 +326,7 @@ shuffle xs
 | 
			
		|||
  | null xs = mempty
 | 
			
		||||
  | otherwise = do
 | 
			
		||||
    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)
 | 
			
		||||
 | 
			
		||||
v2 :: (a, a) -> V2 a
 | 
			
		||||
| 
						 | 
				
			
			
 | 
			
		|||
| 
						 | 
				
			
			@ -163,7 +163,7 @@ drawGrid ui =
 | 
			
		|||
            $ mconcat
 | 
			
		||||
                [ drawBlockCell NormalBlock <$> ui ^. (game . board)
 | 
			
		||||
                , blockMap NormalBlock (ui ^. (game . block))
 | 
			
		||||
                , case (ui ^. preview) of
 | 
			
		||||
                , case ui ^. preview of
 | 
			
		||||
                    Nothing -> M.empty
 | 
			
		||||
                    Just s  -> blockMap (HardDropBlock s) (evalTetris hardDroppedBlock (ui ^. game))
 | 
			
		||||
                , emptyCellMap
 | 
			
		||||
| 
						 | 
				
			
			@ -174,7 +174,7 @@ drawGrid ui =
 | 
			
		|||
 | 
			
		||||
emptyCellMap :: Map Coord (Widget Name)
 | 
			
		||||
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 = withAttr emptyAttr cw
 | 
			
		||||
| 
						 | 
				
			
			@ -222,7 +222,7 @@ drawStats g =
 | 
			
		|||
        ]
 | 
			
		||||
 | 
			
		||||
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 _ = emptyWidget
 | 
			
		||||
| 
						 | 
				
			
			@ -231,8 +231,8 @@ drawInfo :: Game -> Widget Name
 | 
			
		|||
drawInfo g = hLimit 18 -- size of next piece box
 | 
			
		||||
  $ vBox
 | 
			
		||||
    [ drawNextShape (g ^. nextShape)
 | 
			
		||||
    , padTop (Pad 1) $ drawHelp
 | 
			
		||||
    , padTop (Pad 1) $ drawGameOver g
 | 
			
		||||
    , padTop (Pad 1) drawHelp
 | 
			
		||||
    , padTop (Pad 1) (drawGameOver g)
 | 
			
		||||
    ]
 | 
			
		||||
 | 
			
		||||
drawNextShape :: Tetrimino -> Widget Name
 | 
			
		||||
| 
						 | 
				
			
			@ -258,7 +258,7 @@ drawHelp =
 | 
			
		|||
    $ padTopBottom 1
 | 
			
		||||
    $ vBox
 | 
			
		||||
    $ map (uncurry drawKeyInfo)
 | 
			
		||||
    $ [ ("Left"   , "h, ←")
 | 
			
		||||
      [ ("Left"   , "h, ←")
 | 
			
		||||
      , ("Right"  , "l, →")
 | 
			
		||||
      , ("Down"   , "j, ↓")
 | 
			
		||||
      , ("Rotate" , "k, ↑")
 | 
			
		||||
| 
						 | 
				
			
			@ -270,12 +270,12 @@ drawHelp =
 | 
			
		|||
 | 
			
		||||
drawKeyInfo :: String -> String -> Widget Name
 | 
			
		||||
drawKeyInfo action keys =
 | 
			
		||||
  (padRight Max $ padLeft (Pad 1) $ str action)
 | 
			
		||||
    <+> (padLeft Max $ padRight (Pad 1) $ str keys)
 | 
			
		||||
  padRight Max (padLeft (Pad 1) $ str action)
 | 
			
		||||
    <+> padLeft Max (padRight (Pad 1) $ str keys)
 | 
			
		||||
 | 
			
		||||
drawGameOver :: Game -> Widget Name
 | 
			
		||||
drawGameOver g =
 | 
			
		||||
  if (isGameOver g)
 | 
			
		||||
  if isGameOver g
 | 
			
		||||
  then padLeftRight 4 $ withAttr gameOverAttr $ str "GAME OVER"
 | 
			
		||||
  else emptyWidget
 | 
			
		||||
 | 
			
		||||
| 
						 | 
				
			
			
 | 
			
		|||
		Loading…
	
	Add table
		Add a link
		
	
		Reference in a new issue