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

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


module TigerAS where

type VarIdent = String
type TypeIdent = String
  
data Declaration = TypeDec TypeIdent Type | VarDec VarIdent TypeIdent Expr | FunDec VarIdent [TypedVar] TypeIdent Expr
  deriving (Eq, Show)
  
data TypedVar
  = TypedVar VarIdent TypeIdent
  deriving (Eq, Show)

data Type
  = Var TypeIdent
  | Array TypeIdent
  | Record [TypedVar]
  deriving (Eq, Show)

data Expr
  = Sub Expr Expr
  | Dot Expr Expr
  | Apply VarIdent [Expr]
  | Ident TypeIdent
  | RecordVal TypeIdent [AssignField]
  | ArrayVal TypeIdent Expr Expr
  | IntLit Integer
  | StringLit String
  | While Expr Expr
  | For VarIdent Expr Expr Expr
  | If Expr Expr Expr
  | Let [Declaration] [Expr]
  | Assign Expr Expr
  | Op String Expr Expr
  | UnOp String Expr
  | Skip
  | Nil
  | Break
  | Seq [Expr]
  deriving (Show, Eq)

data AssignField 
  = AssignField VarIdent Expr
  deriving (Eq, Show)

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.