[haskell-br] HackerRank

Joao H A Franco jhafranco at gmail.com
Tue Jan 6 17:18:34 UTC 2015


Olá pessoal,

Outro exemplo de implementação:

import Data.Char (digitToInt)

main :: IO ()
main = do _ <- getLine
          interact $ unlines . map (show . findDigits) . lines

findDigits :: String -> Int
findDigits s = length . filter check $ map digitToInt s
                 where check n = (n /= 0) && (read s `mod` n == 0)

Abs.

João Henrique

Em 6 de janeiro de 2015 04:10, Álvaro Pereira <alvaro.bruno em gmail.com>
escreveu:

> Pro Jean, que tava pedindo umas dicas... tô aprendendo haskell ainda, mas
> deixa eu tentar ajudar no que consigo no código haeuhea, vamo lá:
>
> import Data.Char
>> import Control.Monad
>>
>> intDigits :: Integer -> [Int]
>> intDigits n = map (\x -> read [x] :: Int) (show n)
>>
>> Aqui o " :: Int " é desnecessário, porque como você declarou o tipo da
> função (que retorna [Int]), a linguagem já se vira sozinha.
> Além disso, o haskell tem o currying pronto, então "map (\x -> read [x])"
> já é uma função (que "tá faltando" receber o último argumento), então dá
> pra você compor ela com o show. Podendo escrever só assim:
>
> intDigits = map (\x -> read [x]) . show
>
> (daí nem precisa do n)
>
>> charDigits :: [Int] -> [Char]
>> charDigits = map (\x -> intToDigit x)
>>
>> digits :: Integer -> [Char]
>> digits = charDigits . intDigits
>>
>> [Char] e String são as mesmas coisas, você tá convertendo um int pra uma
> lista com os digitos e passando eles pra char, mas não tinha necessidade
> (isso é a mesma coisa que dar show já).
> Tipo, se você fizer:
>
> digits = show
>
> O código continua fazendo a mesma coisa :P
>
>> divide :: Integer -> Char -> Bool
>> divide _ '0' = False
>> divide n c = isMultiple
>>     where digit = toInteger $ digitToInt c
>>           nModDigit = n `mod` digit
>>           isMultiple = nModDigit == 0
>>
>> findDigit :: Integer -> Int
>> findDigit n = foldl (\a b -> a + (if div b then 1 else 0)) 0 list
>>     where div = divide n
>>           list = digits n
>>
>> getStrings :: Integer -> [IO String]
>> getStrings n
>>     | n <= 0 = []
>>     | otherwise = getLine : getStrings (n - 1)
>>
>> Aqui acho q era mais negócio c usar pattern matching do que as guards
> (que nem fez embaixo), mas só pq fica menor/mais bonitim msm
>
>> getIntegers :: [String] -> [Integer]
>> getIntegers [] = []
>> getIntegers (x:xs) = readInteger x : getIntegers xs
>>
>>
> Aqui c podia fazer algo como: getIntegers = map read
>
>> readInteger :: String -> Integer
>> readInteger = read
>>
>> Aqui, c só deu outro nome pro "read".
> Se a intenção foi forçar o tipo, é mei bobera, no sentido que se na outra
> função que c vai usar ela (a getIntegers por exemplo) já tem o tipo
> declarado,
> a linguagem já vai converter pro tipo certo com o read.
>
>> main = do
>>     qtd <- getLine
>>     valStr <- sequence $ getStrings (readInteger qtd)
>>     let valores = getIntegers valStr
>>         digitsFound = map (findDigit) valores
>>     mapM (print) digitsFound
>>
>>
> E no geral c tá usando Integer, sendo que no problema não estouraria o
> Int, daí não tem pq usar. (Integer é mais pesadinho).
> Dá uma olhada depois em coisas como forever, getContents e interact, que
> ajuda em muitos casos na I/O.
>
> Vô botar meu código aqui pro mesmo problema, talvez c tira algumas ideias
> tb:
>
> main = do
>   _ <- getLine
>   interact $ unlines . map (show . solve) . lines
>
> solve ::  String -> Int
> solve line =
>   let n = read line
>   in countDiv n $ digits n
>
> digits :: Int -> [Int]
> digits = map (\x -> read [x]) . show
>
> divides :: Int -> Int -> Bool
> divides _ 0 = False
> divides n d = (n `mod` d == 0)
>
> countDiv :: Int -> [Int] -> Int
> countDiv n nums =
>   let divisors = filter (divides n) nums
>   in length divisors
>
> (Se alguém tiver algumas dicas pra dar em cima dele, é bem vindo tb :D)
>
> _______________________________________________
> haskell-br mailing list
> haskell-br em haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-br
>
>
-------------- Pr�xima Parte ----------
Um anexo em HTML foi limpo...
URL: <http://www.haskell.org/pipermail/haskell-br/attachments/20150106/9878ba22/attachment.html>


More information about the haskell-br mailing list