module Kerst where import Data.List import Data.Char import qualified Data.Map as Map -- Priemgetallen etc isPrime n = n > 1 && foldr (\p r -> p*p > n || ((n `rem` p) /= 0 && r)) True primes primeFactors n | n > 1 = go n primes -- or go n (2:[3,5..]) where -- for one-off invocation go n ps@(p:t) | p*p > n = [n] | r == 0 = p : go q ps | otherwise = go n t where (q,r) = quotRem n p bla x = [(head l, length l) | l <- group (primeFactors x)] primes = 2 : filter isPrime [3,5..] radical = product . nub . primeFactors -- Alfabet verschuiven shift n ' ' = ' ' shift n '-' = '-' shift n a = chr(((ord a - (ord 'a') + n + 26) `rem` 26) + (ord 'a')) -- Opdelen in paartjes chop (x:y:l) = [x,y]: chop l chop [] = [] -- Alle dubbele elementen doubles [] = [] doubles (x:xs) = if not (null ls) then head ls : doubles rs else doubles rs where (ls, rs) = partition (== x) xs --a plus b vig a b = chr(((ord a + ord b - 2 * (ord 'a')) `rem` 26) + (ord 'a')) --a min b invig a b = chr(((ord a - ord b + 26 ) `rem` 26) + (ord 'a')) waarde x = ord x - ord 'a' + 1 letter x = chr (x + ord 'a' - 1) plus a b = letter (waarde a + waarde b) minus a b = letter (waarde a - waarde b) onder y = [(letter n, letter ((waarde y) - n)) | n <- [1 ..(waarde y) - 1]] --kanbovenaan a:b:c: = -- Woordenlijst path = "words.txt" getwords = lines <$> readFile path swap (a, b) = (b, a) -- Binair naar getal (en terug) bintonum = foldr (\x acc -> x + 2*acc) 0 numtobin0 0 = [0] numtobin0 1 = [1] numtobin0 n = if n `rem` 2 == 0 then 0 : numtobin (n `div` 2) else 1 : numtobin ((n-1) `div` 2) numtobin n = take 5 (numtobin0 n ++ repeat 0) -- Frequentie-analyse counts = reverse . sort . map swap . Map.toList . Map.fromListWith (+) . map (\x -> (x, 1)) smtlibn 0 = "\"-\"" smtlibn n = "ite (= x " ++ show n ++ ") " ++ "\"" ++ [chr (n + ord 'a' - 1)] ++ "\" (" ++ smtlibn (n-1) ++ ")" smtlib l = "and " ++ concat (map (uncurry f) l) where f a b = "implies (= x " ++ show a ++ ") (= y " ++ show b ++ ")" smtlib1 l = "(or" ++ concat (map f l) ++ ")" where f a = " (= x "++show a++")" smtlib2 l = "(and" ++ concat (map f l) ++ ")" where f (a, b, c) = " (implies (and (>= x " ++ show a ++ ") (<= x " ++ show b ++ ")) (= y " ++ [c] ++ "))" klokken = [ "12:30" , "12:40" , " 2:00" , "12:00" -- , " 1:00" , " 1:20" , " 3:00" , "12:20" -- , "12:30" , "12:40" , " 2:00" , "12:00" -- , " 1:00" , " 1:20" , " 3:00" , "12:20" -- , " 1:10" , "12:40" , " 3:40" , " 2:20" -- , " 2:20" , " 2:50" , "12:30" , "12:40" -- , " 2:10" , "12:40" , " 2:10" , "12:30" -- , "12:40" , " 1:50" , "12:00" , " 2:00" -- , " 2:00" , "12:40" , " 2:50" , " 1:00" -- , " 1:20" , "12:40" , " 2:50" , " 2:30" -- , "12:00" , " 3:00" , " 3:00" , "12:40" -- , " 2:10" , "12:30" , " 1:20" , " 3:10" -- , " 1:30" , "12:00" , "12:00" , " 2:50" -- , " 1:20" , " 2:10" , " 1:10" , "12:40" -- , " 3:10" , " 2:30" , " 3:20" , " 4:10" -- , " 4:10" , "12:40" , " 1:50" , " 3:10" -- , " 1:10" , "12:40" , " 2:00" , "12:00" -- ] chop4 ls = l : if null r then [] else chop4 r where (l, r) = splitAt 4 ls klokken2 = concat . map (\(a:b:c:d:[]) -> a:b:d:c:[]) . chop4 $ klokken klok "12:40" = ' ' klok "12:00" = 's' klok "12:30" = 'n' klok " 2:00" = 't' klok " 1:10" = 'i' klok " 1:50" = 'o' klok " 2:10" = 'u' klok " 1:00" = 'a' klok " 1:20" = 'm' klok "12:20" = 'p' klok " 3:00" = 'e' klok _ = '-' g 'r' = ' ' g 'x' = 'o' g 'n' = 'n' g _ = '-' opg14 = [ "T ,be ou erkmeiodtoentn em" , " ti t'Godnw srne ah erkes" , "emgute toosenv rrt edg ihm" , "roeSgioaonaejnnrsm sd sdd" , "tedaaraerel otrd om a.szpe" , "hc no nih e e jt emeo iMuon" , "nigiwe tn s mw osdvoazncao" , "raightegkjei letndei.ne ink" ] opg14kol = transpose opg14 score24 " " = -1000 score24 "n " = 384 score24 "ge" = 137 score24 " e" = 97 score24 "re" = 75 score24 "en" = 370 score24 "te" = 135 score24 "ie" = 97 score24 "ve" = 74 score24 "e " = 308 score24 "in" = 131 score24 "el" = 96 score24 "or" = 74 score24 "de" = 258 score24 "ee" = 119 score24 "st" = 93 score24 " g" = 70 score24 "er" = 232 score24 "r " = 118 score24 "s " = 87 score24 "ar" = 70 score24 "t " = 194 score24 "aa" = 111 score24 "nd" = 84 score24 " d" = 178 score24 "he" = 106 score24 " o" = 79 score24 " b" = 69 score24 "an" = 172 score24 "et" = 105 score24 "va" = 77 score24 "ng" = 69 score24 " v" = 143 score24 " h" = 105 score24 "ch" = 76 score24 ". " = 300 score24 ", " = 300 score24 " T" = 0 score24 [a,'T'] = -1000 score24 " G" = 0 score24 [a,'G'] = -1000 score24 " S" = 0 score24 [a,'S'] = -1000 score24 " M" = 0 score24 [a,'M'] = -1000 score24 "T " = -1000 score24 "G " = -1000 score24 "S " = -1000 score24 "M " = -1000 score24 _ = 0 scorepaar (a,b) = score24 [a,b] scorekolompaar (a,b) = sum (map scorepaar (zip a b)) {- comb a b = [a, b] -- sortOn snd [(k1,k2) | k1 <- opg14kol, k2 <- opg14kol, k1 /= k2] sortOn (negate . scorekolompaar) [(k1,k2) | k1 <- opg14kol, k2 <- opg14kol, k1 /= k2] k = opg14kol !! 14 zip [0..] opg14kol sortOn (negate . \(x,y,z)->z) [(k,k2,scorekolompaar (k,k2)) | k2 <- opg14kol, k /= k2] -} -- OPGAVE 24 opg24 = [ "Beehbkea eted lebare n E" , "dgpdv lnia eontkvrlsd etZau" , "EeaeZlmoaeih. d tjentvlstod" , "dseioherlrertn dena kannar" , "nnl d avdaiera o n lteen r" , "g ieā€™nernrnd ,avle eitfr " , "p tor semaanropaoeenvh or " , " dnuaennr Eadjeevnld dvaBo" , "no, aoSke vknoaee ndtok e" , "ntmjriwednvndai aedbr B " ] -- OPGAVE 22 toRom0 :: Int -> [Int] toRom0 0 = [] toRom0 1 = [1] toRom0 2 = [1,1] toRom0 3 = [1,1,1] toRom0 4 = [5,1] toRom0 5 = [5] toRom0 6 = [1,5] toRom0 7 = [1,1,5] toRom0 8 = [1,1,1,5] toRom0 9 = [10,1] toRom2 1 = 'I' toRom2 5 = 'V' toRom2 10 = 'X' toRom2 50 = 'L' toRom2 100 = 'C' toRom2 500 = 'D' toRom2 1000 = 'M' toRom1 :: Int -> [Int] toRom1 0 = [] toRom1 n = toRom0 n1 ++ map (10*) (toRom1 n10) where (n10, n1) = n `divMod` 10 toRom n = reverse (map toRom2 (toRom1 n)) romanRange = [1..3999] -- Alle romeinse getallen van lengte 5 l5 = [(n, r) | n <- romanRange, let r = toRom n, length r == 5] -- Geeft mogelijke letters op plek i possibleDigit i = nub . map ((!! i) . snd) -- I,V kunnen niet vooraan -- I kan niet op plek 2 -- Verder kan alles -- F is oneven -- Eerste twee letters zijn gelijk (want D = F) -- Eerste vier kunnen alleen "XLCDM" zijn (I en V kunnen niet vooraan staan bij B t/m E) f0 = [(n, r) | (n, r) <- l5, r !! 0 == r !! 1, n `rem` 2 == 1, not ('I' `elem` (take 4 r)), not ('V' `elem` (take 4 r))] -- Eerste (en tweede dus) letter van F is C,M -- Laatste letter van F is I,V -- Laatste letter van D is geen I (want het is tweede letter van J) -- Dus laatste letter van F is geen I (D = F), dus is het een V f = [(n, r) | (n, r) <- f0, r !! 4 == 'V'] -- Tweede letter van J is V j = [(n, r) | (n, r) <- l5, r !! 1 == 'V'] -- Enige opties eindigen op III -- Eerste letter van E is eerste van F, dus C,M -- Verder is het de eerste letter van F tm J, dus geen I,V -- LET OP: AVICII impliceert (r !! 2) `elem` "CM" e = [(n, r) | (n, r) <- l5, r !! 0 `elem` "CM", not ('I' `elem` r), not ('V' `elem` r), (r !! 2) `elem` "CM"] -- J is een deler van E -- Eerste van J is laatste van E je = [(jn, jr, en, er) | (jn, jr) <- j, (en, er) <- e, en `rem` jn == 0, er !! 4 == jr !! 0] -- J is 18 of 108 -- E is tevens een 30-voud -- Eerste van J is X,C -- Als eerste van J = C, dan ligt E vast -- C is priem -- Laatste van C is I (door J) c0 = [(n, r) | (n, r) <- l5, isPrime n] c = [(n, r) | (n, r) <- l5, isPrime n, r !! 4 == 'I'] -- p5 = filter (isPrime . fst) l5 div5 = [(n, m) | (n, _) <- l5, (m, r) <- l5, n <= m, m `rem` n == 0, valid (head r)] where valid 'X' = True valid 'C' = True valid 'M' = True valid _ = False {- possibleDigit 0 l5 possibleDigit 1 l5 possibleDigit 2 l5 possibleDigit 3 l5 possibleDigit 4 l5 foo g10_8 foo g10_9 foo g10_10 forM_ je (print) possibleDigit 3 f --lx0 n = groupBy (\a b -> snd a == snd b) . map (id *** (!! n)) $ l5 -- --lx1 n = [ (ll, lh, x) | l <- lx0 n, let (ll, x) = head l, let (lh, _) = last l] -- ---- putStrLn $ smtlib2 (lx1 4) -- --f i = "(assert (rom"++show i++" j m5"++show i++"))" -- ----putStrLn $ unlines $ f <$> [1..5] -- ----smtlib1 $ map fst c0 -- -- --g i = "(get-value ((chr (letter "++show i++"))))" --putStrLn$ unlines $ map g [13..44] -} {- text = "emokrytrtjnidntgvqumvdasxxrjkfuhranjnhrcrgdnofrwnsdynffwlpwsykxxoorqzeuwyy" --mapM print $ counts text -- (zip text (tail text)) map g text -} {- OPGAVE 23b op23b = [49754821752, 205797003264, 527905927368, 627002220879, 734847565824, 1653916667976, 1889607516147] forM op23b (print . primeFactors') op23b2 = map (round . (**(1/3))) op23b forM op23b2 print mapM print [primeFactors (n - 1) | n <- op23b2] -} {- WOORDENLIJST MAKEN range = ['A'..'z'] getwords f = map (map toLower . filter (`elem` range)) <$> lines <$> readFile f fs = ["NewFolder/OpenTaal-210G-basis-gekeurd.txt", "NewFolder/OpenTaal-210G-basis-ongekeurd.txt", "NewFolder/OpenTaal-210G-flexievormen.txt", "NewFolder/OpenTaal-210G-verwarrend.txt"] x <- Set.fromList <$> concat <$> mapM getwords fs str = unlines (Set.toList x) writeFile "NewFolder/words.txt" str -} {- OPGAVE 19 a1 = "cdqiajneqgvajnkndwddqn" a2 = "azczdfpjqcjndcscydcqfpjncd" a3 = "cksioupcirkhhlpdnigglhrild" a4 = "fmkcmtsfhgqpskkmqvcvcmgmnhgnsinchgnmomddscehdn" a5 = "qmorlqditapofmqhcdah" doubles (chop a2) l = [a1, a2, a3, a4, a5] s = ["premier", "discjockey", "zangeres", "presentatrice", "striptekenaar", "schrijver", "atleet", "neuroloog", "dominee", "natuurkundige", "dichter", "schooldirecteur", "auteur", "voetballer", "journalist", "predikant", "kunstenaar", "cameraman"] zipWith invig <$> l <*> s -} {- OPGAVE 17 lo = "aehinrttwxxz" rb = "abcaaacaaafb" loc = "aadedacafaaeg" rbc = "afiiijklrsxxz" zipWith vig rbc loc -} {- OPGAVE 7 l = ["boommarter", "bruinvis", "damhert", "veldspitsmuis", "waterspitsmuis", "arend", "tuimelaar", "otter"] w2 = l !! 2 product (map waarde w2) primeFactors (2496) primeFactors (2520) primeFactors (232) primeFactors (5400) primeFactors (6320) primeFactors (132) primeFactors (990) exp2 = map (round . (2**)) [0..] nats = [1..] sum $ zipWith (*) (map waarde w2) exp2 (map waarde w2) -} -- ********************** -- **** **** -- **** OPGELOST **** -- **** **** -- ********************** {- OPGAVE 1c opties l = [map (shift (-2)) l, map (shift (0)) l, map (shift (-1)) l, map (shift (-8)) l] opties2 l = [ map (shift (0)) l , map (shift (-1)) l] words <- getwords --chars = "abceghijklmnoprstvwz" --words = filter (\w -> length w < 10 && all (`elem` chars) w) words0 w1 = filter ("le" `isInfixOf`) words w0 = filter ("le" `isPrefixOf`) words --check = map isInfixOf . map (:"le") $ "beinotz" -- --filter (\w -> or (map ($ w) check)) w1 filter ("eo" `isSuffixOf`) words map (shift 8) "ven" map (shift (-1)) "womu" -} {- OPGAVE 4 --[ [a,b,c] | [a,b,c] <- words , a=='e', b=='n', waarde c >= 17] --[ q:a:b:c:d:w | q:a:b:c:d:w <- words, plus a b == q, waarde a >= 7, waarde a <= 16, waarde b >= 10, waarde b <= 19, waarde c < waarde a, waarde c >= 2, waarde c <=11, plus c d == a, waarde d >= 5, waarde d <= 8] -} {- OPGAVE 10 g10 :: [Integer] g10 = [2231, 11371, 2165299, 131027147, 179536811, 181493911, 10971260147] g10_8 :: Integer g10_8 = 715140684628284199 g10_9 :: Integer g10_9 = 27799359960895951622945294228650160556473581133507282258716324517526331387881422051374048992068531165469465793 g10_10 :: Integer g10_10 = 612242109049354757693703731756141884122575855425310699918367263271480642730811111952684256523677275662759320997 substrs = concat . map inits1 . tails1 where tails1 = filter (not . null) . tails inits1 = filter (not . null) . inits foo :: Integer -> [Integer] foo n = [p | ps <- substrs ns, let p = read ps, p /= 0, p /= 1, p /= n, n `rem` p == 0] where ns = show n -} {- OPGAVE 11b getal11b :: Integer getal11b = 149554087214664289545813515695286402233339701081845595280362829806993294677384116914834752509152758572737499296520884429057992394694292141612557548625371627496876172206474452242442881793196749137289109800753294410539546425609257468594408930562750601301763664664436344439312492666291833846522323701781919914006843850864368311058859764258893753580174283003166720000 -- Godel encodering primeFactors getal11b -} {- OPGAVE 11c -- spatie-test: mapM print . map (map bintonum) . groupBy (\a b -> (a == bla) == (b == bla)) $ escher2 -- per ongeluk verkeerd om escher = [ [1, 0, 0, 0, 0] , [1, 0, 0, 0, 1] , [1, 0, 1, 0, 0] , [0, 0, 1, 1, 0] , [1, 0, 0, 0, 0] , [1, 0, 1, 0, 1] , [0, 0, 0, 0, 1] , [0, 1, 1, 1, 1] , [1, 0, 0, 0, 0] , [1, 0, 1, 0, 1] , [0, 0, 0, 0, 1] , [1, 0, 1, 1, 0] , [1, 0, 0, 0, 0] , [1, 0, 1, 0, 1] , [0, 0, 0, 1, 0] , [0, 0, 1, 1, 0] , [1, 1, 1, 1, 0] , [1, 0, 0, 0, 0] , [1, 1, 0, 1, 1] , [0, 0, 0, 0, 1] , [0, 0, 0, 0, 1] , [1, 1, 0, 1, 0] , [0, 0, 0, 1, 0] , [1, 1, 0, 1, 1] , [0, 0, 0, 1, 0] , [0, 1, 0, 1, 1] , [1, 0, 0, 0, 0] , [1, 0, 1, 0, 1] , [0, 0, 0, 1, 0] , [0, 0, 0, 1, 0] , [1, 0, 1, 1, 0] , [1, 0, 0, 0, 0] , [1, 1, 0, 0, 1] , [0, 0, 1, 1, 0] , [1, 0, 0, 0, 0] , [1, 0, 0, 0, 1] , [1, 0, 1, 0, 1] , [1, 1, 1, 0, 0] , [0, 0, 0, 0, 1] , [1, 1, 1, 1, 1] , [0, 0, 1, 1, 1] , [1, 1, 1, 1, 1] , [1, 0, 0, 0, 0] , [1, 1, 0, 0, 1] , [0, 0, 1, 1, 1] , [0, 0, 1, 1, 1] , [1, 0, 0, 0, 0] , [1, 0, 1, 0, 1] , [1, 1, 0, 0, 1] , [0, 0, 0, 0, 1] , [0, 0, 0, 0, 1] , [1, 1, 0, 1, 0] , [1, 0, 0, 0, 0] , [0, 0, 1, 0, 1] , [1, 0, 0, 0, 0] , [1, 0, 0, 0, 1] , [1, 1, 1, 1, 0] , [0, 0, 0, 1, 0] , [0, 1, 0, 1, 0] , [0, 1, 0, 1, 0] , [0, 0, 0, 1, 0] , [1, 0, 0, 1, 1] , [1, 0, 0, 0, 0] , [0, 0, 0, 1, 0] , [0, 0, 1, 1, 0] , [0, 1, 1, 1, 1] , [1, 0, 0, 0, 0] , [0, 0, 1, 1, 0] , [0, 0, 1, 0, 1] , [1, 1, 0, 1, 1] , [0, 0, 0, 1, 0] , [0, 1, 0, 1, 0] , [1, 1, 1, 1, 0] , [0, 0, 1, 1, 1] , [0, 1, 0, 0, 1] , [1, 0, 0, 0, 0] , [1, 0, 1, 0, 0] , [1, 1, 1, 1, 0] , [0, 0, 0, 1, 0] , [1, 1, 0, 0, 1] , [1, 1, 0, 1, 1] , [0, 0, 0, 1, 0] , [1, 0, 1, 0, 1] , [1, 0, 0, 0, 0] , [1, 1, 1, 1, 0] , [0, 0, 0, 1, 0] , [1, 1, 0, 1, 0] , [0, 0, 1, 1, 1] , [1, 1, 0, 0, 1] , [1, 0, 0, 0, 0] , [1, 1, 1, 0, 0] , [0, 0, 0, 1, 0] , [1, 0, 0, 0, 0] , [1, 0, 0, 0, 1] , [1, 1, 1, 1, 0] , [0, 0, 0, 1, 0] , [1, 1, 0, 1, 1] , [0, 0, 0, 1, 0] , [1, 0, 1, 0, 0] , [0, 1, 1, 1, 1] , [0, 0, 0, 0, 1] , [0, 0, 0, 0, 1] , [1, 1, 1, 0, 0] , [1, 0, 0, 0, 0] , [1, 1, 1, 1, 0] , [0, 0, 1, 1, 0] , [1, 0, 0, 0, 0] , [1, 0, 1, 0, 0] , [0, 1, 1, 1, 1] , [0, 0, 0, 1, 0] , [0, 0, 0, 1, 0] , [1, 0, 1, 0, 1] , [1, 0, 1, 0, 0] , [1, 0, 0, 0, 0] , [1, 1, 0, 1, 1] , [0, 0, 0, 1, 0] , [0, 1, 1, 1, 1] , [1, 1, 1, 1, 0] , [0, 0, 0, 0, 1] , [1, 0, 1, 1, 0] , [1, 0, 0, 0, 0] , [1, 1, 0, 0, 1] , [0, 0, 1, 1, 0] , [1, 0, 0, 0, 1] , [1, 1, 1, 0, 0] , [0, 0, 0, 0, 1] , [0, 0, 0, 0, 1] , [0, 1, 0, 0, 1] , [1, 0, 0, 0, 0] , [0, 1, 0, 1, 0] , [0, 0, 1, 1, 0] , [1, 0, 1, 0, 1] , [1, 1, 1, 0, 0] , [0, 0, 0, 1, 0] , [0, 1, 1, 1, 1] , [1, 0, 0, 0, 0] , [1, 1, 0, 1, 1] , [0, 0, 0, 0, 1] , [1, 0, 0, 0, 0] , [1, 1, 0, 0, 1] , [0, 0, 1, 1, 0] , [1, 0, 0, 0, 0] , [1, 1, 0, 0, 1] , [0, 0, 0, 0, 1] , [0, 0, 0, 0, 1] , [1, 1, 0, 1, 0] , [1, 0, 0, 0, 0] , [1, 1, 0, 0, 1] , [1, 1, 1, 0, 0] , [0, 0, 0, 1, 0] , [1, 0, 1, 1, 0] , [1, 0, 0, 0, 0] , [1, 0, 1, 0, 1] , [0, 0, 1, 1, 0] , [0, 1, 1, 1, 1] , [1, 0, 0, 0, 0] , [1, 0, 0, 0, 1] , [1, 0, 1, 0, 1] , [1, 1, 1, 0, 0] , [0, 0, 0, 0, 1] , [1, 1, 1, 1, 1] , [0, 0, 1, 1, 1] , [1, 1, 1, 1, 1] ] escher2 = [ [0, 1, 0, 0, 1] , [1, 1, 1, 0, 0] , [0, 0, 1, 0, 0] , [1, 0, 0, 1, 0] , [1, 1, 1, 0, 0] , [1, 0, 0, 0, 0] , [1, 1, 1, 1, 0] , [0, 1, 0, 1, 1] , [0, 1, 0, 1, 0] , [1, 1, 1, 0, 0] , [0, 1, 0, 1, 1] , [0, 0, 0, 1, 0] , [1, 0, 0, 0, 0] , [0, 0, 1, 1, 0] , [1, 1, 1, 0, 0] , [0, 0, 0, 1, 0] , [0, 0, 1, 1, 1] , [1, 0, 1, 1, 1] , [0, 0, 0, 0, 1] , [1, 1, 1, 0, 1] , [0, 1, 0, 1, 0] , [1, 0, 0, 0, 0] , [0, 1, 1, 0, 0] , [0, 0, 0, 0, 1] , [1, 1, 1, 0, 1] , [1, 1, 1, 0, 0] , [0, 0, 0, 1, 0] , [1, 1, 1, 0, 1] , [1, 1, 1, 0, 0] , [0, 0, 1, 0, 0] , [1, 1, 1, 0, 0] , [0, 0, 0, 0, 1] , [1, 0, 0, 0, 0] , [1, 1, 1, 1, 0] , [1, 0, 0, 0, 0] , [0, 0, 1, 1, 1] , [1, 0, 0, 0, 0] , [1, 1, 1, 0, 0] , [0, 0, 0, 0, 1] , [1, 0, 0, 0, 0] , [1, 1, 1, 1, 1] ] escherF 1 = ' ' escherF 8 = 'e' -- helemaal escherF 16 = 'a' -- helemaal aa ee komt vaak voor escherF 21 = 't' -- eind: n t r escherF 12 = 'i' escherF 19 = 'k' -- eind: n t r escherF 15 = 'n' escherF 7 = 'r' -- raadselen escherF 27 = 'l' -- helemaal escherF 13 = 'w' escherF 26 = 'h' -- helemaal escherF 11 = 'm' -- helemaal escherF 5 = 's' -- telkens escherF 30 = 'd' escherF 10 = 'g' -- dertig escherF 17 = '.' escherF 18 = 'j' escherF 28 = 'o' escherF 20 = 'u' escherF 31 = 'p' escherF 25 = 'z' escherF _ = '-' map (escherF . bintonum) (reverse escher) -- Niet perfect, maar goed genoeg map ((shift 13) . escherF . bintonum) (escher2) -} {- OPGAVE 12 tonko = ["noll", "hu", "tonde", "tonko", "noll", "tonko", "tonde", "tongo", "de", "de", "go", "tonde", "tonko", "me", "la", "tonko", "ra", "go", "tonti", "tonko", "hu", "go", "tonsu", "go", "la", "tonko", "me", "tonde", "tonhu", "tonko", "ti", "noll", "la", "tonko", "tonde", "tonti", "noll", "noll", "tonti", "tonko", "noll", "tonko", "by", "go", "hu", "me", "ni", "ko", "tonko", "noll", "noll", "la", "tonko", "tonra", "tonko", "fy", "hu", "tongo", "tonde", "tonko", "tonme", "tonko", "fy", "hu", "tongo", "tonde", "tonko", "tonni", "tonvy", "tonko", "tonby", "go", "tonan", "ko", "tonko", "me", "tonde", "tonko", "tonra", "tonhu", "tonko", "tonme", "tonko", "me", "tonde", "tonko", "tonde", "fy", "go", "hu", "tonko", "go", "la", "tonko", "tonni", "tonko", "me", "tonde", "tonko", "ni", "go", "tonko", "vy", "po", "la", "ti", "tonko", "ti", "me", "de", "ra", "tonti", "tonko", "ra", "po", "tongo", "ti", "go", "la", "tonvy"] tonkoF "tonko" = ' ' tonkoF "tonde" = 's' tonkoF "go" = 'e' tonkoF "noll" = 'a' tonkoF "me" = 'i' tonkoF "la" = 'n' tonkoF "hu" = 'l' tonkoF "tonti" = 't' tonkoF "tongo" = 'u' tonkoF "ti" = 'd' tonkoF "ra" = 'h' tonkoF "fy" = 'p' tonkoF "tonsu" = 'v' tonkoF "de" = 'c' tonkoF "tonvy" = '.' tonkoF "tonra" = 'X' tonkoF "tonni" = 'Z' tonkoF "tonme" = 'Y' tonkoF "tonhu" = ',' tonkoF "po" = 'o' tonkoF "ni" = 'j' tonkoF "ko" = 'k' tonkoF "vy" = 'm' tonkoF "tonby" = 'w' tonkoF "tonan" = 'r' tonkoF "by" = 'g' -- map tonkoF tonko -} {- OPGAVE 23a primeFactors 134670 primeFactors 4044121 primeFactors 1012036 primeFactors 122793 primeFactors 106742 primeFactors 62465 primeFactors 14112 primeFactors 4068289 primeFactors 2036162 opg23a n = let l = primeFactors n in last l * n map opg23a [2010..2019] -} {- OPGAVE 25 -- Let op: ij is 1 letter (als y) text = "rgx hppeq hx fy gpiay x;\nvpq cn jizy qppg qjob mxe!\nzx jifymnobycfq nqphkyc upi nqphkx,\nnqycg upi nqxg yi yce upi xe.\n\nfjjmappin zyq fy zyqqym\nfyzy x pgn c kgsn d.\nhppm cn byq is yyi gyqqym\njt zxi byq ym qjob qvyy?" opg25f '\n' = '\n' opg25f ' ' = ' ' opg25f '.' = '.' opg25f '!' = '!' opg25f ';' = ';' opg25f ',' = ',' opg25f '?' = '?' opg25f 'y' = 'e' -- onderscheidt opg25f 'q' = 't' -- onderscheidt opg25f 'p' = 'a' -- dubbele letter opg25f 'i' = 'n' -- doorgaans opg25f 'n' = 's' -- doorgaans opg25f 'f' = 'd' -- doorgaans opg25f 'j' = 'o' -- doorgaans opg25f 'm' = 'r' -- doorgaans opg25f 'a' = 'g' -- doorgaans opg25f 'o' = 'c' -- onderscheidt opg25f 'b' = 'h' -- onderscheidt opg25f 'c' = 'i' -- onderscheidt opg25f 'v' = 'w' -- twee opg25f 't' = 'f' -- of opg25f 'g' = 'l' -- steil / als opg25f 'u' = 'v' -- van opg25f 'z' = 'z' -- zijn opg25f 'x' = 'y' -- zijn opg25f 'e' = 'k' opg25f 'r' = 'b' opg25f 'h' = 'm' -- maakt mij opg25f 's' = 'u' -- nu opg25f 'k' = 'p' -- plus opg25f 'd' = 'j' opg25f x = '-' map opg25f text -- Stampei is een nieuw oud-Hollands gerecht -- en staat niet in het woordenboek -}