module AufgabeFFP8 where import Data.Array import Data.List hiding ((\\)) import Test.QuickCheck import Debug.Trace type Nat = Int -- Minfree basic version minfree_bv :: [Int] -> Int minfree_bv xs = head ([0..] \\ xs) (\\) :: Eq a => [a] -> [a] -> [a] xs \\ ys = filter (\x -> x `notElem` ys) xs -- Minfree checklist minfree_chl :: [Int] -> Int minfree_chl = search . checklist search :: Array Int Bool -> Int search = length . takeWhile id . elems checklist :: [Int] -> Array Int Bool checklist xs = accumArray (||) False (0,n) (zip (filter (<=n) xs) (repeat True)) where n = length xs -- minfree countlist minfree_col :: [Int] -> Int minfree_col = search_countlist . countlist countlist :: [Int] -> Array Int Int countlist xs = accumArray (+) 0 (0, n) (zip xs (repeat 1)) where n = safe_maximum xs safe_maximum :: [Int] -> Int safe_maximum [] = 0 safe_maximum xs = maximum xs search_countlist :: Array Int Int -> Int search_countlist = length . takeWhile (/= 0) . elems -- minfree basic daq minfree_b :: [Int] -> Int minfree_b xs = if (null ([0..b-1] \\ us)) then (head ([b..] \\ vs)) else (head ([0..] \\ us)) where (us, vs) = partition ( Int minfree_r = minfrom_r 0 minfrom_r :: Nat -> [Nat] -> Nat minfrom_r a xs | null xs = a | length us == b-a = minfrom_r b vs | otherwise = minfrom_r a us where b = a + 1 + (length xs) `div` 2 (us, vs) = partition ( Int minfree_o xs = minfrom_o 0 (length xs, xs) minfrom_o :: Int -> (Int, [Int]) -> Int minfrom_o a (n, xs) | n == 0 = a | m == b-a = minfrom_o b (n-m, vs) | otherwise = minfrom_o a (m, us) where (us,vs) = partition (Bool) -> (p->s) ->(p-> [p]) -> (p-> [s] -> s)-> p -> s divideAndConquer indiv solve divide combine initPb = dAC initPb where dAC pb | indiv pb = solve pb | otherwise = combine pb (map dAC (divide pb)) -- minfree basic daq higher order minfree_bhof :: [Int] -> Int minfree_bhof xs = divideAndConquer b_indiv b_solve b_divide b_combine (False, xs) b_indiv :: (Bool, [Int]) -> Bool b_indiv (b, _) = b b_solve :: (Bool, [Int]) -> Int b_solve (_, xs) = head xs b_divide :: (Bool, [Int]) -> [(Bool, [Int])] b_divide (n, xs) = if (null ([0..b-1] \\ us)) then [(True, [b..] \\ vs)] else [(True, [0..] \\ us)] where (us, vs) = partition ( [Int] -> Int b_combine xs sols = head sols -- minfree refined daq higher order r_indiv :: (Int, [Int]) -> Bool r_indiv (a, []) = True r_indiv _ = False r_solve :: (Int, [Int]) -> Int r_solve (a, []) = a r_divide :: (Int, [Int]) -> [(Int, [Int])] r_divide (a, xs) | length smaller == b-a = [(b, bigger)] | otherwise = [(a, smaller)] where b = a + 1 + (length xs) `div` 2 (smaller, bigger) = partition ( [Int] -> Int r_combine _ (a:[]) = a minfree_rhof :: [Int] -> Int minfree_rhof xs = divideAndConquer r_indiv r_solve r_divide r_combine (0, xs) -- minfree optimized daq higher order o_indiv :: (Int, Int, [Int]) -> Bool o_indiv (a, 0, []) = True o_indiv _ = False o_solve :: (Int, Int, [Int]) -> Int o_solve (a, 0, []) = a o_divide :: (Int, Int, [Int]) -> [(Int, Int, [Int])] o_divide (a, n, xs) | ls == b-a = [(b, length bigger, bigger)] | otherwise = [(a, ls, smaller)] where b = a + 1 + n `div` 2 (smaller, bigger) = partition ( [Int] -> Int o_combine _ (a:[]) = a minfree_ohof :: [Int] -> Int minfree_ohof xs = divideAndConquer o_indiv o_solve o_divide o_combine (0, length xs, xs) -- QuickCheck part functions = [ minfree_bv, minfree_chl, minfree_col, minfree_b, minfree_r, minfree_o, minfree_bhof, minfree_rhof, minfree_ohof] -- calc values of all function calc_all :: [Int] -> [Int] calc_all xs = [f xs | f <- functions ] -- check if all values of a list are the same all_eq :: [Int] -> Bool all_eq (x:[]) = True all_eq (x:y:xs) | x == y = all_eq (y:xs) | otherwise = False -- check if a list contains no duplicates --no_dups :: [Int] -> Bool --no_dups [] = True --no_dups (x:xs) -- | x `elem` xs = False -- | otherwise = no_dups xs prop_allImplsEq_a :: [Int] -> Bool prop_allImplsEq_a xs = all_eq $ calc_all (nub xs) -- keine negativen listenelemented durch vorbedingung entfernt prop_allImplsEq_b :: [Int] -> Property prop_allImplsEq_b xs = all (>=0) xs ==> all_eq $ calc_all (nub xs)