
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

On Mon, Aug 29, 2011 at 11:52 PM, Neuman Vong
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!
What errors are you getting?
{-# 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 _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

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

Hi Brent, thanks for your reply. I had another go at the code
following your advice, but I ended up going down a different path
eventually taking out the filter and replacing it with a recursive
function (see below). I like that this version is clearer to read, but
unfortunately I've doubled the number of lines. I have an equivalent
of it in python which is even more terse than the first version but
reads better than the second, which makes me suspect again that I'm
not taking full advantage of Haskell. But... is this the wrong way to
think?
(Thanks, for replying too, Antoine! I forget the exact errors I was having.)
module Main
where
import Control.Monad (guard, when)
import Data.Text (unpack, pack, splitOn)
import Data.List (maximumBy)
import Data.Function (on)
import System (getArgs, getProgName)
data Rate = Rate { prefix::String, price::String } deriving (Show)
find :: Int -> String -> [Rate] -> Maybe Rate
find _ _ [] = Nothing
find index key rates
| length rates == 1 = Just (last rates)
| length key <= index = Just (longestPrefix rates)
| otherwise = find (index + 1) key (match index key rates)
match :: Int -> String -> [Rate] -> [Rate]
match index key rates = do
rate <- rates
when (index < length (prefix rate))
(guard $ (prefix rate !! index) == (key !! index))
return rate
longestPrefix :: [Rate] -> Rate
longestPrefix = maximumBy (compare `on` (length . prefix))
toRates :: [String] -> [Rate]
toRates [] = []
toRates rates = map toRate rates
toRate :: String -> Rate
toRate line = let prefix:price:_ = splitOn' ", " line in Rate prefix price
splitOn' :: String -> String -> [String]
splitOn' delim str = fmap unpack (splitOn (pack delim) (pack str))
main = getArgs >>= \args ->
case args of
[] -> getProgName >>= \progName -> error ("Usage: " ++
progName ++ " <key>")
key:_ -> interact ((++ "\n") . show' . (find 0 key) . toRates . lines)
where show' Nothing = "Couldn't find a match"
show' (Just rate) = show rate
On Tue, Aug 30, 2011 at 7:48 AM, Brent Yorgey
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
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- neuman

On Wed, Aug 31, 2011 at 01:28:36AM -0700, Neuman Vong wrote:
... I like that this version is clearer to read, but unfortunately I've doubled the number of lines. ...
Of course, "clearer to read" depends on what you are experienced at reading. Personally, I find this version less clear to read. =) But trying lots of different ways to do something is always good.
find :: Int -> String -> [Rate] -> Maybe Rate find _ _ [] = Nothing find index key rates | length rates == 1 = Just (last rates)
In general, try to avoid testing the length of a list (which is expensive if the list is long), and you should definitely never test if the length of a list is equal to a small number. You should also avoid using 'last' (which can crash if the list is empty). You can solve both these problems at once by pattern matching the list: find index key [rate] = Just rate
| length key <= index = Just (longestPrefix rates) | otherwise = find (index + 1) key (match index key rates)
My general advice is to avoid writing explicitly recursive functions as much as possible, instead preferring to write algorithms in terms of existing recursive combinators like map, foldr, filter... In general it makes your programs more modular and easier to understand (once you get used to it). However, in this particular case I am having trouble figuring out exactly what 'find' does so I don't have a good suggestion of a different way to write it. Generally, the idea is to think about incrementally transforming a data structure through a number of intermediate steps until finally reaching the answer, rather than computing the answer "all in one go". In strict languages this sort of repeated transformation of a data structure can be less efficient, but Haskell's laziness makes it viable. If you'd like an example of the sort of thing I'm talking about let me know and I could make one up.
match :: Int -> String -> [Rate] -> [Rate] match index key rates = do rate <- rates when (index < length (prefix rate)) (guard $ (prefix rate !! index) == (key !! index)) return rate
longestPrefix :: [Rate] -> Rate longestPrefix = maximumBy (compare `on` (length . prefix))
toRates :: [String] -> [Rate] toRates [] = [] toRates rates = map toRate rates
toRates = map toRate. map can correctly handle the empty list case already.
toRate :: String -> Rate toRate line = let prefix:price:_ = splitOn' ", " line in Rate prefix price
splitOn' :: String -> String -> [String] splitOn' delim str = fmap unpack (splitOn (pack delim) (pack str))
If you are just going to be using strings anyway, it's silly to convert to Text or Bytestring or whatever it is you are converting to here just to get access to splitOn. Instead you could use the splitOn function from the Data.List.Split module ('cabal install split'). -Brent
main = getArgs >>= \args -> case args of [] -> getProgName >>= \progName -> error ("Usage: " ++ progName ++ " <key>") key:_ -> interact ((++ "\n") . show' . (find 0 key) . toRates . lines) where show' Nothing = "Couldn't find a match" show' (Just rate) = show rate
On Tue, Aug 30, 2011 at 7:48 AM, Brent Yorgey
wrote: 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
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- neuman
participants (3)
-
Antoine Latter
-
Brent Yorgey
-
Neuman Vong