[Haskell-cafe] Making a strict (non-lazy) GCL Interpreter

Hector Guilarte hectorg87 at gmail.com
Tue Jun 30 01:37:04 EDT 2009


Hi everyone!

(First of all, I don't know Monads!)

I made a GCL (Guarded Command Language) Compiler and Interpreter for my
Languages and Machines course in my University with alex, happy and ghc. I
asked about a week ago about the use of unsafePerformIO for that same
project, now I have two new doubts:

1) When more than a Condition is true in a
    if cond1 -> instruction1
    |  cond2 -> instruction2
    ...
    | condN -> instructionN
    fi
  I need to randomly select ONE of the valid conditions and execute it's
instruction. I know there is a Random Monad, but it returns an IO Int, Is
there anyway I can do some Random that doesn't involve IO? or any other
solution? That part of the code is:

(My code is in Spanish. TablaOutput is a type and it stands for the tupe of
the Symbol Table (Data.Map) and the Output [String], obtenerValidos checks
wich pair of (condition,instruction) are true and makes a list out of them,
ejecutarUnoRand is the Instruction that executes one of the instructions
randomly)

evalSeleccion:: [(BoolY,Instruccion)] -> TablaOutput -> TablaOutput
evalSeleccion lista tabla =
    let validos = obtenerValidos lista [] tabla
    in if (isEmpty validos) then error "Las guardias del If estan
incompletas"
        else ejecutarUnoRand validos tabla

obtenerValidos:: [(BoolY,Instruccion)] -> [(BoolY,Instruccion)] ->
TablaOutput -> [(BoolY,Instruccion)]
obtenerValidos [] validos tabla = validos
obtenerValidos ((boolY,instruccion):bloqueIns) validos tabla = if (evalBoolY
boolY (fst tabla)) then obtenerValidos bloqueIns (validos ++
[(boolY,instruccion)]) tabla

else obtenerValidos bloqueIns validos tabla

ejecutarUnoRand:: [(BoolY,Instruccion)] -> TablaOutput -> TablaOutput
ejecutarUnoRand validos tabla =
    let rand = 0 --getStdRandom (randomR (0,(length validos))) HERE'S WHERE
I'M SUPPOSED TO DO RANDOM, RIGHT NOW I'M JUST CHOSING THE FIRST
    in evalInstruccion (snd (validos !! rand)) tabla

2) Since Haskell is Lazy, and my GCL program is being interpreted in Haskell
then my GCL is Lazy too (I know is not as simple as that but believe me,
somehow it is behaving lazy). The problem is that it can't be lazy (said to
me by my teacher today) so I tried using seq, I'll paste the code after
this:
Programs in GCL like:
a)
var i : value
main
    i <- 1 / 0
end

b)
var i : value
main
    i <- 1 / 0;
    show i
end

c)
var i : value
var foo : array of 2
main
    i <- foo[42]
end

d)
var i : value
main
    i <- foo[42];
    show i
end

acts like this:
a and c finish interpretation
b throws division by zero error and finish interpretation
d throws index out of bounds error and finish interpretation

Now the code:
(again, it is in Spanish. ListLValue is a List of L-Values for the
assigments, ListExpr is the list of Expressions to be assigned, Tabla is the
Symbol Table (Data.Map), actualizarVar updates a Variable in the Symbol
Table with the new value "valor", ActualizarArray updates the position
"indice" of an array in the Symbol Table. evalExpr evaluates an arithmetic
Expression and returns an Int. Inside evalExpr are the verifications for
division by zero of modulo by zero.)

evalAsignacion:: ListLvalue -> ListExpr -> Tabla -> Tabla
evalAsignacion [] [] tabla = tabla
evalAsignacion ((Lid id):valueList) (expr:exprList) tabla =
    let valor = (evalExpr expr tabla)
    in valor `seq` evalAsignacion valueList exprList (actualizarVar id valor
tabla)
evalAsignacion ((LArrayPosition id exprArray):valueList) (expr:exprList)
tabla =
    let valor = (evalExpr expr tabla)
        indice = (evalExpr exprArray tabla)
    in valor `seq` indice `seq` evalAsignacion valueList exprList
(actualizarArray id indice valor tabla)

evalExpr:: Expr -> Tabla -> Int
evalExpr expr tabla =
    let salida = (snd (evalAritmetico expr tabla))
    in salida `seq` if (isLeft salida) then error (getLeft salida)
                              else getRight salida

--((Int,Int) is the Line and Colum, that's for error reporting)
evalAritmetico :: Expr -> Tabla -> ((Int,Int),(Either String Int))
--LET ME KNOW IF YOU NEED THIS PART TOO


Thanks in advance,

Hector Guilarte
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20090630/710da9dd/attachment.html


More information about the Haskell-Cafe mailing list