module Sol_Exercise_13 where import Data.Char (isDigit, digitToInt) import Data.List (find, isInfixOf, isSuffixOf, nub, sort, intersect) import System.Random (randomRIO) import Test.QuickCheck {- Library -- nicht veraendern -} {- G13.1 -} {- Using global generator -} nRandomR :: (Int, Int) -> Int -> IO [Int] nRandomR lowhigh = randHelp [] where randHelp :: [Int] -> Int -> IO [Int] randHelp xs 0 = return xs randHelp xs n = do i <- randomRIO lowhigh if i `elem` xs then randHelp xs n else randHelp (i : xs) (n - 1) {- {- Using local generator (needs to be threaded through) -} nRandomR' :: (Int, Int) -> Int -> IO [Int] nRandomR' lowhigh n = do gen <- newStdGen return (randHelp gen [] n) where randHelp :: StdGen -> [Int] -> Int -> [Int] randHelp gen xs 0 = xs randHelp gen xs n = if i `elem` xs then randHelp gen' xs n else randHelp gen' (i : xs) (n - 1) where (i, gen') = randomR (0,9) gen -} {- G13.2 -} getLineInt :: IO Int getLineInt = do line <- getLine if all isDigit line then return (read line) else do putStrLn "Not a number" getLineInt guessNum :: IO Int guessNum = do rnd <- randomRIO (0,100) putStrLn "Guess a number between 0 and 100" doGuessNum rnd 1 where doGuessNum rnd cnt = do num <- getLineInt if num < rnd then do putStrLn "The number you are looking for is greater" doGuessNum rnd (cnt+1) else if num > rnd then do putStrLn "The number you are looking for is smaller" doGuessNum rnd (cnt+1) else do putStrLn "You found it!" return cnt {- H13.1 -} getSorted :: IO [String] getSorted = do lines <- getLines return $ sort lines where getLines = do l <- getLine if null l then return [] else do ls <- getLines return (l : ls) -- Ohne do-Syntax: getSorted' :: IO [String] getSorted' = getLines >>= return . sort where getLines = getLine >>= \l -> if null l then return [] else (getLines >>= return . (l:)) {- H13.2 -} bullsAndBears :: IO () bullsAndBears = do xs <- nRandomR (0,9) 4 putStrLn (" ****")-- ++ concatMap show xs) game xs 10 where game xs 0 = do putStrLn ("You lost! Secret number was " ++ concatMap show xs) game xs n = do putStr (if n == 1 then "10 " else " " ++ show (11 - n) ++ " ") ys <- getGuess [] 4 res <- return $ answer xs (reverse ys) putStrLn (" " ++ concatMap show res) if head res == 4 then do putStrLn "You won!" else game xs (n - 1) answer xs ys = [bulls, bears] where bulls = length $ filter id $ zipWith (==) xs ys bears = length (intersect xs ys) - bulls getGuess xs 0 = return xs getGuess xs n = do x <- getChar if x `elem` ['0' .. '9'] && not (digitToInt x `elem` xs) then getGuess (digitToInt x : xs) (n - 1) else do -- Deletes the last character from the screen putStr "\b \b" getGuess xs n {- H13.2 -}