{-# LANGUAGE OverloadedStrings #-} module Skylighting.Syntax.LiterateCurry (syntax) where import Skylighting.Types syntax :: Syntax syntax = read $! "Syntax {sName = \"Literate Curry\", sFilename = \"literate-curry.xml\", sShortname = \"LiterateCurry\", sContexts = fromList [(\"Code\",Context {cName = \"Code\", cSyntax = \"Literate Curry\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"\\\\{-[^#]\", reCaseSensitive = True}), rAttribute = CommentTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Literate Curry\",\"multiline\")]},Rule {rMatcher = IncludeRules (\"Curry\",\"\"), 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}),(\"Text\",Context {cName = \"Text\", cSyntax = \"Literate Curry\", cRules = [Rule {rMatcher = DetectChar '>', rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Just 0, rContextSwitch = [Push (\"Literate Curry\",\"Code\")]},Rule {rMatcher = DetectChar '<', rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Just 0, rContextSwitch = [Push (\"Literate Curry\",\"Code\")]},Rule {rMatcher = StringDetect \"\\\\begin{code}\", rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Literate Curry\",\"normals\")]},Rule {rMatcher = StringDetect \"\\\\begin{spec}\", rAttribute = NormalTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Literate Curry\",\"normals\")]}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"lineend\",Context {cName = \"lineend\", cSyntax = \"Literate Curry\", cRules = [Rule {rMatcher = DetectChar '>', rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Just 0, rContextSwitch = [Push (\"Literate Curry\",\"restart\")]},Rule {rMatcher = DetectChar '<', rAttribute = OtherTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Just 0, rContextSwitch = [Push (\"Literate Curry\",\"restart\")]}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"multiline\",Context {cName = \"multiline\", cSyntax = \"Literate Curry\", 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 Curry\",\"lineend\")], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"normals\",Context {cName = \"normals\", cSyntax = \"Literate Curry\", 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 (\"Curry\",\"\"), 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}),(\"restart\",Context {cName = \"restart\", cSyntax = \"Literate Curry\", 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})], sAuthor = \"Bj\\246rn Peem\\246ller (bjp@informatik.uni-kiel.de)\", sVersion = \"1\", sLicense = \"LGPL\", sExtensions = [\"*.lcurry\"], sStartingContext = \"Text\"}"