Haskell解题集:PAT (Basic Level) Practice (中文)
[malicTOC]
开个project,长期更新,目标是用纯函数式的Haskell语言把PAT基础级做完…
P1001 角谷猜想
main= do line<-getLine let p = read line::Int print $ halistone p 0 haliOp:: Int->Int haliOp x | mod x 2 ==0 = div x 2 | otherwise = div ((3*x)+1) 2 halistone :: Int-> Int -> Int halistone 1 p = p halistone x p = halistone (haliOp x) (p+1)
P1002 写出这个数
给出一串数字,各位加和之后用拼音输出和的各位上的数字
import Data.Char main=do line<-getLine let s = show $ sum $ map (\x -> ord x - ord '0') line output 0 s output :: Int->[Char] -> IO() output _ [] = return () output 0 (x:xs) = do putStr $ pinyin x output 1 xs output 1 (x:xs)= do putStr " " putStr (pinyin x) output 1 xs pinyin :: Char -> String pinyin w | w=='0' ="ling" | w=='1' = "yi" | w=='2' = "er" | w=='3' = "san" | w=='4' = "si" | w=='5' = "wu" | w=='6' = "liu" | w=='7' = "qi" | w=='8' = "ba" | w=='9' = "jiu"
1004:
给出学生信息,输出成绩最高与最低的学生姓名与学号
data Person = Person String String Int score :: Person -> Int score ( Person _ _ x) = x name :: Person -> String name (Person s _ _ ) = s idNum :: Person -> String idNum (Person _ s _ ) = s main=do line<-getLine ctx<-getContents let p = [Person (c!!0) (c!!1) (read (c!!2) ::Int)|c<-[words c|c<-lines ctx]] output (rec cMax p) output (rec cMin p) rec :: (Person-> Person-> Person) -> [Person]->Person rec _ [x] = x rec f (x:xs) = f x (rec f xs) cMax :: Person-> Person-> Person cMax x y = if score x > score y then x else y cMin :: Person-> Person-> Person cMin x y = if score x < score y then x else y output :: Person -> IO() output x = putStrLn $ (name x) ++ " " ++ (idNum x)
1006 简单的字符串处理
main=do line<-getLine let n=read line ::Int let huns = div n 100 let tens = div (mod n 100) 10 let ones = mod n 10 repStr "B" huns repStr "S"tens repArr [1..ones] putStrLn "" repStr :: String -> Int -> IO() repStr _ 0 = return () repStr s x = do putStr s repStr s (x-1) repArr :: [Int]->IO() repArr [] = return () repArr (x:xs) = do putStr (show x) repArr xs
1007 素数对猜想,素数处理
main=do line<-getLine let p = read line :: Integer let u = primes p let prGap = zipWith (-) (tail u) u print $ howmany 2 prGap primes :: Integer -> [Integer] primes 1 = [] primes 2 = [2] primes n = qs ++ [x | x <- [sqrtn..n], and [mod x y /= 0 | y <- qs]] where qs = primes sqrtn sqrtn = floor $ sqrt $ fromInteger n + 1 howmany :: Integer -> [Integer] -> Integer howmany _ [] = 0 howmany v (x:xs) | v==x = 1 + howmany v xs | otherwise = howmany v xs
1008 数组元素循环右移问题 :基本数组操作
import Data.List main=do line<-getLine let n = [read x::Int|x<-words line]!!1 line<-getLine let p = [read x::Int|x<-words line] putStrLn $ intercalate " " [show x|x<-rightShift n p] rightShift :: Int->[Int]->[Int] rightShift 0 p = p rightShift n p =rightShift (n-1) (last p : init p)
1009 说反话 : 简单的字符操作
import Data.List main=do line<-getLine let p = [x|x<-words line] putStrLn $ intercalate " " (reverse p)
1012 数字分类:多种的基本数据操作与格式化输出
import Data.List import Text.Printf main=do line<-getLine let p = tail [read x::Int | x<-words line] let a1= filter (\x -> mod x 10 ==0 ) p let a2= filter (\x -> mod x 5 ==1 ) p let a3= filter (\x -> mod x 5 ==2 ) p let a4= filter (\x -> mod x 5 ==3 ) p let a5= filter (\x -> mod x 5 ==4 ) p let r1= if length a1 >0 then sum a1 else -1 let r2= if length a2>0 then interlaceAdd a2 else -1 let r3= if length a3>0 then length a3 else -1 let r4= if length a4>0 then average a4 else -1 let r5= if length a5>0 then maxL a5 else -1 if r1/=(-1) then printf "%d" r1 else printf "N" printf " " if r2/=(-1) then printf "%d" r2 else printf "N" printf " " if r3/=(-1) then printf "%d" r3 else printf "N" printf " " if r4/=(-1) then printf "%.1f" r4 else printf "N" printf " " if r5/=(-1) then printf "%d" r5 else printf "N" printf "\n" interlaceAdd :: [Int] -> Int interlaceAdd [] = 0 interlaceAdd (x:xs) = x - (interlaceAdd xs) maxL :: [Int]->Int maxL [x] = x maxL (x:xs) = max x (maxL xs) average :: [Int]->Float average p = s/l where s = read (show (sum p))::Float l = read (show (length p))::Float
P1061
main=do line<-getLine line<-getLine let scoreWeight=[read x::Int| x<-words line] line<-getLine let rightAnswer=[read x::Int| x<-words line] ctx<-getContents let p=[ [ read x :: Int |x<-words z] | z<-[s | s<- lines ctx]] solve scoreWeight rightAnswer p solve :: [Int]->[Int] -> [[Int]] -> IO() solve _ _ [] = return () solve scoreWeight rightAnswer (phd:pList) = do print $ givenScore scoreWeight rightAnswer phd solve scoreWeight rightAnswer pList givenScore :: [Int]-> [Int]->[Int] -> Int givenScore [] _ _ = 0 givenScore (sh:sList) (rh:rList) (ph:pList) | rh == ph = sh + givenScore sList rList pList | rh /= ph = givenScore sList rList pList
P1079 延迟的回文数
main=do line<-getLine let z = findNext line 10 output $ z putStrLn $ if isPali (last z) then ((last z) ++" is a palindromic number.") else "Not found in 10 iterations." isPali :: [Char] -> Bool isPali [] = True isPali [x]= True isPali x = (head x == last x) && (isPali $ init (tail x)) genNext :: [Char] -> [Char] genNext x = show $ (read x::Integer) + (read (reverse x) ::Integer) findNext :: [Char] -> Int ->[[Char]] findNext s 0 = [s] findNext s x = if isPali s then [s] else s:(findNext (genNext s) (x-1)) output :: [[Char]] -> IO() output [x] = return () output (x:y:xs) = do putStrLn (x ++" + " ++(reverse x) ++" = " ++ y) output (y:xs)
P1086
main=do line<-getLine let p=[read x::Int|x<-words line] putStrLn $ show (read ( reverse $ show (product p))::Int)
P1091
main=do line<-getLine line<-getLine let r=[read x::Int| x<-words line] ana r ana :: [Int]->IO() ana [] = return () ana (x:xs) = do solve 1 x ana xs backword :: Int -> [Char] ->[Char] backword 0 x=[] backword s x= (backword (s-1) $ init x )++[ last x] solve :: Int->Int->IO() solve 10 x = putStrLn "No" solve a x = do let digits = length $ show x if (backword digits (show (a*(x^2)))) == show x then putStrLn ((show a)++" "++(show (a*(x^2)))) else solve (a+1) x