module Exercise_10_Sol where import Data.List import Data.List.Split import Data.Ord import Network import System.IO import System.Random (randomRIO) import Text.Read (readMaybe) {-G10.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 -} {-G10.2-} getLineInt :: IO Int getLineInt = do line <- getLine case readMaybe line :: Maybe Int of Nothing -> do putStrLn "Not a number" getLineInt Just n -> return n 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 {-H10.1-} ioLoop :: (a -> Maybe b) -> IO a -> IO b ioLoop f act = do x <- act case f x of Nothing -> ioLoop f act Just b -> return b getInteger :: IO Integer getInteger = ioLoop readMaybe getLine {-H10.2-} readNameMap :: FilePath -> IO [(Integer, String)] readNameMap p = do s <- readFile p return (map parseLine (lines s)) where parseLine s = let cols = splitOn "," s in (read (cols !! 0), read (cols !! 3) ++ " " ++ read (cols !! 2)) -- etwas knapper: readNameMap' :: FilePath -> IO [(Integer, String)] readNameMap' p = fmap (map parseLine . lines) (readFile p) where parseLine s = let getCol = (splitOn "," s !!) in (read (getCol 0), read (getCol 3) ++ " " ++ read (getCol 2)) submissionQuery :: [(Integer, String)] -> IO () submissionQuery m = do putStrLn "Please enter ID" s <- getLine case lookup (read s) m of Nothing -> putStrLn "None" Just name -> putStrLn name -- etwas knapper: submissionQuery' :: [(Integer, String)] -> IO () submissionQuery' m = putStrLn "Please enter ID" >> readLn >>= (putStrLn . maybe "None" id . flip lookup m) {-H10.3-} captcha :: IO Bool captcha = do h <- connectTo "vmnipkow3.in.tum.de" (PortNumber 8080) putStr "Connected. Enter user name: " name <- getLine hPutStrLn h ("REGISTER " ++ name) response <- hGetLine h verdict <- case words response of ["CHALLENGE", n'] -> case readMaybe n' of Just n -> do putStrLn "The challenge is:" challenge <- times n (hGetLine h) foreach challenge putStrLn putStr "Enter solution: " response <- getLine hPutStrLn h ("SOLUTION " ++ response) verdict <- hGetLine h return (verdict == "ACK") _ -> return False _ -> return False hClose h return verdict where times 0 io = return [] times n io = do x <- io xs <- times (n - 1) io return (x : xs) foreach [] io = return () foreach (x:xs) io = do io x foreach xs io {-H10.4-} type Var = Int type Literal = Int type Clause = [Literal] type Assignment = [Var] {-WETT-} vars :: [Clause] -> [Var] vars clauses = nub [abs literal | clause <- clauses, literal <- clause] isSatisfied :: Clause -> Assignment -> Bool isSatisfied clause ass = or [if l > 0 then l `elem` ass else (-l) `notElem` ass | l <- clause] countSatisfied :: [Clause] -> Assignment -> Int countSatisfied clauses ass = length [clause | clause <- clauses, isSatisfied clause ass] maxSat :: [Clause] -> (Assignment, Int) maxSat clauses = maximumBy (comparing snd) [(ass, countSatisfied clauses ass) | ass <- subsequences (vars clauses)] {-TTEW-}