De-sugaring Do-Notation Function - haskell

sugar a function that use's Do notation. But I'm struggling somewhat with creating/converting the function to using >>= and lambda's only. Any help appreciated.
This function takes a filepath, reads it, turns it into a list, then it takes the resulting list, splits it in half, based on its length, and lastly writes two files one taking the first half of the list, and one file consisting of the second half of the list. That is the idea anyway.
splitFile :: FilePath -> IO ()
splitFile file = do
x <- readFileUTF8 file
let y = splitAt (div (length $ lines x) 2) $ lines x
writeFile "/tmp/foo.txt-part1" $ unlines $ fst y
writeFile "/tmp/foo.txt-part2" $ unlines $ snd y

splitFile :: FilePath -> IO ()
splitFile file =
readFileUTF8 file >>= \x ->
let y = splitAt (div (length $ lines x) 2) $ lines x in
(writeFile "/tmp/foo.txt-part1" $ unlines $ fst y) >>
(writeFile "/tmp/foo.txt-part2" $ unlines $ snd y)
but you can replace >> .. with >>= \_ -> ...
You can also turn y into a pattern match, but to be completely faithful to the original you need to use a lazy pattern ~(a, b)
..
let (a, b) = splitAt (div (length $ lines x) 2) $ lines x in
writeFile "/tmp/foo.txt-part1" (unlines a) >>
writeFile "/tmp/foo.txt-part2" (unlines b)

Related

Changing the order of arguments for function and list with flip in haskell

I have the following (from here):
for_ [1..10] $ (\x -> T.putStrLn $ T.pack $ show x )
I'm trying to rewrite this in terms more like
applylike myfunction toList
rather than
applylike tolist myfunction
I understand the flip function can be employed to change argument order:
flip :: (a -> b -> c) -> b -> a -> c
flip f takes its (first) two arguments in the reverse order of f.
>>> flip (++) "hello" "world"
"worldhello"
This works as my original:
import Data.Foldable (for_)
:t flip
-- 1
for_ [1..10] $ (\x -> T.putStrLn $ T.pack $ show x )
-- success
But when I try to apply it directly, this fails:
-- 2
flip for_ $ (\x -> T.putStrLn $ T.pack $ show x ) [1..10]
-- fail
I notice, however, that if I remove the $ operator which was required in (1), it succeeds:
-- 3
flip for_ (\x -> T.putStrLn $ T.pack $ show x ) [1..10]
-- success
But I don't understand why that scans correctly. When I remove the $ operator from the original non-flipped version (1), that also fails.
-- 4
for_ [1..10] (\x -> T.putStrLn $ T.pack $ show x )
-- fail
How are these being parsed that $ is required in (1) and required not to be present in (3)?
Update
Apologies: 4 above does succeed. I must have had a typo while investigating this, which certainly added to my confusion. For future readers, 4 does not fail and the universe makes more sense, and both comments and the answer accepted below were very helpful in this investigation.
Because that's how the $ operator works. This operator is not part of Haskell syntax, but a regular user-defined operator, like any other. It's defined like this:
f $ x = f x
Therefore, if you write something like:
f a $ b
That is the same as:
f a b
But if you write something like:
f $ a b
That is the same as:
f (a b)
This is because function application a b (i.e. function a applied to argument b) has the highest precedence in Haskell, nothing can bind stronger than the function application, including the $ operator.
Therefore, your first attempt:
flip for_ $ (\x -> T.putStrLn $ T.pack $ show x ) [1..10]
Is really equivalent to:
flip for_ ( (\x -> T.putStrLn $ T.pack $ show x ) [1..10] )
Which is clearly not what you meant.

What's preventing IO flush in my code?

I tried solving this, and the following is trial stuff.
When I test this in ghci with hSetBuffering stdout NoBuffering, solveAct 1, 15 10, ghci showed few lines of results and blocked much time, and showed rest result at once.
How can I see the intermediate results in real time?
import Control.Monad
import Data.List
import Data.Maybe
import System.IO
readInts = fmap read . words <$> getLine :: IO [Int]
main = do
t <- readLn :: IO Int
hSetBuffering stdout NoBuffering
sequence_ $ solveAct <$> [1..t]
showTable x = intercalate "\n" $ intercalate " " . fmap show <$> x
solveAct i = do
[j, n] <- readInts
putStrLn $ "Case #" ++ show i ++ ":"
putStrLn $ showTable (take n $ solve (j-1))
digits n = [[x ^ y | y <- [1..n-1]] | x <- [2..10]]
primes = 2 : [x | x <- [3,5..], all (\y -> x `rem` y /= 0) $ takeWhile (<= intSqrt x) primes]
intSqrt = floor . sqrt . fromIntegral
getNDivisor n = listToMaybe [x | x <- takeWhile (<= intSqrt n) primes, n `rem` x == 0]
casesOfMat = subsequences . transpose . digits
casesOfJam n = fmap ([1 + x^n | x <- [2..10]]:) $ casesOfMat n
eachBaseReps n = fmap sum . transpose <$> casesOfJam n
solve :: Int -> [[Int]]
solve n = do
decimals <- eachBaseReps n
let divs = getNDivisor <$> decimals
guard $ all isJust divs
return $ last decimals : catMaybes divs
You are seeing the results in real time. It's just that the computation of all isJust . map getNDivisor takes a long time for the third element of eachBaseReps 14.

Error in recursive function / trying to find all subdirectories of a given directory

I'm trying to write a function that returns all subdirectories of a given directory (recursive).
What I have so far is:
import System.Directory
import Control.Monad
import Data.List
getSubDirs :: FilePath -> IO [FilePath]
getSubDirs dir =
getDirectoryContents dir
>>= filterM (\x -> return $ x /= "." && x /= "..")
>>= mapM (makeAbsolute . (\x -> dir ++ "/" ++ x))
>>= filterM doesDirectoryExist
>>= return . reverse
getDirTree :: [FilePath] -> IO [FilePath]
getDirTree [] = return []
getDirTree l#(x:xs) = do
a <- getSubDirs x >>= getDirTree
b <- getDirTree xs
return (nub $ l ++ a ++ b)
Which seems to work. But there is something wrong with the recursion - I would like to get rid of the nub in getDirTree.
This looks wrong:
getDirTree l#(x:xs) = do
-- ...
b <- getDirTree xs
return (nub $ l ++ a ++ b)
The last line adds l which is x:xs with b, which will contain the l argument in the getDirTree xs call, so b will contain xs. Hence xs is included twice (at every recursive step!).
Try return ( x : a ++ b ) instead.
This seems to work:
getDirTree' :: FilePath -> IO [FilePath]
getDirTree' path = do
subs <- getSubDirs path
as <- mapM getDirTree' subs
return $ subs ++ concat as

Don't know how to use . and $ operator in Haskell

I am not sure how to implement the . and the $ operators to simplify the following definitions:
compress :: [Char] -> [Char]
compress [] = []
compress as
| g as 1 == 1 = [head as] ++ compress (drop 1 as)
| otherwise = [head as] ++ show (g as 1) ++ compress (drop (g as 1) as)
g :: [Char] -> Int -> Int
g [] i = i
g (a:[]) i = i
g (a:as) i
| a == head as = g as (i + 1)
| otherwise = i
main = getLine >>= \str -> putStrLn $ compress str
I've read that the . operator is a functional composition so that the output of one function goes to the input of another, and $ is a substitute for a parenthesis.
Therefore, I tried changing it to
compress :: [Char] -> [Char]
compress [] = []
compress as
| g as 1 == 1 = [head as] ++ compress . drop 1 as
| otherwise = [head as] ++ show (g as 1) ++ compress . drop (g as 1) as
g :: [Char] -> Int -> Int
g [] i = i
g (a:[]) i = i
g (a:as) i
| a == head as = g as (i + 1)
| otherwise = i
main = getLine >>= \str -> putStrLn $ compress str
But I get type errors saying
could not match '[Char]' with a0 -> [Char]
I am a bit confused on how to use those operators.
I do not see a way of using ($) and (.) in this code.
However, you can simplify your code as this:
compress :: [Char] -> [Char]
compress [] = []
compress as#(x:xs)
| g as 1 == 1 = x : compress xs
| otherwise = x : show (g as 1) ++ compress (drop (g as 1) as)
g :: [Char] -> Int -> Int
g (a:as) i
| a == head as = g as (i + 1)
| otherwise = i
g _ i = i
main = getLine >>= putStrLn . compress
For instance, this:
[head as] ++ compress (drop 1 as)
is the same as this:
head as : compress (drop 1 as)
And by using pattern matching, it becomes even shorter:
x : compress xs
The operators you want to use are commonly use to write a shorter version (with less parentheses) of a function. For instance, your compress function could be written this way:
compress :: [Char] -> [Char]
compress = concatMap (\x -> head x : show (length x)) . group
instead of this:
compress :: [Char] -> [Char]
compress xs = concat $ map (\x -> head x : show (length x)) $ group xs
or even this
compress :: [Char] -> [Char]
compress xs = concatMap (\x -> head x : show (length x)) (group xs)
Here is a simpler example:
capitalizeWords :: String -> String
capitalizeWords string = unwords (map (\(f:rest) -> toUpper f : rest) (words string))
main = putStrLn (capitalizeWords "here you are")
can be rewritten to:
capitalizeWords :: String -> String
capitalizeWords = unwords . map (\(f:rest) -> toUpper f : rest) . words
main = putStrLn $ capitalizeWords "here you are"
Here are the explanations:
The ($) can be used in the main function because this operator can be viewed as wrapping in parentheses what is on the right of it.
For the capitalizeWords function, it can first be simplify to this:
capitalizeWords string = unwords $ map (\(f:rest) -> toUpper f : rest) (words string)
using the previous explanation.
Again, we can use ($):
capitalizeWords string = unwords $ map (\(f:rest) -> toUpper f : rest) $ words string
And as the string parameter is on the right of both side of the equality, we can use composition to remove this parameter. So we get the final capitalizeWords function shown above.
You can learn more about the ($) and (.) operators here.
There are tools that can help you writing point-free functions like hlint and pointfree.

In Haskell, I want to make simple concordancer. But it response errors again, and again

import System.IO
import Data.List
import Data.Char
printlist :: Show a => a -> IO ()
printlist x = putStr (show x)
main = do
handle <- openFile "/usr/local/share/corpus" ReadMode
text <- hGetContents handle
let wlist = words text
clist = map (\k -> take ((k + 15) - k + 1).drop (k - 10))(elemIndices "word" wlist)
printlist clist
What can I do to finish my job.
please, give me a answer or hints
Well I felt nice, so I fixed up the errors here
import Data.List
printlist :: Show a => a -> IO ()
printlist = putStr . show
main = do
text <- readFile "/usr/local/share/corpus" -- removed useless handle
let clist = zipWith (flip ($)) (repeat text)
-- ^ applied each function to file
-- since you currently had
-- clist :: [String -> String]
. map (\k -> take 16 . drop (k-10))
. elemIndices "word"
$ words text -- inlined wlist
printlist clist -- fixed indenting
So now what this does is produce a list of functions of type String -> String and apply each of them to the file /usr/local/share/corpus and print the result.
I suppose the map part can be rewritten to be
(.:) = (.) . (.)
infixr 9 .:
map (take 16 .: drop . subtract 10)
Which is arguably prettier.

Resources