Hello,

On Thursday 15 January 2009 11:33, Trent W.Buck wrote:
> I've tried to cherry-pick the least contentious suggestions made by
> hlint.  In many cases I haven't applied hlint's suggestion, but rather
> have tweaked it a little.

As we discussed earlier on #darcs, I have some reservations about the value 
one should place on suggestions from such an automated tool. For me, to place 
any faith on such a tool would require me to study it in detail and decide 
whether liked what it did or not. And since I fundamentally doubt that this 
sort of mechanism will be able to add dramatic value to a piece of code, I 
simply ignore them when I meet them.

I should mention that I did notice the appearance of DrHaskell (as it was 
originally named) and its subsequent renaming to hlint. But I must confess 
that I got the impression that the advice by hlint for Haskell code was not 
of the same grave nature as the advice from the original lint for C code, 
warning about doubtful constructions like "if (c=' ')" instead of "if (c==' 
')" or passing a pointer where an int is expected. The examples you bring out 
here does not change this impression.

> 
> Because the heavy lifting was done by an automated tool, I have
> attributed it as such.  I can change the attribution to be in my name
> if you feel that's more appropriate. 

I most firmly believe that such changes should be attributed to a human being, 
as any change should. The heavy lifting was not at all done by the tool, it 
was done by you, in choosing to use this particular tool.

> 
> In all cases, I have set the patch name to be the hint name from
> hlint.

This leaves an impression that I firmly believe we should avoid to make: That 
the darcs code base is wholly hlint'ified on a regular basis.

> 
> Thu Jan 15 13:08:04 EST 2009  hlint
>   * Redundant if.
> 
> Thu Jan 15 13:11:05 EST 2009  hlint
>   * Use a more efficient monadic variant.
> 
> Thu Jan 15 14:02:04 EST 2009  hlint
>   * Use print.
> 
> Thu Jan 15 14:02:12 EST 2009  hlint
>   * Use concatMap.
> 
> Thu Jan 15 14:30:47 EST 2009  hlint
>   * Use one map.
> 
> Thu Jan 15 14:31:19 EST 2009  hlint
>   * Use (:).
> 
> Thu Jan 15 14:32:23 EST 2009  hlint
>   * Use const.
> 
> Thu Jan 15 14:32:41 EST 2009  hlint
>   * Use replicate.
> 
> 

Having set the stage, I will now comment on the individual changes. I have not 
done this sort of thing before, so maybe this is needlessly clumsy, but I 
have simply copied the whole patch file into the mail, removed what seemed 
unnecessary and written comments in between. And please have firmly in mind 
that a person's view of style differences, such as these, is highly dependent 
on taste, experience, habits, and a lot of other things that are not 
particularly easy to define precisely.

New patches:

> [Redundant if.
> hlint**20090115020804
>  Ignore-this: 609fb1781e8d1b9233e7af73920316f7
> ] hunk ./src/Darcs/Patch/Read.hs 135
>
>  skip_newline :: ParserM m => m Bool
>  skip_newline = do s <- peek_input
> -                  if B.null s
> -                    then return False
> -                    else if BC.head s /= '\n'
> -                         then return False
> -                         else alter_input B.tail >> return True
> +                  if B.null s || (BC.head s /= '\n')
> +                  then return False
> +                  else alter_input B.tail >> return True
>
>  readTok :: ParserM m => FileNameFormat -> m (Prim C(x y))
>  readTok x = do

I find the changed version more difficult to read than the original: Try the 
"telephone test" from Kernighan and Plauger's "The Elements of Programming 
Style": Read the code aloud over the telephone and see if you can make 
someone understand it. In any case, when I read the original, I say to 
myself, roughly, ok, empty list, out of the way, then I have something 
non-empty in my hand, then check the first element. Whereas in the changed 
version, I have this boolean expression that combines two conditions with || 
(or), one of which is something that checks something with /= (different 
from), ugh, hard thinking needed.

> [Use a more efficient monadic variant.
> hlint**20090115021105
>  Ignore-this: d9c5421104db4f9f24ce486162fac198
> ] hunk ./src/Darcs/Patch/Test.hs 312
>  check_patch (PP (FP f AddFile)) =  create_file $ fn2fp f
>  check_patch (PP (FP f (Hunk line old new))) = do
>      file_exists $ fn2fp f
> -    mapM (delete_line (fn2fp f) line) old
> -    mapM (insert_line (fn2fp f) line) (reverse new)
> +    mapM_ (delete_line (fn2fp f) line) old
> +    mapM_ (insert_line (fn2fp f) line) (reverse new)
>      is_valid
>  check_patch (PP (FP f (TokReplace t old new))) =
>      modify_file (fn2fp f) (try_tok_possibly t old new)
> hunk ./src/Darcs/Patch/Test.hs 321
>  -- and PNothings which may have contained new...
>  check_patch (PP (FP f (Binary o n))) = do
>      file_exists $ fn2fp f
> -    mapM (delete_line (fn2fp f) 1) (linesPS o)
> +    mapM_ (delete_line (fn2fp f) 1) (linesPS o)
>      file_empty $ fn2fp f
> hunk ./src/Darcs/Patch/Test.hs 323
> -    mapM (insert_line (fn2fp f) 1) (reverse $ linesPS n)
> +    mapM_ (insert_line (fn2fp f) 1) (reverse $ linesPS n)
>      is_valid

I have no opinion about this, I am not familiar with mapM or mapM_.

>
>  check_patch (PP (DP d AddDir)) = create_dir $ fn2fp d
> [Use print.
> hlint**20090115030204
>  Ignore-this: e378f8a54b687a4e260011aac8d85704
> ] hunk ./src/Darcs/Patch/Check.hs 58
>  do_verbose_check :: PatchCheck a -> a
>  do_verbose_check (PC p) =
>      case p (P [] []) of
> -    (pc, b) -> unsafePerformIO $ do putStrLn $ show pc
> +    (pc, b) -> unsafePerformIO $ do print pc
>                                      return b
>
>  is_valid :: PatchCheck Bool
> hunk ./src/microbench.hs 38
>              _ -> fail $ unwords $ "Invalid arguments:  ":args
>
>  sloppyReadFilePS :: String -> IO B.ByteString
> -sloppyReadFilePS f = B.readFile f `catch` \e -> do putStrLn (show e); 
return B.empty
> +sloppyReadFilePS f = B.readFile f `catch` \e -> print e >> return B.empty

I tend to think that this change is a bad idea, although I rarely move in such 
parts of the world: As far as I can tell, if someone decided to add some 
constant string to the message printed, for example, then this change would 
have to be undone, but I am not really sure - a person who moves comfortably 
among monads would probably tell me that the added string could be fitted in 
in some other way.

> [Use concatMap.
> hlint**20090115030212
>  Ignore-this: 43cea881b78185e84ee53cf0d5b075f4
> ] hunk ./src/CommandLine.hs 112
>  parseCmd ftable s = parse (commandline ftable) "" s
>
>  urlEncode :: String -> String
> -urlEncode s = concat $ map escapeC s
> +urlEncode s = concatMap escapeC s
>      where escapeC x = if allowed x then [x] else '%':(intToHex $ ord x)
>            intToHex i = map intToDigit [i `div` 16, i `mod` 16]
>            allowed x = x `elem` ['a' .. 'z'] ++ ['A' .. 'Z'] ++ ['0' .. '9']
> hunk ./src/Darcs/Repository/Prefs.lhs 327
>                   "tar","bz2","z","zip","jar","so","a",
>                   "tgz","mpg","mpeg","iso","exe","doc",
>                   "elc", "pyc"]
> -    where ext_regexes exts = concat $ map ext_regex exts
> +    where ext_regexes exts = concatMap ext_regex exts
>            ext_regex e = ["\\."++e++"$", "\\."++map toUpper e++"$"]
>
>  filetype_function :: IO (FilePath -> FileType)
> hunk ./src/Darcs/SlurpDirectory/Internal.hs 108
>  instance Show Slurpy where
>      show (Slurpy fn (SlurpDir _ l)) =
>          "Dir " ++ (fn2fp fn) ++ "\n" ++
> -              concat (map show $ map_to_slurpies l) ++ "End Dir " ++ (fn2fp 
fn) ++ "\n"
> +              concatMap show (map_to_slurpies l) ++ "End Dir " ++ (fn2fp 
fn) ++ "\n"
>      show (Slurpy fn (SlurpFile _ _)) = "File " ++ (fn2fp fn) ++ "\n"
>
>  mapSlurpyNames :: (FileName -> FileName) -> Slurpy -> Slurpy

I never use concatMap myself. I seem to recall somebody expressing the opinion 
that including concatMap as part of the fundamental arsenal of functions was 
a mistake and I wouldn't disagree. But, again, this is very much a matter of 
taste and I don't consider the use of concatMap wrong in any sense.

> [Use one map.
> hlint**20090115033047
>  Ignore-this: 6ba09e739f2f1053c86e21d67df73fcd
> ] hunk ./src/Darcs/Commands/SetPref.lhs 69
>   "\n" ++
>   "Valid preferences are:\n" ++
>   "\n" ++
> - (unlines $ map unwords $ map (\ (x,y) -> [" ",x,"--",y]) valid_pref_data) 
++
> + (unlines $ map (\ (x,y) -> unwords [" ",x,"--",y]) valid_pref_data) ++
>   "\n" ++
>   "For example, a project using GNU autotools, with a `make test' target\n" 
++
>   "to perform regression tests, might enable Darcs' integrated regression\n" 
++

I cannot easily understand either of these variants.

> [Use (:).
> hlint**20090115033119
>  Ignore-this: db2b1893adc4c9b6c1e09b17c0031c5a
> ] hunk ./src/Darcs/Arguments.lhs 1207
>      show_short_options a ++ show_long_options b ++ latex_help h ++ "\\\\"
>  option_latex (DarcsArgOption a b _ arg h) =
>      show_short_options a ++
> -    show_long_options (map (++(" "++arg)) b) ++ latex_help h ++ "\\\\"
> +    show_long_options (map (++(' ':arg)) b) ++ latex_help h ++ "\\\\"
>  option_latex (DarcsAbsPathOrStdOption a b _ arg h) =
>      show_short_options a ++
> hunk ./src/Darcs/Arguments.lhs 1210
> -    show_long_options (map (++(" "++arg)) b) ++ latex_help h ++ "\\\\"
> +    show_long_options (map (++(' ':arg)) b) ++ latex_help h ++ "\\\\"
>  option_latex (DarcsAbsPathOption a b _ arg h) =
>      show_short_options a ++
> hunk ./src/Darcs/Arguments.lhs 1213
> -    show_long_options (map (++(" "++arg)) b) ++ latex_help h ++ "\\\\"
> +    show_long_options (map (++(' ':arg)) b) ++ latex_help h ++ "\\\\"
>  option_latex (DarcsOptAbsPathOption a b _ _ arg h) =
>      show_short_options a ++
>      show_long_options (map (++("[="++arg++"]")) b) ++ latex_help h ++ 
"\\\\"

I have to break off here and comment on the above hunks separately: The code 
is clearly about constructing character strings to be displayed to the human 
user. So performance is not a particularly pressing issue. In such a setting, 
matters are considerably eased, in my opinion, if you just decide to say, 
well, everything is a string and they are combined using ++. Instead of 
having to think carefully about each individual concatenation, could this now 
be expressed in a more compact or efficient manner. If you do the latter, the 
code becomes more difficult to change, for example, if you decide to extend 
one of the strings of length 1 that is incidentally represented as a 
character constant.

> hunk ./src/Darcs/Commands/Put.lhs 65
>                      command_prereq = amInRepository,
>                      command_get_arg_possibilities = get_preflist "repos",
>                      command_argdefaults = nodefaults,
> -                    command_advanced_options = [applyas] ++ 
network_options,
> +                    command_advanced_options = applyas : network_options,
>                      command_basic_options = [match_one_context, 
set_scripts_executable,
>                                               get_inventory_choices,
>                                               set_default, 
working_repo_dir]}
> hunk ./src/Darcs/Commands/Tag.lhs 118
>                                 return ("TAG " ++ name, comment)
>           add_patch_name :: [DarcsFlag] -> String -> [DarcsFlag]
>           add_patch_name o a| has_patch_name o = o
> -                           | otherwise = [PatchName a] ++ o
> +                           | otherwise = PatchName a : o
>           has_patch_name (PatchName _:_) = True
>           has_patch_name (_:fs) = has_patch_name fs
>           has_patch_name [] = False

I am not exactly sure what this code is about, except that it seems to be 
option analysis, hence again, we can safely ignore any performance 
considerations. So whether the changed version is clearer than the original 
depends a lot on the way one would think about these lists that are 
constructed: If they are simply a way of grouping a set of related things, 
then I would say that the original version is preferred. Whereas if there is 
some interpretation of the order in which things are sitting in the lists, 
then the changed version may make more sense.

> hunk ./src/Darcs/Repository/Format.hs 82
>  default_repo_format = RF [[rp2ps Darcs1_0]]
>
>  create_repo_format :: [DarcsFlag] -> RepoFormat
> -create_repo_format fs = RF ([map rp2ps flags2inv] ++ maybe2)
> +create_repo_format fs = RF (map rp2ps flags2inv : maybe2)
>      where flags2inv | UseFormat2 `elem` fs = [HashedInventory]
>                      | UseHashedInventory `elem` fs = [HashedInventory]
>                      | UseOldFashionedInventory `elem` fs = [Darcs1_0]

I don't know what this is about, the previous comment (to the option analysis 
hunks) may apply here as well.

> [Use const.
> hlint**20090115033223
>  Ignore-this: a3040fd61db26146d9279d9e7b732a61
> ] hunk ./src/Darcs/ColorPrinter.hs 236
>  -- @policy@ is not set to use an alternative to color. In that case,
>  -- it makes the text bold instead.
>  color :: Policy -> Color -> Doc -> Doc
> -color po | poAltColor po = \_ -> make_bold
> +color po | poAltColor po = const make_bold
>           | otherwise     = make_color
>
>  make_color, make_color' :: Color -> Doc -> Doc
> hunk ./src/Darcs/Commands/ShowFiles.lhs 90
>  to_list_manifest opts = files_dirs (NoFiles `notElem` opts) (Directories 
`elem` opts)
>
>  files_dirs :: Bool -> Bool -> Slurpy -> [FilePath]
> -files_dirs False False = \_ -> []
> +files_dirs False False = const []
>  files_dirs False True  = list_slurpy_dirs
>  files_dirs True  False = list_slurpy_files
>  files_dirs True  True  = list_slurpy
> hunk ./src/Darcs/Lock.hs 75
>  withLock :: String -> IO a -> IO a
>  releaseLock :: String -> IO ()
>
> -withLock s job = bracket (getlock s 30) releaseLock (\_ -> job)
> +withLock s job = bracket (getlock s 30) releaseLock (const job)
>
>  -- | Tries to perform some task if it can obtain the lock,
>  -- Otherwise, just gives up without doing the task
> hunk ./src/Darcs/Patch/ReadMonads.hs 62
>                                      case k x of
>                                          SM y -> y s'
>      return x         = SM (\s -> Just (x,s))
> -    fail _           = SM (\_ -> Nothing)
> +    fail _           = SM (const Nothing)
>
>  instance ParserM SM where
>      work f = SM f
> hunk ./src/Darcs/Repository/Prefs.lhs 246
>    exists <- doesDirectoryExist dir
>    if exists then return $ Just dir
>              else userDir
> - `catch` \_ -> userDir -- no such environment variable
> + `catch` (const userDir) -- no such environment variable
>   where userDir = (getAppUserDataDirectory "darcs" >>= return.Just)
>                     `catchall` (return Nothing)
>
> hunk ./src/Darcs/SlurpDirectory/Internal.hs 275
>  smWriteFilePS :: FileName -> B.ByteString -> SlurpMonad ()
>  smWriteFilePS f ps = -- this implementation could be made rather more 
direct
>                       -- and limited to a single pass down the Slurpy
> -                     modifyFileSlurpy f (\_ -> sl)
> +                     modifyFileSlurpy f (const sl)
>                       `mplus` insertSlurpy f sl
>      where sl = Slurpy (own_name f) (SlurpFile undef_time_size ps)
>
> hunk ./src/Darcs/SlurpDirectory/Internal.hs 364
>                                  return (isDirectory fs)
>
>  -- |slurp is how we get a slurpy in the first place\ldots
> -slurp = slurp_unboring (\_->True) . toPath
> +slurp = slurp_unboring (const True) . toPath
>  mmap_slurp d = do canmmap <- can_I_use_mmap
> hunk ./src/Darcs/SlurpDirectory/Internal.hs 366
> -                  if canmmap then genslurp True (\_->True) d
> -                             else genslurp False (\_->True) d
> +                  if canmmap then genslurp True (const True) d
> +                             else genslurp False (const True) d
>  slurp_unboring = genslurp False
>  genslurp :: Bool -> (FilePath -> Bool)
>           -> FilePath -> IO Slurpy
> hunk ./src/Darcs/Utils.hs 79
>  isHardwareFaultErrorType _ = False
>
>  catchall :: IO a -> IO a -> IO a
> -a `catchall` b = a `catchNonSignal` (\_ -> b)
> +a `catchall` b = a `catchNonSignal` (const b)
>
>  maybeGetEnv :: String -> IO (Maybe String)
>  maybeGetEnv s = (getEnv s >>= return.Just) `catchall` return Nothing -- err 
can only be isDoesNotExist
> hunk ./src/Darcs/Utils.hs 264
>
>  without_buffering :: IO a -> IO a
>  without_buffering job = withoutProgress $ do
> -    bracket nobuf rebuf $ \_ -> job
> +    bracket nobuf rebuf (const job)
>      where nobuf = do is_term <- hIsTerminalDevice stdin
>                       bi <- hGetBuffering stdin
>                       raw <- get_raw_mode
> hunk ./src/Exec.hs 161
>            then bracket
>                     (do setFdOption stdInput NonBlockingRead False)
>                     (\_ -> setFdOption stdInput NonBlockingRead True)
> -                   (\_ -> x)
> +                   (const x)
>            else do x
>  #else
>  withoutNonBlock x = do x
> hunk ./src/RegChars.hs 50
>  normalRegChars ('\\':c:_) = error $ "'\\"++[c]++"' not supported."
>  normalRegChars (c1:'-':c2:cs) = ((>= c1) &&& (<= c2)) ||| normalRegChars cs
>  normalRegChars (c:cs) = (== c) ||| normalRegChars cs
> -normalRegChars [] = \_ -> False
> +normalRegChars [] = const False

I rarely use const myself, so I think the originals read clearer than the 
modified ones.

>
>
> [Use replicate.
> hlint**20090115033241
>  Ignore-this: 9802026b0051d4ab6377b75ce6a453f4
> ] hunk ./src/Crypt/SHA256.hs 30
>
>  sha256sum :: B.ByteString -> String
>  sha256sum p = unsafePerformIO $
> -              withCString (take 64 $ repeat 'x') $ \digestCString ->
> +              withCString (replicate 64 'x') $ \digestCString ->
>                unsafeUseAsCStringLen p $ \(ptr,n) ->
>                do let digest = castPtr digestCString :: Ptr Word8
>                   c_sha256 ptr (fromIntegral n) digest
> hunk ./src/Darcs/Repository/Cache.hs 78
>  cacheHash :: B.ByteString -> String
>  cacheHash ps = case show (B.length ps) of
>                   x | l > 10 -> sha256sum ps
> -                   | otherwise -> take (10-l) (repeat '0') ++ x 
++'-':sha256sum ps
> +                   | otherwise -> replicate (10-l) '0' ++ x ++'-':sha256sum 
ps
>                                          where l = length x
>
>  okayHash :: String -> Bool

These changes make sense. There even seems to be more to be done here: The 
repeated "10", for example, couldn't that be avoided, somehow? Nevertheless, 
here we find ourselves in areas (Crypt/SHA256.hs and 
Darcs/Repository/Cache.hs) that seem extremely delicate, so that a lot of 
advantage would have to come out of such changes for me to happily recommend 
them. So this is really a case of "If it ain't broken, don't fix it" in my 
view.

Thanks and best regards
Thorkil
_______________________________________________
darcs-users mailing list
[email protected]
http://lists.osuosl.org/mailman/listinfo/darcs-users

Reply via email to