
On Mon, Aug 29, 2011 at 09:52:28PM -0700, Neuman Vong wrote:
Hi Haskell people,
I'm pretty new to Haskell still. There were a bunch of things I didn't know how to do in the following script, I'm hoping some people on this list can help with. For example, I had trouble returning an ExitCode and using getProgName without getting a compile-time type error. I feel like I'm doing something wrong with the Text/[Char] conversions too. I'd also really appreciate any style tips. Thanks in advance!
Hi Neuman, This looks pretty good. I'm not very familiar with the Text library, so perhaps someone else can comment on the conversions between Text and String. But I can offer a few comments on style:
{-# LANGUAGE OverloadedStrings #-} module Main where
import System (getArgs) import System.IO (hPutStrLn, stderr) import Data.Text (pack, splitOn, length, isPrefixOf, Text) import Prelude hiding (length)
data Rate = Rate Text Text deriving (Show)
If you use record syntax: data Rate = Rate { getPrefix :: Text, getPrice :: Text } then you get the selector functions getPrefix and getPrice for free (so you don't have to write them in the 'where' clause below).
findBestPrefix number rates = foldl1 longestPrefix $ matching rates where getLength rate = length $ getPrefix rate getPrefix (Rate prefix _) = prefix getPrice (Rate _ price) = price longestPrefix r1 r2 = if getLength r1 > getLength r2 then r1 else r2 matching rates = [ rate | rate <- rates, getPrefix rate `isPrefixOf` number ]
The matching function can also be implemented with a call to 'filter'. The following three definitions are all equivalent, showing a progression of simplification: matching rates = filter (\rate -> getPrefix rate `isPrefixOf` number) rates matching = filter (\rate -> getPrefix rate `isPrefixOf` number) matching = filter ((`isPrefixOf` number) . getPrefix) At this point you could even inline the definition of matching if you wanted. You should use whichever of these definitions you find clearest, I just wanted to show what is possible.
makeRates = map $ \line -> let (prefix:rate:_) = splitOn ", " (pack line) in Rate prefix rate
main = getArgs >>= \args -> let findBest number rates = findBestPrefix number $ makeRates rates in case args of (arg:_) -> interact $ (++ "\n") . show . findBest (pack arg) . lines _ -> hPutStrLn stderr "Pass in a number as the first argument"
One general tip: it helps a lot, especially when learning, to give explicit type signatures to all your top-level functions. In fact, I still do this. I *first* write down a type signature, and *then* write an implementation. This may help you with your issues using getProgName and and ExitCode, although without more information about exactly what you were trying it's hard to know. -Brent