Perhaps you could split up the format checking and the unpacking into two different functions:
parseMessage :: String -> String
parseMessage s = go (words s)
where
go log = if isValid log
then parse log
else "false"
parse ("I":time:msg) = "Info"
parse ("W":time:msg) = -- etc.
On Mon, Feb 23, 2015 at 12:39 PM, Roelof Wobben <r.wobben@home.nl> wrote:
Oke,
But then I do not check on the I
Sorry for being difficult.
Roelof
Alex Hammel schreef op 23-2-2015 om 21:33:
For that you need a guard:
parseMessage :: String -> String
parseMessage s = go (words s)
where
go logMessage
| isValid logMessage = doSomething
| otherwise = "false"
On Mon, Feb 23, 2015 at 12:30 PM, Roelof Wobben <r.wobben@home.nl> wrote:
Thanks,
Can I somehow also test if the string is valid so that the isvalid function is used.
Roelof
Alex Hammel schreef op 23-2-2015 om 21:23:
You can pattern match on string literals:
parseMessage :: String -> String
parseMessage s = go (words s)
where
go ("I":_:_) = "Info"
go _ = "false"
You don't need to call it "go2", btw. Functions in where-blocks don't leak into the global scope, so there's no conflict with the `go` in your other function.
On Mon, Feb 23, 2015 at 12:15 PM, Roelof Wobben <r.wobben@home.nl> wrote:
Sorry ,
I cannot change that function. I have to use it,
But I think I found a solution for a step earlier,
To parse a line and change it to another line which will be a member of LogMessage :
-- | Main entry point to the application.
{-# OPTIONS_GHC -Wall #-}
module LogAnalysis where
import Data.Char (isLetter, isDigit)
isValid :: String -> Bool
isValid s = go (words s)
where
go ([a]:b:_) = isLetter a && all isDigit b
go _ = False
parseMessage :: String -> String
parseMessage s = go2 (words s)
where
go2 (a:_:_) = case a of
"I" -> "Info "
_ -> "False"
go2 _ = "false"
-- | The main entry point.
main :: IO ()
main = do
putStrLn $ parseMessage "I 656 He trusts to you to set them free,"
But I feels wierd, to use first a pattern matching and later do a case of.
Is this a good way or are there better ways,
Roelfo
Alex Hammel schreef op 23-2-2015 om 21:01:
Constructors with names like 'Unknown' are a code smell, IMO. I'd just define the data type like this:
data LogMessage = LogMessage MessageType TimeStamp String
and use `Either String LogMessage` in contexts where parsing can fail:
parseLogEntry :: String -> Either String LogMesage
parseLogEntry str
| isValid str = Right $ mkLogMessage str
| otherwise = Left $ "Poorly-formatted log entry: " ++ str
As for implementing mkLogMessage: you already know how to unpack the parts of a log message with `words` and pattern matching. After that it's just a matter of type-casting everything correctly and passing it to the `LogMessage` constructor.
On Mon, Feb 23, 2015 at 10:14 AM, Roelof Wobben <r.wobben@home.nl> wrote:
Thanks,
This works :
-- | Main entry point to the application.
{-# OPTIONS_GHC -Wall #-}
module LogAnalysis where
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 $ ( show (isValid "I 656 He trusts to you to set them free,"))
Now I have to ty to find out how I can check if a has the contents of I/W/E and how to make the right output (Error/Warning/Info 22) " Text" )
and then make it work with this datatype :
data LogMessage = LogMessage MessageType TimeStamp String
| Unknown String
deriving (Show, Eq)
Roelof
Konstantine Rybnikov schreef op 23-2-2015 om 18:49:
You can use it.print x = putStrLn (show x)As Alex mentioned, there's a `print` function, which does exactly this:As Alex mentioned, isValid returns Bool, while type for putStrLn is `String -> IO ()`. So, in order to print something of type Bool, you need to first convert it to String. For example, via a function `show`:putStrLn (show True)
On Mon, Feb 23, 2015 at 7:19 PM, Roelof Wobben <r.wobben@home.nl> wrote:
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:67Couldn't match typeBoolwith[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:
Good luck.My suggestion is to rename second isValid.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.
On Mon, Feb 23, 2015 at 4:50 PM, Roelof Wobben <r.wobben@home.nl> wrote:
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:27Couldn't match expected type ‘[Char] -> [Char]’ with actual type[Char]The functionisValidis 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
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe