module Util where import TypesConstants import Graphics.Gloss import Data.List import System.Random import qualified Data.Tuple as DT {- -----------drawing functions------------- -} drawBoard :: Board -> Picture drawBoard b | not (started b) = drawStartScreen b | not (automatic b) && gameOver b = drawEndOfGame b | automatic b = pictures [drawLogo b, drawBorder b, drawTumFoods b, drawSnake b] | otherwise = pictures [drawLogo b, drawBorder b, drawFood b, drawSnake b] drawStartScreen :: Board -> Picture drawStartScreen b = pictures [color black $ rectangleSolid x y, translate (-188.0) 0.0 $ scale 0.5 0.5 $ color white $ text "press space"] where (x,y) = mapTuple fromIntegral $ res b drawEndOfGame :: Board -> Picture drawEndOfGame b = pictures [color red $ rectangleSolid x y, translate (-32.0) 0.0 $ scale 0.5 0.5 $ color black $ text $ show $ length $ snake b] where (x,y) = mapTuple fromIntegral $ res b drawBorder :: Board -> Picture drawBorder b = color white $ rectangleWire (s+1) (s+1) where s = fst . mapTuple fromIntegral $ res b drawFood :: Board -> Picture drawFood b = drawOperator b pos where pos = food b drawOperator :: Board -> Pos -> Picture drawOperator b (x,y) = translate x' y' $ scale 0.1 0.1 $ color white $ text op where (x',y') = scaleUp b (x, y) op = currentFood b drawSquare :: Board -> Pos -> Picture drawSquare b (x,y) = translate x' y' $ rectangleSolid 16.0 16.0 where (x',y') = scaleUp b (x+0.5, y+0.5) -- because everything is drawn around a center, but i dont like that drawSnake :: Board -> Picture drawSnake b = pictures $ snakePics ++ borders where pos = snake b snakeColor | not $ automatic b = green | otherwise = tumBlue snakeHeadColor | not $ automatic b = dark . dark . dark $ green | gameOver b = tumBlue | otherwise = dark tumBlue snakePics = color snakeHeadColor (drawSquare b $ head pos) : map (color snakeColor . drawSquare b) (tail pos) borders = map (\(x',y') -> let (x,y) = scaleUp b (x'+0.5, y'+0.5) in translate x y $ rectangleWire 16.0 16.0) pos drawLogo :: Board -> Picture drawLogo b = pictures[color lilaDark $ pictures [polygon leftPartUpper, polygon leftPartLower], color lilaLight $ pictures [polygon middlePartBig, polygon middlePartSmall], color pinkBright $ pictures [polygon rightPartLower, polygon rightPartUpper]] drawTumFoods :: Board -> Picture drawTumFoods b = case fds of [] -> blank ((s, (x',y')):fds) -> let (x,y) = scaleUp b (x', y') in translate x y $ scale 0.1 0.1 $ color white $ text s where fds = tumFoods b {- -----------other utility functions------------- -} scaleUp :: Board -> Pos -> Pos scaleUp _ (x,y) = (x*16.0, y*16.0) scaleUp1 :: Board -> Pos -> Pos scaleUp1 b (x,y) = let factor = (/2) . fromIntegral . fst $ size b in (x*factor, y*factor) allMoves :: Board -> [Pos] allMoves b = [(fromIntegral x, fromIntegral y) | x <- [minVal..maxVal], y <- [minVal..maxVal]] \\ snake b where maxVal = fst (size b) `div` 2 - 1 minVal = (- 1) * fst (size b) `div` 2 checkGO :: [Pos] -> Board -> Bool checkGO snake b = length snake /= length (nub snake) || any (\(x,y) -> x < -(w/2) || y < - (h/2) || x > ((w/2) - 1) || y > (h/2) - 1) snake where (w, h) = mapTuple fromIntegral $ size b newFood :: Board -> [Pos] -> (Pos, String, StdGen) newFood b snk = (move, op, newGen2) where (move, newGen) = getRandomElement (r b) $ allMoves b (op, newGen2) = getRandomElement newGen allOps mapTuple :: (a -> b) -> (a,a) -> (b,b) mapTuple f (x, y) = (f x, f y) --returns random element from the list along with new Random Generator (dont forget to update it in calling function, otherwise always same number will be returned) getRandomElement :: StdGen -> [a] -> (a, StdGen) getRandomElement gen xs = (xs !! index, newGen) where (index, newGen) = randomR (0, length xs - 1) gen getNRandomElements :: Eq a => StdGen -> [a] -> Int -> ([a], StdGen) getNRandomElements generator list x = go generator list x [] where go gen xs 0 current = (current, gen) go gen [] n current = (current, gen) go gen xs n current = go newGen newXS (n-1) (elem:current) where (elem, newGen) = getRandomElement gen xs newXS = delete elem xs