module Tetris where
 
import Control.Concurrent
import System.Console.ANSI
import System.IO
import System.Random
import qualified Data.Map.Strict as M
import Data.Char
import Foreign.C.Types
 
getHiddenChar = fmap (chr.fromEnum) c_getch
foreign import ccall "conio.h getch" -- unsafe "conio.h getch"
    c_getch :: IO CInt
 
(cols, rows, lboard, uboard, numStrScore) = (10, 20, 25, 4, 14)
scoreChart = map (^2) [0..]
 
type Point = (Int, Int)        -- (row, column)
type Field = [(Int, [Point])]  -- (type index, points)
type Item  = (Int, Int, Point) -- (type index, orientation, central point)
data GameState =
     GameState { field :: Field, item :: Item, run :: Bool, score :: Int, timerDelay :: Int }
 
makeGS f i r s t = GameState { field = f, item = i, run = r, score = s, timerDelay = t }
 
 
timer :: MVar GameState -> IO ()
timer m = do
    inGS @ GameState { field = f, item = i, run = r, score = s, timerDelay = t } <- takeMVar m
 
    newGameState <- if not r then return inGS else do
 
        let i' = move (-1) 0 i
        if testItem f i' then do
            drawPoints ' ' $ itemTypePoints i
            drawPoints '*' $ itemTypePoints i'
            return $ makeGS f i' r s t
 
        else do
            let f' = itemTypePoints i : f
                (fnew, delLines) = compressField f'
                snew = (s+) . sum . map (scoreChart !!) $ delLines
                tnew = t -- надо бы дописать увеличение скорости
 
            if null delLines then return () else do
                setCursorPosition numStrScore 0
                putStr $ "Score: " ++ show snew
                setCursorPosition (numStrScore + 2) 0
                putStr $ "Speed: " ++ show (tnew `div` 10^5)
                mapM_ (drawPoints ' ') f'
                mapM_ (drawPoints '*') fnew
 
            inew <- newItem
            if testItem fnew inew then do
                drawPoints '*' $ itemTypePoints inew
                return $ makeGS fnew inew r snew tnew
 
            else do
                setCursorPosition (numStrScore + 4) 0 >> putStr "Game over!"
                return $ makeGS fnew inew False snew tnew
 
    putMVar m $! newGameState
    threadDelay t
    timer m
 
 
waitKeyPress :: MVar GameState -> IO ()
waitKeyPress m = do
    a <- getHiddenChar --getChar
    inGS @ GameState { field = f, item = i, run = r, score = s, timerDelay = t } <- takeMVar m
 
    let execCommand transform = do
            let i' = transform i
            if not $ testItem f i' then return inGS else do
                drawPoints ' ' $ itemTypePoints i
                drawPoints '*' $ itemTypePoints i'
                return $ makeGS f i' r s t
 
    newGameState <- case a of
 
        'n' -> do                          -- new game
            drawBackground
            inew <- newItem
            drawPoints '*' $ itemTypePoints inew
            return $ makeGS [] inew True 0 (10^6)
 
        'p' -> do                         -- pause / go
            setCursorPosition (numStrScore + 4) 0
            putStr $ if r then "Pause..." else "        "
            return $ makeGS f i (not r) s t
 
        'a' -> execCommand $ move 0 (-1)  -- move left
        'd' -> execCommand $ move 0 1     -- move right
        'w' -> execCommand $ move 1 0     -- move up :)
        's' -> execCommand $ move (-1) 0  -- move down :)
        'q' -> execCommand $ rotate 1     -- rotate left
        'e' -> execCommand $ rotate (-1)  -- rotate right
        ' ' -> execCommand $ fallDown f   -- fall down
        _   -> return inGS                -- nothing
 
    putMVar m $! newGameState
    waitKeyPress m
 
 
itO = [(0,-1),(0,0),(-1,-1),(-1,0)]; itI = [(0,-2),(0,-1),(0,0),(0,1)]
itS = [(-1,-1),(-1,0),(0,0),(0,1)];  itZ = [(0,-1),(0,0),(-1,0),(-1,1)]
itL = [(0,-1),(0,0),(0,1),(-1,-1)];  itJ = [(0,-1),(0,0),(0,1),(-1,1)]
itT = [(0,-1),(0,0),(0,1),(-1,0)]
 
items :: [[[Point]]]
items = [replicate 4 itO, or2 itI, or2 itS, or2 itZ, ori 4 itL, ori 4 itJ, ori 4 itT] where
    ori k = take k . iterate (map $ \(r,c) -> (c,-r)) -- for right rotate \(r,c) -> (-c,r)
    or2 i = ori 2 i ++ ori 2 i
 
itemTypePoints :: Item -> (Int, [Point])
itemTypePoints (n, o, (cpr, cpc)) = (,) n . map (\(r,c) -> (r+cpr, c+cpc)) $ items !! n !! o
 
move :: Int -> Int -> Item -> Item
move dr dc (n, o, (cpr, cpc)) = (n, o, (cpr+dr, cpc+dc))
 
rotate :: Int -> Item -> Item
rotate d (n, o, cp) = (n, (o+d) `mod` 4, cp)
 
testItem :: Field -> Item -> Bool
testItem f = all (\p@(r,c) -> r>=0 && c>=0 && c<cols && all (not . elem p) (map snd f))
    . snd . itemTypePoints
 
fallDown :: Field -> Item -> Item
fallDown f i | testItem f i' = fallDown f i' | otherwise = i where i' = move (-1) 0 i
 
compressField :: Field -> (Field, [Int])
compressField f | null fl  = (f, []) | otherwise = (f', [length fl]) where
    fl = M.keys . M.filter (>=cols) . M.fromListWith (+) . map (\(r,_) -> (r,1)) . concat . map snd $ f
    f' = filter (not . null . snd) . map (fmap $ map (\(r,c) -> (r - length (filter (<r) fl), c))
         . filter (not . (`elem` fl) . fst) ) $ f
 
newItem :: IO Item
newItem = getStdRandom (randomR (0, 6)) >>= \n -> return (n, 0, (rows - 1, cols `div` 2))
 
drawPoint :: Char -> Point -> IO ()
drawPoint sym (r,c) =
    setCursorPosition r0 c0 >> putStr s >> setCursorPosition (r0+1) c0 >> putStr s where
        r0 = uboard + (rows - 1 - r)*2
        c0 = lboard + c*2
        s  = [sym, sym]
 
drawPoints :: Char -> (Int, [Point]) -> IO ()
drawPoints sym (n, ps) = do
    if sym == ' ' then setSGR [Reset]
    else do
        setSGR [SetColor Background Dull White]
        setSGR [SetColor Foreground Vivid (toEnum $ n + 1)]
    mapM_ (drawPoint sym) ps
    setSGR [Reset]
 
drawBackground :: IO ()
drawBackground = do
    clearScreen
 
    setCursorPosition uboard 0
    let leftSpase = replicate (lboard - 1) ' '
    putStr $ unlines $ replicate (rows*2) (leftSpase ++ '|':replicate (cols*2) ' ' ++ "|")
    putStr $ leftSpase ++ '+':replicate (cols*2) '-' ++ "+"
 
    setCursorPosition uboard 0
    putStrLn "Controls:"
    putStrLn ""
    putStrLn "move left - 'a'"
    putStrLn "    right - 'd'"
    putStrLn "rot  left - 'q'"
    putStrLn "    right - 'e'"
    putStrLn "fall down - ' '"
    putStrLn "new  game - 'n'"
 
    setCursorPosition numStrScore 0 >> putStr "Score: 0"
    setCursorPosition (numStrScore + 2) 0 >> putStr "Speed: 0"
 
main :: IO ()
main = do
    hSetBuffering stdin NoBuffering
    hSetBuffering stdout NoBuffering
 
    setTitle "Tetris v 1.0"
    hideCursor
    setCursorPosition uboard 0
    putStrLn "Hello, Windows user! Resize the heigth of terminal window to maximum"
    putStrLn "and press any key..."
    _ <- getHiddenChar --getChar
    drawBackground
 
    m <- newEmptyMVar
    putMVar m $! makeGS [] (0, 0, (0,0)) False 0 (10^6)
    forkIO (timer m)
    waitKeyPress m 
by

Haskell online compiler

Write, Run & Share Haskell code online using OneCompiler's Haskell online compiler for free. It's one of the robust, feature-rich online compilers for Haskell language, running the latest Haskell version 8.6. Getting started with the OneCompiler's Haskell editor is easy and fast. The editor shows sample boilerplate code when you choose language as Haskell and start coding.

Taking inputs (stdin)

OneCompiler's Haskell online editor supports stdin and users can give inputs to programs using the STDIN textbox under the I/O tab. Following is a sample Haskell program which takes name as input and prints hello message with your name.

main = do  
    name <- getLine  
    putStrLn ("Hello " ++ name ++ ", Happy learning!") 

About Haskell

Haskell is purely a functional programming language which was introduced in 1990's.

Key Features

  • Haskell is both compiled and interpreted
  • Lazy language as the results are computed only if required
  • Pure functions
  • Pattern matching on data structures
  • Emphasizes on what to do but not on how to do
  • Glasgow Haskell Compiler (GHC), most widely used Haskell compiler also written in Haskell.
  • Data is immutable

Syntax help

Data Types

Data-typeDescription
NumbersHaskell is intelligent to identify numbers without specifying data type
CharactersHaskell is intelligent to identify characters and strings without specifying data type
TupleTo declare multiple values in a single data type. Tuples are represented in single paranthesis. For example (10, 20, 'apple')
BooleanTo represent boolean values, true or false
ListTo declare same type of values in a single data type. Lists are represented in square braces.For example [1, 2, 3] or `['a','b','c','d']

Control statements

If-Else / Nested If-Else:

When ever you want to perform a set of operations based on a condition or set of conditions, then If-Else/ Nested-If-Else are used.

Example:

main = do   
   let age = 21 
   if age > 18 
      then putStrLn "Adult" 
   else putStrLn "child"

Functions

Function is a sub-routine which contains set of statements. Usually functions are written when multiple calls are required to same set of statements which increases re-usuability and modularity. Functions play an important role in Haskell, since it is a purely functional language.

Example

multiply :: Integer -> Integer -> Integer   --declaration of a function 
multiply x1 x2 =  x1 * x2                   --definition of a function

main = do 
   putStrLn "Multiplication value is:"  
   print(multiply 10 5)    --calling a function