' rev 10/06/2023 ' rajout Amps par minutes ' nota COM5 à 19200 bds avec RN41 distant 'Declare Sub Amps_NowClick(Sender as QLabel) ' rev 17/01/2019 ' rev 17/01/2019 reperes de modif at @@@ ' was My_QGridEx_190117.inc ' ligne 70,71 ' ligne 402 ' ligne 438 ' ligne 556 ' ligne 1549 '***************************************************************************************** ' QGridEx Copyright 2007 Michael Zito ' Released under the LGPL ' Build: 2007.04.23 ' 'Properties: ' MinDataRow : Function that returns the lowest Row Containing Data ' MinDataCol : Function that returns the lowest Column Containing Data ' MaxDataRow : Function that returns the highest Row Containing Data ' MaxDataCol : Function that returns the highest Column Containing Data ' CurrFile : Holds the name of the currently open file ' EnterData: Determines cursor movement on Enter: qgByRow or qgByCol (<-Default) ' IsChanged: BOOLEAN, Set to 1 (True) in OnSetEditText Event ' SelRange: UDT that holds coordinates of selected range ' SelColor: Color the select rectangle is drawn in ' SelMode: BOOLEAN, True = goRangeSelect, False = goEditing ' SelExists: BOOLEAN, True = A Range is Selected, False = No Range selected ' EditColLabels: BOOLEAN, True = Row 0 Editing Enabled, False = Row 0 Editing Disabled ' 'Methods: ' Initialize: Clears All Data, Initializes Arrays, Labels Rows and Columns ' LoadData: Loads Data from Tab Delimited File into Grid ' SaveData: Saves current Grid data as Tab Delimited File ' Returns True if User presses OK, False if User Cancels ' PrintGrid: Prints all data in the grid with or without gridlines ' RSet: Right alignment of cell contents ' CSet: Center Alignment of cell contents ' LSet: Left Alignment of cell contents ' Justify: LSets Text, RSets numbers, CSets ColHeaders ' ToggleSelMode: Toggles between SelectRange and Editing Modes ' ToggleEditTopRow: Toggles Row 0 editing on/off ' rngCut: Cuts Selected Cells to QGridEx Clipboard ' rngCopy: Copies Selected Cells to QGridEx Clipboard ' rngPaste: Pastes Selected Cells From QGridEx Clipboard ' rngDelete: Deletes Selected Cells ' rngSelAll: Selects All Data in the QGridEx ' rngFillDown: Fills selected rows with value in .tRow of SelRange ' rngFillRight: Fills selected cols with value in .lCol of SelRange ' rngFillSeries: Opens a dialog, fill rows or cols with linear or ' exponential series ' Sort: Opens a dialog, sorts strings or numbers in ascending or ' descending order. Chooses approprite sort based on 1st ' value in selected column ' 'Events Defined: ' ***** Range Selection Works! Code is in the DrawCell Event ***** ' DrawCell(c AS Integer, r As Integer,State As Integer, Rect AS QRect): ' Draws selection border and sets Row and Col Coordinates of SelRange UDT ' OnKeyDown (Key AS WORD, Shift AS INTEGER): ' Key Handling Routines ' OnSelectCell (c AS INTEGER, r AS INTEGER, flag AS INTEGER): ' Stores copy of most recently selected cell data for Undo w/ESC ' OnSetEditText (c AS INTEGER, r AS INTEGER, s AS STRING): ' Updates TopDataRow() Array ' 'Popup Menu: ' Cut, Copy, Paste, Delete, Select All ' Fill Down, Fill Right, Fill Series, Sort ' Toggle Select mode ' Toggle Editing of Column Labels ' '***************************************************************************************** Declare Sub Visu_TrameClick(Sender as QCheckBox) '----- Win API Declares DECLARE FUNCTION QG_SetFocus LIB "user32" ALIAS "SetFocus"(hwnd AS LONG) AS LONG '----- Constant Declarations '@@@ CONST qgMaxCols =24 '25 'Max Allowable is 255 (BYTE) CONST qgMaxRows = 6 '500 'Max Allowable is 65535 (WORD) CONST ChauffDataName ="D:\RapidQ\_BT_Edfinfo\Datas\ChauffProgrData.tab" CONST qgByRow = 0 'Data Entry Modes CONST qgByCol = 1 '----- UDTs Type typSelRange lCol As Integer tRow As Integer rCol AS Integer bRow As Integer End Type '----- Begin Object Definition *********************************************************** TYPE QGridEx EXTENDS QStringGrid PRIVATE: TempCell AS STRING * 100 'Remembers Current Cell Contents Missing AS STRING SelAllActive As Byte ' PUBLIC: '--- PopUp Menu Objects QG_PopUpMenu As QPopUpMenu mnuCut AS QMenuItem mnuCopy AS QMenuItem mnuPaste AS QMenuItem mnuDelete AS QMenuItem mnuSep_1 As QMenuItem mnuSelectAll As QMenuItem mnuSep_2 As QMenuItem mnuSort As QMenuItem mnuFillDown as QMenuItem mnuFillRight As QMenuItem mnuFillSeries As QMenuItem mnuSep_3 As QMenuItem mnuSelectMode As QMenuItem mnuEditRow0 As QMenuItem '--- Sort Dialog Objects QG_dlgSortData as QForm dlgSort_lblSortBy as QLabel dlgSort_cmbSortByCol as QComboBox dlgSort_grpType as QGroupBox dlgSort_rdoAscend as QRadioButton dlgSort_rdoDescend as QRadioButton dlgSort_btnOK as QButton dlgSort_btnCancel as QButton '--- Fill Series Dialog Objects QG_dlgFillSeries as QForm dlgFill_grpSeries as QGroupBox dlgFill_rdoColumns as QRadioButton dlgFill_rdoRows as QRadioButton dlgFill_grpType as QGroupBox dlgFill_rdoLinear as QRadioButton dlgFill_rdoExp as QRadioButton dlgFill_lblStep as QLabel dlgFill_txtStep as QEdit dlgFill_lblEnd as QLabel dlgFill_txtEnd as QEdit dlgFill_btnOK as QButton dlgFill_btnCancel as QButton PUBLIC: TopDataRow(qgMaxCols) AS Word 'Array holding max row w/data in each Col UsePopup AS LONG PROPERTY SET Set_Popup dlgSaveQG AS QSaveDialog dlgOpenQG AS QOpenDialog CurrFile AS STRING IsChanged As Byte SelRange As typSelRange 'Selected Range Coordinates SelExists As Byte SelMode As Byte SelColor As Integer EditColLabels AS Byte EnterData As Byte '--------------------------------------------------------------------------- '--------------------------- Functions ------------------------------------- '--------------------------------------------------------------------------- FUNCTION RSet(s As String, c As Integer) As String 'Mimics right justify by left paddding string w/spaces Dim p As Integer With QGridEx s = LTrim$(RTrim$(s)) If s <> "" Then p = (.ColWidths(c) -.TextWidth(s))\.TextWidth(" ") -_ 0.5 * .TextWidth(" ") 'leave some room on right s = Space$(p) + s Result = s End If End With End Function '--------------------------------------------------------------------------- FUNCTION CSet(s As String, c As Integer) As String 'Mimics center justify by paddding string w/spaces Dim p As Integer With QGridEx s = Ltrim$(RTrim$(s)) If s <> "" Then p = 0.5 * (.ColWidths(c) - .TextWidth(s)) \ .TextWidth(" ") s = Space$(p) + s Result = s End If End With End Function '--------------------------------------------------------------------------- FUNCTION LSet(s As String) As String 'Trims all spaces, Left justify is default Result = RTrim$(LTrim$(s)) End Function '--------------------------------------------------------------------------- FUNCTION IsNumeric(s As String) As Integer 'Tests if a string is a valid number s = Rtrim$(Ltrim$(s)) With QGridEx If Val(s) <> 0 Or Left$(s,1) = "0" Then Result = 1 Else Result = 0 End If End With End Function '--------------------------------------------------------------------------- Function Justify (s As String, c As Integer, r As Integer) As String With QGridEx s = LTrim$(RTrim$(s)) Select Case r Case 0 'Top Row, Center Result = .CSet(Left$(s,13),c) Case Else Select Case .IsNumeric(s) Case 1 Result = .RSet(s,c) 'Numbers Right Case 0 Result = .LSet(s) 'Text Left End Select End Select End With End Function '--------------------------------------------------------------------------- '---------------------- Property Functions --------------------------------- '--------------------------------------------------------------------------- FUNCTION MaxDataRow () AS INTEGER 'Reads thru the QGridEx.TopDataRow Array 'Returns the highest single row with data DIM i AS INTEGER 'Loop counters... DIM x AS INTEGER WITH QGridEx x=0 'Clear exisitng value FOR i = 1 TO qgMaxCols IF .TopDataRow(i) > x THEN x = .TopDataRow(i) END IF NEXT i Result = x END WITH END FUNCTION '--------------------------------------------------------------------------- FUNCTION MaxDataCol () AS INTEGER 'Reads thru the QGridEx.TopDataRow Array 'Returns the highest single column with data DIM i AS INTEGER 'Loop counters... DIM x AS INTEGER WITH QGridEx x=0 'Clear exisitng value FOR i = 1 TO qgMaxCols IF .TopDataRow(i) <> 0 THEN x = i END IF NEXT i Result = x END WITH END FUNCTION '--------------------------------------------------------------------------- FUNCTION MinDataRow () AS INTEGER 'Reads thru the QGridEx.TopDataRow Array 'Returns the lowest single row with data DIM i AS INTEGER 'Loop counters... DIM j As Integer Dim x As Integer WITH QGridEx x = .MaxDataRow FOR i = 1 TO qgMaxCols If .TopDataRow(i) > 0 Then For j = 1 to .TopDataRow(i) IF RTrim$(LTrim$(.Cell(i,j))) <> "" THEN If j < x Then x = j END IF Next j End If NEXT i If x > 0 Then Result = x Else Result = 0 END WITH END FUNCTION '--------------------------------------------------------------------------- FUNCTION MinDataCol () AS INTEGER 'Reads thru the QGridEx.TopDataRow Array 'Returns the lowest single column with data DIM i AS INTEGER 'Loop counters... WITH QGridEx FOR i = 1 TO qgMaxCols IF .TopDataRow(i) <> 0 THEN Result = i Exit Function END IF NEXT i Result = 0 END WITH END FUNCTION '--------------------------------------------------------------------------- ' Sub UpdateTopDataRow(r As Integer) ' 'r = old MaxDataRow sent from sort routine ' ' Dim i As Integer ' Dim j As Integer ' Dim c As Integer ' ' With QGridEx ' c = .MaxDataCol ' For i = 1 to c ' For j = r to 0 Step -1 ' If Ltrim$(RTrim$(.Cell(i,j))) <> "" Then ' .TopDataRow(i) = j ' Exit For ' End If ' Next ' Next ' End With ' ' End Sub '--------------------------------------------------------------------------- '---------------------------- METHOD SUBs ---------------------------------- '--------------------------------------------------------------------------- SUB Initialize DIM i AS INTEGER 'Loop counters... DIM j AS INTEGER WITH QGridEx IF .MaxDataRow > 0 THEN 'If data is present DIM NumRows AS INTEGER DIM NumCols AS INTEGER NumCols = .MaxDataCol 'Call Fn once outside loop for speed NumRows = .MaxDataRow FOR i = 1 TO NumCols 'For each column with data FOR j = 1 to NumRows 'For each row in those columns .Cell(i,j) = "" 'Clear all data NEXT j NEXT i END IF FOR i = 1 TO qgMaxCols 'Initialize TopDataRow Array .TopDataRow(i) = 0 NEXT i .ColCount = qgMaxCols+1 'Setup the Data Grid .RowCount = qgMaxRows+1 .LeftCol = 1 .TopRow = 1 FOR i = 1 TO qgMaxRows 'Label rows w/numbers .Cell(0,i) = .RSet(STR$(i),0) 'Center the label NEXT i .Cell(0,0) = .Rset("Case",0) FOR i = 1 TO qgMaxCols 'Label columns w/letters ' .Cell(i,0) = .CSet(" "+STR$(i)+" ",i) ' @@@ de 0 à 23 .Cell(i,0) = .CSet(" "+STR$(i-1)+" ",i) ' .Cell(i,0) = .CSet("Var " + STR$(i),i) ' IF i <= 26 THEN 'using alpha ASCII codes ' .Cell(i,0) =.CSet(CHR$(i+64),i) 'A - Z ' ELSE 'AA, AB, .... ZZ ' .Cell(i,0) = .CSet(CHR$(INT(i/26.1)+64)+ _ 'Center the label ' CHR$(i+64-INT(i/26.1)*26),i) ' END IF 'Center the label NEXT i .CurrFile = "NewData.stz" .Font.Name = "Arial" .EnterData = qgByCol .TempCell = "" .SelMode = 0 .SelAllActive = 0 .IsChanged = 0 .AddOptions (10, 13, 14, 11, 5, 4)', 7, 6) .Col=1:.Row=1 QG_SetFocus(.Handle) '@@@ ' My Own init 'Label columns w/letters .Cell(0,1) = "Cumulus" .Cell(0,2) = "Salon " .Cell(0,3) = "SDB " .Cell(0,4) = "CH3-CH2" .Cell(0,5) = "CH1 " .Cell(0,6) = "Codage " END WITH END SUB '--------------------------------------------------------------------------- FUNCTION LoadData() As Integer DIM i AS INTEGER 'Loop counters... DIM j AS INTEGER DIM File AS QFileStream 'Open the file WITH QGridEx qsShowOpen: ' .dlgOpenQG.Caption = "Open File" .dlgOpenQG.Filter = "Tab Files|*.tab|All Files|*.*" .dlgOpenQG.FilterIndex = 1 'Use Tab Files as our default '@@@ 17-01 .dlgOpenQG.Caption = "Open file : "+ChauffDataName ' D:\RapidQ\_BT_Edfinfo\Datas\ChauffProgrData.tab .dlgOpenQG.FileName=ChauffDataName IF .dlgOpenQG.Execute = 1 THEN 'User pressed OK IF FileExists(.dlgOpenQG.FileName) THEN 'Check if file is there .Initialize DIM NumRows AS INTEGER File.Open(.dlgOpenQG.FileName, 0) 'fmOpenRead NumRows = File.LineCount .LoadFromStream (File, 0, 1, NumRows) File.Close FOR i = 1 to qgMaxCols .Cell(i,0) = .CSet(.Cell(i,0),i) Next FOR i = 1 to qgMaxCols 'Initialize TopDataRow Array FOR j = 1 TO NumRows IF .Cell(i,j) <> "" THEN .Cell(i,j) = .Justify(.Cell(i,j),i,j) .TopDataRow(i) = j END IF NEXT j NEXT i .TempCell = .Cell(1,1) 'Store first cell's value .CurrFile = .dlgOpenQG.FileName 'Set the Current Filename .IsChanged = 0 .LoadData = 1 ELSE 'File doesn't exist IF MessageDlg(.dlgOpenQG.FileName + " does not exist", 0, 4, 0) = 1 THEN GoTo qsShowOpen END IF END IF .LoadData = 0 END IF END WITH 'QGridEx END Function '--------------------------------------------------------------------------- FUNCTION SaveData (SaveAs AS BYTE) AS INTEGER DIM File AS QFileStream IF SaveAs = 1 THEN GOTO qsShowSave WITH QGridEx IF Right$(.CurrFile,11) <> "NewData.tab" THEN 'The file has been saved before .dlgSaveQG.FileName = .CurrFile File.Open(.dlgSaveQG.FileName, 65535) '65535 = fmCreate .SaveToStream (File, 0, 1, .MaxDataRow) 'save the data File.Close Result = 1 'Return Success .IsChanged = 0 EXIT FUNCTION END IF qsShowSave: IF SaveAs = 1 THEN .dlgSaveQG.Caption = "Save Data As" ELSE .dlgSaveQG.Caption = "Save Data" END IF .dlgSaveQG.FileName = .CurrFile .dlgSaveQG.Filter = "Tab Files|*.tab|All Files|*.*" .dlgSaveQG.FilterIndex = 1 'Use Tab Files as our default IF .dlgSaveQG.Execute = 1 AND LEN(.dlgSaveQG.FileName) <> 0 THEN IF INSTR(UCASE$(.dlgSaveQG.FileName), ".TAB") = 0 THEN .dlgSaveQG.FileName = .dlgSaveQG.FileName + ".tab" END IF File.Open(.dlgSaveQG.FileName, 65535) '65535 = fmCreate .SaveToStream (File, 0, 1, .MaxDataRow) 'save the data File.Close .CurrFile = .dlgSaveQG.FileName Result = 1 'Return Success .IsChanged = 0 ELSE Result = 0 'Return Cancel END IF END WITH 'QGridEx END FUNCTION '--------------------------------------------------------------------------- Sub PrintGrid(Prn AS INTEGER, Orient AS INTEGER, Copies AS INTEGER, doGrid As Byte) DefInt i,j,k,r,c,n Dim MaxR As Integer Dim MaxC As Integer Dim StartRow As Integer Dim EndRow As Integer Dim StartCol As Integer Dim EndCol As Integer Dim ColsPerPage As Byte Dim RowsPerPage As Byte Dim hSpc As Byte Dim Temp As String Dim Filler As String Dim Buff As String * 13 Dim RowLabelBuff As String * 5 Dim Sep As String Dim Mrgn As Integer Dim s As String With QGridEx If .MaxDataRow = 0 Then Exit Sub 'Don't print non-existent data PRINTER.PrinterIndex = Prn If Printer.Capabilities.Orientation = 1 Then PRINTER.Orientation = Orient If Printer.Capabilities.Copies = 1 Then PRINTER.Copies = Copies Mrgn = 100 MaxR = .MaxDataRow MaxC = .MaxDataCol If Orient = poPortrait Then ColsPerPage = 6 RowsPerPage = 55 Else ColsPerPage = 8 RowsPerPage = 44 End If If ColsPerPage > MaxC Then ColsPerPage = MaxC If RowsPerPage > MaxR Then RowsPerPage = MaxR Printer.Font.Name = "Courier New" Printer.Font.Size = 10 Printer.Font.AddStyles (fsBold) hSpc = Printer.TextHeight(" ") If doGrid = 1 Then Sep = "|" Printer.Font.AddStyles (FsUnderline) Else Sep = " " Printer.Font.DelStyles (FsUnderline) End If Printer.BeginDoc 'Start the print job For i = 1 to Ceil(MaxC/ColsPerPage) If i = 1 Then StartCol = 1 : EndCol = ColsPerPage Else StartCol = StartCol + ColsPerPage EndCol = StartCol + ColsPerPage If StartCol >= MaxC Then StartCol = MaxC If EndCol >= MaxC Then EndCol = MaxC End If For j = 1 to Ceil(MaxR/RowsPerPage) If j = 1 Then StartRow = 1 : EndRow = RowsPerPage Else StartRow = StartRow + RowsPerPage EndRow = StartRow + RowsPerPage If StartRow >= MaxR Then StartRow = MaxR If EndRow >= MaxR Then EndRow = MaxR End If If StartRow <> 1 Or StartCol <> 1 Then Printer.NewPage s = "Data Listing For: " + .CurrFile 'Header on each page Printer.TextOut(Mrgn, hSpc, s, 0, -1) 'Print the Header s = "" 'Labels on Each Page Temp =Rtrim$(LTrim$(.Cell(0,0))) 'Row Label Filler = Space$(Len(RowLabelBuff) - Len(Temp)) RowLabelBuff = Filler + Temp s = s + Sep + RowLabelBuff + Sep For k = StartCol to EndCol Temp =Rtrim$(LTrim$(.Cell(k,0))) 'Col Labels Filler = Space$(Len(Buff) - Len(Temp)) Buff = Filler + Temp s = s + Buff + Sep Next k Printer.TextOut(Mrgn, 3*hSpc, s, 0, -1) 'Print Col Header n=0 'Row Counter For r = StartRow to EndRow 'For each row s = "" Temp =Rtrim$(LTrim$(.Cell(0,r))) 'Add Row Label Filler = Space$(Len(RowLabelBuff) - Len(Temp)) RowLabelBuff = Filler + Temp s = s + Sep + RowLabelBuff + Sep For c = StartCol to EndCol 'For Each Col Temp =Rtrim$(LTrim$(.Cell(c,r))) 'Add Cell Data Filler = Space$(Len(Buff) - Len(Temp)) Buff = Filler + Temp s = s + Buff + Sep Next c n = n + 1 'Increment Row Ptr Printer.TextOut(Mrgn, 3*hSpc + hSpc*n , s, 0, -1) 'Print The Row Next r Next j'Rows 'New page w/same cols Next i'Cols 'New set of cols Printer.EndDoc 'Send the print job End With End Sub '--------------------------------------------------------------------------- Sub strSort(c As Integer, Ascend As Byte) 'Sorts the entire grid based on data in column "c" (for string data) 'Original Code by By OvalX, 2003. Adapted to QGridEx by Michael Zito, 2007 With QGridEx DIM J AS INTEGER DIM MemStr AS QMemoryStream DIM NumRows AS INTEGER NumRows = .MaxDataRow DIM SortArray(1 TO NumRows) AS STRING IF c > 1 THEN .SwapCols (1, c) 'Put Sort Col 1st .SaveToStream (MemStr,1,1,NumRows) 'Transfer data MemStr.Position = 0 FOR J = 1 TO NumRows SortArray(J) = MemStr.ReadLine & "\n" NEXT J MemStr.CLOSE IF Ascend = 1 THEN 'Do the sort QUICKSORT(SortArray(1), SortArray(NumRows), Ascend) ELSEIF Ascend = 0 THEN QUICKSORT(SortArray(1), SortArray(NumRows), Descend) END IF FOR J = 1 TO NumRows 'Transfer data back MemStr.WriteStr(SortArray(J), LEN(SortArray(J))) NEXT J MemStr.Position = 0 .LoadFromStream(MemStr, 1, 1, NumRows) MemStr.CLOSE IF c > 1 THEN .SwapCols (1, c) 'Put sort col back ' .UpDateTopDataRow(NumRows) End With END Sub '--------------------------------------------------------------------------- SUB numSort (StartEl As Integer, NumEls As Integer, c As Integer, Ascend As Byte) 'Sorts the entire grid based on data in column "c" (for numerical data) 'Based on Quicksort as described in BASIC Techniques and Utilities by Ethan Winer 'Adapted to QGridEx with MemoryStream Stack by Michael Zito, 2007 With QGridEx DIM i AS INTEGER DIM j AS INTEGER DIM NumRows As Integer DIM QStack As QMemoryStream DIM Temp As Double DIM First As Integer DIM Last As Integer NumRows = .MaxDataRow 'need this for UpdateTopDataRow First = StartEl 'initialize work variables Last = StartEl + NumEls - 1 QStack.Position = 0 If First >= Last Then Exit Sub 'Nothing to do! DIM Array(StartEl to NumEls) As Double For i = StartEl to NumEls 'Initialize array Array(i) = Val(.Cell(c,i)) Next Select Case Ascend Case 1 'Ascending DO DO Temp = Array((Last + First) \ 2) 'seek midpoint I = First J = Last DO WHILE Array(I) < Temp I = I + 1 WEND WHILE Array(J) > Temp J = J - 1 WEND IF I > J THEN EXIT DO IF I < J THEN SWAP Array(I), Array(J) .SwapRows(i,j) End If I = I + 1 J = J - 1 LOOP UNTIL I > J IF I < Last THEN QStack.WriteNum(i,4) 'Push i QStack.WriteNum(Last,4) 'Push Last END IF Last = J LOOP UNTIL First >= Last IF QStack.Position = 0 THEN EXIT DO 'Done QStack.Position = QStack.Position - 8 'Get last 2 items First = QStack.ReadNum(4) 'Pop First Last = QStack.ReadNum(4) 'Pop Last QStack.Position = QStack.Position - 8 'Reset ptr LOOP Case 0 'Descending DO DO Temp = Array((Last + First) \ 2) 'seek midpoint I = First J = Last DO WHILE Array(I) > Temp I = I + 1 WEND WHILE Array(J) < Temp J = J - 1 WEND IF I > J THEN EXIT DO IF I < J THEN SWAP Array(I), Array(J) .SwapRows(i,j) End If I = I + 1 J = J - 1 LOOP UNTIL I > J IF I < Last THEN QStack.WriteNum(i,4) 'Push i QStack.WriteNum(Last,4) 'Push Last END IF Last = J LOOP UNTIL First >= Last IF QStack.Position = 0 THEN EXIT DO 'Done QStack.Position = QStack.Position - 8 'Read last 2 nums First = QStack.ReadNum(4) 'Pop First Last = QStack.ReadNum(4) 'Pop Last QStack.Position = QStack.Position - 8 'Reset ptr LOOP End Select For i = StartEl To NumEls .Cell(0,i) = .RSet(Str$(i),0) 'Renumber the rows Next ' .UpDateTopDataRow(NumRows) QStack.Size = 0 QStack.Close End With END SUB '--------------------------------------------------------------------------- Sub Sort Dim i As Integer Dim s As String Dim c As Integer Dim MaxR as Integer Dim Direction As Byte With QGridEx If .QG_dlgSortData.ShowModal = 1 Then c = .dlgSort_cmbSortByCol.ItemIndex + 1 If .TopDataRow(c) = 0 Then'no data in col ShowMessage("No Data in Selected Column") Exit Sub End If If .dlgSort_rdoAscend.Checked = True Then Direction = 1 'Ascending Else Direction = 0 'Descending End If MaxR = .MaxDataRow For i = 1 to MaxR 'From 1st row to last s = Rtrim$(LTrim$(.Cell(c,i))) 'in the slected column If s <> "" Then 'Find first row with data Screen.Cursor = -11 If .Isnumeric(s) = 1 Then 'If it's a number .numSort(1,.MaxDataRow,c,Direction) 'Use numSort Else 'It's a string .strSort(c,Direction) 'Use strSort End If Screen.Cursor = 0 Exit For 'Found data, bail End If Next End If End With End Sub '--------------------------------------------------------------------------- Sub ToggleEditTopRow Dim i As Integer With QGridEx If .EditColLabels = 0 Then 'Enter EditCol .Row = 0 .Col = 1 .FixedRows = 0 .EditColLabels = 1 Else For i = 1 to qgMaxCols 'No Blank Col Headers! If .Cell(i,0) = "" Then .Cell(i,0) = .CSet("Var " + Str$(i),i) End If Next .Row = 1 .Col = 1 .FixedRows = 1 .EditColLabels = 0 End if End With End Sub ' '--------------------------------------------------------------------------- Sub ToggleSelMode Dim lstCol as Byte With QGridEx If .SelMode = 0 and .MaxDataRow > 0 Then 'Enter SelMode lstCol = .Col 'need this trick to remove editor .Col = .Col+1 .DelOptions(10,13) .Col = lstCol .SelMode = 1 Else 'Exit SelMode lstCol = .Col 'need this trick to restore editor .Col = .Col+1 .AddOptions(10,13) .Col = lstCol .SelRange.lCol = 0 'Zero out range related data .SelRange.tRow = 0 .SelRange.rCol = 0 .SelRange.bRow = 0 .SelMode = 0 .SelExists = 0 End if End With End Sub '--------------------------------------------------------------------------- ' ***** SelectRange Event Code ***** ' Works BEST if selection is from upper Left to lower Right ' Works from upper right to lower left IF select entire left col 1st then move right ' Works from lower left to upper right IF select entire bottom row 1st then move up ' Does NOT WORK if selection is from lower right to upper left ' If you over-select, you must backtrack the selection and then go forward ' Uncomment below to see how selection behaves '------------------------------------------------------------------------------- Sub DrawCell(c AS Integer, r As Integer,State As Integer, Rect AS QRect) WITH QGridEx Select Case State Case 1 'Draw in SelColor .SelRange.tRow = .Row '<- Row and Col stay constant so .SelRange.lCol = .Col 'no need to use OnSelectCell .SelRange.bRow = r '<- These vary depending on how .SelRange.rCol = c 'the mouse is moved during selection If .SelRange.bRow <= .SelRange.tRow Then SWAP .SelRange.tRow,.SelRange.bRow End If If .SelRange.rCol <= .SelRange.lCol Then SWAP .SelRange.lCol,.SelRange.rCol End If ' .Cell(5,6) ="c= "+STR$(c) 'uncomment to see behavior ' .Cell(6,6) ="r= "+STR$(r) ' .Cell(5,1) ="Top= "+STR$(.SelRange.tRow) ' .Cell(5,2) ="Left= "+STR$(.SelRange.lCol) ' .Cell(6,3) ="Bottom= "+STR$(.SelRange.bRow) ' .Cell(6,4) ="Right= "+STR$(.SelRange.rCol) .Rectangle(Rect.Left, Rect.Top, Rect.Left+.ColWidths(c), Rect.Top+.RowHeights(r), .SelColor) ' .FillRect(Rect.Left, Rect.Top, Rect.Left+.ColWidths(c), Rect.Top+.RowHeights(r), .SelColor) ' .TextOut(Rect.Left+2, Rect.Top+2, .Cell(c, r), 0, .SelColor) Case 2 'Draw the SelAll Rectangle in SelColor .Rectangle(Rect.Left, Rect.Top, Rect.Left+.ColWidths(c), Rect.Top+.RowHeights(r), .SelColor) ' .FillRect(Rect.Left, Rect.Top, Rect.Left+.ColWidths(c), Rect.Top+.RowHeights(r), .SelColor) ' .TextOut(Rect.Left+2, Rect.Top+2, .Cell(c, r), 0, .SelColor) Case 3 'Erase the SelAll Rectangle in Color .Rectangle(Rect.Left, Rect.Top, Rect.Left+.ColWidths(c), Rect.Top+.RowHeights(r), .Color) End Select END WITH End Sub '------------------------------------------------------------------------------ Sub rngCopy Dim i As Integer Dim j As Integer Dim s As String With QGridEx If .SelMode = 1 Then s = "" For j = .SelRange.tRow to .SelRange.bRow For i = .SelRange.lcol to .SelRange.rCol s = s + RTrim$(Ltrim$(.Cell(i,j))) If i < .SelRange.rCol Then s = s + .Separator Next If j < .SelRange.bRow Then s = s + Chr$(10) ' s = s + Chr$(10) Next .SelExists = 1 Else ShowMessage("Not in Select Mode") End If Clipboard.Text = s End With End Sub '--------------------------------------------------------------------------- Sub rngDelete Dim i As Integer Dim j As Integer Dim k As Integer With QGridEx If .SelMode = 1 Then Select Case .SelAllActive Case 0 For i = .SelRange.lcol to .SelRange.rCol For j = .SelRange.bRow to .SelRange.tRow Step -1 .Cell(i,j) = "" If j = .TopDataRow(i) And j > 0 Then .TopDataRow(i) = j-1 Next For k = j to 1 Step -1 If .Cell(i,k) = "" Then 'Check for empty rows above .TopDataRow(i) = k-1 Else Exit For 'Have found data, bail End If Next Next Case 1 For i = .SelRange.lcol to .SelRange.rCol For j = .SelRange.bRow to 1 Step -1 .Cell(i,j) = "" If j = .TopDataRow(i) Then .TopDataRow(i) = j-1 Next Next End Select .SelExists = 0 Else ShowMessage("Not in Select Mode") End If End With End Sub '--------------------------------------------------------------------------- Sub rngCut With QGridEx If .SelMode = 1 Then .rngCopy .rngDelete .SelExists = 1 Else ShowMessage("Not in Select Mode") End If End With End Sub '--------------------------------------------------------------------------- Sub rngPaste Dim i As Integer Dim j As Integer Dim r As Integer Dim c As Integer Dim s As String With QGridEx Dim Mem As QMemoryStream If Clipboard.HasFormat(1) = 1 Then Mem.Position = 0 Mem.Write(Clipboard.Text) Mem.Position = 0 .LoadFromStream(Mem,.Row,.Col,.Row + Mem.LineCount) Mem.Position = 0 'justify and update TopDataRow s = Mem.ReadLine c = TALLY(s, Chr$(9)) + .Col r = Mem.LineCount + .Row + 1 For i = .Col to c For j = .Row to r .Cell(i,j) = .Justify(.Cell(i,j),i,j) IF .Cell(i,j) <> "" And j > .TopDataRow(i) THEN .TopDataRow(i) = j Next Next Mem.Size = 0 Mem.Position = 0 End If End With End Sub '------------------------------------------------------------------------------ Sub rngSelAll Dim i As Integer Dim j As Integer Dim aRect as Qrect With QGridEx If .SelMode = 1 And .MaxDataRow > 0 Then For i = .SelRange.lcol to .SelRange.rCol 'Erase Current HiLite 'Draw Reactangles For j = .SelRange.tRow to .SelRange.bRow aRect.Left = .ColWidths(0)+1 + (.ColWidths(i)+1) * (i-1) aRect.Top = .RowHeights(0)+1 + (.RowHeights(j)+1) * (j-1) .DrawCell(i,j,3,aRect) Next Next .SelRange.lcol = .MinDataCol 'Set new Range .SelRange.tRow = .MinDataRow .SelRange.rCol = .MaxDataCol .SelRange.bRow = .MaxDataRow For i = .SelRange.lcol to .SelRange.rCol 'Draw SelAll Hilite 'Draw Reactangles For j = .SelRange.tRow to .SelRange.bRow aRect.Left = .ColWidths(0)+1 + (.ColWidths(i)+1) * (i-1) aRect.Top = .RowHeights(0)+1 + (.RowHeights(j)+1) * (j-1) .DrawCell(i,j,2,aRect) Next Next .SelAllActive = 1 Else ShowMessage("No data to Select") End If End With End Sub '------------------------------------------------------------------------------ Sub rngFillDown Dim i As Integer Dim j As Integer Dim s As String With QGridEx If .SelMode = 0 Then Exit Sub For i = .SelRange.lCol to .SelRange.rCol For j = .SelRange.tRow to .SelRange.bRow s = Rtrim$(Ltrim$(.Cell(i,.SelRange.tRow))) If s <> "" Then .Cell(i,j) = .Justify(s,i,j) ' .Cell(i,j) = .RSet(s,i) If j > .TopDataRow(i) Then .TopDataRow(i) = j End If End If Next Next End With End Sub '------------------------------------------------------------------------------ Sub rngFillRight Dim i As Integer Dim j As Integer Dim s As String With QGridEx If .SelMode = 0 Then Exit Sub For i = .SelRange.tRow to .SelRange.bRow For j = .SelRange.lCol to .SelRange.rCol s = Rtrim$(Ltrim$(.Cell(.SelRange.lCol,i))) If s <> "" Then .Cell(j,i) = .Justify(s,j,i) ' .Cell(j,i) = .RSet(s,j) If i > .TopDataRow(j) Then .TopDataRow(j) = i End If End If Next Next End With End Sub '------------------------------------------------------------------------------ Sub rngFillSeries Dim i As Integer Dim j As Integer Dim x As Single Dim n As Single Dim z As Single With QGridEx If .QG_dlgFillSeries.ShowModal = 1 Then x = Val(.dlgFill_txtStep.Text) z = Val(.dlgFill_txtEnd.Text) Select Case .dlgFill_rdoColumns.Checked Case 1 'By Col If z = 0 Then 'All Sel'd Rows For i = .SelRange.lCol to .SelRange.rCol For j= .SelRange.tRow + 1 to .SelRange.bRow If .dlgFill_rdoLinear.Checked = 1 Then n = x + Val(.Cell(i,j-1)) 'Addition Else n = x * Val(.Cell(i,j-1)) 'Multiplication End If .Cell(i,j) = .RSet(Str$(n),i) If j > .TopDataRow(i) Then .TopDataRow(i) = j End If Next Next Else 'Up to stop point Select Case .SelMode Case 1 For i = .SelRange.lCol to .SelRange.rCol For j= .Row + 1 to .RowCount'qgMaxRows If Val(.Cell(i,j-1)) >= z Then Exit For If .dlgFill_rdoLinear.Checked = 1 Then n = x + Val(.Cell(i,j-1)) 'Addition Else n = x * Val(.Cell(i,j-1)) 'Multiplication End If .Cell(i,j) = .RSet(Str$(n),i) If j > .TopDataRow(i) Then .TopDataRow(i) = j End If If n >= z Then Exit For Next Next Case 0 If .Cell(.Col,.Row) <> "" Then For j= .Row + 1 to .RowCount If Val(.Cell(.Col,j-1)) >= z Then Exit For If .dlgFill_rdoLinear.Checked = 1 Then n = x + Val(.Cell(.Col,j-1)) 'Addition Else n = x * Val(.Cell(.Col,j-1)) 'Multiplication End If .Cell(.Col,j) = .RSet(Str$(n),.Col) If j > .TopDataRow(.Col) Then .TopDataRow(.Col) = j End If If n >= z Then Exit For Next End If End Select End If Case 0 'By Row If z = 0 Then 'All Sel'd Rows For j= .SelRange.tRow to .SelRange.bRow For i = .SelRange.lCol + 1 to .SelRange.rCol If .dlgFill_rdoLinear.Checked = 1 Then n = x + Val(.Cell(i-1,j)) 'Addition Else n = x * Val(.Cell(i-1,j)) 'Multiplication End If .Cell(i,j) = .RSet(Str$(n),i) If j > .TopDataRow(i) Then .TopDataRow(i) = j End If Next Next Else 'Up to stop point Select Case .SelMode Case 1 For j= .SelRange.tRow to .SelRange.bRow' For i = .Col + 1 to .ColCount'qgMaxCols If Val(.Cell(i-1,j)) >= z Then Exit For If .dlgFill_rdoLinear.Checked = 1 Then n = x + Val(.Cell(i-1,j)) 'Addition Else n = x * Val(.Cell(i-1,j)) 'Multiplication End If .Cell(i,j) = .RSet(Str$(n),i) If j > .TopDataRow(i) Then .TopDataRow(i) = j End If If n >= z Then Exit For Next Next Case 0 If .Cell(.Col,.Row) <> "" Then For i = .Col + 1 to .ColCount'qgMaxCols If Val(.Cell(i-1,.Row)) >= z Then Exit For If .dlgFill_rdoLinear.Checked = 1 Then n = x + Val(.Cell(i-1,.Row)) 'Addition Else n = x * Val(.Cell(i-1,.Row)) 'Multiplication End If .Cell(i,.Row) = .RSet(Str$(n),i) If .Row > .TopDataRow(i) Then .TopDataRow(i) = .Row End If If n >= z Then Exit For Next End If End Select End If End Select End If End With End Sub '-------------------------------------------------------------------------- '----------------------------- Pop Up ------------------------------------- '-------------------------------------------------------------------------- With QGridEx Event QG_PopUpMenu.OnPopUp .mnuCut.Enabled = .SelMode .mnuCopy.Enabled = .SelMode .mnuPaste.Enabled = Clipboard.HasFormat(1)'.SelExists .mnuDelete.Enabled = .SelMode .mnuSelectAll.Enabled = .SelMode .mnuFillDown.Enabled = .SelRange.bRow > .SelRange.tRow .mnuFillRight.Enabled = .SelRange.rCol > .SelRange.lCol .mnuFillSeries.Enabled = .MaxDataRow > 0 .mnuSort.Enabled = .MaxDataRow > 0 .mnuSelectMode.Checked = .SelMode .mnuEditRow0.Checked = .EditColLabels End Event '--- mnuCut Sub OnClic_mnuCut .rngCut End Sub '--- mnuCopy Sub OnClic_mnuCopy .rngCopy End Sub '--- mnuPaste Sub OnClic_mnuPaste .rngPaste End Sub '--- mnuDelete Sub OnClic_mnuDelete .rngDelete End Sub '--- mnuSelectAll Sub OnClic_mnuSelectAll .rngSelAll End Sub '--- mnuFillDown Sub OnClic_mnuFillDown .rngFillDown End Sub '--- mnuFillRight Sub OnClic_mnuFillRight .rngFillRight End Sub '--- mnuFillSeries Sub OnClic_mnuFillSeries .rngFillSeries End Sub '--- mnuFillSeries Sub OnClic_mnuSort .Sort End Sub '--- mnuSelectMode Sub OnClic_mnuSelectMode .ToggleSelMode End Sub '--- mnuEditRow0 Sub OnClic_mnuEditRow0 .ToggleEditTopRow End Sub PROPERTY SET Set_Popup(Use as long) .QG_PopUpMenu.AutoPopup = Use END PROPERTY End With '--------------------------------------------------------------------------- '---------------------------- Sort Dialog Events --------------------------- '--------------------------------------------------------------------------- Sub dlgSort_FormLoad Dim i As Integer With QGridEx .QG_dlgSortData.Left = Screen.Width\2 - .QG_dlgSortData.Width\2 .QG_dlgSortData.Top= Screen.Height\2 - .QG_dlgSortData.Height\2 .dlgSort_cmbSortByCol.Clear 'Clear Last Call For i = 0 to qgMaxCols-1 'Load the ComboBox .dlgSort_cmbSortByCol.AddItems(RTrim$(LTrim$(.Cell(i+1,0)))) Next .dlgSort_cmbSortByCol.ItemIndex = .Col-1'0 .dlgSort_rdoAscend.Checked = 1 End With End Sub '------------------------- Fill Series Dialog Events ----------------------- Sub dlgFill_FormLoad With QGridEx .QG_dlgFillSeries.Left = Screen.Width\2 - .QG_dlgFillSeries.Width\2 .QG_dlgFillSeries.Top= Screen.Height\2 - .QG_dlgFillSeries.Height\2 .dlgFill_rdoColumns.Checked = 1 .dlgFill_rdoLinear.Checked = 1 .dlgFill_txtStep.Text = "1" .dlgFill_txtEnd.Text = "" QG_SetFocus(.dlgFill_txtStep.Handle) End With End Sub '----------------------------- EVENT SUBs ---------------------------------- EVENT OnKeyDown (Key AS WORD, Shift AS INTEGER) 'Key Handling Routines WITH QGridEx SELECT CASE Shift CASE 0 'No Shift key pressed SELECT CASE Key CASE &HD'VK_RETURN .Cell(.Col,.Row) = .Justify(.Cell(.Col,.Row),.Col,.Row) Select Case .EnterData Case qgByCol IF .Row < .RowCount-1 THEN 'If room to move down .Row = .Row + 1 'increment row pointer ELSE .Row = 1 END IF Case qgByRow IF .Col < .ColCount-1 THEN 'If room to move right .Col = .Col + 1 'increment col pointer ELSE .Col = 1 END IF End Select CASE &H9,&H21,&H22,&H26, &H28'Tab, Arrows, PgUp, PgDn .Cell(.Col,.Row) = .Justify(.Cell(.Col,.Row),.Col,.Row) CASE &H1B'VK_ESCAPE If .TempCell <> "" Then .Cell( .Col, .Row) = .Justify(.TempCell,.Col,.Row) 'restore last cell value End If CASE &H71'VK_F2 'Toggle edit and select modes .ToggleSelMode CASE &H74'VK_F5 'Toggle editing of Row 0 .ToggleEditTopRow CASE ELSE END SELECT CASE 256'ShiftDown SELECT CASE Key CASE &HD'VK_RETURN IF .Row > 1 THEN 'If room to move up .Cell(.Col,.Row) = .Justify(.Cell(.Col,.Row),.Col,.Row) .Row = .Row - 1 'decrement row pointer END IF CASE &H26'VK_UP CASE &H28'VK_DOWN CASE &H25'VK_LEFT CASE &H27'VK_RIGHT CASE &H21'PgUp CASE &H22'PgDown CASE ELSE END SELECT CASE 1'CtrlDown SELECT CASE Key CASE &H9'VK_TAB IF .Col > 1 THEN 'If room to move left .Cell(.Col,.Row) = .Justify(.Cell(.Col,.Row),.Col,.Row) .Col = .Col - 1 'decrement col pointer END IF Case &H43'c If .Selmode = 1 Then .rngCopy Case &H56'v If .Selmode = 1 Then .rngPaste Case &H58'x If .Selmode = 1 Then .rngCut Case &H41'a If .Selmode = 1 Then .rngSelAll Case &H44'd If .Selmode = 1 Then .rngFillDown Case &H52'r If .Selmode = 1 Then .rngFillRight CASE &H26'VK_UP .Row = .MinDataRow CASE &H28'VK_DOWN .Row = .TopDataRow(.Col) CASE ELSE END SELECT CASE 16'AltDown END SELECT END WITH END EVENT '------------------------------------------------------------------------------ EVENT OnSetEditText (c AS INTEGER, r AS INTEGER, s AS STRING) 'Update TopDataRow DIM i AS INTEGER 'Loop counters... WITH QGridEx .IsChanged = 1 IF s <> "" THEN 'User entered new data IF r > .TopDataRow(c) THEN .TopDataRow(c) = r 'Data in a higher row, update highest row ELSE 'User may have deleted exisitng data IF r = .TopDataRow(c) THEN 'Deletion is from the highest row FOR i = r TO 0 STEP -1 'Work backwards from current row IF .Cell(c,i) <> "" THEN 'Have found data in the cell .TopDataRow(c) = i 'Update highest row EXIT FOR 'Bail END IF NEXT i END IF END IF END WITH 'Prints MaxDataRow/Col function result in cell as test 'QGridEx.Cell(7,1) = STR$(QGridEx.MaxDataRow) END EVENT '------------------------------------------------------------------------------ EVENT OnSelectCell(c AS INTEGER, r AS INTEGER, CanSelect AS INTEGER) Dim i As Integer Dim j As Integer Dim OldColor As Long With QGridEx If .SelAllActive = 1 Then .Repaint .SelAllActive = 0 End If .TempCell = Rtrim$(.Cell(c,r)) 'Store CurrVal for Undo on ESC End With END EVENT '------------------------------------------------------------------------------ CONSTRUCTOR Parent = EDF_BT Align = alClient ' DefaultColWidth = 100 '@@@ DefaultRowHeight = 20 DefaultColWidth = 32 AddOptions (10, 13, 14, 11, 5, 4)', 7, 6) Separator = chr$(9) 'TAB delimited ' Separator = "," 'CSV Row = 1 Col = 1 RowCount = qgMaxRows+1 ColCount = qgMaxCols+1 'ColWidths(0) = 39 ColWidths(0) = 64 ' largeur 1ere colonne Visible = 1 Font.Name = "Arial" OnDrawCell = QGridEx.DrawCell Missing = "" SelColor = RGB(0,90,202)'RGB(196,216,255)'RGB(146,217,255)' CurrFile = "NewData.stz" EnterData = qgByCol TempCell = "" IsChanged = 0 EditColLabels = 0 SelMode = 0 SelExists = 0 SelAllActive = 0 '--- Sort Dialog QG_dlgSortData.Center QG_dlgSortData.Caption = "Sort Data" QG_dlgSortData.Top = 151 QG_dlgSortData.Left = 272 QG_dlgSortData.Width = 274 QG_dlgSortData.Height = 150 QG_dlgSortData.BorderStyle = bsDialog QG_dlgSortData.OnShow = QGridEx.dlgSort_FormLoad dlgSort_lblSortBy.Parent = QGridEx.QG_dlgSortData dlgSort_lblSortBy.Top = 18 dlgSort_lblSortBy.Left = 16 dlgSort_lblSortBy.Width = 36 dlgSort_lblSortBy.Height = 13 dlgSort_lblSortBy.Caption = "Sort by:" dlgSort_cmbSortByCol.Parent = QGridEx.QG_dlgSortData dlgSort_cmbSortByCol.Top = 42 dlgSort_cmbSortByCol.Left = 14 dlgSort_cmbSortByCol.Width = 129 dlgSort_cmbSortByCol.Height = 21 dlgSort_cmbSortByCol.Text = "" dlgSort_cmbSortByCol.TabOrder = 0 dlgSort_grpType.Parent = QGridEx.QG_dlgSortData dlgSort_grpType.Top = 11 dlgSort_grpType.Left = 156 dlgSort_grpType.Width = 96 dlgSort_grpType.Height = 54 dlgSort_grpType.Caption = "" dlgSort_rdoAscend.Parent = QGridEx.dlgSort_grpType dlgSort_rdoAscend.Top = 10 dlgSort_rdoAscend.Left = 11 dlgSort_rdoAscend.Width = 74 dlgSort_rdoAscend.Height = 17 dlgSort_rdoAscend.Caption = "&Ascending" dlgSort_rdoDescend.Parent = QGridEx.dlgSort_grpType dlgSort_rdoDescend.Top = 27 dlgSort_rdoDescend.Left = 11 dlgSort_rdoDescend.Width = 77 dlgSort_rdoDescend.Height = 25 dlgSort_rdoDescend.Caption = "&Descending" dlgSort_btnOK.Parent = QGridEx.QG_dlgSortData dlgSort_btnOK.Top = 80 dlgSort_btnOK.Left = 35 dlgSort_btnOK.Width = 73 dlgSort_btnOK.Height = 25 dlgSort_btnOK.Caption = "&OK" dlgSort_btnOK.ModalResult = 1 dlgSort_btnOK.Default = True dlgSort_btnCancel.Parent = QGridEx.QG_dlgSortData dlgSort_btnCancel.Top = 80 dlgSort_btnCancel.Left = 165 dlgSort_btnCancel.Width = 73 dlgSort_btnCancel.Height = 25 dlgSort_btnCancel.Caption = "&Cancel" dlgSort_btnCancel.ModalResult = 2 dlgSort_btnCancel.Cancel = True '--- Fill Series Dialog QG_dlgFillSeries.Center QG_dlgFillSeries.Caption = "Fill Series" QG_dlgFillSeries.BorderStyle = 3 'Dialog QG_dlgFillSeries.Top = 122 QG_dlgFillSeries.Left = 238 QG_dlgFillSeries.Width = 308 QG_dlgFillSeries.Height = 155 QG_dlgFillSeries.OnShow = QGridEx.dlgFill_FormLoad dlgFill_grpSeries.Parent = QGridEx.QG_dlgFillSeries dlgFill_grpSeries.Top = 9 dlgFill_grpSeries.Left = 8 dlgFill_grpSeries.Width = 95 dlgFill_grpSeries.Height = 60 dlgFill_grpSeries.Caption = "Series in:" dlgFill_grpSeries.TabOrder = 2 dlgFill_rdoColumns.Parent = QGridEx.dlgFill_grpSeries dlgFill_rdoColumns.Top = 17 dlgFill_rdoColumns.Left = 7 dlgFill_rdoColumns.Width = 62 dlgFill_rdoColumns.Height = 17 dlgFill_rdoColumns.Caption = "Columns" dlgFill_rdoRows.Parent = QGridEx.dlgFill_grpSeries dlgFill_rdoRows.Top = 37 dlgFill_rdoRows.Left = 7 dlgFill_rdoRows.Width = 55 dlgFill_rdoRows.Height = 17 dlgFill_rdoRows.Caption = "Rows" dlgFill_grpType.Parent = QGridEx.QG_dlgFillSeries dlgFill_grpType.Top = 9 dlgFill_grpType.Left = 105 dlgFill_grpType.Width = 95 dlgFill_grpType.Height = 60 dlgFill_grpType.Caption = "Series Type:" dlgFill_grpType.TabOrder = 3 dlgFill_rdoLinear.Parent = QGridEx.dlgFill_grpType dlgFill_rdoLinear.Top = 16 dlgFill_rdoLinear.Left = 6 dlgFill_rdoLinear.Width = 81 dlgFill_rdoLinear.Height = 17 dlgFill_rdoLinear.Caption = "Linear" dlgFill_rdoExp.Parent = QGridEx.dlgFill_grpType dlgFill_rdoExp.Top = 36 dlgFill_rdoExp.Left = 6 dlgFill_rdoExp.Width = 81 dlgFill_rdoExp.Height = 17 dlgFill_rdoExp.Caption = "Exponential" dlgFill_lblStep.Parent = QGridEx.QG_dlgFillSeries dlgFill_lblStep.Top = 72 dlgFill_lblStep.Left = 23 dlgFill_lblStep.Width = 52 dlgFill_lblStep.Height = 13 dlgFill_lblStep.Caption = "Step Value" dlgFill_txtStep.Parent = QGridEx.QG_dlgFillSeries dlgFill_txtStep.Top = 91 dlgFill_txtStep.Left = 13 dlgFill_txtStep.Width = 81 dlgFill_txtStep.Height = 21 dlgFill_txtStep.Text = "" dlgFill_txtStep.TabOrder = 0 dlgFill_lblEnd.Parent = QGridEx.QG_dlgFillSeries dlgFill_lblEnd.Top = 74 dlgFill_lblEnd.Left = 126 dlgFill_lblEnd.Width = 49 dlgFill_lblEnd.Height = 13 dlgFill_lblEnd.Caption = "End Value" dlgFill_txtEnd.Parent = QGridEx.QG_dlgFillSeries dlgFill_txtEnd.Top = 90 dlgFill_txtEnd.Left = 114 dlgFill_txtEnd.Width = 81 dlgFill_txtEnd.Height = 21 dlgFill_txtEnd.Text = "" dlgFill_txtEnd.TabOrder = 1 dlgFill_btnOK.Parent = QGridEx.QG_dlgFillSeries dlgFill_btnOK.Top = 12 dlgFill_btnOK.Left = 214 dlgFill_btnOK.Width = 73 dlgFill_btnOK.Height = 25 dlgFill_btnOK.Caption = "&OK" dlgFill_btnOK.ModalResult = 1 dlgFill_btnOK.Default = True dlgFill_btnCancel.Parent = QGridEx.QG_dlgFillSeries dlgFill_btnCancel.Top = 43 dlgFill_btnCancel.Left = 214 dlgFill_btnCancel.Width = 73 dlgFill_btnCancel.Height = 25 dlgFill_btnCancel.Caption = "&Cancel" dlgFill_btnCancel.ModalResult = 2 dlgFill_btnCancel.Cancel = True '--- PopUp Menu PopUpMenu = QGridEx.QG_PopUpMenu mnuCut.Caption = "Cu&t" mnuCut.OnClick = QGridEx.OnClic_mnuCut mnuCopy.Caption = "&Copy" mnuCopy.OnClick = QGridEx.OnClic_mnuCopy mnuPaste.Caption = "&Paste" mnuPaste.OnClick = QGridEx.OnClic_mnuPaste mnuDelete.Caption = "&Delete" mnuDelete.OnClick = QGridEx.OnClic_mnuDelete mnuSep_1.Caption = "-" mnuSelectAll.Caption = "Select &All" mnuSelectAll.OnClick = QGridEx.OnClic_mnuSelectAll mnuSep_2.Caption = "-" mnuFillDown.Caption = "Fill Down" mnuFillDown.OnClick = QGridEx.OnClic_mnuFillDown mnuFillRight.Caption = "Fill Right" mnuFillRight.OnClick =QGridEx.OnClic_mnuFillRight mnuFillSeries.Caption = "Fill Series..." mnuFillSeries.OnClick =QGridEx.OnClic_mnuFillSeries mnuSort.Caption = "Sort..." mnuSort.OnClick = QGridEx.OnClic_mnuSort mnuSep_3.Caption = "-" mnuSelectMode.Caption = "Select &Mode" mnuSelectMode.OnClick = QGridEx.OnClic_mnuSelectMode mnuEditRow0.Caption = "&Edit Variable Names" mnuEditRow0.OnClick = QGridEx.OnClic_mnuEditRow0 QG_PopUpMenu.AddItems QGridEx.mnuCut, QGridEx.mnuCopy, QGridEx.mnuPaste, _ QGridEx.mnuDelete, QGridEx.mnuSep_1, QGridEx.mnuSelectAll,_ QGridEx.mnuSep_2, QGridEx.mnuFillDown,QGridEx.mnuFillRight,_ QGridEx.mnuFillSeries,QGridEx.mnuSort,QGridEx.mnuSep_3,_ QGridEx.mnuSelectMode,QGridEx.mnuEditRow0 END CONSTRUCTOR END TYPE '