{- * Copyright (c): Uwe Schmidt, FH Wedel * * You may study, modify and distribute this source code * FOR NON-COMMERCIAL PURPOSES ONLY. * This copyright message has to remain unchanged. * * Note that this document is provided 'as is', * WITHOUT WARRANTY of any kind either expressed or implied. -} module ListComp where import Prelude hiding ( concat , length , map ) import qualified Prelude import Data.Char ( isLower ) l1 :: [Int] l1 = [x^2 | x <- [1..5]] l2 = [(x,y) | x <- [1,2,3], y <- [4,5]] l3 = [(x,y) | x <- [1..3], y <- [x..3]] concat :: [[t]] -> [t] concat xss = [x | xs <- xss, x <- xs] firsts :: [(a, b)] -> [a] firsts ps = [x | (x, _) <- ps] add :: Num a => [a] -> [a] -> [a] add xs ys = [x + y | (x, y) <- zip xs ys] length :: [t] -> Int length xs = sum [1 | _ <- xs] map :: (a -> b) -> [a] -> [b] map f xs = [f x | x <- xs] factors :: Int -> [Int] factors n = [x | x <- [1..n] , n `mod` x == 0 ] prime :: Int -> Bool prime n = factors n == [1, n] primes :: Int -> [Int] primes n = [x | x <- [2..n], prime x] find :: Eq a => a -> [(a, b)] -> [b] find k t = [v | (k', v) <- t, k' == k] notThere :: Eq a => a -> [(a, b)] -> Bool notThere k t = null (find k t) -- Funktionen mit zip pairs :: [a] -> [(a,a)] pairs xs = zip xs (tail xs) isSorted :: Ord a => [a] -> Bool isSorted xs = and [x <= y | (x,y) <- pairs xs] positions :: Eq a => a -> [a] -> [Int] positions x xs = [i | (x',i) <- zip xs [0..n], x == x'] where n = length xs - 1 found :: Eq a => a -> [a] -> Bool found x xs = not (null (positions x xs)) -- String comprehension lowers :: String -> Int lowers xs = length [x | x <- xs, isLower x] count :: Eq t => t -> [t] -> Int count x xs = length [x' | x' <- xs, x' == x] count' x xs = length [x | x <- xs, x == x] pyth :: Int -> [(Int, Int, Int)] pyth n = [(x,y,z) | x <- [1 .. n] , y <- [1 .. n] , z <- [1 .. n] , x*x + y*y == z*z , x <= y , x `gcd` y == 1 ] pyth' :: Int -> [(Int, Int, Int)] pyth' n = [ (x, y, z) | x <- [1 .. n] , y <- [x .. n] , z <- [y+1 .. n] , x*x + y*y == z*z , x `gcd` y == 1 ] pyth'' :: Int -> [(Int, Int, Int)] pyth'' n = [ (x, y, z) | x <- [1 .. n] , y <- [x .. n] , x `gcd` y == 1 , z <- isqrt (x*x + y*y) , z <= n ] -- | isqrt returns the single element list [sqrt n] -- if n is a square number, else [] -- -- The algorithm is an integer variant -- of the "Heron's method" or "Babylonian method" isqrt :: Int -> [Int] isqrt n | cand * cand == n = [cand] | otherwise = [] where next x = ((x*x + n) `div` (2*x)) toLarge x = x * x > n cand = head (dropWhile toLarge (iterate next n)) len :: Int -> Int len n = n * n * n len' :: Int -> Int len' n = Prelude.length [ (x, y, z) | x <- [1 .. n] , y <- [x .. n] , z <- [y+1 .. n] ] len'' :: Int -> Int len'' n = Prelude.length [ (x, y) | x <- [1 .. n] , y <- [x .. n] ]