[Haskell-beginners] Help me improve my code

Neuman Vong neuman at twilio.com
Tue Aug 30 06:52:28 CEST 2011


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!

{-# 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)

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 ]

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"


-- 
neuman
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/beginners/attachments/20110829/ff436ec4/attachment.htm>


More information about the Beginners mailing list