---------------------------------------------------------------- -- -- | Compilation -- Monad and combinators for quickly assembling simple -- compilers. -- -- @Control\/Compilation\/Sequence.hs@ -- -- A generic compilation monad for quickly assembling simple -- compilers for target languages that are primarily -- sequences of instructions (possibly with nesting, e.g., -- loop constructs or procedures). -- ---------------------------------------------------------------- -- {-# LANGUAGE MultiParamTypeClasses, ScopedTypeVariables #-} module Control.Compilation.Sequence where import Control.Compilation ---------------------------------------------------------------- -- | State extension class definition, and combinators for -- compiling into a sequence (possibly with nested blocks) -- of instructions. class StateExtension a => Sequence a b where project :: a -> [[b]] inject :: [[b]] -> a -> a nest :: [b] -> Compilation a () nest xs = do s :: a <- get xss :: [[b]] <- return $ project s set $ inject (xs : xss) s unnest :: Compilation a [b] unnest = do s :: a <- get xs :: [[b]] <- return $ project s set $ inject (tail $ xs) s return $ head $ project s depth :: Compilation a Integer depth = do s <- get xss :: [[b]] <- return $ project s return $ toInteger $ length xss --eof