| 
    1module ListComp where 
   2 
   3import Prelude hiding ( concat 
   4                      , length 
   5                      , map 
   6                      ) 
   7 
   8import qualified Prelude 
   9 
  10import Data.Char ( isLower ) 
  11 
  12l1 :: [Int] 
  13l1 = [x^2 | x <- [1..5]] 
  14 
  15l2 = [(x,y) | x <- [1,2,3], y <- [4,5]] 
  16 
  17l3 = [(x,y) | x <- [1..3], y <- [x..3]] 
  18 
  19concat     :: [[t]] -> [t] 
  20concat xss = [x | xs <- xss, x <- xs] 
  21 
  22firsts    :: [(a, b)] -> [a] 
  23firsts ps = [x | (x, _) <- ps] 
  24 
  25add :: Num a => [a] -> [a] -> [a] 
  26add xs ys = [x + y | (x, y) <- zip xs ys] 
  27 
  28length :: [t] -> Int 
  29length xs = sum [1 | _ <- xs] 
  30 
  31map :: (a -> b) -> [a] -> [b] 
  32map f xs = [f x | x <- xs] 
  33 
  34factors :: Int -> [Int] 
  35factors n = [x | x <- [1..n] 
  36               , n `mod` x == 0 
  37            ] 
  38 
  39prime :: Int -> Bool 
  40prime n = factors n == [1, n] 
  41 
  42primes :: Int -> [Int] 
  43primes n = [x | x <- [2..n], prime x] 
  44 
  45find :: Eq a => a -> [(a, b)] -> [b] 
  46find k t = [v | (k', v) <- t, k' == k] 
  47 
  48notThere :: Eq a => a -> [(a, b)] -> Bool 
  49notThere k t = null (find k t) 
  50 
  51-- Funktionen mit zip 
  52 
  53pairs :: [a] -> [(a,a)] 
  54pairs xs = zip xs (tail xs) 
  55 
  56isSorted :: Ord a => [a] -> Bool 
  57isSorted xs = and [x <= y | (x,y) <- pairs xs] 
  58 
  59positions :: Eq a => a -> [a] -> [Int] 
  60positions x xs 
  61    = [i | (x',i) <- zip xs [0..n], x == x'] 
  62      where 
  63        n = length xs - 1 
  64 
  65found :: Eq a => a -> [a] -> Bool 
  66found x xs = not (null (positions x xs)) 
  67 
  68-- String comprehension 
  69 
  70lowers :: String -> Int 
  71lowers xs = length [x | x <- xs, isLower x] 
  72 
  73count :: Eq t => t -> [t] -> Int 
  74count x xs = length [x' | x' <- xs, x' == x] 
  75 
  76count' x xs = length [x | x <- xs, x == x] 
  77 
  78pyth :: Int -> [(Int, Int, Int)] 
  79pyth n 
  80    = [(x,y,z) 
  81      | x <- [1 .. n] 
  82      , y <- [1 .. n] 
  83      , z <- [1 .. n] 
  84      , x*x + y*y == z*z 
  85      , x <= y 
  86      , x `gcd` y == 1 
  87      ] 
  88 
  89pyth' :: Int -> [(Int, Int, Int)] 
  90pyth' n 
  91    = [ (x, y, z) 
  92      | x <- [1 .. n] 
  93      , y <- [x .. n] 
  94      , z <- [y+1 .. n] 
  95      , x*x + y*y == z*z 
  96      , x `gcd` y == 1 
  97      ] 
  98 
  99pyth'' :: Int -> [(Int, Int, Int)] 
 100pyth'' n 
 101    = [ (x, y, z) 
 102      | x <- [1 .. n] 
 103      , y <- [x .. n] 
 104      , x `gcd` y == 1 
 105      , z <- isqrt (x*x + y*y) 
 106      , z <= n 
 107      ] 
 108 
 109-- | isqrt returns the single element list [sqrt n] 
 110--   if n is a square number, else [] 
 111-- 
 112-- The algorithm is an integer variant 
 113-- of the "Heron's method" or "Babylonian method" 
 114 
 115isqrt :: Int -> [Int] 
 116isqrt n 
 117    | cand * cand == n = [cand] 
 118    | otherwise        = [] 
 119    where 
 120      next x 
 121          = ((x*x + n) `div` (2*x)) 
 122      toLarge x 
 123          = x * x > n 
 124      cand 
 125          = head (dropWhile toLarge (iterate next n)) 
 126 
 127 
 128len :: Int -> Int 
 129len n 
 130    = n * n * n 
 131 
 132len' :: Int -> Int 
 133len' n 
 134    = Prelude.length 
 135      [ (x, y, z) 
 136      | x <- [1 .. n] 
 137      , y <- [x .. n] 
 138      , z <- [y+1 .. n] 
 139      ] 
 140 
 141len'' :: Int -> Int 
 142len'' n 
 143    = Prelude.length 
 144      [ (x, y) 
 145      | x <- [1 .. n] 
 146      , y <- [x .. n] 
 147      ] 
 | 
    
| Letzte Änderung: 12.01.2016 | © Prof. Dr. Uwe Schmidt |