[Haskell-beginners] Convert String to List/Array of Numbers
Daniel Fischer
daniel.is.fischer at web.de
Wed Sep 8 14:29:23 EDT 2010
On Wednesday 08 September 2010 19:24:12, Lorenzo Isella wrote:
> Hi Daniel,
> Thanks for your help.
> I have a couple of questions left
> (1) The first one is quite down to earth.
> The snippet below
>
> ---------------------------------------------------
> main :: IO ()
>
> main = do
> txt <- readFile "mydata.dat"
>
> let dat = convert txt
>
> print dat -- this prints out my chunk of data
>
> return ()
That `return ()' is superfluous, print already has the appropriate type,
print :: Show a => a -> IO ()
return () is only needed to
- fill in do-nothing branches, if condition then doSomething else return ()
or
case expression of
pat1 -> doSomething
pat2 -> doSomethingElse
_ -> return ()
- convert something to the appropriate type, e.g. if
action :: IO ExitCode
and you need an IO () in some place, then you use
action >> return ()
>
> convert x = lines x
>
> -----------------------------------------------
>
> pretty much does what it is supposed to do, but if I use this definition
> of convert x
>
> convert x = map (map read . words) . lines x
>
> I bump into compilation errors. Is that the way I am supposed to deal
> with your function?
Yes and no.
First of all, function application binds tighter than composition, so
convert x = map (map read . words) . lines x
is parsed as
convert x = (map ((map read) . words)) . (lines x)
which gives a type error because (lines x) :: [String], while the
composition expects something of type (a -> b) as second argument.
The correct form of convert could be
convert x = (map (map read . words) . lines) x
or
convert x = map (map read . words) . lines $ x
or, point-free,
convert = map (map read . words) . lines
In the latter case, you have to give it a type signature,
convert :: Read a => String -> [[a]]
or disable the monomorphism restriction
({-# LANGUAGE NoMonomorphismRestriction #-} pragma in the file resp. the
command-line flag -XNoMonomorphismRestriction), otherwise it'll likely give
rise to other type errors.
Once that is fixed, your problems aren't over yet.
Then you get compilation errors because the compiler has no way to infer at
which type to use read, should it try to read Integers, Bools, ... ?
Usually, in real code the type can be inferred from the context, at least
enough for the defaulting rules to apply (if you pass dat to something
expecting [[Bool]], the compiler knows it should use Bool's Read instance,
if it's expecting (Num a => [[a]]), it can be defaulted (and will be
defaulted to Integer unless you have an explicit default declaration
stating otherwise).
In the code above, all the compiler can find out is that
dat :: (Read a, Show a) => [[a]]
GHC will compile it if you pass -XExtendedDefaultRules on the command line
(or put {-# LANGUAGE ExtendedDefaultRules #-} at the top of the module),
then the type variable a will be defaulted to () [which is rather useless].
More realistically, you need to tell the compiler the type of dat,
let dat :: [[Integer]] -- or ((Num a, Read a) => [[a]])
dat = convert txt
>
> (2) This is a bit more about I/O in general. I start an action with "do"
> to read some files and I define outside the action some functions which
> are supposed to operate (within the do action) on the read data.
Yes, you define the functions that do the actual work as pure functions
(mostly) and then bind them together in a - preferably small - main
function doing the necessary I/O (reading data or configuration files,
outputting results).
> Is this the way it always has to be? I read something about monads but
> did not get very far (and hope that they are not badly needed for simple
> I/O).
To do basic I/O, you don't need to know anything about monads, all you need
is a little nowledge of the do-notation.
> Is there a way in Haskell to have the action return to the outside
> world e.g. the value of dat and then work with it elsewhere?
For the few cases where it's necessary, there is such a beast.
Its name begins with the word `unsafe', for good reasons (the full name is
unsafePerformIO, available from System.IO.Unsafe).
When you're tempted to use it, ask yourself "Is this really a good idea?"
(like if you're tempted to use goto in C, only more so - sometimes it is,
but rarely).
> That is what I would do in Python or R, but I think I understood that
> Haskell's philosophy is different...
Well, you pass it as a parameter to other functions and IO-actions.
> Am I on the right track here? And what is the benefit of this?
Purity allows some optimisations that can't be done for functions which
might have side-effects.
And it's much easier to reason about pure (side-effect-free) functions.
>
> Cheers
>
> Lorenzo
More information about the Beginners
mailing list