module SugarSyntax where
import qualified Data.Set as S
import PureSyntax
data SuProgram = SuProgram Name Name SuBlock Name deriving Eq
type SuBlock = [SuCommand]
newtype Info = Info (FilePath, Int) deriving (Show, Eq, Ord)
data SuCommand
= SuAssign Info Name Expression
| SuWhile Info Expression SuBlock
| SuIfElse Info Expression SuBlock SuBlock
| Macro Info Name FilePath Expression
| Switch Info Expression [(Expression, SuBlock)] SuBlock
deriving (Show, Eq, Ord)
namesSuProg :: SuProgram -> S.Set Name
namesSuProg (SuProgram n r b w) = foldr S.insert (namesSuBlock b) [n, r, w]
namesSuBlock :: SuBlock -> S.Set Name
namesSuBlock = S.unions . map namesSuComm
namesSuComm :: SuCommand -> S.Set Name
namesSuComm comm = case comm of
SuAssign _ n e -> S.insert n (namesExpr e)
SuWhile _ e b -> S.union (namesExpr e) (namesSuBlock b)
SuIfElse _ e bt bf -> S.unions [namesExpr e, namesSuBlock bt, namesSuBlock bf]
Macro _ n _ e -> S.insert n (namesExpr e)
Switch _ e eb b -> S.unions
[ namesExpr e
, S.unions (map (\(e, b) -> S.union (namesExpr e) (namesSuBlock b)) eb)
, namesSuBlock b
]