[Haskell-beginners] record problem when updating fields with an IO a type

Manfred Lotz manfred.lotz at arcor.de
Fri Apr 1 16:28:05 CEST 2011


Hi there,
I have a problem where I like to update a record with an IO a. Not
quite sure how to describe it.

Here is a minimal example: I get a list of numbers from the command
line and I like to add those numbers n and randome numbers from a
range from [0..n] in two fields of a record. 

<---------------------------snip---------------------------->
module Main where

import System.Environment.UTF8
import System.Random

data NumRec = NumRec {
  mxV :: Int,
  mxR :: Int
  } deriving (Show,Read)


initNumRec = NumRec { mxV = 0, mxR = 0 }

toInt s = read s :: Int


addRandom m n = do
  let mxv = mxV m
  let mxr = mxR m
  let r = rand n
  m { mxV = mxv + n,
          mxR = mxr + r }

rand :: Int -> IO Int
rand max = getStdRandom (randomR (0, max))         
                   

main = do  
    args <- getArgs  
    print args
    let ilist = map toInt args
    let mixed = foldl addRandom initNumRec ilist
    print mixed
<---------------------------snap---------------------------->

I get the following error when compiling:

[1 of 1] Compiling Main             ( minimal.hs, minimal.o )

minimal.hs:22:23:
    Couldn't match expected type `Int' with actual type `IO Int'
    In the second argument of `(+)', namely `r'
    In the `mxR' field of a record
    In the expression: m {mxV = mxv + n, mxR = mxr + r}


How can I correct the compile error? 



-- 
Manfred





More information about the Beginners mailing list