Plan 9 from Bell Labs’s /usr/web/sources/contrib/fernan/nhc98/src/libraries/parsec/examples/while/WhileAS.hs

Copyright © 2021 Plan 9 Foundation.
Distributed under the MIT License.
Download the Plan 9 distribution.


module WhileAS where

type  VarIdent = String
type  Label = Int
-- type  Selector = String
  
type Prog = Stat
-- type Prog = Prog [Dec] [Stat]

-- Contains name, a list of input vars, output var, body respectively and of course
-- the two labels ln and lx
data Dec = Proc [VarIdent] VarIdent VarIdent Label Stat Label

data AExp 
  = Var VarIdent 
  | IntLit Integer
  | AOp String AExp AExp
-- | Var  VarIdent (Maybe Selector)
-- | Nil
  | Dummy
  deriving (Eq, Show)
  
data BExp 
  = BUnOp String BExp
  | BoolLit Bool
  | BOp String BExp BExp
  | RelOp String AExp AExp
-- | POp VarIdent (Maybe Selector)
  deriving (Eq, Show)

data Stat
  = Assign VarIdent AExp Label
  | Skip Label
  | Seq [Stat]
  | If BExp Label Stat Stat
  | While BExp Label Stat
-- | Call VarIdent [AExp] VarIdent Label Label
-- | Malloc VarIdent (Maybe Selector) Label
  deriving (Show, Eq)

Bell Labs OSI certified Powered by Plan 9

(Return to Plan 9 Home Page)

Copyright © 2021 Plan 9 Foundation. All Rights Reserved.
Comments to webmaster@9p.io.