[Haskell] please improve this code - thanks

Jason Dagit dagitj at gmail.com
Sat Aug 24 19:38:38 CEST 2013


On Sat, Aug 24, 2013 at 5:45 AM, Me <itmitica at gmail.com> wrote:

> Hi all.
> I'm new to haskell. I have a puny piece of code:
>
> import Data.List.Split
>
> padL :: Int -> String -> String
> padL n s
>     | length s < n = replicate (n - length s) '0' ++ s
>

You use `length s` but the computation is not shared between the two uses.
So at run-time the length of s must be computed twice. A where clause would
introduce some sharing. Additionally, (++) is going to traverse all of
`replicate (n - length s) '0'`. So if `n - length s` is large that will be
costly, but I don't see an easy fix for that.


>     | otherwise = s
>

padL :: Int -> String -> String
padL n s
    | n' < n   = replicate (n - n') '0' ++ s
    | otherwise = s
  where
  n' = length s


>
> strInc :: String -> String -> String
> strInc sep str =
>         let strarr = splitOn sep str
>             zprefix = strarr !! 0
>

This has a rather serious bug. What happen when strarr is []?


>             znumber = strarr !! 1
>

Similar to above.

If find you're self using (!!) that's a hint that your program is brittle
(sensitive to the layout of the list) plus it's an inefficient way to get
at an element (because it's a list you have to traverse it to get the
element). In this case, pattern matching would be much better.

case splitOn sep str of
  (zprefix:znumber:_) -> ...
  _  -> error "What should we do here?"

Where you should really put something reasonable there instead of an error.
But, if there isn't anything reasonable that's an indicator that our types
are not very precise.

        in zprefix ++ sep ++ padL ( length (znumber) ) ( show ( read (
> znumber ) + 1 ) )
>
> Prelude> :l strinc
> [1 of 1] Compiling Main ( strinc.hs, interpreted )
> Ok, modules loaded: Main.
> *Main> strInc "-" "xs-00009"
> "xs-00010"
> *Main> strInc "<>" "yxs<>000099"
> "yxs<>000100"
>
> Is it good haskell, bad haskell or average haskell? How can it be
> rewritten?
>

It gets the job done but it could be improved. In particular, instead of
using String for everything you could make a data type. Lists (at least in
Haskell) are more like (possibly infinite) streams than they are bounded
arrays. Using (!!) is considered a code smell in Haskell.

Additionally, it's good to separate out the concerns. I see at least two
orthogonal concerns in the original program:
  * Parsing a string into a prefix and a value?
  * Incrementing a value (that happens to have a prefix)

Something like the code below could separate those concerns. I've used the
data type `Prefixed` to store the prefix with the value. You might also
want to store the separator depending on your goals.

Here is a sketch of how I would separate the two concerns above:

data Prefixed a = Prefixed String a

prefixedIncrement :: Num a => Prefixed a -> Prefixed a
prefixedIncrement (Prefixed s n) = Prefixed s (n + 1)

parsePrefixed :: Read a => String -> Maybe (Prefixed a)
parsePrefixed ...

There are other concerns in the code as well, such as how to format the
prefixed string/value pair for display. Perhaps that would start out like
this:

showPrefixed :: Show a => Prefixed a -> String
showPrefixed ...

You might try asking questions like this on the Haskell-beginners mailing
list: http://www.haskell.org/mailman/listinfo/beginners

I hope that helps,
Jason
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell/attachments/20130824/066e63a7/attachment.htm>


More information about the Haskell mailing list