{-# LANGUAGE OverloadedStrings #-} module Skylighting.Syntax.LiterateHaskell (syntax) where import Skylighting.Types import Data.Map import Skylighting.Regex syntax :: Syntax syntax = Syntax { sName = "Literate Haskell" , sFilename = "literate-haskell.xml" , sShortname = "LiterateHaskell" , sContexts = fromList [ ( "comments'" , Context { cName = "comments'" , cSyntax = "Literate Haskell" , cRules = [ Rule { rMatcher = Detect2Chars '-' '}' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = CommentTok , cLineEmptyContext = [] , cLineEndContext = [ Push ( "Literate Haskell" , "uncomments" ) ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "normal" , Context { cName = "normal" , cSyntax = "Literate Haskell" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "\\{-[^#]" , reCompiled = Just (compileRegex True "\\{-[^#]") , reCaseSensitive = True } , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Literate Haskell" , "comments'" ) ] } , Rule { rMatcher = IncludeRules ( "Haskell" , "" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "normals" , Context { cName = "normals" , cSyntax = "Literate Haskell" , cRules = [ Rule { rMatcher = StringDetect "\\end{code}" , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = StringDetect "\\end{spec}" , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = IncludeRules ( "Haskell" , "" ) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "recomments" , Context { cName = "recomments" , cSyntax = "Literate Haskell" , cRules = [ Rule { rMatcher = Detect2Chars '-' '}' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Pop , Pop ] } ] , cAttribute = CommentTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "text" , Context { cName = "text" , cSyntax = "Literate Haskell" , cRules = [ Rule { rMatcher = DetectChar '>' , rAttribute = OtherTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [ Push ( "Literate Haskell" , "normal" ) ] } , Rule { rMatcher = DetectChar '<' , rAttribute = OtherTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [ Push ( "Literate Haskell" , "normal" ) ] } , Rule { rMatcher = StringDetect "\\begin{code}" , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Literate Haskell" , "normals" ) ] } , Rule { rMatcher = StringDetect "\\begin{spec}" , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Literate Haskell" , "normals" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "uncomments" , Context { cName = "uncomments" , cSyntax = "Literate Haskell" , cRules = [ Rule { rMatcher = DetectChar '>' , rAttribute = OtherTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [ Push ( "Literate Haskell" , "recomments" ) ] } , Rule { rMatcher = DetectChar '<' , rAttribute = OtherTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [ Push ( "Literate Haskell" , "recomments" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) ] , sAuthor = "Nicolas Wu (zenzike@gmail.com)" , sVersion = "3" , sLicense = "LGPL" , sExtensions = [ "*.lhs" ] , sStartingContext = "text" }