And when Im trying this:
{-# OPTIONS_GHC -Wall #-}
module LogAnalysis where
import Log;
import Data.Char (isLetter, isDigit)
isValid :: String -> Bool
isValid s = go (words s)
where
go ([a]:b:_) = isLetter a && all isDigit b
go _ = False
-- | The main entry point.
main :: IO ()
main = do
putStrLn $ isValid "I 4764 He trusts to you to set them free,"
I see this error message :
src/LogAnalysis.hs@19:16-19:67
Couldn't match type
Bool
with
[Char]
Expected type: String Actual type: Bool …
In the second argument of ‘($)’, namely ‘isValid "I 4764 He
trusts to you to set them free,"’
In a stmt of a 'do' block: putStrLn $ isValid "I 4764 He
trusts to you to set them free,"
Roelof
Roelof Wobben schreef op 23-2-2015 om 17:19:
I tried it another way more like
explained on this page :
http://www.seas.upenn.edu/~cis194/spring13/lectures/02-ADTs.html
so I tried this :
parseMessage :: [Char] -> [Char]
parseMessage s
case Errornumber of
IsDigit Errornumber -> "Geldige string"
otherwise -> "Ongeldige string"
where
Error = s words
Errornumber = Error(ErrorNumber _ _ )
Errorcode = Error(_ Errorcode _ )
but now I cannot use where :(
Roelof
Roelof Wobben schreef op 23-2-2015 om 16:10:
Oke,
Then I make there a mistake,
What I try to do is to send the file to parseMessage and let
IsValid check if it´s have the right format.
Then after the where I try to check if the function isValid
returns true or false.
Roelof
Konstantine Rybnikov schreef op 23-2-2015 om 16:03:
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.
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe