clafer-0.3.7: clafer compiles Clafer models to other formats, such as Alloy, XML, HTML, Dot.

Safe HaskellNone

Language.Clafer.Front.LayoutResolver

Description

Resolves indentation into explicit nesting using { }

Synopsis

Documentation

data LayEnv Source

Constructors

LayEnv 

Fields

level :: Int
 
levels :: [Int]
 
input :: String
 
output :: String
 
brCtr :: Int
 

Instances

Show LayEnv 

type LastNl = (Int, Int)Source

ident level of new line, current level or parenthesis

data ExToken Source

Constructors

NewLine LastNl 
ExToken Token 

Instances

Show ExToken 

data LEnv Source

ident level stack, last new line

Constructors

LEnv [Int] (Maybe LastNl) 

getToken :: Monad m => ExToken -> ClaferT m TokenSource

resolveLayout :: Monad m => [Token] -> ClaferT m [Token]Source

resolve :: Monad m => LEnv -> [ExToken] -> ClaferT m [Token]Source

isExTokenIn :: [String] -> ExToken -> BoolSource

incrGlobalSource

Arguments

:: Monad m 
=> Position

If the token is on the same line as this position, update the column position.

-> Int

Number of characters to add to the position.

-> Token 
-> ClaferT m Token 

Add to the global and column positions of a token. | The column position is only changed if the token is on | the same line as the given position.

tokenLookup :: String -> Maybe IntSource

position :: Token -> PositionSource

Get the position of a token.

line :: Token -> IntSource

Get the line number of a token.

column :: Token -> IntSource

Get the column number of a token.

isTokenIn :: [String] -> Token -> BoolSource

Check if a token is one of the given symbols.

isLayoutOpen :: Token -> BoolSource

Check if a token is the layout open token.

isLayoutClose :: Token -> BoolSource

Check if a token is the layout close token.

tokenLength :: Token -> IntSource

Get the number of characters in the token.

addNewLines :: Monad m => [Token] -> ClaferT m [ExToken]Source

addNewLines' :: Monad m => Int -> [Token] -> ClaferT m [ExToken]Source

adjust :: Monad m => [Token] -> ClaferT m [Token]Source

updToken :: Monad m => [Token] -> ClaferT m [Token]Source

addTokenSource

Arguments

:: Monad m 
=> Position

Position of the new token.

-> String

Symbol in the new token.

-> [Token]

The rest of the tokens. These will have their positions updated to make room for the new token.

-> ClaferT m [Token] 

Insert a new symbol token at the begninning of a list of tokens.

resLayout :: String -> StringSource

emit :: MonadState LayEnv m => Char -> m ()Source

readC :: (Num a, Ord a) => a -> StateT LayEnv Identity CharSource

emitIndent :: MonadState LayEnv m => Int -> m ()Source

emitDedent :: MonadState LayEnv m => Int -> m ()Source

revertLayout :: String -> StringSource

revertLayout' :: [String] -> Int -> [String]Source