{-# LANGUAGE OverloadedStrings #-} module Skylighting.Syntax.Noweb (syntax) where import Skylighting.Types import Data.Map import Skylighting.Regex syntax :: Syntax syntax = Syntax { sName = "noweb" , sFilename = "noweb.xml" , sShortname = "Noweb" , sContexts = fromList [ ( "CodeQuote" , Context { cName = "CodeQuote" , cSyntax = "noweb" , cRules = [ Rule { rMatcher = Detect2Chars '@' ']' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\]\\](?!\\])" , reCompiled = Just (compileRegex True "\\]\\](?!\\])") , reCaseSensitive = True } , rAttribute = RegionMarkerTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = IncludeRules ( "noweb" , "SectionNames" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "C++" , "" ) , rAttribute = NormalTok , rIncludeAttribute = True , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "CodeSection" , Context { cName = "CodeSection" , cSyntax = "noweb" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "@$" , reCompiled = Just (compileRegex True "@$") , reCaseSensitive = True } , rAttribute = RegionMarkerTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [ Push ( "noweb" , "RawDocumentation" ) ] } , Rule { rMatcher = RegExpr RE { reString = "@(?=[\\s%])" , reCompiled = Just (compileRegex True "@(?=[\\s%])") , reCaseSensitive = True } , rAttribute = RegionMarkerTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [ Push ( "noweb" , "RawDocumentation" ) ] } , Rule { rMatcher = RegExpr RE { reString = "<<.*>>=$" , reCompiled = Just (compileRegex True "<<.*>>=$") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = True , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [ Push ( "noweb" , "RawDocumentation" ) ] } , Rule { rMatcher = IncludeRules ( "noweb" , "SectionNames" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = IncludeRules ( "C++" , "" ) , rAttribute = NormalTok , rIncludeAttribute = True , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "RawDocumentation" , Context { cName = "RawDocumentation" , cSyntax = "noweb" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "<<.*>>=$" , reCompiled = Just (compileRegex True "<<.*>>=$") , reCaseSensitive = True } , rAttribute = RegionMarkerTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [ Push ( "noweb" , "CodeSection" ) ] } , Rule { rMatcher = Detect2Chars '@' '[' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Detect2Chars '[' '[' , rAttribute = RegionMarkerTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "noweb" , "CodeQuote" ) ] } , Rule { rMatcher = IncludeRules ( "HTML" , "" ) , rAttribute = NormalTok , rIncludeAttribute = True , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "SectionNames" , Context { cName = "SectionNames" , cSyntax = "noweb" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "@<<" , reCompiled = Just (compileRegex True "@<<") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "<<.*[^@]>>(?!=)" , reCompiled = Just (compileRegex True "<<.*[^@]>>(?!=)") , reCaseSensitive = True } , rAttribute = RegionMarkerTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) ] , sAuthor = "Scott Collins (scc@scottcollins.net)" , sVersion = "2" , sLicense = "" , sExtensions = [ "*.w" , "*.nw" ] , sStartingContext = "RawDocumentation" }