
Roelof,
You defined isValid function in the upper-scope first, and then you defined
a symbol (variable) that re-wrote that name to something different (string
"Geldige string"). That's why you get an error saying it doesn't expect
arguments.
My suggestion is to rename second isValid.
Good luck.
On Mon, Feb 23, 2015 at 4:50 PM, Roelof Wobben
Chaddaï Fouché schreef op 23-2-2015 om 13:20:
Note that Roelof is doing the CIS 194 Homework http://www.seas.upenn.edu/~cis194/fall14/hw/03-ADTs.pdf (the older version of fall2014, not the one currently running). This is much clearer than Roelof's description, and gives among other information an algebraic datatype to represent log messages.
-- Jedaï
Correct and Im trying to do exercise 1 of Week 2,
I have tried this solution :
-- | Main entry point to the application. {-# OPTIONS_GHC -Wall #-}
module LogAnalysis where
import Log; import Data.Char (isLetter, isDigit)
isValid :: [Char] -> Bool isValid s = go (words s) where go ([a]:b:_) = isLetter a && all isDigit b go _ = False
parseMessage :: [Char] -> [Char] parseMessage s = isValid s where isValid = "Geldige string" _ = "Ongeldige string"
-- | The main entry point. main :: IO () main = do putStrLn $ parseMessage "I 4764 He trusts to you to set them free,"
but I see this error message :
src/LogAnalysis.hs@16:18-16:27 Couldn't match expected type ‘[Char] -> [Char]’ with actual type [Char] The function isValid is applied to one argument, but its type [Char] has none … In the expression: isValid s In an equation for ‘parseMessage’: parseMessage s = isValid s where isValid = "Geldige string" _ = "Ongeldige string"
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe