-- GeNeRaTeD fOr: ../../CBS/Funcons/Computations/Control flow/Normal/Iterating/Indefinite/do-while.aterm {-# LANGUAGE OverloadedStrings #-} module Funcons.Core.Computations.ControlFlow.Normal.Iterating.Indefinite.DoWhile where import Funcons.EDSL entities = [] types = typeEnvFromList [] funcons = libFromList [("do-while",NonStrictFuncon stepDo_while)] -- | -- /do-while(C,B)/ first executes /C/ . -- Then it evaluates /B/ . Depending on whether the value is /true/ or /false/ , -- it then repeats, or terminates normally. do_while_ fargs = FApp "do-while" (FTuple fargs) stepDo_while fargs = evalRules [rewrite1] [] where rewrite1 = do let env = emptyEnv env <- fsMatch fargs [PMetaVar "C",PMetaVar "B"] env rewriteTermTo (TApp "sequential" (TTuple [TVar "C",TApp "if-then-else" (TTuple [TVar "B",TApp "do-while" (TTuple [TVar "C",TVar "B"]),TTuple []])])) env