{-# LANGUAGE OverloadedStrings #-} module Skylighting.Syntax.Purebasic (syntax) where import Skylighting.Types import Data.Map import Skylighting.Regex import qualified Data.Set syntax :: Syntax syntax = Syntax { sName = "PureBasic" , sFilename = "purebasic.xml" , sShortname = "Purebasic" , sContexts = fromList [ ( "Comment1" , Context { cName = "Comment1" , cSyntax = "PureBasic" , cRules = [ Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = False , keywordDelims = Data.Set.fromList "\t\n !%&()*+,-./:;<=>?[\\]^{|}~" } (makeWordSet True []) , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = CommentTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Normal" , Context { cName = "Normal" , cSyntax = "PureBasic" , cRules = [ Rule { rMatcher = AnyChar "-+*/%|=!<>!^&~" , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = AnyChar ",.:()[]\\" , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\b(if)([\\s]|$)" , reCompiled = Just (compileRegex False "\\b(if)([\\s]|$)") , reCaseSensitive = False } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\b(endif)([\\s]|$)" , reCompiled = Just (compileRegex False "\\b(endif)([\\s]|$)") , reCaseSensitive = False } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\b(while)([\\s]|$)" , reCompiled = Just (compileRegex False "\\b(while)([\\s]|$)") , reCaseSensitive = False } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\b(wend)([\\s]|$)" , reCompiled = Just (compileRegex False "\\b(wend)([\\s]|$)") , reCaseSensitive = False } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\b(repeat)([\\s]|$)" , reCompiled = Just (compileRegex False "\\b(repeat)([\\s]|$)") , reCaseSensitive = False } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\b(until)([\\s]|$)" , reCompiled = Just (compileRegex False "\\b(until)([\\s]|$)") , reCaseSensitive = False } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\b(select)([\\s]|$)" , reCompiled = Just (compileRegex False "\\b(select)([\\s]|$)") , reCaseSensitive = False } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\b(endselect)([\\s]|$)" , reCompiled = Just (compileRegex False "\\b(endselect)([\\s]|$)") , reCaseSensitive = False } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\b(for|foreach)([\\s]|$)" , reCompiled = Just (compileRegex False "\\b(for|foreach)([\\s]|$)") , reCaseSensitive = False } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\b(next)([\\s]|$)" , reCompiled = Just (compileRegex False "\\b(next)([\\s]|$)") , reCaseSensitive = False } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\b(procedure|proceduredll)([.\\s]|$)" , reCompiled = Just (compileRegex False "\\b(procedure|proceduredll)([.\\s]|$)") , reCaseSensitive = False } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\b(endprocedure)([\\s]|$)" , reCompiled = Just (compileRegex False "\\b(endprocedure)([\\s]|$)") , reCaseSensitive = False } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\b(structure)([\\s]|$)" , reCompiled = Just (compileRegex False "\\b(structure)([\\s]|$)") , reCaseSensitive = False } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\b(endstructure)([\\s]|$)" , reCompiled = Just (compileRegex False "\\b(endstructure)([\\s]|$)") , reCaseSensitive = False } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\b(interface)([\\s]|$)" , reCompiled = Just (compileRegex False "\\b(interface)([\\s]|$)") , reCaseSensitive = False } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\b(endinterface)([\\s]|$)" , reCompiled = Just (compileRegex False "\\b(endinterface)([\\s]|$)") , reCaseSensitive = False } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\b(enumeration)([\\s]|$)" , reCompiled = Just (compileRegex False "\\b(enumeration)([\\s]|$)") , reCaseSensitive = False } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\b(endenumeration)([\\s]|$)" , reCompiled = Just (compileRegex False "\\b(endenumeration)([\\s]|$)") , reCaseSensitive = False } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\b(datasection)([\\s]|$)" , reCompiled = Just (compileRegex False "\\b(datasection)([\\s]|$)") , reCaseSensitive = False } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\b(enddatasection)([\\s]|$)" , reCompiled = Just (compileRegex False "\\b(enddatasection)([\\s]|$)") , reCaseSensitive = False } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = False , keywordDelims = Data.Set.fromList "\t\n !%&()*+,-./:;<=>?[\\]^{|}~" } (makeWordSet False [ "Break" , "Case" , "Continue" , "Data" , "DataSection" , "Declare" , "DeclareModule" , "Default" , "DefType" , "Dim" , "Else" , "ElseIf" , "End" , "EndDataSection" , "EndDeclareModule" , "EndEnumeration" , "EndIf" , "EndInterface" , "EndModule" , "EndProcedure" , "EndSelect" , "EndStructure" , "Enumeration" , "Extends" , "FakeReturn" , "For" , "ForEach" , "Global" , "Gosub" , "Goto" , "If" , "IncludeBinary" , "IncludeFile" , "IncludePath" , "Interface" , "Module" , "NewList" , "Next" , "Procedure" , "ProcedureDLL" , "ProcedureReturn" , "Protected" , "Read" , "Repeat" , "Restore" , "Return" , "Select" , "Shared" , "Static" , "Step" , "Structure" , "To" , "Until" , "UnuseModule" , "UseModule" , "Wend" , "While" , "With" , "XIncludeFile" ]) , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\b(compilerif)([\\s]|$)" , reCompiled = Just (compileRegex False "\\b(compilerif)([\\s]|$)") , reCaseSensitive = False } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\b(compilerendif)([\\s]|$)" , reCompiled = Just (compileRegex False "\\b(compilerendif)([\\s]|$)") , reCaseSensitive = False } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\b(compilerselect)([\\s]|$)" , reCompiled = Just (compileRegex False "\\b(compilerselect)([\\s]|$)") , reCaseSensitive = False } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\b(compilerendselect)([\\s]|$)" , reCompiled = Just (compileRegex False "\\b(compilerendselect)([\\s]|$)") , reCaseSensitive = False } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = False , keywordDelims = Data.Set.fromList "\t\n !%&()*+,-./:;<=>?[\\]^{|}~" } (makeWordSet False [ "CompilerCase" , "CompilerDefault" , "CompilerElse" , "CompilerEndIf" , "CompilerEndSelect" , "CompilerIf" , "CompilerSelect" ]) , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = False , keywordDelims = Data.Set.fromList "\t\n !%&()*+,-./:;<=>?[\\]^{|}~" } (makeWordSet False [ "AbortFTPFile" , "Abs" , "ACos" , "ACosH" , "Add3DArchive" , "AddBillboard" , "AddCipherBuffer" , "AddDate" , "AddElement" , "AddEntityAnimationTime" , "AddGadgetColumn" , "AddGadgetItem" , "AddGadgetItem3D" , "AddJSONElement" , "AddJSONMember" , "AddKeyboardShortcut" , "AddMailAttachment" , "AddMailAttachmentData" , "AddMailRecipient" , "AddMapElement" , "AddMaterialLayer" , "AddNodeAnimationTime" , "AddPackFile" , "AddPackMemory" , "AddSplinePoint" , "AddStaticGeometryEntity" , "AddStatusBarField" , "AddSubMesh" , "AddSysTrayIcon" , "AddTerrainTexture" , "AddVertexPoseReference" , "AddWindowTimer" , "AESDecoder" , "AESEncoder" , "AffectedDatabaseRows" , "AllocateMemory" , "AllocateStructure" , "Alpha" , "AlphaBlend" , "AmbientColor" , "AntialiasingMode" , "ApplyEntityForce" , "ApplyEntityImpulse" , "ArraySize" , "Asc" , "ASin" , "ASinH" , "ATan" , "ATan2" , "ATanH" , "AttachEntityObject" , "AttachNodeObject" , "AttachRibbonEffect" , "AudioCDLength" , "AudioCDName" , "AudioCDStatus" , "AudioCDTrackLength" , "AudioCDTracks" , "AudioCDTrackSeconds" , "AvailableProgramOutput" , "AvailableScreenMemory" , "AvailableSerialPortInput" , "AvailableSerialPortOutput" , "BackColor" , "Base64Decoder" , "Base64Encoder" , "BillboardGroupCommonDirection" , "BillboardGroupCommonUpVector" , "BillboardGroupID" , "BillboardGroupMaterial" , "BillboardGroupX" , "BillboardGroupY" , "BillboardGroupZ" , "BillboardHeight" , "BillboardLocate" , "BillboardWidth" , "BillboardX" , "BillboardY" , "BillboardZ" , "Bin" , "BindEvent" , "BindGadgetEvent" , "BindMenuEvent" , "Blue" , "Box" , "BoxedGradient" , "BuildMeshShadowVolume" , "BuildMeshTangents" , "BuildStaticGeometry" , "BuildTerrain" , "ButtonGadget" , "ButtonGadget3D" , "ButtonImageGadget" , "CalendarGadget" , "CallCFunction" , "CallCFunctionFast" , "CallFunction" , "CallFunctionFast" , "CameraBackColor" , "CameraDirection" , "CameraDirectionX" , "CameraDirectionY" , "CameraDirectionZ" , "CameraFixedYawAxis" , "CameraFollow" , "CameraFOV" , "CameraID" , "CameraLookAt" , "CameraPitch" , "CameraProjectionMode" , "CameraProjectionX" , "CameraProjectionY" , "CameraRange" , "CameraRenderMode" , "CameraRoll" , "CameraViewHeight" , "CameraViewWidth" , "CameraViewX" , "CameraViewY" , "CameraX" , "CameraY" , "CameraYaw" , "CameraZ" , "CanvasGadget" , "CanvasOutput" , "CatchImage" , "CatchJSON" , "CatchMusic" , "CatchSound" , "CatchSprite" , "CatchXML" , "ChangeCurrentElement" , "ChangeGamma" , "ChangeListIconGadgetDisplay" , "ChangeSysTrayIcon" , "CheckBoxGadget" , "CheckBoxGadget3D" , "CheckDatabaseNull" , "CheckFilename" , "CheckFTPConnection" , "CheckObjectVisibility" , "ChildXMLNode" , "Chr" , "Circle" , "CircularGradient" , "ClearBillboards" , "ClearClipboard" , "ClearConsole" , "ClearDebugOutput" , "ClearGadgetItemList" , "ClearGadgetItems" , "ClearGadgetItems3D" , "ClearJSONElements" , "ClearJSONMembers" , "ClearList" , "ClearMap" , "ClearScreen" , "ClearSpline" , "ClipOutput" , "ClipSprite" , "CloseConsole" , "CloseCryptRandom" , "CloseDatabase" , "CloseFile" , "CloseFTP" , "CloseGadgetList" , "CloseGadgetList3D" , "CloseHelp" , "CloseLibrary" , "CloseNetworkConnection" , "CloseNetworkServer" , "ClosePack" , "ClosePreferences" , "CloseProgram" , "CloseScreen" , "CloseSerialPort" , "CloseSubMenu" , "CloseWindow" , "CloseWindow3D" , "CocoaMessage" , "ColorRequester" , "ComboBoxGadget" , "ComboBoxGadget3D" , "CompareMemory" , "CompareMemoryString" , "ComposeJSON" , "ComposeXML" , "CompositorEffectParameter" , "CompressMemory" , "ComputerName" , "ComputeSpline" , "ConeTwistJoint" , "ConicalGradient" , "ConnectionID" , "ConsoleColor" , "ConsoleCursor" , "ConsoleError" , "ConsoleLocate" , "ConsoleTitle" , "ContainerGadget" , "ContainerGadget3D" , "ConvertLocalToWorldPosition" , "ConvertWorldToLocalPosition" , "CopyArray" , "CopyDirectory" , "CopyEntity" , "CopyFile" , "CopyImage" , "CopyLight" , "CopyList" , "CopyMap" , "CopyMaterial" , "CopyMemory" , "CopyMemoryString" , "CopyMesh" , "CopySprite" , "CopyTexture" , "CopyXMLNode" , "Cos" , "CosH" , "CountBillboards" , "CountCPUs" , "CountGadgetItems" , "CountGadgetItems3D" , "CountLibraryFunctions" , "CountList" , "CountMaterialLayers" , "CountProgramParameters" , "CountRegularExpressionGroups" , "CountSplinePoints" , "CountString" , "CPUName" , "CRC32FileFingerprint" , "CRC32Fingerprint" , "CreateBillboardGroup" , "CreateCamera" , "CreateCompositorEffect" , "CreateCube" , "CreateCubeMapTexture" , "CreateCylinder" , "CreateDialog" , "CreateDirectory" , "CreateEntity" , "CreateFile" , "CreateFTPDirectory" , "CreateGadgetList" , "CreateImage" , "CreateImageMenu" , "CreateJSON" , "CreateLensFlareEffect" , "CreateLight" , "CreateLine3D" , "CreateMail" , "CreateMaterial" , "CreateMenu" , "CreateMesh" , "CreateMutex" , "CreateNetworkServer" , "CreateNode" , "CreateNodeAnimation" , "CreateNodeAnimationKeyFrame" , "CreatePack" , "CreateParticleEmitter" , "CreatePlane" , "CreatePopupImageMenu" , "CreatePopupMenu" , "CreatePreferences" , "CreateRegularExpression" , "CreateRenderTexture" , "CreateRibbonEffect" , "CreateSemaphore" , "CreateSphere" , "CreateSpline" , "CreateSprite" , "CreateStaticGeometry" , "CreateStatusBar" , "CreateTerrain" , "CreateText3D" , "CreateTexture" , "CreateThread" , "CreateToolBar" , "CreateVertexAnimation" , "CreateVertexPoseKeyFrame" , "CreateVertexTrack" , "CreateWater" , "CreateXML" , "CreateXMLNode" , "CryptRandom" , "CryptRandomData" , "CustomFilterCallback" , "CustomGradient" , "DatabaseColumnIndex" , "DatabaseColumnName" , "DatabaseColumns" , "DatabaseColumnSize" , "DatabaseColumnType" , "DatabaseDriverDescription" , "DatabaseDriverName" , "DatabaseError" , "DatabaseID" , "DatabaseQuery" , "DatabaseUpdate" , "Date" , "DateGadget" , "Day" , "DayOfWeek" , "DayOfYear" , "DefaultPrinter" , "DefineTerrainTile" , "Degree" , "Delay" , "DeleteDirectory" , "DeleteElement" , "DeleteFile" , "DeleteFTPDirectory" , "DeleteFTPFile" , "DeleteMapElement" , "DeleteXMLNode" , "DESFingerprint" , "DesktopDepth" , "DesktopFrequency" , "DesktopHeight" , "DesktopMouseX" , "DesktopMouseY" , "DesktopName" , "DesktopWidth" , "DesktopX" , "DesktopY" , "DetachEntityObject" , "DetachNodeObject" , "DetachRibbonEffect" , "DialogError" , "DialogGadget" , "DialogID" , "DialogWindow" , "DirectoryEntryAttributes" , "DirectoryEntryDate" , "DirectoryEntryName" , "DirectoryEntrySize" , "DirectoryEntryType" , "DisableEntityBody" , "DisableGadget" , "DisableGadget3D" , "DisableLightShadows" , "DisableMaterialLighting" , "DisableMenuItem" , "DisableParticleEmitter" , "DisableToolBarButton" , "DisableWindow" , "DisableWindow3D" , "DisplayPopupMenu" , "DisplaySprite" , "DisplayTransparentSprite" , "DoubleClickTime" , "DragFiles" , "DragImage" , "DragOSFormats" , "DragPrivate" , "DragText" , "DrawAlphaImage" , "DrawImage" , "DrawingBuffer" , "DrawingBufferPitch" , "DrawingBufferPixelFormat" , "DrawingFont" , "DrawingMode" , "DrawRotatedText" , "DrawText" , "EditorGadget" , "EditorGadget3D" , "EjectAudioCD" , "ElapsedMilliseconds" , "Ellipse" , "EllipticalGradient" , "EnableGadgetDrop" , "EnableGraphicalConsole" , "EnableHingeJointAngularMotor" , "EnableManualEntityBoneControl" , "EnableWindowDrop" , "EnableWorldCollisions" , "EnableWorldPhysics" , "EncodeImage" , "Engine3DStatus" , "EntityAngularFactor" , "EntityAnimationBlendMode" , "EntityAnimationStatus" , "EntityBonePitch" , "EntityBoneRoll" , "EntityBoneX" , "EntityBoneY" , "EntityBoneYaw" , "EntityBoneZ" , "EntityBoundingBox" , "EntityCollide" , "EntityCubeMapTexture" , "EntityCustomParameter" , "EntityFixedYawAxis" , "EntityID" , "EntityLinearFactor" , "EntityLookAt" , "EntityParentNode" , "EntityPhysicBody" , "EntityPitch" , "EntityRenderMode" , "EntityRoll" , "EntityVelocity" , "EntityX" , "EntityY" , "EntityYaw" , "EntityZ" , "EnvironmentVariableName" , "EnvironmentVariableValue" , "Eof" , "ErrorAddress" , "ErrorCode" , "ErrorFile" , "ErrorLine" , "ErrorMessage" , "ErrorRegister" , "ErrorTargetAddress" , "EventClient" , "EventData" , "EventDropAction" , "EventDropBuffer" , "EventDropFiles" , "EventDropImage" , "EventDropPrivate" , "EventDropSize" , "EventDropText" , "EventDropType" , "EventDropX" , "EventDropY" , "EventGadget" , "EventGadget3D" , "EventlParam" , "EventMenu" , "EventServer" , "EventTimer" , "EventType" , "EventType3D" , "EventWindow" , "EventWindow3D" , "EventwParam" , "ExamineAssembly" , "ExamineDatabaseDrivers" , "ExamineDesktops" , "ExamineDirectory" , "ExamineEnvironmentVariables" , "ExamineFTPDirectory" , "ExamineIPAddresses" , "ExamineJoystick" , "ExamineJSONMembers" , "ExamineKeyboard" , "ExamineLibraryFunctions" , "ExamineMD5Fingerprint" , "ExamineMouse" , "ExaminePack" , "ExaminePreferenceGroups" , "ExaminePreferenceKeys" , "ExamineRegularExpression" , "ExamineScreenModes" , "ExamineSHA1Fingerprint" , "ExamineWorldCollisions" , "ExamineXMLAttributes" , "Exp" , "ExplorerComboGadget" , "ExplorerListGadget" , "ExplorerTreeGadget" , "ExportJSON" , "ExportJSONSize" , "ExportXML" , "ExportXMLSize" , "ExtractJSONArray" , "ExtractJSONList" , "ExtractJSONMap" , "ExtractJSONStructure" , "ExtractRegularExpression" , "ExtractXMLArray" , "ExtractXMLList" , "ExtractXMLMap" , "ExtractXMLStructure" , "FetchEntityMaterial" , "FetchOrientation" , "FileBuffersSize" , "FileID" , "FileSeek" , "FileSize" , "FillArea" , "FillMemory" , "FindMapElement" , "FindString" , "FinishCipher" , "FinishDatabaseQuery" , "FinishDirectory" , "FinishFingerprint" , "FinishFTPDirectory" , "FinishMesh" , "FirstDatabaseRow" , "FirstElement" , "FirstWorldCollisionEntity" , "FlipBuffers" , "FlushFileBuffers" , "Fog" , "FontID" , "FontRequester" , "FormatDate" , "FormatXML" , "FrameGadget" , "FrameGadget3D" , "FreeArray" , "FreeBillboardGroup" , "FreeCamera" , "FreeDialog" , "FreeEffect" , "FreeEntity" , "FreeEntityJoints" , "FreeFont" , "FreeGadget" , "FreeGadget3D" , "FreeImage" , "FreeIP" , "FreeJoint" , "FreeJSON" , "FreeLight" , "FreeList" , "FreeMail" , "FreeMap" , "FreeMaterial" , "FreeMemory" , "FreeMenu" , "FreeMesh" , "FreeMovie" , "FreeMusic" , "FreeMutex" , "FreeNode" , "FreeNodeAnimation" , "FreeParticleEmitter" , "FreeRegularExpression" , "FreeSemaphore" , "FreeSound" , "FreeSound3D" , "FreeSpline" , "FreeSprite" , "FreeStaticGeometry" , "FreeStatusBar" , "FreeStructure" , "FreeTerrain" , "FreeText3D" , "FreeTexture" , "FreeToolBar" , "FreeWater" , "FreeXML" , "FrontColor" , "FTPDirectoryEntryAttributes" , "FTPDirectoryEntryDate" , "FTPDirectoryEntryName" , "FTPDirectoryEntryRaw" , "FTPDirectoryEntrySize" , "FTPDirectoryEntryType" , "FTPProgress" , "GadgetHeight" , "GadgetHeight3D" , "GadgetID" , "GadgetID3D" , "GadgetItemID" , "GadgetToolTip" , "GadgetToolTip3D" , "GadgetType" , "GadgetType3D" , "GadgetWidth" , "GadgetWidth3D" , "GadgetX" , "GadgetX3D" , "GadgetY" , "GadgetY3D" , "GetActiveGadget" , "GetActiveGadget3D" , "GetActiveWindow" , "GetActiveWindow3D" , "GetClientIP" , "GetClientPort" , "GetClipboardImage" , "GetClipboardText" , "GetCurrentDirectory" , "GetDatabaseBlob" , "GetDatabaseDouble" , "GetDatabaseFloat" , "GetDatabaseLong" , "GetDatabaseQuad" , "GetDatabaseString" , "GetEntityAnimationLength" , "GetEntityAnimationTime" , "GetEntityAnimationWeight" , "GetEntityAttribute" , "GetEntityCollisionGroup" , "GetEntityCollisionMask" , "GetEnvironmentVariable" , "GetExtensionPart" , "GetFileAttributes" , "GetFileDate" , "GetFilePart" , "GetFTPDirectory" , "GetFunction" , "GetFunctionEntry" , "GetGadgetAttribute" , "GetGadgetAttribute3D" , "GetGadgetColor" , "GetGadgetData" , "GetGadgetData3D" , "GetGadgetFont" , "GetGadgetItemAttribute" , "GetGadgetItemColor" , "GetGadgetItemData" , "GetGadgetItemData3D" , "GetGadgetItemState" , "GetGadgetItemState3D" , "GetGadgetItemText" , "GetGadgetItemText3D" , "GetGadgetState" , "GetGadgetState3D" , "GetGadgetText" , "GetGadgetText3D" , "GetHomeDirectory" , "GetHTTPHeader" , "GetJointAttribute" , "GetJSONBoolean" , "GetJSONDouble" , "GetJSONElement" , "GetJSONFloat" , "GetJSONInteger" , "GetJSONMember" , "GetJSONQuad" , "GetJSONString" , "GetLightColor" , "GetMailAttribute" , "GetMailBody" , "GetMaterialAttribute" , "GetMaterialColor" , "GetMenuItemState" , "GetMenuItemText" , "GetMenuTitleText" , "GetMeshData" , "GetMusicPosition" , "GetMusicRow" , "GetNodeAnimationKeyFrameTime" , "GetNodeAnimationLength" , "GetNodeAnimationTime" , "GetNodeAnimationWeight" , "GetOriginX" , "GetOriginY" , "GetPathPart" , "GetRuntimeDouble" , "GetRuntimeInteger" , "GetRuntimeString" , "GetScriptMaterial" , "GetScriptParticleEmitter" , "GetScriptTexture" , "GetSerialPortStatus" , "GetSoundFrequency" , "GetSoundPosition" , "GetTemporaryDirectory" , "GetTerrainTileHeightAtPoint" , "GetTerrainTileLayerBlend" , "GetToolBarButtonState" , "GetURLPart" , "GetW" , "GetWindowColor" , "GetWindowData" , "GetWindowState" , "GetWindowTitle" , "GetWindowTitle3D" , "GetX" , "GetXMLAttribute" , "GetXMLEncoding" , "GetXMLNodeName" , "GetXMLNodeOffset" , "GetXMLNodeText" , "GetXMLStandalone" , "GetY" , "GetZ" , "GrabDrawingImage" , "GrabImage" , "GrabSprite" , "GradientColor" , "Green" , "Hex" , "HideBillboardGroup" , "HideEffect" , "HideEntity" , "HideGadget" , "HideGadget3D" , "HideLight" , "HideMenu" , "HideParticleEmitter" , "HideWindow" , "HideWindow3D" , "HingeJoint" , "HingeJointMotorTarget" , "HostName" , "Hour" , "HyperLinkGadget" , "ImageDepth" , "ImageFormat" , "ImageGadget" , "ImageGadget3D" , "ImageHeight" , "ImageID" , "ImageOutput" , "ImageWidth" , "Infinity" , "InitAudioCD" , "InitEngine3D" , "InitJoystick" , "InitKeyboard" , "InitMouse" , "InitMovie" , "InitNetwork" , "InitScintilla" , "InitSound" , "InitSprite" , "Inkey" , "Input" , "InputEvent3D" , "InputRequester" , "InsertElement" , "InsertJSONArray" , "InsertJSONList" , "InsertJSONMap" , "InsertJSONStructure" , "InsertString" , "InsertXMLArray" , "InsertXMLList" , "InsertXMLMap" , "InsertXMLStructure" , "InstructionAddress" , "InstructionString" , "Int" , "IntQ" , "IPAddressField" , "IPAddressGadget" , "IPString" , "IsBillboardGroup" , "IsCamera" , "IsDatabase" , "IsDialog" , "IsDirectory" , "IsEffect" , "IsEntity" , "IsFile" , "IsFingerprint" , "IsFont" , "IsFtp" , "IsGadget" , "IsGadget3D" , "IsImage" , "IsInfinity" , "IsJSON" , "IsLibrary" , "IsLight" , "IsMail" , "IsMaterial" , "IsMenu" , "IsMesh" , "IsMovie" , "IsMusic" , "IsNaN" , "IsNode" , "IsParticleEmitter" , "IsProgram" , "IsRegularExpression" , "IsRuntime" , "IsScreenActive" , "IsSerialPort" , "IsSound" , "IsSound3D" , "IsSprite" , "IsStaticGeometry" , "IsStatusBar" , "IsSysTrayIcon" , "IsText3D" , "IsTexture" , "IsThread" , "IsToolBar" , "IsWindow" , "IsWindow3D" , "IsXML" , "JoystickAxisX" , "JoystickAxisY" , "JoystickAxisZ" , "JoystickButton" , "JoystickName" , "JSONArraySize" , "JSONErrorLine" , "JSONErrorMessage" , "JSONErrorPosition" , "JSONMemberKey" , "JSONMemberValue" , "JSONObjectSize" , "JSONType" , "JSONValue" , "KeyboardInkey" , "KeyboardMode" , "KeyboardPushed" , "KeyboardReleased" , "KillProgram" , "KillThread" , "LastElement" , "LCase" , "Left" , "Len" , "LensFlareEffectColor" , "LibraryFunctionAddress" , "LibraryFunctionName" , "LibraryID" , "LightAttenuation" , "LightDirection" , "LightDirectionX" , "LightDirectionY" , "LightDirectionZ" , "LightID" , "LightLookAt" , "LightPitch" , "LightRoll" , "LightX" , "LightY" , "LightYaw" , "LightZ" , "Line" , "LinearGradient" , "LineXY" , "ListIconGadget" , "ListIndex" , "ListSize" , "ListViewGadget" , "ListViewGadget3D" , "LoadFont" , "LoadImage" , "LoadJSON" , "LoadMesh" , "LoadMovie" , "LoadMusic" , "LoadSound" , "LoadSound3D" , "LoadSprite" , "LoadTexture" , "LoadWorld" , "LoadXML" , "Loc" , "LockMutex" , "Lof" , "Log" , "Log10" , "LSet" , "LTrim" , "MailProgress" , "MainXMLNode" , "MakeIPAddress" , "MapKey" , "MapSize" , "MatchRegularExpression" , "MaterialBlendingMode" , "MaterialCullingMode" , "MaterialFilteringMode" , "MaterialFog" , "MaterialID" , "MaterialShadingMode" , "MaterialShininess" , "MD5FileFingerprint" , "MD5Fingerprint" , "MDIGadget" , "MemorySize" , "MemoryStatus" , "MemoryStringLength" , "MenuBar" , "MenuHeight" , "MenuID" , "MenuItem" , "MenuTitle" , "MergeLists" , "MeshFace" , "MeshID" , "MeshIndex" , "MeshIndexCount" , "MeshPoseCount" , "MeshPoseName" , "MeshRadius" , "MeshVertexColor" , "MeshVertexCount" , "MeshVertexNormal" , "MeshVertexPosition" , "MeshVertexTangent" , "MeshVertexTextureCoordinate" , "MessageRequester" , "Mid" , "Minute" , "Mod" , "Month" , "MouseButton" , "MouseDeltaX" , "MouseDeltaY" , "MouseLocate" , "MousePick" , "MouseRayCast" , "MouseWheel" , "MouseX" , "MouseY" , "MoveBillboard" , "MoveBillboardGroup" , "MoveCamera" , "MoveElement" , "MoveEntity" , "MoveEntityBone" , "MoveLight" , "MoveMemory" , "MoveNode" , "MoveParticleEmitter" , "MoveText3D" , "MoveXMLNode" , "MovieAudio" , "MovieHeight" , "MovieInfo" , "MovieLength" , "MovieSeek" , "MovieStatus" , "MovieWidth" , "MusicVolume" , "NaN" , "NetworkClientEvent" , "NetworkServerEvent" , "NewPrinterPage" , "NextDatabaseDriver" , "NextDatabaseRow" , "NextDirectoryEntry" , "NextElement" , "NextEnvironmentVariable" , "NextFingerprint" , "NextFTPDirectoryEntry" , "NextInstruction" , "NextIPAddress" , "NextJSONMember" , "NextLibraryFunction" , "NextMapElement" , "NextPackEntry" , "NextPreferenceGroup" , "NextPreferenceKey" , "NextRegularExpressionMatch" , "NextScreenMode" , "NextSelectedFilename" , "NextWorldCollision" , "NextXMLAttribute" , "NextXMLNode" , "NodeAnimationKeyFramePitch" , "NodeAnimationKeyFrameRoll" , "NodeAnimationKeyFrameX" , "NodeAnimationKeyFrameY" , "NodeAnimationKeyFrameYaw" , "NodeAnimationKeyFrameZ" , "NodeAnimationStatus" , "NodeFixedYawAxis" , "NodeID" , "NodeLookAt" , "NodePitch" , "NodeRoll" , "NodeX" , "NodeY" , "NodeYaw" , "NodeZ" , "NormalizeMesh" , "NormalX" , "NormalY" , "NormalZ" , "OnErrorCall" , "OnErrorDefault" , "OnErrorExit" , "OnErrorGoto" , "OpenConsole" , "OpenCryptRandom" , "OpenDatabase" , "OpenDatabaseRequester" , "OpenFile" , "OpenFileRequester" , "OpenFTP" , "OpenGadgetList" , "OpenGadgetList3D" , "OpenGLGadget" , "OpenHelp" , "OpenLibrary" , "OpenNetworkConnection" , "OpenPack" , "OpenPreferences" , "OpenScreen" , "OpenSerialPort" , "OpenSubMenu" , "OpenWindow" , "OpenWindow3D" , "OpenWindowedScreen" , "OpenXMLDialog" , "OptionGadget" , "OptionGadget3D" , "OSVersion" , "OutputDepth" , "OutputHeight" , "OutputWidth" , "PackEntryName" , "PackEntrySize" , "PackEntryType" , "PanelGadget" , "PanelGadget3D" , "ParentXMLNode" , "Parse3DScripts" , "ParseDate" , "ParseJSON" , "ParseXML" , "ParticleColorFader" , "ParticleColorRange" , "ParticleEmissionRate" , "ParticleEmitterDirection" , "ParticleEmitterID" , "ParticleEmitterX" , "ParticleEmitterY" , "ParticleEmitterZ" , "ParticleMaterial" , "ParticleSize" , "ParticleSpeedFactor" , "ParticleTimeToLive" , "ParticleVelocity" , "PathRequester" , "PauseAudioCD" , "PauseMovie" , "PauseSound" , "PauseThread" , "PeekA" , "PeekB" , "PeekC" , "PeekD" , "PeekF" , "PeekI" , "PeekL" , "PeekQ" , "PeekS" , "PeekU" , "PeekW" , "PickX" , "PickY" , "PickZ" , "Pitch" , "PlayAudioCD" , "PlayMovie" , "PlayMusic" , "PlaySound" , "PlaySound3D" , "Plot" , "Point" , "PointJoint" , "PointPick" , "PokeA" , "PokeB" , "PokeC" , "PokeD" , "PokeF" , "PokeI" , "PokeL" , "PokeQ" , "PokeS" , "PokeU" , "PokeW" , "PopListPosition" , "PopMapPosition" , "PostEvent" , "Pow" , "PreferenceComment" , "PreferenceGroup" , "PreferenceGroupName" , "PreferenceKeyName" , "PreferenceKeyValue" , "PreviousDatabaseRow" , "PreviousElement" , "PreviousXMLNode" , "Print" , "PrinterOutput" , "PrinterPageHeight" , "PrinterPageWidth" , "PrintN" , "PrintRequester" , "ProgramExitCode" , "ProgramFilename" , "ProgramID" , "ProgramParameter" , "ProgramRunning" , "ProgressBarGadget" , "ProgressBarGadget3D" , "PurifierGranularity" , "PushListPosition" , "PushMapPosition" , "Radian" , "RaiseError" , "Random" , "RandomData" , "RandomizeArray" , "RandomizeList" , "RandomSeed" , "RawKey" , "RayCast" , "RayCollide" , "RayPick" , "ReadAsciiCharacter" , "ReadByte" , "ReadCharacter" , "ReadConsoleData" , "ReadData" , "ReadDouble" , "ReadFile" , "ReadFloat" , "ReadInteger" , "ReadLong" , "ReadPreferenceDouble" , "ReadPreferenceFloat" , "ReadPreferenceInteger" , "ReadPreferenceLong" , "ReadPreferenceQuad" , "ReadPreferenceString" , "ReadProgramData" , "ReadProgramError" , "ReadProgramString" , "ReadQuad" , "ReadSerialPortData" , "ReadString" , "ReadStringFormat" , "ReadUnicodeCharacter" , "ReadWord" , "ReAllocateMemory" , "ReceiveFTPFile" , "ReceiveHTTPFile" , "ReceiveNetworkData" , "Red" , "RegularExpressionError" , "RegularExpressionGroup" , "RegularExpressionGroupLength" , "RegularExpressionGroupPosition" , "RegularExpressionMatchLength" , "RegularExpressionMatchPosition" , "RegularExpressionMatchString" , "RegularExpressionNamedGroup" , "RegularExpressionNamedGroupLength" , "RegularExpressionNamedGroupPosition" , "ReleaseMouse" , "ReloadMaterial" , "RemoveBillboard" , "RemoveEnvironmentVariable" , "RemoveGadgetColumn" , "RemoveGadgetItem" , "RemoveGadgetItem3D" , "RemoveJSONElement" , "RemoveJSONMember" , "RemoveKeyboardShortcut" , "RemoveMailRecipient" , "RemoveMaterialLayer" , "RemovePackFile" , "RemovePreferenceGroup" , "RemovePreferenceKey" , "RemoveString" , "RemoveSysTrayIcon" , "RemoveWindowTimer" , "RemoveXMLAttribute" , "RenameFile" , "RenameFTPFile" , "RenderWorld" , "ReplaceRegularExpression" , "ReplaceString" , "ResetGradientColors" , "ResetList" , "ResetMap" , "ResetMaterial" , "ResetProfiler" , "ResizeBillboard" , "ResizeGadget" , "ResizeGadget3D" , "ResizeImage" , "ResizeJSONElements" , "ResizeMovie" , "ResizeParticleEmitter" , "ResizeWindow" , "ResizeWindow3D" , "ResolveXMLAttributeName" , "ResolveXMLNodeName" , "ResumeAudioCD" , "ResumeMovie" , "ResumeSound" , "ResumeThread" , "ReverseString" , "RGB" , "RGBA" , "RibbonEffectColor" , "RibbonEffectWidth" , "Right" , "Roll" , "RootXMLNode" , "RotateBillboardGroup" , "RotateCamera" , "RotateEntity" , "RotateEntityBone" , "RotateLight" , "RotateMaterial" , "RotateNode" , "RotateSprite" , "Round" , "RoundBox" , "RSet" , "RTrim" , "RunProgram" , "SaveDebugOutput" , "SaveFileRequester" , "SaveImage" , "SaveJSON" , "SaveMesh" , "SaveRenderTexture" , "SaveSprite" , "SaveTerrain" , "SaveXML" , "ScaleEntity" , "ScaleMaterial" , "ScaleNode" , "ScaleText3D" , "ScintillaGadget" , "ScintillaSendMessage" , "ScreenDepth" , "ScreenHeight" , "ScreenID" , "ScreenModeDepth" , "ScreenModeHeight" , "ScreenModeRefreshRate" , "ScreenModeWidth" , "ScreenOutput" , "ScreenWidth" , "ScrollAreaGadget" , "ScrollAreaGadget3D" , "ScrollBarGadget" , "ScrollBarGadget3D" , "ScrollMaterial" , "Second" , "SecondWorldCollisionEntity" , "SelectedFilePattern" , "SelectedFontColor" , "SelectedFontName" , "SelectedFontSize" , "SelectedFontStyle" , "SelectElement" , "SendFTPFile" , "SendMail" , "SendNetworkData" , "SendNetworkString" , "SerialPortError" , "SerialPortID" , "SerialPortTimeouts" , "ServerID" , "SetActiveGadget" , "SetActiveGadget3D" , "SetActiveWindow" , "SetActiveWindow3D" , "SetClipboardImage" , "SetClipboardText" , "SetCurrentDirectory" , "SetDatabaseBlob" , "SetDragCallback" , "SetDropCallback" , "SetEntityAnimationLength" , "SetEntityAnimationTime" , "SetEntityAnimationWeight" , "SetEntityAttribute" , "SetEntityCollisionFilter" , "SetEntityMaterial" , "SetEnvironmentVariable" , "SetFileAttributes" , "SetFileDate" , "SetFrameRate" , "SetFTPDirectory" , "SetGadgetAttribute" , "SetGadgetAttribute3D" , "SetGadgetColor" , "SetGadgetData" , "SetGadgetData3D" , "SetGadgetFont" , "SetGadgetItemAttribute" , "SetGadgetItemColor" , "SetGadgetItemData" , "SetGadgetItemData3D" , "SetGadgetItemImage" , "SetGadgetItemState" , "SetGadgetItemState3D" , "SetGadgetItemText" , "SetGadgetItemText3D" , "SetGadgetState" , "SetGadgetState3D" , "SetGadgetText" , "SetGadgetText3D" , "SetGUITheme3D" , "SetJointAttribute" , "SetJSONArray" , "SetJSONBoolean" , "SetJSONDouble" , "SetJSONFloat" , "SetJSONInteger" , "SetJSONNull" , "SetJSONObject" , "SetJSONQuad" , "SetJSONString" , "SetLightColor" , "SetMailAttribute" , "SetMailBody" , "SetMaterialAttribute" , "SetMaterialColor" , "SetMenuItemState" , "SetMenuItemText" , "SetMenuTitleText" , "SetMeshData" , "SetMeshMaterial" , "SetMusicPosition" , "SetNodeAnimationKeyFramePosition" , "SetNodeAnimationKeyFrameRotation" , "SetNodeAnimationKeyFrameScale" , "SetNodeAnimationLength" , "SetNodeAnimationTime" , "SetNodeAnimationWeight" , "SetOrientation" , "SetOrigin" , "SetRenderQueue" , "SetRuntimeDouble" , "SetRuntimeInteger" , "SetRuntimeString" , "SetSerialPortStatus" , "SetSoundFrequency" , "SetSoundPosition" , "SetTerrainTileHeightAtPoint" , "SetTerrainTileLayerBlend" , "SetToolBarButtonState" , "SetupTerrains" , "SetURLPart" , "SetWindowCallback" , "SetWindowColor" , "SetWindowData" , "SetWindowState" , "SetWindowTitle" , "SetWindowTitle3D" , "SetXMLAttribute" , "SetXMLEncoding" , "SetXMLNodeName" , "SetXMLNodeOffset" , "SetXMLNodeText" , "SetXMLStandalone" , "SHA1FileFingerprint" , "SHA1Fingerprint" , "ShortcutGadget" , "ShowAssemblyViewer" , "ShowCallstack" , "ShowDebugOutput" , "ShowGUI" , "ShowLibraryViewer" , "ShowMemoryViewer" , "ShowProfiler" , "ShowVariableViewer" , "ShowWatchlist" , "Sign" , "SignalSemaphore" , "Sin" , "SinH" , "SkyBox" , "SkyDome" , "SliderJoint" , "SmartWindowRefresh" , "SortArray" , "SortList" , "SortStructuredArray" , "SortStructuredList" , "SoundCone3D" , "SoundID3D" , "SoundLength" , "SoundListenerLocate" , "SoundPan" , "SoundRange3D" , "SoundStatus" , "SoundVolume" , "SoundVolume3D" , "Space" , "SpinGadget" , "SpinGadget3D" , "SplinePointX" , "SplinePointY" , "SplinePointZ" , "SplineX" , "SplineY" , "SplineZ" , "SplitList" , "SplitterGadget" , "SpotLightRange" , "SpriteBlendingMode" , "SpriteCollision" , "SpriteDepth" , "SpriteHeight" , "SpriteID" , "SpriteOutput" , "SpritePixelCollision" , "SpriteQuality" , "SpriteWidth" , "Sqr" , "StartAESCipher" , "StartDrawing" , "StartEntityAnimation" , "StartNodeAnimation" , "StartPrinting" , "StartProfiler" , "StatusBarHeight" , "StatusBarID" , "StatusBarImage" , "StatusBarProgress" , "StatusBarText" , "StickyWindow" , "StopAudioCD" , "StopDrawing" , "StopEntityAnimation" , "StopMovie" , "StopMusic" , "StopNodeAnimation" , "StopPrinting" , "StopProfiler" , "StopSound" , "StopSound3D" , "Str" , "StrD" , "StrF" , "StringByteLength" , "StringField" , "StringGadget" , "StringGadget3D" , "StrU" , "SubMeshCount" , "Sun" , "SwapElements" , "SwitchCamera" , "SysTrayIconToolTip" , "Tan" , "TanH" , "TerrainHeight" , "TerrainLocate" , "TerrainMousePick" , "TerrainPhysicBody" , "TerrainRenderMode" , "TerrainTileHeightAtPosition" , "TerrainTileLayerMapSize" , "TerrainTilePointX" , "TerrainTilePointY" , "TerrainTileSize" , "Text3DAlignment" , "Text3DCaption" , "Text3DColor" , "Text3DID" , "TextGadget" , "TextGadget3D" , "TextHeight" , "TextureHeight" , "TextureID" , "TextureOutput" , "TextureWidth" , "TextWidth" , "ThreadID" , "ThreadPriority" , "ToolBarHeight" , "ToolBarID" , "ToolBarImageButton" , "ToolBarSeparator" , "ToolBarStandardButton" , "ToolBarToolTip" , "TrackBarGadget" , "TransformMesh" , "TransformSprite" , "TransparentSpriteColor" , "TreeGadget" , "Trim" , "TruncateFile" , "TryLockMutex" , "TrySemaphore" , "UCase" , "UnbindEvent" , "UnbindGadgetEvent" , "UnbindMenuEvent" , "UnclipOutput" , "UncompressMemory" , "UncompressPackFile" , "UncompressPackMemory" , "UnlockMutex" , "UpdateEntityAnimation" , "UpdateMesh" , "UpdateMeshBoundingBox" , "UpdateRenderTexture" , "UpdateSplinePoint" , "UpdateTerrain" , "UpdateTerrainTileLayerBlend" , "UpdateVertexPoseReference" , "URLDecoder" , "URLEncoder" , "UseAudioCD" , "UseBriefLZPacker" , "UseFLACSoundDecoder" , "UseGadgetList" , "UseJCALG1Packer" , "UseJPEG2000ImageDecoder" , "UseJPEG2000ImageEncoder" , "UseJPEGImageDecoder" , "UseJPEGImageEncoder" , "UseLZMAPacker" , "UseODBCDatabase" , "UseOGGSoundDecoder" , "UsePNGImageDecoder" , "UsePNGImageEncoder" , "UsePostgreSQLDatabase" , "UserName" , "UseSQLiteDatabase" , "UseTGAImageDecoder" , "UseTIFFImageDecoder" , "UseZipPacker" , "Val" , "ValD" , "ValF" , "VertexPoseReferenceCount" , "WaitProgram" , "WaitSemaphore" , "WaitThread" , "WaitWindowEvent" , "WaterColor" , "WaterHeight" , "WebGadget" , "WebGadgetPath" , "WindowBounds" , "WindowEvent" , "WindowEvent3D" , "WindowHeight" , "WindowHeight3D" , "WindowID" , "WindowID3D" , "WindowMouseX" , "WindowMouseY" , "WindowOutput" , "WindowWidth" , "WindowWidth3D" , "WindowX" , "WindowX3D" , "WindowY" , "WindowY3D" , "WorldCollisionAppliedImpulse" , "WorldCollisionContact" , "WorldCollisionNormal" , "WorldDebug" , "WorldGravity" , "WorldShadows" , "WriteAsciiCharacter" , "WriteByte" , "WriteCharacter" , "WriteConsoleData" , "WriteData" , "WriteDouble" , "WriteFloat" , "WriteInteger" , "WriteLong" , "WritePreferenceDouble" , "WritePreferenceFloat" , "WritePreferenceInteger" , "WritePreferenceLong" , "WritePreferenceQuad" , "WritePreferenceString" , "WriteProgramData" , "WriteProgramString" , "WriteProgramStringN" , "WriteQuad" , "WriteSerialPortData" , "WriteSerialPortString" , "WriteString" , "WriteStringFormat" , "WriteStringN" , "WriteUnicodeCharacter" , "WriteWord" , "XMLAttributeName" , "XMLAttributeValue" , "XMLChildCount" , "XMLError" , "XMLErrorLine" , "XMLErrorPosition" , "XMLNodeFromID" , "XMLNodeFromPath" , "XMLNodePath" , "XMLNodeType" , "XMLStatus" , "Yaw" , "Year" , "ZoomSprite" ]) , rAttribute = FunctionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = False , keywordDelims = Data.Set.fromList "\t\n !%&()*+,-./:;<=>?[\\]^{|}~" } (makeWordSet False [ "CallDebugger" , "Debug" ]) , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\#+[a-zA-Z_\\x7f-\\xff][a-zA-Z0-9_\\x7f-\\xff]*" , reCompiled = Just (compileRegex True "\\#+[a-zA-Z_\\x7f-\\xff][a-zA-Z0-9_\\x7f-\\xff]*") , reCaseSensitive = True } , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Float , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Int , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '"' , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "PureBasic" , "String" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\s*;+\\s*BEGIN.*$" , reCompiled = Just (compileRegex True "\\s*;+\\s*BEGIN.*$") , reCaseSensitive = True } , rAttribute = RegionMarkerTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\s*;+\\s*END.*$" , reCompiled = Just (compileRegex True "\\s*;+\\s*END.*$") , reCaseSensitive = True } , rAttribute = RegionMarkerTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Just 0 , rContextSwitch = [] } , Rule { rMatcher = DetectChar ';' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "PureBasic" , "Comment1" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "String" , Context { cName = "String" , cSyntax = "PureBasic" , cRules = [ Rule { rMatcher = DetectChar '"' , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = StringTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) ] , sAuthor = "Alexander Clay (Tuireann@EpicBasic.org);Sven Langenkamp (ace@kylixforum.de)" , sVersion = "6" , sLicense = "LGPL" , sExtensions = [ "*.pb" , "*.pbi" ] , sStartingContext = "Normal" }