
Right now, my program is ike this
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 == '\n' = le_bloco xs
| x == '"' = litstr (xs)
| x /= ' ' = pchave (x:xs) []
| x == ' ' = le_bloco xs
| otherwise = do { putStr "Outro\n" ; le_bloco xs }
le_bloco [] = return ()
separador :: String -> IO ()
separador (x:xs)
| x `elem` listS = do{ putStr [x] ; putStr " <separador>\n" ; le_bloco
xs}
cnum :: String -> IO ()
cnum (x:xs)
| x `elem` listCF = do{ putChar x ; cnum xs}
| otherwise = do{ putStr "