Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.

Writing to excel file and plot

hhadavi
Beginner
783 Views
Hi,

I want to write two columns of x and y in an excel file and then plot it. I have looked at AutoDice as a reference and I see that the xlPrimary is used as x vlaues. But I like to write x values in first row and the y values in the second row and plot y (the second row0 versus the x (the fiirst row).

can anuone help me with it.

Thanks
0 Kudos
2 Replies
JohnNichols
Valued Contributor III
783 Views
Excellent manual in EXCEL:

Copy columns into XY order wanted and then replot.

Not the sort of question likely to be answered on this forum.

JMN

0 Kudos
Paul_Curtis
Valued Contributor I
783 Views
Values are written into cells explicitly by (column, row) index, so you can populate your spreadsheet however you want.

The code below provides some IVF F90 wrapper routines for writing a value into a cell. The pointer worksheet is INT(INT_PTR_KIND()) and is module-local.

[bash]SUBROUTINE PutRealInCell (column, row, argval) IMPLICIT NONE CHARACTER(LEN=*), INTENT(IN) :: column INTEGER, INTENT(IN) :: row REAL, INTENT(IN) :: argval INTEGER :: range range = column_range (column, row) status = AUTOSETPROPERTYREAL4 (range, "VALUE", argval) END SUBROUTINE PutRealInCell INTEGER FUNCTION column_range (column, row1, row2) RESULT (range) IMPLICIT NONE CHARACTER(LEN=*), INTENT(IN) :: column INTEGER, INTENT(IN) :: row1 INTEGER, INTENT(IN), OPTIONAL :: row2 CHARACTER(LEN=12) :: cell_id TYPE(VARIANT) :: vBSTR1, vBSTR2 INTEGER*4 :: pBSTR1, pBSTR2 WRITE (cell_id, '(A,I6,A)') column, row1, CHAR(0) pBSTR1 = leftpack (cell_id) CALL VariantInit (vBSTR1) vBSTR1%VT = VT_BSTR pBSTR1 = StringToBSTR (cell_id) vBSTR1%VU%PTR_VAL = pBSTR1 IF (PRESENT(row2)) THEN WRITE (cell_id, '(A,I6,A)') column, row1, CHAR(0) pBSTR2 = leftpack (cell_id) CALL VariantInit (vBSTR2) vBSTR2%VT = VT_BSTR pBSTR2 = StringToBSTR (cell_id) vBSTR2%VU%PTR_VAL = pBSTR2 range = $Worksheet_GetRange (worksheet, vBSTR1, vBSTR2, $STATUS=status) status = VariantClear(vBSTR2) IF (pBSTR2 /= 0) CALL SysFreeString (pBSTR2) ELSE range = $Worksheet_GetRange (worksheet, vBSTR1, $STATUS=status) END IF status = VariantClear(vBSTR1) IF (pBSTR1 /= 0) CALL SysFreeString (pBSTR1) END FUNCTION column_range ! renamed from ConvertStringToBstr(), which has a linker conflict INTEGER(INT_PTR_KIND()) FUNCTION StringToBSTR(string) USE OLEAUT32 USE IFNLS CHARACTER*(*), INTENT(IN) :: string INTEGER(INT_PTR_KIND()) bstr INTEGER*4 length INTEGER*2, ALLOCATABLE :: unistr(:) ! First call to MBConvertMBToUnicode determines the length to allocate ALLOCATE (unistr(0)) length = MBConvertMBToUnicode(string, unistr) DEALLOCATE (unistr) ! Special case for all spaces IF (length < 0) THEN ALLOCATE (unistr(2)) unistr(1) = #20 ! Single space unistr(2) = 0 ! Null terminate ELSE ! Second call to MBConvertMBToUnicode does the conversion ALLOCATE (unistr(length+1)) length = MBConvertMBToUnicode(string, unistr) unistr(length+1) = 0 ! Null terminate END IF bstr = SysAllocString(unistr) DEALLOCATE (unistr) StringToBSTR = bstr END FUNCTION StringToBSTR SUBROUTINE worksheet_setup IMPLICIT NONE INTEGER :: range TYPE(VARIANT) :: vBSTR1, vBSTR2 INTEGER*4 :: pBSTR1, pBSTR2 INTEGER, PARAMETER :: xlRight = -4152 ! #HFFFFEFC8 CALL VariantInit (vBSTR1) vBSTR1%VT = VT_BSTR pBSTR1 = StringToBSTR ('A1'//CHAR(0)) vBSTR1%VU%PTR_VAL = pBSTR1 CALL VariantInit (vBSTR2) vBSTR2%VT = VT_BSTR pBSTR2 = StringToBSTR ('J5002'//CHAR(0)) vBSTR2%VU%PTR_VAL = pBSTR2 range = $Worksheet_GetRange (worksheet, vBSTR1, vBSTR2, $STATUS=status) !status = AUTOSETPROPERTYINTEGER2 (range, "ClearContents", 1) status = AUTOSETPROPERTYINTEGER2 (range, "FontSize", INT2(8)) status = AUTOSETPROPERTYINTEGER2 (range, "HorizontalAlignment", INT2(xlRight)) status = AUTOSETPROPERTYINTEGER2 (range, "RowHeight", INT2(10)) status = VariantClear(vBSTR1) IF (pBSTR1 /= 0) CALL SysFreeString (pBSTR1) status = VariantClear(vBSTR2) IF (pBSTR2 /= 0) CALL SysFreeString (pBSTR2) END SUBROUTINE worksheet_setup [/bash]
0 Kudos
Reply