Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1.  Directory statistics (Alexander.Vladislav.Popov )
   2. Re:  Please, help me for myFirstCode (Henk-Jan van Tuyl)
   3. Re:  Please, help me for myFirstCode (David McBride)
   4. Re:  Please, help me for myFirstCode (Brent Yorgey)


----------------------------------------------------------------------

Message: 1
Date: Tue, 26 Oct 2010 13:14:17 +0600
From: "Alexander.Vladislav.Popov "
        <alexander.vladislav.po...@gmail.com>
Subject: [Haskell-beginners] Directory statistics
To: beginners@haskell.org
Message-ID:
        <aanlktin_aphblq1mccd+frav5z8dpmao_h2am8jm5...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

Hi, haskellers.

I’ve written a program to assess directory utilization in the selected
path. It displays on the console a list indicating directory size and
path. The list is sorted by descending size. I need some criticism and
some models I could follow to write a more concise and expressive
program.

Thanks in advance.
Alexander.

> {-# LANGUAGE ScopedTypeVariables #-}
> module Main (main) where

> import Control.Exception (SomeException, finally, bracket, handle)
> import Control.Monad
> import Data.List
> import System.Directory
> import System.Environment
> import System.IO
> import Text.Printf

> main :: IO ()
> main = do
>        args <- getArgs
>        if null args
>          then
>            putStr "Displays directory utilization in the selected 
> path.\nUsage: dirstat <path>\n"
>          else
>            mapM_ ds3 args

It safely returns a file size. If an error occurs during file opening,
it will return 0.

> filesize :: FilePath -> IO Integer
> filesize path = (withFile path ReadMode hFileSize) `catch` const (return 0)

Get size of a directory.

> ds :: FilePath -> IO Integer
> ds path = do
>     contents <- getDirectoryContents path `catch` const (return [])
>     let visibles = getVisible contents
>     let path' = clrSlash path
>     a <- (liftM sum) $ sequence $ map (\p -> filesize (path' `mkpath` p)) 
> visibles -- size of a current dir
>     (liftM ((+a) . sum)) $ mapM (\p -> ds (path' `mkpath` p)) visibles -- 
> current + children

Returns a list of pairs: (file size, path)

> ds2 :: FilePath -> IO [(Integer, FilePath)]
> ds2 path = do
>     contents <- getDirectoryContents path
>     let visibles = getVisible contents
>     let path' = clrSlash path
>     let paths = map (\p -> path' `mkpath` p) visibles
>     let pairs = map (\p -> (ds p, p)) paths
>     a <- sequenceFst pairs
>     return $ (reverse . sort . filter (\e -> fst e > 0)) a

Compare it to the function *sequence :: (Monad m) => [m a] -> m [a]*

> sequenceFst :: (Monad m) => [(m t, t1)] -> m [(t, t1)]
> {-# INLINE sequenceFst #-}
> sequenceFst ms = foldr k (return []) ms
>                  where
>                    k (ms, p) m' = do { s <- ms; xs <- m'; return ((s,p):xs) }

Driver

> ds3 :: FilePath -> IO ()
> ds3 path = do
>     s <- ds2 path
>     prn s
>         where
>            prn []     = return ()
>            prn (s:ss) = (putStr . showDir) s >> prn ss

Auxiliary

> skipDots     = (`notElem` [".", ".."])
> getVisible   = filter skipDots
> mkpath p1 p2 = p1 ++ "/" ++ p2
> clrSlash     = reverse . dropWhile (\c -> c =='/' || c == '\\') . reverse

Displays information about a directory.

> showDir :: (Integer, String) -> String
> showDir (s,p) = printVolume s 3 ++ "\t" ++ show p ++ "\n"

*Main> shred "1234567890"
["123","456","789","0"]

> shred [] = []
> shred ss =  (take 3 ss) : (shred (drop 3 ss))

*Main> prettyNum "1234567890"
"1 234 567 890"

> prettyNum = concat . intersperse " " . (map reverse) . reverse . shred . 
> reverse

*Main> units (1024*1024*1024)
[1073741824,1048576,1024,1,0]

> units :: Integer -> [Integer]
> units 0 = [0]
> units x = x : units' x
>     where
>       units' 0 = []
>       units' x = y : units' y
>           where
>             y = round (fromIntegral x / 1024)

Just SI prefixes

> prefix = ["B", "K", "M", "G", "T", "P", "E", "Z", "Y"]

*Main> tagged (1024*1024*1024)
[("1 073 741 824","B"),("1 048 576","K"),("1 024","M"),("1","G"),("0","T")]

> tagged x = (map (prettyNum . show) $ units x) `zip` prefix

*Main> printVolume (1024*1024*1024) 5
1 024 M

> printVolume x width = printf "%*s %s" width (fst one) (snd one)
>     where
>        one = head $ dropWhile (\p -> length (fst p) > width) $ tagged x


------------------------------

Message: 2
Date: Tue, 26 Oct 2010 15:34:13 +0200
From: "Henk-Jan van Tuyl" <hjgt...@chello.nl>
Subject: Re: [Haskell-beginners] Please, help me for myFirstCode
To: beginners@haskell.org, "Sok H. Chang" <shae...@gmail.com>
Message-ID: <op.vk6qnbj2pz0...@zen5.arnhem.chello.nl>
Content-Type: text/plain; charset=iso-8859-15; format=flowed;
        delsp=yes

On Tue, 26 Oct 2010 08:36:58 +0200, Sok H. Chang <shae...@gmail.com> wrote:

-----------------------------------------------------------------------------------------------------------------------
> import System
> import System.Random
>
> main = do myHeader <- readFile "C:\\Documents and Settings\\myHeader.txt"
> putStrLn $ myExtractSentence myHeader
> myExtractSentence file = ary !! ranNoInt
> where
>          ranNoInt =<< ranNo                        -- *mark
>          ranNo = randomRIO (0, n-1)
>          n = length ary
>          ary = lines file
> ----------------------------------------------------------------------------------------------------------------------
> There are two questions.
>
> 1) I've got following error message.
> Haskell>ghc --make Test01.hs -o Test
> [1 of 1] Compiling Main             ( Test01.hs, Test01.o )
>
> Test01.hs:10:9: parse error (possibly incorrect indentation)
>
> How can fix it?

The lay-out is wrong: putStrLn should be in the same column as the  
"myHeader" above it; avoid tabs to prevent unexpected lay-out problems.  
The lay-out could be like this:
-----------------------------------------------------------------------------------------------------------------------

main =
   do
     myHeader <- readFile "C:\\Documents and Settings\\myHeader.txt"
     putStrLn $ myExtractSentence myHeader

-----------------------------------------------------------------------------------------------------------------------


>
> 2) Is it OK at "*mark" line?
>

Note that ranNoInt is a value inside the IO monad, you cannot use directly  
as an index.

Regards,
Henk-Jan van Tuyl


-- 
http://Van.Tuyl.eu/
http://members.chello.nl/hjgtuyl/tourdemonad.html
--


------------------------------

Message: 3
Date: Tue, 26 Oct 2010 09:45:43 -0400
From: David McBride <dmcbr...@neondsl.com>
Subject: Re: [Haskell-beginners] Please, help me for myFirstCode
To: "Sok H. Chang" <shae...@gmail.com>
Cc: beginners@haskell.org
Message-ID:
        <aanlkti=bnclbdy7gdy75+pyrbwgjmref5evholayt...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

2) No.

1) That is your syntax error.  You should have "ranNoInt = <something>".
The =<< operator is meant for the definition of the function.

Try this:

import System
import System.Random

main = readFile "C:\\Documents and Settings\\myHeader.txt" >>=
myExtractSentence >>= putStrLn

myExtractSentence file = do
  ranNoInt <- ranNo
  return $ ary !! ranNoInt
  where
         ranNo = randomRIO (0, n-1)
         n = length ary
         ary = lines file


On Tue, Oct 26, 2010 at 2:36 AM, Sok H. Chang <shae...@gmail.com> wrote:

> Hello, everyone.
>
> I need help for my first code.
> I write this code for extracting one sentence from text file.
>
> The code is
>
> -----------------------------------------------------------------------------------------------------------------------
> import System
> import System.Random
>
> main = do myHeader <- readFile "C:\\Documents and Settings\\myHeader.txt"
>  putStrLn $ myExtractSentence myHeader
> myExtractSentence file = ary !! ranNoInt
>  where
>          ranNoInt =<< ranNo                        -- *mark
>          ranNo = randomRIO (0, n-1)
>          n = length ary
>          ary = lines file
>
> ----------------------------------------------------------------------------------------------------------------------
> There are two questions.
>
> 1) I've got following error message.
> Haskell>ghc --make Test01.hs -o Test
> [1 of 1] Compiling Main             ( Test01.hs, Test01.o )
>
> Test01.hs:10:9: parse error (possibly incorrect indentation)
>
> How can fix it?
>
> 2) Is it OK at "*mark" line?
>
> Thank you.
>
> S. CHANG
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20101026/a0ae4e9a/attachment-0001.html

------------------------------

Message: 4
Date: Tue, 26 Oct 2010 10:16:06 -0400
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] Please, help me for myFirstCode
To: beginners@haskell.org
Message-ID: <20101026141606.ga5...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

Just a meta-observation: although such a program might be easy in
other languages, a program involving file I/O and random number
generation is probably not a very good choice for one's first Haskell
program!  Is there a particular book or tutorial you are following
along with?

-Brent

On Tue, Oct 26, 2010 at 03:36:58PM +0900, Sok H. Chang wrote:
> Hello, everyone.
> 
> I need help for my first code.
> I write this code for extracting one sentence from text file.
> 
> The code is
> -----------------------------------------------------------------------------------------------------------------------
> import System
> import System.Random
> 
> main = do myHeader <- readFile "C:\\Documents and Settings\\myHeader.txt"
> putStrLn $ myExtractSentence myHeader
> myExtractSentence file = ary !! ranNoInt
> where
>          ranNoInt =<< ranNo                        -- *mark
>          ranNo = randomRIO (0, n-1)
>          n = length ary
>          ary = lines file
> ----------------------------------------------------------------------------------------------------------------------
> There are two questions.
> 
> 1) I've got following error message.
> Haskell>ghc --make Test01.hs -o Test
> [1 of 1] Compiling Main             ( Test01.hs, Test01.o )
> 
> Test01.hs:10:9: parse error (possibly incorrect indentation)
> 
> How can fix it?
> 
> 2) Is it OK at "*mark" line?
> 
> Thank you.
> 
> S. CHANG

> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners



------------------------------

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 28, Issue 39
*****************************************

Reply via email to