Rocket jBASE

 View Only
  • 1.  Source for XML jEDI

    Posted 05-10-2022 08:02
     SUBROUTINE XMLJEDI(parameters, jedi_command, item_id, data_record, defer_commit, error_code)
    * 04/27/22 by Dan Ell, Tyler McDonaugh, Jenna Hernandez, Charles Barouch *
    ! ********************************************************************** *
    ! Creates an xpath model of all the tags in an XML document *
    ! and treats the XML document like a read-only jBASE file. *
    ! ********************************************************************** *
    !
    ! Add this to the current directory to create a jEDI file for XML
    !
    ! ED . SAMPLE.XML
    ! .I JBC__SOB JediInitSUB XMLJEDI filename=/big/tmp/SampleLarge.xml,xmlmap=SAMPLE.MAP,dict=SAMPLE.XML]D
    ! 001 JBC__SOB JediInitSUB XMLJEDI filename=/big/tmp/SampleLarge.xml,xmlmap=SAMPLE.MAP,dict=SAMPLE.XML]D
    ! .FI
    !
    ! xmlmap is the item ID to XML.MAPS which holds this information
    !
    ! ED XML.MAPS SAMPLE.MAP
    ! 001 Sample PLANT xml file <-- Description (not used in this program)
    ! 002 PLANT <-- Record tag pre-defined (not in this program), <Record> ... </Record>
    ! 003 PLANT>COMMON]PLANT>BOTANICAL <-- XMLPath variables Added by this program if not predefined
    ! 004 MR2]D]MT]CALL XXXX <-- Conversion or sub applied to data before presenting
    !
    COMMON /XMLJEDI/ id_list, R.XMLMAP, SEQ.FILE, F.XML.MAPS, start_tag, end_tag, buffered_items(2400), from_to, dict_file, F.DICT, high_buffer
    GOSUB Initialize
    *
    *** Allow XMLJEDI_VERBOSE for debugging
    *
    IF NOT(GETENV('XMLJEDI_VERBOSE',verbose)) THEN verbose = ''
    IF verbose = 2 THEN DEBUG
    *
    * Main Process
    *
    error_code = 0
    ON jedi_command+1 GOSUB ...
    InitCmd, OpenCmd, CloseCmd, ...
    SelectCmd, SelectEndCmd, ReadNextCmd, ...
    ReadRecordCmd, WriteRecordCmd, DeleteRecordCmd, ...
    LockCmd, UnLockCmd, IoctlCmd, ...
    ClearFileCmd, DeleteFileCmd, CreateFileCmd, SyncCmd, ...
    DisconnectCmd, TransBeginCmd, TransCommitCmd, TransRollBackCmd, ...
    ReadVCmd, WriteVCmd, ErrorCmd
    IF verbose = 1 THEN CRT 'Returning out of XMLJEDI'
    *
    *** Exit routine
    *
    RETURN
    *
    * Start of Subroutines
    *
    *
    Initialize:
    *
    EQUATE k_shell TO CHAR(255):'k'
    EQUATE LF TO CHAR(10)
    EQUATE CR TO CHAR(13)
    file_name_index = INDEX(parameters,'filename=',1)
    IF file_name_index THEN
    file_name = parameters[file_name_index+9,999]
    file_name = FIELD(file_name,' ',1)
    file_name = FIELD(file_name,',',1)
    END ELSE
    file_name = ''
    END
    xml_map_index = INDEX(parameters,'xmlmap=',1)
    IF xml_map_index THEN
    xml_map = parameters[xml_map_index+7,999]
    xml_map = FIELD(xml_map,' ',1)
    xml_map = FIELD(xml_map,',',1)
    END ELSE
    xml_map = ''
    END
    dict_index = INDEX(parameters,'dict=',1)
    IF dict_index THEN
    dict_file = parameters[dict_index+5,999]
    dict_file = FIELD(dict_file,' ',1)
    dict_file = FIELD(dict_file,',',1)
    END ELSE
    dict_file = ''
    END
    block_index = INDEX(parameters,'blocksize=',1)
    IF block_index THEN
    block_size = parameters[block_index+10,999]
    block_size = FIELD(block_size,' ',1)
    block_size = FIELD(block_size,',',1)
    END ELSE
    block_size = 16384
    END
    RETURN
    *
    ErrorCmd:
    *
    CRT SYSTEM(40):":Invalid command sent to XMLJEDI.b jEDI driver"
    error_code = 5 ;! EIO
    RETURN
    *
    InitCmd:
    IF verbose = 1 THEN CRT 'jedi_command = "InitCmd"'
    RETURN ;! Don't need to do anything
    *
    OpenCmd:
    *
    IF verbose = 1 THEN CRT 'jedi_command = "OpenCmd"'
    high_buffer = 0
    OPEN 'XML.MAPS' TO F.XML.MAPS ELSE STOP 201,'XML.MAPS'
    IF dict_file THEN
    OPEN dict_file TO F.DICT ELSE
    dict_file = ''
    END
    END
    READ R.XMLMAP FROM F.XML.MAPS, xml_map THEN
    start_tag = '<':R.XMLMAP<2>:'>'
    end_tag = '</':R.XMLMAP<2>:'>'
    head_command = k_shell:'head -c80 ':file_name:' 2>/dev/null'
    EXECUTE head_command CAPTURING top_line
    tail_command = k_shell:'tail -c80 ':file_name:' 2>/dev/null'
    EXECUTE tail_command CAPTURING bottom_line
    IF INDEX(top_line,start_tag,1) AND INDEX(bottom_line,end_tag,1) THEN
    from_to = '' ; MAT buffered_items = '' ;* Reset buffer
    END ELSE
    error_code = 201
    END
    END ELSE
    error_code = 201
    END
    RETURN
    *
    CloseCmd:
    *
    IF verbose = 1 THEN CRT 'jedi_command = "CloseCmd"'
    RETURN ;! Don't need to do anything
    *
    SelectCmd:
    *
    IF verbose = 1 THEN CRT 'jedi_command = "SelectCmd"'
    id_list = ''
    xxx_command = k_shell:"grep '":start_tag:"' ":file_name:" | wc -l 2>/dev/null"
    EXECUTE xxx_command CAPTURING XML.LINES.MAX
    FOR XML.LINES.CNT = 1 TO XML.LINES.MAX
    id_list<-1> = XML.LINES.CNT
    NEXT XML.LINES.CNT
    RETURN
    *
    SelectEndCmd:
    *
    IF verbose = 1 THEN CRT 'jedi_command = "EndCmd"'
    RETURN ;! Don't need to do anything
    *
    ReadNextCmd:
    *
    IF verbose = 1 THEN CRT 'jedi_command = "ReadNextCmd"'
    READNEXT item_id FROM id_list ELSE
    error_code = 100 ;! end_record
    END
    RETURN
    *
    ReadRecordCmd:
    *
    IF verbose = 1 THEN CRT 'jedi_command = "ReadRecordCmd"'
    *
    *** Check if already in buffer
    *
    first_buffer = from_to<1>
    last_buffer = from_to<2>
    IF item_id >= first_buffer AND item_id <= last_buffer THEN
    IF verbose = 4 OR verbose = 5 THEN
    CRT item_id:' in buffer'
    END
    buffer_number = item_id - first_buffer + 1
    data_record = buffered_items(buffer_number)
    RETURN
    END
    IF verbose = 4 OR verbose = 5 THEN
    CRT item_id:' was not >= ':first_buffer:' and <= ':last_buffer
    END
    buffer = ''
    buffer_count = 0 ;* Number of items in the buffer
    buffer_start = 1 ;* First item in the current buffer
    IF verbose = 8 THEN DEBUG
    OPENSEQ file_name TO SEQ.FILE SETTING io_error THEN
    LOOP
    this_block = ''
    READBLK this_block FROM SEQ.FILE, block_size THEN
    buffer := this_block
    first_start_in_block = INDEX(this_block,start_tag,1)
    count_block = this_block[first_start_in_block,LEN(this_block)] ;* disregard before start_tag
    prior_count = buffer_count
    IF INDEX(this_block[1,first_start_in_block-1],end_tag,1) THEN
    start_index = INDEX(buffer,start_tag,prior_count+1)
    buffer = buffer[start_index,LEN(buffer)]
    buffer_start += prior_count
    END
    buffer_count = COUNT(buffer,end_tag) ;* number of items in this buffer
    IF (buffer_count + buffer_start - 1) >= item_id THEN
    GOSUB ParseXML
    item_location = item_id - buffer_start + 1
    data_record = buffered_items(item_location) ;* this item_id
    EXIT
    END
    END ELSE
    error_code = 100 ;* Not on file
    data_record = ''
    EXIT
    END
    REPEAT
    END ELSE
    IF NOT(io_error) THEN
    io_error = 201
    END
    error_code = io_error
    END
    CLOSE SEQ.FILE
    RETURN
    *
    ParseXML:
    *
    IF verbose = 1 THEN CRT '"ParseXML"'
    from_to = '' ; MAT buffered_items = '' ;* Reset buffer
    first_buffer = buffer_start
    last_buffer = buffer_start + buffer_count - 1
    from_to<1> = first_buffer
    from_to<2> = last_buffer
    IF verbose = 4 OR verbose = 5 THEN
    CRT 'BUFFER-':item_id:' from ':from_to<1>:' to ':from_to<2>:' in ':LEN(buffer):' size buffer'
    END
    IF verbose = 7 THEN
    IF buffer_count > high_buffer THEN
    high_buffer = buffer_count
    CRT 'highest buffer_count = "':buffer_count:'"'
    END
    END
    FOR start_count = 1 TO buffer_count
    begin_record = INDEX(buffer,start_tag,start_count)
    IF verbose = 3 THEN DEBUG
    end_record = INDEX(buffer[begin_record,block_size],end_tag,1)
    data_xml = buffer[begin_record,end_record-1]:end_tag
    CONVERT LF:CR TO "" IN data_xml
    GOSUB ParseRecord
    buffered_items(start_count) = data_record
    IF verbose = 5 THEN
    CRT SPACE(3):data_record[1,40]
    END
    NEXT start_count
    RETURN
    *
    ParseRecord:
    *
    xpath_name = ''
    data_record=''
    instance = 0
    LOOP
    instance += 1
    begin_element = INDEX(data_xml,'<',instance)
    end_element = INDEX(data_xml,'>',instance)
    UNTIL begin_element = 0 OR end_element=0 DO
    element = data_xml[begin_element+1,(end_element-begin_element-1)]
    BEGIN CASE
    CASE element[LEN(element)-1,1] = '/' ;* skip
    CASE element[1,1] = '/' ;* self closing ???
    xpath_name = DELETE(xpath_name,DCOUNT(xpath_name,@AM))
    CASE 1 ;* add to xpath_name, check for value
    xpath_name<-1>= element
    begin_element2 = INDEX(data_xml,'<',instance+1)
    xpath_value = data_xml[end_element+1,(begin_element2-end_element-1)] ;* after > and before <
    IF xpath_value # '' THEN
    xpath_loc=xpath_name
    DEL xpath_loc<1> ;* Remove record start tag
    CONVERT @AM TO '>' IN xpath_loc
    LOCATE xpath_loc IN R.XMLMAP<3> SETTING data_attribute ELSE
    R.XMLMAP<3,-1>=xpath_loc
    WRITEV R.XMLMAP<3> ON F.XML.MAPS, xml_map, 3
    IF dict_file THEN
    R.DICT = 'A'
    R.DICT<2> = data_attribute
    dict_heading = xpath_loc
    CONVERT '>' TO ' ' IN dict_heading
    R.DICT<3> = dict_heading
    R.DICT<9> = 'L'
    R.DICT<10> = '10'
    WRITE R.DICT ON F.DICT,data_attribute
    dict_name = xpath_loc
    CONVERT '>' TO '_' IN dict_name
    WRITE R.DICT ON F.DICT,dict_name
    END
    END
    data_conversion = R.XMLMAP<4,data_attribute>
    IF LEN(data_conversion) THEN
    IF data_conversion[1,5] = 'CALL ' THEN
    data_conversion_sub = data_conversion[6,999]
    in_data = xpath_value
    CALL @data_conversion_sub(in_data,out_data)
    xpath_value = out_data
    END ELSE
    data_conversion = RAISE(data_conversion) ;* sub-valued conversions to values
    xpath_value = ICONV(xpath_value,data_conversion)
    END
    END
    data_record<data_attribute>=xpath_value
    END
    END CASE
    REPEAT
    RETURN
    *
    ReadVCmd:
    *
    IF verbose = 1 THEN CRT 'jedi_command = "ReadVCmd"'
    IF verbose = 1 THEN CRT 'XMLJEDI ReadVCmd'
    RETURN
    *
    WriteRecordCmd:
    *
    IF verbose = 1 THEN CRT 'jedi_command = "WriteRecordCmd"'
    CRT 'WRITE not supported'
    ErrCode = 5
    RETURN
    *
    WriteVCmd:
    *
    IF verbose = 1 THEN CRT 'XMLJEDI WriteVCmd'
    RETURN
    *
    DeleteRecordCmd:
    *
    IF verbose = 1 THEN CRT 'jedi_command = "DeleteRecordCmd"'
    CRT 'DELETE not supported'
    ErrCode = 5
    RETURN
    *
    LockCmd:
    *
    IF verbose = 1 THEN CRT 'jedi_command = "LockRecordCmd"'
    IF verbose = 1 THEN CRT 'XMLJEDI LockCmd'
    RETURN
    *
    *
    UnLockCmd:
    *
    IF verbose = 1 THEN CRT 'jedi_command = "UnlockRecordCmd"'
    IF verbose = 1 THEN CRT 'XMLJEDI UnLockCmd'
    RETURN
    *
    IoctlCmd:
    *
    IF verbose = 1 THEN CRT 'jedi_command = "IoctlCmd"'
    error_code = 2005 ;! Needed for select
    Record = 1 ;! Turn off fast access
    RETURN
    *
    DeleteFileCmd:
    *
    IF verbose = 1 THEN CRT 'jedi_command = "DeleteFileCmd"'
    CRT 'DELETE-FILE not supported'
    ErrCode = 5
    RETURN
    *
    ClearFileCmd:
    *
    IF verbose = 1 THEN CRT 'jedi_command = "ClearFileCmd"'
    CRT 'CLEAR-FILE not supported'
    ErrCode = 5
    RETURN
    *
    CreateFileCmd:
    *
    IF verbose = 1 THEN CRT 'jedi_command = "CreateFileCmd"'
    RETURN ;! Don't need to do anything
    *
    SyncCmd:
    *
    IF verbose = 1 THEN CRT 'jedi_command = "SyncCmd"'
    RETURN ;! Don't need to do anything
    !*
    DisconnectCmd:
    *
    IF verbose = 1 THEN CRT 'jedi_command = "DisconnectCmd"'
    RETURN ;! Don't need to do anything
    *
    TransBeginCmd:
    *
    IF verbose = 1 THEN CRT 'jedi_command = "TransBeginCmd"'
    RETURN ;! Don't need to do anything
    *
    TransCommitCmd:
    *
    IF verbose = 1 THEN CRT 'jedi_command = "TransCommitCmd"'
    RETURN ;! Don't need to do anything
    *
    TransRollBackCmd:
    *
    IF verbose = 1 THEN CRT 'jedi_command = "TransRollBackCmd"'
    RETURN ;! Don't need to do anything

    MAKEXML program

    tcl_stmt = SENTENCE()
    o_option = INDEX(tcl_stmt,' -o',1)
    IF o_option THEN
    CHANGE '-o' TO '' IN tcl_stmt
    tcl_stmt = TRIM(tcl_stmt)
    END
    k_shell = CHAR(255):'k'
    PROMPT ''
    number = FIELD(tcl_stmt,' ',2)
    file_path = FIELD(tcl_stmt,' ',3)
    IF NOT(NUM(number)) THEN
    number = FIELD(tcl_stmt,' ',3)
    file_path = FIELD(tcl_stmt,' ',2)
    END
    LOOP
    IF LEN(number) THEN
    IF NOT(NUM(number)) THEN GO HELP
    IF number < 1 OR number # INT(number) THEN GO HELP
    EXIT
    END ELSE
    CRT
    CRT 'Number of XML rows? : ':
    INPUT number
    END
    REPEAT
    LOOP
    IF LEN(file_path) THEN
    EXECUTE k_shell:'ls -1 ':file_path:' 2> /dev/null' CAPTURING exists_path
    IF file_path = exists_path THEN
    IF NOT(o_option) THEN
    CRT
    CRT file_path:' exists. Overwrite? (Y/N) : ':
    INPUT overwrite
    IF overwrite # 'Y' AND overwrite # 'y' THEN STOP
    END
    EXECUTE k_shell:'rm -f ':file_path
    END
    EXECUTE k_shell:'touch ':file_path
    OPENSEQ file_path TO S.FILE ELSE STOP 201,file_path
    EXIT
    END ELSE
    CRT
    CRT 'Enter full path for XML file : ':
    INPUT file_path
    END
    REPEAT
    *
    *** Create XML file
    *
    GOSUB LOADARRAYS ;* Load random data
    WRITESEQ '<CATALOG>' ON S.FILE ELSE NULL
    FOR xml_row_count = 1 TO number
    GOSUB CREATEXMLROW
    WRITESEQ xml_row ON S.FILE ELSE NULL
    NEXT xml_row_count
    WRITESEQ '</CATALOG>' ON S.FILE ELSE NULL
    CRT
    CRT number:' XML records written to ':file_path
    *
    *** Exit program
    *
    STOP
    *
    CREATEXMLROW:
    *
    xml_row = '<PLANT>' ;* start record
    xml_row := '<XMLROW>':xml_row_count:'</XMLROW>'
    xml_elements = '' ; last_element = 0
    GOSUB GETELEMENTS
    FOR element_count = 1 TO 6
    xml_row := xml_elements<element_count>
    NEXT element_count
    xml_row := '</PLANT>' ;* end record
    RETURN
    *
    GETELEMENTS:
    *
    *
    *** COMMON element
    *
    common_value = RND(36)
    IF common_value = '' THEN
    IF RND(10) > 5 THEN
    xml_elements<-1> := '<COMMON></COMMON>'
    END
    END ELSE
    xml_elements<-1> := '<COMMON>':plant_common<common_value>:'</COMMON>'
    END
    *
    *** BOTANICAL element
    *
    botanical_value = RND(36)
    IF botanical_value = '' THEN
    IF RND(10) > 5 THEN
    xml_elements<-1> := '<BOTANICAL></BOTANICAL>'
    END
    END ELSE
    xml_elements<-1> := '<BOTANICAL>':plant_botanical<botanical_value>:'</BOTANICAL>'
    END
    *
    *** ZONE element
    *
    plant_zone = RND(36)
    IF plant_zone = 0 THEN
    IF RND(10) > 5 THEN
    xml_elements<-1> := '<ZONE></ZONE>'
    END
    END ELSE
    xml_elements<-1> := '<ZONE>':plant_zone:'</ZONE>'
    END
    *
    *** LIGHT element
    *
    light_value = RND(4)
    IF light_value = '' THEN
    IF RND(10) > 5 THEN
    xml_elements<-1> := '<LIGHT></LIGHT>'
    END
    END ELSE
    xml_elements<-1> := '<LIGHT>':plant_light<light_value>:'</LIGHT>'
    END
    *
    *** PRICE element
    *
    plant_price = RND(1000) + 300
    plant_price = OCONV(plant_price,'MR2,$')
    IF plant_price = 0 THEN
    IF RND(10) > 5 THEN
    xml_elements<-1> := '<PRICE></PRICE>'
    END
    END ELSE
    xml_elements<-1> := '<PRICE>':plant_price:'</PRICE>'
    END
    *
    *** AVAILABILITY element
    *
    plant_availability = RND(15000)
    plant_availability = OCONV(plant_availability,'MR0,')
    IF plant_availability = 0 THEN
    IF RND(10) > 5 THEN
    xml_elements<-1> := '<AVAILABILITY></AVAILABILITY>'
    END
    END ELSE
    xml_elements<-1> := '<AVAILABILITY>':plant_availability:'</AVAILABILITY>'
    END
    RETURN
    *
    HELP:
    *
    CRT
    CRT 'usage: MAKEXML /full/path/to/xml 99999'
    CRT
    STOP
    *
    LOADARRAYS:
    *
    plant_common = "Bloodroot"
    plant_common<-1> = "Columbine"
    plant_common<-1> = "Marsh Marigold"
    plant_common<-1> = "Cowslip"
    plant_common<-1> = "Dutchman's-Breeches"
    plant_common<-1> = "Ginger, Wild"
    plant_common<-1> = "Hepatica"
    plant_common<-1> = "Liverleaf"
    plant_common<-1> = "Jack-In-The-Pulpit"
    plant_common<-1> = "Mayapple"
    plant_common<-1> = "Phlox, Woodland"
    plant_common<-1> = "Phlox, Blue"
    plant_common<-1> = "Spring-Beauty"
    plant_common<-1> = "Trillium"
    plant_common<-1> = "Wake Robin"
    plant_common<-1> = "Violet, Dog-Tooth"
    plant_common<-1> = "Trout Lily"
    plant_common<-1> = "Adder's-Tongue"
    plant_common<-1> = "Anemone"
    plant_common<-1> = "Grecian Windflower"
    plant_common<-1> = "Bee Balm"
    plant_common<-1> = "Bergamot"
    plant_common<-1> = "Black-Eyed Susan"
    plant_common<-1> = "Buttercup"
    plant_common<-1> = "Crowfoot"
    plant_common<-1> = "Butterfly Weed"
    plant_common<-1> = "Cinquefoil"
    plant_common<-1> = "Primrose"
    plant_common<-1> = "Gentian"
    plant_common<-1> = "Blue Gentian"
    plant_common<-1> = "Jacob's Ladder"
    plant_common<-1> = "Greek Valerian"
    plant_common<-1> = "California Poppy"
    plant_common<-1> = "Shooting Star"
    plant_common<-1> = "Snakeroot"
    plant_common<-1> = "Cardinal Flower"
    plant_botanical = "Sanguinaria canadensis"
    plant_botanical<-1> = "Aquilegia canadensis"
    plant_botanical<-1> = "Caltha palustris"
    plant_botanical<-1> = "Caltha palustris"
    plant_botanical<-1> = "Dicentra cucullaria"
    plant_botanical<-1> = "Asarum canadense"
    plant_botanical<-1> = "Hepatica americana"
    plant_botanical<-1> = "Hepatica americana"
    plant_botanical<-1> = "Arisaema triphyllum"
    plant_botanical<-1> = "Podophyllum peltatum"
    plant_botanical<-1> = "Phlox divaricata"
    plant_botanical<-1> = "Phlox divaricata"
    plant_botanical<-1> = "Claytonia Virginica"
    plant_botanical<-1> = "Trillium grandiflorum"
    plant_botanical<-1> = "Trillium grandiflorum"
    plant_botanical<-1> = "Erythronium americanum"
    plant_botanical<-1> = "Erythronium americanum"
    plant_botanical<-1> = "Erythronium americanum"
    plant_botanical<-1> = "Anemone blanda"
    plant_botanical<-1> = "Anemone blanda"
    plant_botanical<-1> = "Monarda didyma"
    plant_botanical<-1> = "Monarda didyma"
    plant_botanical<-1> = "Rudbeckia hirta"
    plant_botanical<-1> = "Ranunculus"
    plant_botanical<-1> = "Ranunculus"
    plant_botanical<-1> = "Asclepias tuberosa"
    plant_botanical<-1> = "Potentilla"
    plant_botanical<-1> = "Oenothera"
    plant_botanical<-1> = "Gentiana"
    plant_botanical<-1> = "Gentiana"
    plant_botanical<-1> = "Polemonium caeruleum"
    plant_botanical<-1> = "Polemonium caeruleum"
    plant_botanical<-1> = "Eschscholzia californica"
    plant_botanical<-1> = "Dodecatheon"
    plant_botanical<-1> = "Cimicifuga"
    plant_botanical<-1> = "Lobelia cardinalis"
    plant_light = "Mostly Shady"
    plant_light<-1> = "Sun or Shade"
    plant_light<-1> = "Shade"
    plant_light<-1> = "Sunny"
    RETURN

    TESTXML program

    tcl_command = SENTENCE()
    xml_stub_name = FIELD(tcl_command,' ',2)
    OPEN '.' TO F.DOT ELSE STOP 201,'current directory'
    READ R.STUB FROM F.DOT,xml_stub_name ELSE R.STUB = ''
    IF NOT(INDEX(R.STUB,'SUB XMLJEDI ',1)) THEN
    CRT
    CRT xml_stub_name:' is not a XMLJEDI stub'
    CRT
    STOP
    END
    block_size_index = INDEX(R.STUB,'blocksize=',1)
    IF block_size_index THEN
    block_size = R.STUB[block_size_index+10,9999]
    block_size = FIELD(block_size,' ',1)
    block_size = FIELD(block_size,',',1)
    CHANGE 'blocksize=':block_size TO '' IN R.STUB
    R.STUB = TRIM(R.STUB)
    CHANGE ',,' TO ',' IN R.STUB
    CHANGE ', ,' TO ',' IN R.STUB
    END
    FOR block_size = 8192 TO 256000 STEP 1024
    R.NEW = R.STUB:',blocksize=':block_size
    WRITE R.NEW ON F.DOT,xml_stub_name
    time_in = TIME()
    EXECUTE 'SELECT ':xml_stub_name:' WITH *A1' RTNLIST DEAD CAPTURING Nada
    elapsed = TIME() - time_in
    CRT block_size:' ':OCONV(elapsed,'MTS')
    NEXT block_size




    ------------------------------
    Dan Ell
    Senior Software Engineer
    Rocket Internal - All Brands
    ------------------------------