
Hi Haskellers, I'm asking some advice on a small piece of code representing a simplified version of a treatment I need to perform. I have a line-oriented string/file, from which I want to extract only a substring of those lines starting with char '+' (the detail of the extraction is irrelevant here, I'll just return what follows the '+'). [I also simplified the "eol" parser for shorter code.] I came out with the code below. The line parser returns a "Maybe String". The complete parser return a "[Maybe String]" by mere concatenation. The main function filters the 'Nothing' with 'catMaybes'.
import Text.ParserCombinators.Parsec import Data.Maybe
maybePlusFile :: GenParser Char st [Maybe String] maybePlusFile = endBy maybePlusLine eol
maybePlusLine :: GenParser Char st (Maybe String) maybePlusLine = try (do char('+') result <- many (noneOf "\n") return $ Just result) <|> do many (noneOf "\n") return $ Nothing
eol = char '\n'
selectPlus :: String -> Either ParseError [String] selectPlus input = case parse maybePlusFile "(input)" input of Left e -> Left e Right mblist -> Right $ catMaybes mblist
This works as expected (or so it seems), as the ghci dump shows:
GHCi, version 6.10.1: http://www.haskell.org/ghc/ :? for help ... Prelude> :l selectPlus.hs [1 of 1] Compiling Main ( selectPlus.hs, interpreted ) Ok, modules loaded: Main. *Main> selectPlus "abc\n+123\ndef\n+456\n" Loading package parsec-2.1.0.1 ... linking ... done. Right ["123","456"] *Main>
I'd like to know if this code is good style, and how you would possibly improve it. Thanks in advance. --Serge

Hi Serge, Serge LE HUITOUZE wrote:
I'm asking some advice on a small piece of code representing a simplified version of a treatment I need to perform. I have a line-oriented string/file, from which I want to extract only a substring of those lines starting with char '+' (the detail of the extraction is irrelevant here, I'll just return what follows the '+').
This isn't really answering your question, but I thought I'd share anyway: why use Parsec to retrieve those lines? It seems a simple function is a lot easier: selectPlus :: String -> [String] selectPlus = map tail . filter ((== '+') . head) . lines I hope this helps you. Martijn.

Or for a bit of variety: selectPlus s = [cs | ('+':cs) <- lines s] --Ben On 4 Sep 2009, at 20:40, Martijn van Steenbergen wrote:
Hi Serge,
Serge LE HUITOUZE wrote:
I'm asking some advice on a small piece of code representing a simplified version of a treatment I need to perform. I have a line-oriented string/file, from which I want to extract only a substring of those lines starting with char '+' (the detail of the extraction is irrelevant here, I'll just return what follows the '+').
This isn't really answering your question, but I thought I'd share anyway: why use Parsec to retrieve those lines? It seems a simple function is a lot easier:
selectPlus :: String -> [String] selectPlus = map tail . filter ((== '+') . head) . lines
I hope this helps you.
Martijn.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Am Freitag 04 September 2009 21:23:35 schrieb Serge LE HUITOUZE:
Hi Haskellers,
I'm asking some advice on a small piece of code representing a simplified version of a treatment I need to perform. I have a line-oriented string/file, from which I want to extract only a substring of those lines starting with char '+' (the detail of the extraction is irrelevant here, I'll just return what follows the '+'). [I also simplified the "eol" parser for shorter code.]
I came out with the code below. The line parser returns a "Maybe String". The complete parser return a "[Maybe String]" by mere concatenation. The main function filters the 'Nothing' with 'catMaybes'.
import Text.ParserCombinators.Parsec import Data.Maybe
maybePlusFile :: GenParser Char st [Maybe String] maybePlusFile = endBy maybePlusLine eol
maybePlusLine :: GenParser Char st (Maybe String) maybePlusLine = try (do char('+')
No need for try here, char '+' either fails without consuming input or the whole branch succeeds.
result <- many (noneOf "\n") return $ Just result) <|> do many (noneOf "\n") return $ Nothing
eol = char '\n'
maybePlusLine = do char '+' fmap Just $ manyTill anyChar eol <|> do skipMany (noneOf "\n") return Nothing maybePlusFile = many maybePlusLine
selectPlus :: String -> Either ParseError [String] selectPlus input = case parse maybePlusFile "(input)" input of Left e -> Left e Right mblist -> Right $ catMaybes mblist
This works as expected (or so it seems), as the ghci dump shows:
GHCi, version 6.10.1: http://www.haskell.org/ghc/ :? for help ... Prelude> :l selectPlus.hs [1 of 1] Compiling Main ( selectPlus.hs, interpreted ) Ok, modules loaded: Main. *Main> selectPlus "abc\n+123\ndef\n+456\n" Loading package parsec-2.1.0.1 ... linking ... done. Right ["123","456"] *Main>
I'd like to know if this code is good style, and how you would possibly improve it.
Except for the superfluous try, it's good. Unless you can't guarantee that the input ends with a newline. Then you should take care of that (for example eol = char '\n' <|> (eof >> return '\n') ). If it's such a simple extraction, there's no need for a parser, however, map tail . filter startsPlus . lines $ input where startsPlus ('+':_) = True startsPlus _ = False will do fine.
Thanks in advance.
--Serge

Hi everyone, I ran into this error when recompiling some code I hadn't worked on in a while: Foo.hs:19:7: Could not find module `Control.Monad.Error': it was found in multiple packages: monads-fd-0.0.0.1 mtl-1.1.0.2 I gather that monads-fd is supposed to be a replacement for mtl, but I have both of them (mtl from the normal GHC 6.10.4 install, monads-fd from cabal). I don't really care which one I use, though mtl has been fine in the past. In the past, I had to manually uninstall cabal packages that used incompatible libraries. Is this still the case? TIA, Mike

Although also a bit of a global hack, you could also hide one of the
packages using
ghc-pkg hide mtl-1.1.02
instead of uninstalling them I think.
Also, if you make a cabal file, you could specify the exact module you
want to use.
On Fri, Sep 4, 2009 at 11:03 PM, Michael Vanier
Hi everyone,
I ran into this error when recompiling some code I hadn't worked on in a while:
Foo.hs:19:7: Could not find module `Control.Monad.Error': it was found in multiple packages: monads-fd-0.0.0.1 mtl-1.1.0.2
I gather that monads-fd is supposed to be a replacement for mtl, but I have both of them (mtl from the normal GHC 6.10.4 install, monads-fd from cabal). I don't really care which one I use, though mtl has been fine in the past. In the past, I had to manually uninstall cabal packages that used incompatible libraries. Is this still the case?
TIA,
Mike
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (6)
-
Ben Moseley
-
Daniel Fischer
-
Martijn van Steenbergen
-
Michael Vanier
-
Peter Verswyvelen
-
Serge LE HUITOUZE