[Haskell-beginners] University project - weird problem

Renato dos Santos Leal renatodossantosleal at gmail.com
Wed Apr 21 20:09:35 EDT 2010


I've seen that there is something like hIsEOF that I can use to find EOF

to do so I need something like eof <- hIsEOF hdl
(hdl: the file that i'm reading)

how can I put it as a guard in le_bloco?

2010/4/21 Stephen Blackheath [to Haskell-Beginners] <
mutilating.cauliflowers.stephen at blacksapphire.com>

> Renato,
>
> GHC and Hugs both comply with the Haskell 98 standard, so the same program
> will work in both if it's written in Haskell 98.
>
> I've never used Hugs so I don't know what your error means.  I just tried
> loading it into GHC with -Wall on (enable all warnings) and I got lots of
>
> c.hs:21:0:
>    Warning: Pattern match(es) are non-exhaustive
>             In the definition of `le_bloco': Patterns not matched: []
>
> c.hs:32:0:
>    Warning: Pattern match(es) are non-exhaustive
>             In the definition of `separador': Patterns not matched: []
>
> ...
>
> It looks like you are not handling the end-of-list case.  This might be
> related to your problems.  If you run in GHC with -Wall, and fix all the
> warnings, you should find most of your problems go away.  (Haskell is truly
> wonderful in this way.)
>
>
> Steve
>
>
> Renato dos Santos Leal wrote:
>
>> Thank you Stephen!
>>
>> Yes, I'm using hugs. My teacher told me to use it and he corrects our
>> projects using it, the differece between hugs and GHC, is it large?
>>
>> I don't know if I got what you meant with pure functions, but I'll keep
>> studying.
>>
>> 2010/4/21 Stephen Blackheath [to Haskell-Beginners] <
>> mutilating.cauliflowers.stephen at blacksapphire.com <mailto:
>> mutilating.cauliflowers.stephen at blacksapphire.com>>
>>
>>
>>    Renato,
>>
>>    All I did was I added type signatures to your code, and it worked.
>>     It is a very good idea to put type signatures on all top-level
>>    functions, otherwise you can get confusing errors.
>>
>>    It looks like you are using Hugs - It is much better to use GHC.
>>     That's what everyone uses now.
>>
>>    Another thing:  For a program this size it doesn't matter much, but
>>    in Haskell we always try to make our functions pure if we can (that
>>    is, not IO type).  Then you get the best advantage out of using
>> Haskell.
>>
>>
>>    Steve
>>
>>
>>    listO = ['+', '-', '*', '/', '%', '^', '=', '>', '<', '.', '|', '&',
>>    '!', '~']
>>    listS = [';', '{', '(', ')', '}', '[', ']', ',']
>>    listC = ['0','1'..'9']
>>    listCF = listC ++ ['.']
>>    listA = listO ++ listS ++ [' ']
>>    listPC =
>>    ["auto","double","int","struct","break","else","long","switch","case",
>>
>>    "enum","register","typedef","char","extern","return","union","const",
>>
>>    "float","short","unsigned","continue","for","signed","void","default",
>>             "goto","sizeof","volatile","do","if","static","while"]
>>
>>    verifica :: IO ()
>>
>>    verifica = do
>>       putStr ("Favor visualizar o codigo para ver os bugs e erros do
>>    programa\n")
>>       putStr ("Digite o nome do arquivo de entrada: ")
>>       arqent <- getLine
>>       texto <- readFile arqent
>>       le_bloco texto
>>
>>    le_bloco :: String -> IO ()
>>
>>    le_bloco (x:xs)
>>       | x `elem` listO = do operador (x:xs)
>>       | x `elem` listC = do cnum (x:xs)
>>     --  | x `elem` listS = do separador (x:xs)
>>       | x `elem` listS = do{ putStr[x] ; putStr " <separador>\n" }
>>       | x == '"' = litstr (xs)
>>       | x /= ' ' = pchave (x:xs) []
>>       | x == ' ' = le_bloco xs
>>       | otherwise    = do { putStr "Outro\n" ; le_bloco xs }
>>
>>    separador :: String -> IO ()
>>
>>    separador (x:xs)
>>       | x `elem` listS = do{ putStr [x] ; separador xs}
>>       | otherwise = do{ putStr " <separador>\n" ; le_bloco xs}
>>
>>    cnum :: String -> IO ()
>>
>>    cnum (x:xs)
>>       | x `elem` listCF = do{ putChar x ; cnum xs}
>>       | otherwise = do{ putStr " <cte. numerica>\n" ; le_bloco (x:xs)}
>>
>>    operador :: String -> IO ()
>>
>>    operador (x:xs)
>>       | x `elem` listO = do{ putChar x ; operador xs}
>>       | otherwise = do{ putStr " <operador>\n" ; le_bloco (x:xs)}
>>
>>    litstr :: String -> IO ()
>>
>>    litstr (x:xs)
>>       | x /= '"' = do{ putChar x ; litstr xs}
>>       | otherwise = do{ putStr " <literal string>\n" ; le_bloco xs}
>>
>>    pchave :: String -> String -> IO ()
>>
>>    pchave (x:xs) ys
>>       | x `notElem` listA = pchave xs (ys++[x])
>>       | otherwise = pPCouI (x:xs) ys
>>
>>    pPCouI :: String -> String -> IO ()
>>
>>    pPCouI (x:xs) z
>>       | membroPC z = do{ putStr (z ++ " <palavra chave>\n") ; le_bloco
>>    (x:xs)}
>>       | otherwise = do{putStr z ; putStr " <identificador>\n" ;
>>    le_bloco (x:xs)}
>>
>>    membroPC :: String -> Bool
>>
>>    membroPC x
>>       | x `elem` listPC = True
>>       | otherwise = False
>>
>>
>>    Renato dos Santos Leal wrote:
>>
>>        I've got a university project that demands me to do a program
>>        that receive a .c file and analyze its syntax using haskell.
>>        There are just a few things that I have to analyze:
>>        literal strings, identifiers (in the program: identificadores),
>>        constants (constantes), operators (operadores) and reserverd
>>        words(palavras reservadas)
>>
>>        There are two major problems in the program:
>>
>>        (1) I've got this guard in le_bloco: | x `elem` listS = do
>>        separador (x:xs)
>>        but it doesn't seem to work. Every time I enable it I recieve
>>        this in execution time (after calling verifica)
>>
>>        ERROR - Cannot find "show" function for:
>>        *** Expression : verifica
>>        *** Of type    : IO a
>>
>>        So I've made one workaround that prints the separator but stops
>>        the program...I guess the problem is doing the recursivity
>>
>>        (2) My second problem is: when I have one identifier or keyword
>>        alone in a line or it's the last element of it it just won't
>>        print my coment!
>>        this is the function:
>>
>>        pPCouI (x:xs) z
>>           | membroPC z = do{ putStr (z ++ " <palavra chave>\n") ;
>>        le_bloco (x:xs)}
>>           | otherwise = do{putStr z ; putStr " <identificador>\n" ;
>>        le_bloco (x:xs)}
>>
>>        *Please help me solving those problems as soon as possible!*
>>
>>        Here is the whole program:
>>
>>        listO = ['+', '-', '*', '/', '%', '^', '=', '>', '<', '.', '|',
>>        '&', '!', '~']
>>        listS = [';', '{', '(', ')', '}', '[', ']', ',']
>>        listC = ['0','1'..'9']
>>        listCF = listC ++ ['.']
>>        listA = listO ++ listS ++ [' ']
>>        listPC =
>>
>>  ["auto","double","int","struct","break","else","long","switch","case",
>>
>>  "enum","register","typedef","char","extern","return","union","const",
>>
>>  "float","short","unsigned","continue","for","signed","void","default",
>>                 "goto","sizeof","volatile","do","if","static","while"]
>>
>>        verifica = do
>>           putStr ("Favor visualizar o codigo para ver os bugs e erros
>>        do programa\n")
>>           putStr ("Digite o nome do arquivo de entrada: ")
>>           arqent <- getLine
>>           texto <- readFile arqent
>>           le_bloco texto
>>          le_bloco (x:xs)
>>           | x `elem` listO = do operador (x:xs)
>>           | x `elem` listC = do cnum (x:xs)
>>         --  | x `elem` listS = do separador (x:xs)
>>           | x `elem` listS = do{ putStr[x] ; putStr " <separador>\n" }
>>           | x == '"' = litstr (xs)
>>           | x /= ' ' = pchave (x:xs) []
>>           | x == ' ' = le_bloco xs
>>           | otherwise    = do { putStr "Outro\n" ; le_bloco xs }
>>
>>        separador (x:xs)
>>           | x `elem` listS = do{ putStr [x] ; separador xs}
>>           | otherwise = do{ putStr " <separador>\n" ; le_bloco xs}
>>          cnum (x:xs)
>>           | x `elem` listCF = do{ putChar x ; cnum xs}
>>           | otherwise = do{ putStr " <cte. numerica>\n" ; le_bloco (x:xs)}
>>          operador (x:xs)
>>           | x `elem` listO = do{ putChar x ; operador xs}
>>           | otherwise = do{ putStr " <operador>\n" ; le_bloco (x:xs)}
>>          litstr (x:xs)
>>           | x /= '"' = do{ putChar x ; litstr xs}
>>           | otherwise = do{ putStr " <literal string>\n" ; le_bloco xs}
>>
>>        pchave (x:xs) ys
>>           | x `notElem` listA = pchave xs (ys++[x])
>>           | otherwise = pPCouI (x:xs) ys
>>          pPCouI (x:xs) z
>>           | membroPC z = do{ putStr (z ++ " <palavra chave>\n") ;
>>        le_bloco (x:xs)}
>>           | otherwise = do{putStr z ; putStr " <identificador>\n" ;
>>        le_bloco (x:xs)}
>>          membroPC x
>>           | x `elem` listPC = True
>>           | otherwise = False
>>
>>        I'm sorry for the bad english, it's been a while since the last
>>        time i used it =)
>>        Ah, I'm just starting to learn Haskell, first time i've seen it
>>        was like a month ago so pretend that I know nothing
>>
>>
>>
>>  ------------------------------------------------------------------------
>>
>>        _______________________________________________
>>        Beginners mailing list
>>        Beginners at haskell.org <mailto:Beginners at haskell.org>
>>
>>        http://www.haskell.org/mailman/listinfo/beginners
>>
>>
>>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/beginners/attachments/20100421/115c54bb/attachment-0001.html


More information about the Beginners mailing list