
del_31416no:
Dear list,
I am trying to make a compiler and we are having a hard time getting Alex to work. We have succeded to work out Alex using older version, but with the the 2.2 version we keep getting this error and we havent been able to figure it out.
So this is our tokens definition:
{ module Lexico where import Alex }
%wrapper "posn"
$digit = 0-9 -- digits $alpha = [a-zA-Z] -- alphabetic characters
tokens :-
$white+ ; --Los espacios en blanco los omito \/\/.* ; --Lo que venga despu s de dos barras omito \/\*.*\*\/ ; --Lo que est entre las barras de comentario omito $digit+ { \p s -> TokenEntero p (read s) } \' [$alpha $digit \_]* \' { \p s -> TokenString p (read s)} [$digit]+\.[$digit]+ { \p s -> TokenDouble p (read s) } $alpha [$alpha $digit \_]* { \p s -> TokenVar p (read s) }
And when we call the alexScanTokens "hello" we get this error:
[TokenVar (AlexPn 0 1 1) "*** Exception: Prelude.read: no parse
So we are concerned about the "TokenVar p (read s)" . Would that be the way to read a string?
Use readMaybe rather than read, and check the error. maybeRead :: Read a => String -> Just a maybeRead s = case reads s of [(x, s')] | all isSpace s' -> Just x _ -> Nothing