You can not select more than 25 topics Topics must start with a letter or number, can include dashes ('-') and can be up to 35 characters long.

123 lines
6.2 KiB

9 years ago
9 years ago
  1. module VM where
  2. import Data.Hashable (hash, Hashable(..))
  3. import qualified Data.List as List
  4. import Data.Set (Set)
  5. import qualified Data.Set as Set
  6. import Datatypes
  7. unitMap :: (Cell -> Cell) -> Unit -> Unit
  8. unitMap f (Unit members pivot) = Unit (Set.map f members) (f pivot)
  9. centerUnit :: Unit -> Board -> Unit
  10. centerUnit u b = unitMap (\(x, y) -> (x + deltaX, y - unitTop)) u where
  11. members = unitMembers u
  12. yCoords = Set.map (\(x, y) -> y) members
  13. xCoords = Set.map (\(x, y) -> x) members
  14. unitTop = Set.findMin yCoords
  15. unitLeft = Set.findMin xCoords
  16. unitRight = Set.findMax xCoords
  17. deltaX = (unitLeft + (boardWidth b - unitRight - 1)) `div` 2 - unitLeft
  18. collides :: Unit -> Board -> Bool
  19. collides u b = not . Set.null $ Set.intersection (unitMembers u) (boardFilled b)
  20. isInvalidFor :: Unit -> Board -> Bool
  21. isInvalidFor u b = any isOutside (Set.toList $ unitMembers u) where
  22. isOutside (x, y) = x < 0 || x >= boardWidth b || y < 0 || y >= boardHeight b
  23. checkSpawn :: Game -> Game
  24. checkSpawn game@(Game _ [] _ _ _) = game
  25. checkSpawn game@(Game board (u:us) oldPos _ _) = if u `collides` board
  26. then game { gameUnits = [] }
  27. else game
  28. isCompleted :: Game -> Bool
  29. isCompleted game@(Game _ [] _ _ _) = True
  30. isCompleted _ = False
  31. clearLines :: Board -> (Board, Int)
  32. clearLines (Board width height filled) = let (newFilled, linesDeleted) = tryToDelete yCoords 0 filled
  33. in (Board width height newFilled, linesDeleted)
  34. where
  35. yCoords = Set.toList $ Set.map (\(x, y) -> y) filled
  36. countInLine l items = Set.size $ Set.filter (\(x, y) -> y == l) items
  37. tryToDelete (l:ls) count items = if countInLine l items == width
  38. then tryToDelete ls (count + 1) (deleteLine l items)
  39. else tryToDelete ls count items
  40. tryToDelete [] count items = (items, count)
  41. deleteLine l items = let deleted = Set.filter (\(x, y) -> y /= l) items
  42. in Set.map (\(x, y) -> if y < l then (x, y + 1) else (x, y)) deleted
  43. lockUnit :: Game -> Game
  44. lockUnit (Game board (u:us) _ oldLines oldPoints) = Game newBoard us (Set.fromList []) newLines (newPoints + lineBonus + oldPoints) where
  45. tempBoard = board { boardFilled = Set.union (unitMembers u) (boardFilled board) }
  46. (newBoard, newLines) = clearLines tempBoard
  47. newPoints = (Set.size (unitMembers u)) + (100 * (1 + newLines) * newLines `div` 2)
  48. lineBonus = if oldLines > 1
  49. then floor (fromIntegral ((oldLines - 1) * newPoints) / 10)
  50. else 0
  51. testStep = let unit = Unit (Set.fromList [(2,9)]) (0,0)
  52. board = Board 5 10 (Set.fromList [(0,8),(1,8),(0,9),(1,9),(4,8),(3,9),(4,9)])
  53. in step (Game board [unit] (Set.fromList []) 0 0) MoveSW
  54. testStep2 = let unit = Unit (Set.fromList [(0,3),(1,3),(2,3),(3,3),(1,4),(2,4),(3,4), (1,5),(2,5),(2,6)]) (2,4)
  55. board = Board 6 10 (Set.fromList [(0,8),(0,9),(4,6),(3,7),(4,7),(3,8),(4,8),(2,9),(3,9),(4,9),(5,8),(5,9)])
  56. (g1, n1) = step (Game board [unit] (Set.fromList []) 2 0) MoveSW
  57. (g2, n2) = step g1 MoveSE
  58. (g3, n3) = step g2 MoveSW
  59. (g4, n4) = step g3 MoveSW
  60. in (g4, n4)
  61. testStep3 = let unit = Unit (Set.fromList [(2,9)]) (0,0)
  62. board = Board 5 10 (Set.fromList [(0,8),(1,8),(0,9),(1,9),(4,8),(3,9),(4,9)])
  63. in step (Game board [unit] (Set.fromList []) 0 0) MoveSW
  64. step :: Game -> Command -> (Game, Notes)
  65. step game@(Game _ [] _ _ _) command = (game, ErrorZero)
  66. step game@(Game board (unit:us) oldPositions o l) command =
  67. if newUnit `collides` board || newUnit `isInvalidFor` board
  68. then let final = checkSpawn (lockUnit game) in
  69. (if isCompleted final then (final, Ended) else (final, OK))
  70. else
  71. if Set.member (hash newUnit) oldPositions
  72. then (Game board (newUnit:us) oldPositions o l, ErrorZero)
  73. else (Game board (newUnit:us) newOldPositions o l, OK)
  74. where
  75. newUnit = applyCommand unit command
  76. newOldPositions = Set.insert (hash newUnit) oldPositions
  77. applyWholeUnit :: Unit -> (Cell -> Cell) -> Unit
  78. applyWholeUnit (Unit members pivot) f = Unit (Set.map f members) (f pivot)
  79. applyCommand :: Unit -> Command -> Unit
  80. applyCommand unit MoveW = applyWholeUnit unit move where
  81. move (x, y) = (x - 1, y)
  82. applyCommand unit MoveE = applyWholeUnit unit move where
  83. move (x, y) = (x + 1, y)
  84. applyCommand unit MoveSW = applyWholeUnit unit move where
  85. move (x, y) = (x - ((y + 1) `mod` 2), y + 1)
  86. applyCommand unit MoveSE = applyWholeUnit unit move where
  87. move (x, y) = (x + (y `mod` 2), y + 1)
  88. applyCommand (Unit members pivot) RotateClockwise = Unit (Set.map transform members) pivot where
  89. transform cell = rotateCell pivot cell
  90. applyCommand (Unit members pivot) RotateCounterclockwise = Unit (Set.map transform members) pivot where
  91. transform cell = counterRotateCell pivot cell
  92. rotateCell :: Cell -> Cell -> Cell
  93. rotateCell (px, py) (x, y) = (px - ddiag + (doriz + py `mod` 2) `div` 2, py + doriz) where
  94. (ddiag, doriz) = relativePosition (px, py) (x, y)
  95. counterRotateCell :: Cell -> Cell -> Cell
  96. counterRotateCell pivot = rp . rp . rp . rp . rp where
  97. rp = rotateCell pivot
  98. counterRotateCell2 :: Cell -> Cell -> Cell
  99. counterRotateCell2 (px, py) (x, y) = (px + (ddiag + doriz + py `mod` 2) `div` 2, py + ddiag - doriz) where
  100. (ddiag, doriz) = relativePosition (px, py) (x, y)
  101. relativePosition :: Cell -> Cell -> (Int, Int)
  102. relativePosition (px, py) (x, y) = (diagDir, horizDir) where
  103. diagDir = y - py
  104. horizDir = x - px + (if py `mod` 2 == 0 then diagDir + diagDir `mod` 2 else diagDir - diagDir `mod` 2) `div` 2