Silverfrost Forums

Welcome to our forums

SLow performance with DIRECT ACCESS unformatted files

26 Jan 2015 9:19 #15449

Bill,

I did another test which is useful to compare with the previous by: - increased the record size to 1940

  • introduced a test for no use of share= The results are:

    [FTN95/Win32 Ver. 7.10.0 Copyright (c) Silverfrost Ltd 1993-2014]

    1. real elapse_time, start_open, start_loop, end_loop WARNING - 242: Variable START_OPEN has been given a value but never used NO ERRORS, 1 WARNING [<MAIN> FTN95/Win32 v7.10.0] NO ERRORS [<RANDOMFILE> FTN95/Win32 v7.10.0] NO ERRORS [<DELETE_FILE> FTN95/Win32 v7.10.0] NO ERRORS [<ELAPSE_TIME> FTN95/Win32 v7.10.0] Creating executable: c:\temp\forum\lgotemp@.exe Program entered Starting the test at: 20150126 201205.726

      for testfile1.dat testfile1.dat deleted WRITE 1000 rec 0.055 sec; For ac=DIRECT fo=UNFORMATTED st=REPLACE sh=
      WRITE 1000 rec 0.070 sec; For ac=DIRECT fo=UNFORMATTED st=OLD sh=
      READ 1000 rec 0.051 sec; For ac=DIRECT fo=UNFORMATTED st=OLD sh=
      testfile1.dat deleted WRITE 1000 rec 0.070 sec; For ac=SEQUENTIAL fo=UNFORMATTED st=REPLACE sh=
      WRITE 1000 rec 0.063 sec; For ac=SEQUENTIAL fo=UNFORMATTED st=OLD sh=
      READ 1000 rec 0.074 sec; For ac=SEQUENTIAL fo=UNFORMATTED st=OLD sh=

    DENYNONE for testfile2.dat
    

    testfile2.dat deleted WRITE 1000 rec 0.531 sec; For ac=DIRECT fo=UNFORMATTED st=REPLACE sh=DENYNONE WRITE 1000 rec 0.539 sec; For ac=DIRECT fo=UNFORMATTED st=OLD sh=DENYNONE READ 1000 rec 0.141 sec; For ac=DIRECT fo=UNFORMATTED st=OLD sh=DENYNONE testfile2.dat deleted WRITE 1000 rec 0.066 sec; For ac=SEQUENTIAL fo=UNFORMATTED st=REPLACE sh=DENYNONE WRITE 1000 rec 0.074 sec; For ac=SEQUENTIAL fo=UNFORMATTED st=OLD sh=DENYNONE READ 1000 rec 0.082 sec; For ac=SEQUENTIAL fo=UNFORMATTED st=OLD sh=DENYNONE

    DENYRW   for testfile3.dat
    

    testfile3.dat deleted WRITE 1000 rec 0.070 sec; For ac=DIRECT fo=UNFORMATTED st=REPLACE sh=DENYRW
    WRITE 1000 rec 0.070 sec; For ac=DIRECT fo=UNFORMATTED st=OLD sh=DENYRW
    READ 1000 rec 0.070 sec; For ac=DIRECT fo=UNFORMATTED st=OLD sh=DENYRW
    testfile3.dat deleted WRITE 1000 rec 0.066 sec; For ac=SEQUENTIAL fo=UNFORMATTED st=REPLACE sh=DENYRW
    WRITE 1000 rec 0.070 sec; For ac=SEQUENTIAL fo=UNFORMATTED st=OLD sh=DENYRW
    READ 1000 rec 0.074 sec; For ac=SEQUENTIAL fo=UNFORMATTED st=OLD sh=DENYRW

    DENYWR   for testfile4.dat
    

    testfile4.dat deleted WRITE 1000 rec 0.070 sec; For ac=DIRECT fo=UNFORMATTED st=REPLACE sh=DENYWR
    WRITE 1000 rec 0.070 sec; For ac=DIRECT fo=UNFORMATTED st=OLD sh=DENYWR
    READ 1000 rec 0.070 sec; For ac=DIRECT fo=UNFORMATTED st=OLD sh=DENYWR
    testfile4.dat deleted WRITE 1000 rec 0.066 sec; For ac=SEQUENTIAL fo=UNFORMATTED st=REPLACE sh=DENYWR
    WRITE 1000 rec 0.066 sec; For ac=SEQUENTIAL fo=UNFORMATTED st=OLD sh=DENYWR
    READ 1000 rec 0.063 sec; For ac=SEQUENTIAL fo=UNFORMATTED st=OLD sh=DENYWR

    DENYRD   for testfile5.dat
    

    testfile5.dat deleted WRITE 1000 rec 0.797 sec; For ac=DIRECT fo=UNFORMATTED st=REPLACE sh=DENYRD
    WRITE 1000 rec 0.621 sec; For ac=DIRECT fo=UNFORMATTED st=OLD sh=DENYRD
    READ 1000 rec 0.152 sec; For ac=DIRECT fo=UNFORMATTED st=OLD sh=DENYRD
    testfile5.dat deleted WRITE 1000 rec 0.066 sec; For ac=SEQUENTIAL fo=UNFORMATTED st=REPLACE sh=DENYRD
    WRITE 1000 rec 0.090 sec; For ac=SEQUENTIAL fo=UNFORMATTED st=OLD sh=DENYRD
    READ 1000 rec 0.074 sec; For ac=SEQUENTIAL fo=UNFORMATTED st=OLD sh=DENYRD

26 Jan 2015 9:21 #15450

ctd.

  COMPAT   for testfile6.dat
 testfile6.dat deleted
WRITE 1000 rec 0.578 sec; For ac=DIRECT     fo=UNFORMATTED st=REPLACE sh=COMPAT  
WRITE 1000 rec 0.602 sec; For ac=DIRECT     fo=UNFORMATTED st=OLD     sh=COMPAT  
READ  1000 rec 0.207 sec; For ac=DIRECT     fo=UNFORMATTED st=OLD     sh=COMPAT  
 testfile6.dat deleted
WRITE 1000 rec 0.066 sec; For ac=SEQUENTIAL fo=UNFORMATTED st=REPLACE sh=COMPAT  
WRITE 1000 rec 0.074 sec; For ac=SEQUENTIAL fo=UNFORMATTED st=OLD     sh=COMPAT  
READ  1000 rec 0.070 sec; For ac=SEQUENTIAL fo=UNFORMATTED st=OLD     sh=COMPAT  

Fixing call randomfile now produces more expected performance.

The results also show that omitting SHARE= can improve the direct performance. Sequential access is somewhat faster with the SHARE= options. Is there a need for this file access management ?

You should try different combinations of rec_len and num_rec and see how the run times scale up, identifying cache usage.

The following is the latest test program I generated, where I tried to provide more consistent OPEN options. ( still not complete !!)

!FTN95 application... 
 PROGRAM main 
!  integer print_every 
!  integer failed_open,failed_delete,failed_close,failed_write
  integer, parameter :: rec_len = 1940 
  integer   max_recs, stest, jtest, i, icode, icheck
  character file_name*80
  character iorecord(rec_len)*1
  character ddate*8, ttime*10, zzone*5 
  integer   values(8)
  real      elapse_time, start_open, start_loop, end_loop
  external  elapse_time
!
  character share(6)*8, oper(6)*6, access(6)*10, form(6)*11, status(6)*7 
     DATA OPER   /'WRITE',  'WRITE', 'READ',  'WRITE',     'WRITE',     'READ'/ 
     DATA STATUS /'REPLACE','OLD',   'OLD',   'REPLACE',   'OLD',       'OLD'/ 
     DATA ACCESS /'DIRECT', 'DIRECT','DIRECT','SEQUENTIAL','SEQUENTIAL','SEQUENTIAL'/ 
     DATA FORM   /6*'UNFORMATTED'/ 
     DATA SHARE  /' ', 'DENYNONE', 'DENYRW', 'DENYWR', 'DENYRD', 'COMPAT'/ 

! Test program to open a unformatted direct access file, then write several records 
! then close it and try again. Each failure to open will be logged along with the error code and date/time 
! a 2 second wait will be done, then re-try. 
! 
! The first time, we'll delete the file, then create as a new, then old from then on 
! 
  call date_and_time(ddate,ttime,zzone,values) 
  print *,'Starting the test at: ',ddate(1:8),' ',ttime(1:10) 
!
  max_recs=1000 
!
  do stest=1,6 ! share
    write (file_name, fmt='(a,i0,a)') 'testfile',stest,'.dat'
    print *,' '
    print *,' ',share(stest),' for ', trim (file_name)

    do jtest=1,6 
      if ( jtest==1 .or. jtest==4) call delete_file (file_name)
      start_open = elapse_time () 
      if ( share(stest) == ' ') then
        open (unit   = 15,                 &
              file   = file_name,          &
              iostat = icode,              &
              err    = 12000,              &
              access = access(jtest),      &
              form   = form(jtest),        &
              status = status(jtest),      &
              recl   = rec_len )
      else if ( access(jtest) == 'DIRECT' ) then
        open (unit   = 15,                 &
              file   = file_name,          &
              iostat = icode,              &
              err    = 12000,              &
              access = access(jtest),      &
              form   = form(jtest),        &
              status = status(jtest),      &
              recl   = rec_len,            &
              share  = share(stest) )
      else
26 Jan 2015 9:38 #15451

.ctd/

      else
        open (unit   = 15,                 &
              file   = file_name,          &
              iostat = icode,              &
              err    = 12000,              &
              access = access(jtest),      &
              form   = form(jtest),        &
              status = status(jtest),      &
              share  = share(stest) )
      end if
     ! the READ tests require that the file exists, so change 'replace' to 'old'

      start_loop = elapse_time ()  
      do i=1,max_recs 
        call randomfile (iorecord, rec_len) ! this is always left in to even out the loop timing 
        !This next line must change to reflect read or write and rec= if needed 
        select case (jtest) ! go to (1000,1000,2000,3000,3000,4000),jtest 
         case (1:2)  ! write i 
           write (15, rec=i, err=13000, iostat=icheck) iorecord 
         case (3)    ! read i
           read  (15, rec=i, err=13000, iostat=icheck) iorecord 
         case (4:5)  ! write s
           write (15,        err=13000, iostat=icheck) iorecord 
         case (6)    ! read s
           read  (15,        err=13000, iostat=icheck) iorecord 
        end select
      end do
      end_loop = elapse_time () 
  
      write (*,11) oper(jtest),max_recs,' rec ',     &
                   end_loop-start_loop, ' sec; For', &
                   ' ac=',access(jtest),             & 
                   ' fo=',form(jtest),               &
                   ' st=',status(jtest),             &
                   ' sh=',share(stest) 
11    format (a,i0, a,f0.3,a, 4(a,a) )    
      close (unit = 15, iostat = icode) 
      call sleep1@ (2.) 
    end do ! jtest 
  end do ! stest 
!  pause 
  stop 

 13000 continue
  print *,'io error during accessing file', icheck 
  stop 

 12000 continue
  print *,'open error', icode 
  stop 
   
 END PROGRAM main 
 
 subroutine randomfile (iorecord, length)
   integer   length, i 
   character iorecord(length)*1 
   do i=1,length 
     iorecord(i) = char(int(255.*random@())) 
   end do 
   return 
 end 
    
 subroutine delete_file (file_name)
   character file_name*(*)
   integer   icode
!
      open  (unit   = 15,                 &
             file   = file_name,          &
             status = 'UNKNOWN',          &
             iostat = icode )
!
      close (unit   = 15,                 &
             status = 'DELETE',           &
             iostat = icode )
!
      if ( icode == 0 ) then
        write (*,*) trim (file_name),' deleted'
      else
        write (*,*) '### Unable to delete ',trim (file_name),' : check status !!'
      end if
 end subroutine delete_file

 real function elapse_time ()
   integer*8 clock, clock_rate
   call system_clock ( clock, clock_rate )
   elapse_time = dble (clock) / dble (clock_rate)
 end function elapse_time

I hope this helps. I'd be interested if you identify the problem combinations of ACCESS='DIRECT' and SHARE='xxx' You should see that larger files do not have a huge time penalty, especially when you can skip cache buffering by reducing the number of CLOSE then OPEN operations.

John

ps: there should be an option for larger posts when required !! (or attachments)

26 Jan 2015 11:19 #15453

Bill,

I have produced a test program that tests more alternatives of size and disk buffering. If you watch the program run, using windows explorer, you will see which share= options are continually updating the disk for access='direct'. Other options show the use of the disk cache with fewer changes to the stored file. Sequential access does not appear to work this way and might not not support multiple read/write. I tried to reduce flushing by minimising open/close, but that does not appear to be working as I hoped.

The latest test code is: ! program to test share= performance ! call do_test ( 194, 1000, .false. ) call do_test ( 2048, 2000, .false. ) call do_test ( 20488, 10000, .false. ) call do_test ( 20488, 10000, .true. ) end

!FTN95 application... 
 subroutine do_test (rec_len, max_recs, Minimise_Close)
!
  logical :: Minimise_Close
  integer :: rec_len 
  integer :: max_recs
!
  character iorecord(rec_len)*1
!
  logical :: open_file, close_file
!
  character file_name*80
  integer   stest, jtest, i, icode, icheck
!
  character share(6)*8, oper(6)*6, access(6)*10, form(6)*11, status(6)*7 
     DATA OPER   /'WRITE',  'WRITE', 'READ',  'WRITE',     'WRITE',     'READ'/ 
     DATA STATUS /'REPLACE','OLD',   'OLD',   'REPLACE',   'OLD',       'OLD'/ 
     DATA ACCESS /'DIRECT', 'DIRECT','DIRECT','SEQUENTIAL','SEQUENTIAL','SEQUENTIAL'/ 
     DATA FORM   /6*'UNFORMATTED'/ 
     DATA SHARE  /' ', 'DENYNONE', 'DENYRW', 'DENYWR', 'DENYRD', 'COMPAT'/ 
!
  character ddate*8, ttime*10, zzone*5 
  integer   values(8)
  real      elapse_time, start_open, start_loop, end_loop, mb_sec
  external  elapse_time

! Test program to open a unformatted direct access file, then write several records 
! then close it and try again. Each failure to open will be logged along with the error code and date/time 
! a 2 second wait will be done, then re-try. 
! 
! The first time, we'll delete the file, then create as a new, then old from then on 
! 
  call date_and_time(ddate,ttime,zzone,values) 
  print *,'Starting the test at: ',ddate(1:8),' ',ttime(1:10),'  for',max_recs,' records length =',rec_len
!
  do stest=1,6 ! share
    write (file_name, fmt='(a,i0,a)') 'testfile',stest,'.dat'
    print *,' '
    print *,' ',share(stest),' for ', trim (file_name)

    do jtest=1,6
!
      if ( jtest==1 .or. jtest==4) call delete_file (file_name)
      if ( minimise_close ) then
        open_file  = ( jtest == 1 .or. jtest == 4)
        close_file = ( jtest == 3 .or. jtest == 6)
      else
        open_file  = .true.
        close_file = .true.
      end if
!
      start_open = elapse_time () 
      if ( open_file ) then
        if ( share(stest) == ' ') then  ! omit share =
         if ( access(jtest) == 'DIRECT' ) then
           open (unit   = 15,                 &
                 file   = file_name,          &
                 iostat = icode,              &
                 err    = 12000,              &
                 access = access(jtest),      &
                 form   = form(jtest),        &
                 status = status(jtest),      &
                 recl   = rec_len )
         else
           open (unit   = 15,                 &
                 file   = file_name,          &
                 iostat = icode,              &
                 err    = 12000,              &
                 access = access(jtest),      &
                 form   = form(jtest),        &
                 status = status(jtest) )
         end if
        else   ! include share =
26 Jan 2015 11:21 #15454

.ctd/ else ! include share = if ( access(jtest) == 'DIRECT' ) then open (unit = 15, & file = file_name, & iostat = icode, & err = 12000, & access = access(jtest), & form = form(jtest), & status = status(jtest), & recl = rec_len, & share = share(stest) ) else open (unit = 15, & file = file_name, & iostat = icode, & err = 12000, & access = access(jtest), & form = form(jtest), & status = status(jtest), & share = share(stest) ) end if end if write (,) 'file opened' else if ( access(jtest) /= 'DIRECT' ) then rewind ( unit = 15 ) end if ! the READ tests require that the file exists, so change 'replace' to 'old' ! start_loop = elapse_time ()
do i=1,max_recs call randomfile (iorecord, rec_len) ! this is always left in to even out the loop timing !This next line must change to reflect read or write and rec= if needed select case (jtest) ! go to (1000,1000,2000,3000,3000,4000),jtest case (1:2) ! write i write (15, rec=i, err=13000, iostat=icheck) iorecord case (3) ! read i read (15, rec=i, err=13000, iostat=icheck) iorecord case (4:5) ! write s write (15, err=13000, iostat=icheck) iorecord case (6) ! read s read (15, err=13000, iostat=icheck) iorecord end select end do end_loop = elapse_time () ! mb_sec = real(max_recs)real(rec_len) / (end_loop-start_loop) / 1024. / 1024. write (,11) oper(jtest),max_recs,' rec ', & end_loop-start_loop, ' sec; For', & ' ac=',access(jtest), & ' fo=',form(jtest), & ' st=',status(jtest), & ' sh=',share(stest), & mb_sec 11 format (a,i0, a,f0.3,a, 4(a,a), f7.3,' Mb/sec' )
! if ( close_file ) then close (unit = 15, iostat = icode) write (,) 'file closed' call sleep1@ (2.) end if ! end do ! jtest end do ! stest ! pause return

 13000 continue
  print *,'io error during accessing file', icheck 
  stop 

 12000 continue
  print *,'open error', icode 
  stop 
   
 END subroutine do_test
 
 subroutine randomfile (iorecord, length)
   integer   length, i 
   character iorecord(length)*1 
   do i=1,length 
     iorecord(i) = char(int(255.*random@())) 
   end do 
   return 
 end 
26 Jan 2015 11:26 #15455

.ctd 2/ subroutine delete_file (file_name) character file_name*() integer icode ! open (unit = 15, & file = file_name, & status = 'UNKNOWN', & iostat = icode ) ! close (unit = 15, & status = 'DELETE', & iostat = icode ) ! if ( icode == 0 ) then write (,) trim (file_name),' deleted' else write (,*) '### Unable to delete ',trim (file_name),' : check status !!' end if end subroutine delete_file

 real function elapse_time ()
   integer*8 clock, clock_rate
   call system_clock ( clock, clock_rate )
   elapse_time = dble (clock) / dble (clock_rate)
 end function elapse_time

It does demonstrate performance changes on my HDD, so hopefully it can show changes on your disk alternatives for the various share= options. I hope the trend is consistent with the expected file access attributes.

John

26 Jan 2015 4:12 #15457

John,

[size=18:ed1e36fb58]WOW[/size:ed1e36fb58], you certainly have gone over and above what I could have ever expected, and I am very grateful! You put a lot of effort into this.

If I could state in one sentence what you've found: The use of SHARE has an effect on the performance, and certain SHARE options have a bigger effect than others. There's a lot more you did here, but would that be accurate in your view?

Yes, the original code was inefficient (i.e. use of random()). The original thought there was that if the Antivirus was triggering on some random data, perhaps this would show it. After I was able to identify and workaround the odd IOSTAT values (10005 and 10002) when files were opened, the need for randomized data actually went away. But, left it for consistency.The random() was left in for the reads for timing comparisons.

I only perform one open/close for each block of records, so I am curious about your comment (Mon Jan 26, 2015 3:38 am MST).

It is interesting that the SHARE would cause a difference in performance, and while your numbers are certainly faster than mine it still begs the question: Why?

As far as bigger records, no, not possible. My software has a legacy that dates back to the early 80's, when it was run on machines as simple as S-100 bus, CP/M. File size is set by the variables required. Would that I could change the sizes or formats!! It would make life so much easier. Some of the files created in those early days are still in use today, just much bigger!

When some of the users started using a networking environment in the mid 90's, the question of access restrictions came up. With multiple users on individual machines, sometimes EXCLUSIVE access is required when updating the master files (most of which are binary, unformatted, direct), while in most cases, simple READ access is needed. As well, there are some sequential, formatted files that can be affected. So, yes, I do need to have the SHARE set appropriately, and the setting of this access is dependent on the file usage at the time, and the software asks for that access as needed when opening the file.

I hope to replicate your results on my primary machine later today. It will be an interesting comparison.

I am looking at 'perfmon' to do some more detailed looks at the transfers and IO operations counts associated with these various operations. Once I get that up and running (and a little more time), I'll share it here.

27 Jan 2015 1:21 #15471

Bill,

I have now seen your problem !!

I transferred my latest test code to my notebook, which is running Windows 8.1. This OS must rival Vista as I find it an appalling downgrade from Windows 7.

I am getting huge delays on direct access files with some share= options. ( some cases 20sec, 40 sec and even 250 sec ! I'll update when the tests are complete.) I am trying running in a normal DOS box then running as administrator. Both have big delays for direct access files. Must have something to do with directory access rights. As these delays occur while writing and not just when opening, there could be some incompatibility or tuning required with salflibc.dll and Win 8.1.

Not sure what the solution is, but certainly removing Windows 8.1 would be a good approach.

John

27 Jan 2015 2:12 #15472

John, perhaps removing 8.1 might be a bit premature. It is nice to see that it can happen to others!

I do suspect it has something to do with policies or permissions, but I am at a loss to know. I'm not a SYSADMIN!

Bill

27 Jan 2015 4:14 #15485

I have been using W8.0 since May 2013, and W8.1 since Dec 2013. While the tiles interface is correctly worthy of ridicule and condemnation, the underlying OS is solid and competent. I do most of my work at the command line, and have a third party Start program to make the system behave similarly to W7.

I took John's program of Jan 26, 2015 11:19 am, and modified it as follows.

  1. Removed the call to sleep@. 2. Added a call to delete_file after the END DO !jtest 3. Used CPU_TIME for timing instead of SYSTEM_CLOCK.

These changes allow the code to be run on a ramdisk using FTN95 and Intel Fortran. I see none of the problems of slowdown that others have mentioned, indicating that 'something else' is the culprit. With FTN95 I get speeds of about 30 MB/s, for all except the runs with small files, where the speed can go down to 10 MB/s or less. With Intel Fortran, the corresponding speeds are 45 MB/s and 12 MB/s. (These 'speeds' are as reported by the program, on a laptop with an i5-4200U CPU)

Once you set up a comfortable program development environment under it, you will not complain about W8x. In a multiprocessing environment, I/O to files with shared access is subject to many influences in addition to hardware, OS and compiler brand differences.

27 Jan 2015 5:00 #15495

Just to be clear, using RAMDISK, while exceptionally fast, is not what is being measured. The measurement has to take into account the real world situation that seems to affect the speed, namely using a hard drive. If I was writing a huge number cruncher with vast arrays stored on disk, I'd certainly use RAMDISK!

As John and I have found (perhaps others?), there is something going on. It's not a reflection on FTN95; some folks don't appear to have this issue. Rather, it is an interaction between good/decent code and the OS (so far, WIN7, XP, Win2K on my side). As I also pointed out, if I use my local network to perform these simple benchmarks, I see no major speed issues (there is a little something there, though).

27 Jan 2015 5:40 #15497

Just to be clear, using RAMDISK, while exceptionally fast, is not what is being measured. Agreed, and I don't think that I suggested that. Rather, using a ramdisk removes as a factor the disk I/O (buffering, shared access, other processes using other parts of the disk) and my results serve to measure the I/O routines of the compiler runtime and the ramdisk driver.

Those who have seen dramatic slowdowns have not diagnosed the cause, and have not recorded enough of the circumstances to enable a guess to be made. As of now, we could attribute the slowdowns to butterflies in Tasmania flapping their wings.

27 Jan 2015 10:37 #15503

mecej4,

I agree with your changes 1. and 2. but I disagree with change 3. ( I'd recommend elapsed rather than CPU time)

I also changed the timer I posted to correct real4 precision problems as: real function elapse_time () integer8 clock, clock_rate integer*8 :: start = -1 call system_clock ( clock, clock_rate ) if ( start == -1 ) start = clock elapse_time = dble (clock-start) / dble (clock_rate) end function elapse_time

For access=DIRECT, what I am finding from the results is: share = COMPAT, DENYNONE or DENYRD ( about 3 Mb/sec Win 7, but .34 mb/sec Win 8.1) are much slower than: no share, DENYRW or DENYWR ( about 30 mb/sec on Win 7, 25 mb/sec on Win 8.1 ) For access=sequential, this does not occur as multiple write would not make sense(?) (I could post the pivot tables if required)

It looks like allowing multiple write with Access=DIRECT is the consistent performance problem and noticeably worse on my Win 8.1 'device'.

Mecej4, do you show this with your Win 8.1. performance ? Interesting you have a 4200U also.

My pc's are: Win 8.1 is a i5-4200U dell notebook with 8gb memory and Mcafee virus Win 7 is a i5-2300 acer desktop with 8gb memory and Microsoft virus. Looking at my Win 8.1 notebook, another main change between my Win 7 and Win 8.1 is the type of virus checker. Could this be a problem ?

Any ideas ?

John

As an aside, on delays on my Win 8.1 notebook, in Excel when selecting the number format of an accumulated value in a pivot table, there is a significant delay for the pop-up. Another of the annoying delays on the Win 8.1 device I don't like. It would be good to know the cause.

27 Jan 2015 11:34 #15504

John, the main reason that I turned from SYSTEM_CLOCK to CPU_TIME was that, with your old ELAPSED_TIME function, Intel Fortran gave zero elapsed time for many of the runs, indicating that 23 bits (in REAL*4) were not enough to hold elapsed time. I reran with your new code for ELAPSED_TIME, and the results are hardly different (comparing FTN95 run to FTN95 run and IFort run to IFort run).

The laptop on which I run these tests is an Ultrabook with 4G of RAM, Norton Security Suite, and has an internal 128 GB SSD, with the power plan set to Balanced. The only way to connect a conventional HD is through USB 2/USB 3 or Wifi, and using such a HD would give results that are probably not useful to most people who have other hardware.

If you suspect that your anti-virus software is affecting the results, you could disconnect from the network, disable the anti-virus, run the tests, and reenable the anti-virus before reconnecting to the network.

28 Jan 2015 12:06 (Edited: 28 Jan 2015 1:02) #15505

Mecej4,

I reran with your new code for ELAPSED_TIME, and the results are hardly different (comparing FTN95 run to FTN95 run and IFort run to IFort run).

When comparing SYSTEM_CLOCK to CPU_TIME, there should be a difference. Based on my observation of Task Manager, CPU_TIME should be much less, although CPU_TIME is not always recorded correctly. I will run again on my Win 8.1 and check the difference. I notice quite a few delays when using this pc so there are always the old chestnuts of incompatible drivers etc, when there is no clear reason for the delay.

John

ps: I have run for both CPU and elapsed time. For the cases where there is no significant delay CPU ~ Elapsed time. For the cases where there is significant delays, CPU time is much less and about the same time as for the share= tests where there are not significant delays. This could show that the delays are a waiting delay, but waiting on what ?

28 Jan 2015 12:53 #15506

there are always the old chestnuts of incompatible drivers etc, when there is no clear reason for the delay May be so these days, but I remember that older 386/486 PCs came with a plug-in VGA card and, until the card-specific drivers were installed, with the generic VGA driver scrolling on the CMD screen was so slow that the machine was nearly unusable.

Have you checked the list in the Device Manager control panel to see if any devices are lacking proper drivers?

28 Jan 2015 1:24 #15507

Regarding use of RAM Disk vs. HD:

Here is some data taken using my old test code without the generation of random data (not your new stuff John) run on the HD vs. the RamDisk. Clearly, the elapsed time is greater on the physical drive, but not by much. Except for those DIRECT UNFORMATTED write operations with SHARE=COMPAT , DENYRD and DENYNONE on the HD. In those cases, the HD access time stands out!

Notice that while the elapsed time for RAM Disk is fast, there are significant differences in time even then and under the same conditions as the HD times. This would indicate that additional time is being consumed doing an electronic version of what the HD is doing physically. Just doesn't take as long.

                        RAM Disk        HD                              
write   5000    rec      0.25928        84.62793        ac=dir  fo=unf  st=rep  sh=denynone
write   5000    rec      0.31299        84.89453        ac=dir  fo=unf  st=old  sh=denynone
read    5000    rec      0.08643         0.59277        ac=dir  fo=unf  st=old  sh=denynone
write   5000    rec      0.02734         0.02930        ac=seq  fo=unf  st=rep  sh=denynone
write   5000    rec      0.05469         0.05420        ac=seq  fo=unf  st=old  sh=denynone
read    5000    rec      0.08789         0.07422        ac=seq  fo=unf  st=old  sh=denynone
write   5000    rec      0.03174         0.03613        ac=dir  fo=unf  st=rep  sh=denyrw
write   5000    rec      0.02051         0.02783        ac=dir  fo=unf  st=old  sh=denyrw
read    5000    rec      0.00391         0.00635        ac=dir  fo=unf  st=old  sh=denyrw
write   5000    rec      0.00586         0.00537        ac=seq  fo=unf  st=rep  sh=denyrw
write   5000    rec      0.00586         0.00635        ac=seq  fo=unf  st=old  sh=denyrw
read    5000    rec      0.00537         0.00537        ac=seq  fo=unf  st=old  sh=denyrw
write   5000    rec      0.03711         0.03662        ac=dir  fo=unf  st=rep  sh=denywr
write   5000    rec      0.02002         0.02100        ac=dir  fo=unf  st=old  sh=denywr
read    5000    rec      0.00635         0.00635        ac=dir  fo=unf  st=old  sh=denywr
write   5000    rec      0.00195         0.00586        ac=seq  fo=unf  st=rep  sh=denywr
write   5000    rec      0.00586         0.00635        ac=seq  fo=unf  st=old  sh=denywr
read    5000    rec      0.00586         0.00586        ac=seq  fo=unf  st=old  sh=denywr
write   5000    rec      0.28809        97.95752        ac=dir  fo=unf  st=rep  sh=denyrd
write   5000    rec      0.27490        95.17139        ac=dir  fo=unf  st=old  sh=denyrd
read    5000    rec      0.08057         0.56641        ac=dir  fo=unf  st=old  sh=denyrd
write   5000    rec      0.02686         0.03857        ac=seq  fo=unf  st=rep  sh=denyrd
write   5000    rec      0.01904         0.01563        ac=seq  fo=unf  st=old  sh=denyrd
read    5000    rec      0.07275         0.07227        ac=seq  fo=unf  st=old  sh=denyrd
write   5000    rec      0.26709        88.37158        ac=dir  fo=unf  st=rep  sh=compat
write   5000    rec      0.26563        87.88721        ac=dir  fo=unf  st=old  sh=compat
read    5000    rec      0.05664         0.58643        ac=dir  fo=unf  st=old  sh=compat
write   5000    rec      0.01074         0.03564        ac=seq  fo=unf  st=rep  sh=compat
write   5000    rec      0.01074         0.04004        ac=seq  fo=unf  st=old  sh=compat
read    5000    rec      0.06104         0.08252        ac=seq  fo=unf  st=old  sh=compat

Something is there, and it is certainly more substantial than a butterfly!

28 Jan 2015 3:52 #15508

These are the results taken from a pivot table summary from my latest program which includes elapsed and cpu time reports. DIRECT SEQUENTIAL elapse cpu elapse cpu Row Labels Mb/sec Mb/sec Mb/sec Mb/sec WRITE_1 15.33 18.35 30.38 31.10 sh= 30.09 30.06 30.24 30.10 sh=COMPAT 0.45 6.25 27.95 30.67 sh=DENYNONE 0.45 6.13 30.42 30.88 sh=DENYRD 0.45 5.94 30.58 30.88 sh=DENYRW 31.36 32.13 31.99 32.06 sh=DENYWR 29.19 29.59 31.09 32.03

WRITE_2         15.63   18.73   29.96   30.72
sh=             30.99   31.20   30.87   30.92
sh=COMPAT        0.44    6.28   28.16   29.75
sh=DENYNONE      0.46    6.22   29.51   29.89
sh=DENYRD        0.46    6.23   29.26   30.81
sh=DENYRW       31.08   31.24   30.54   30.92
sh=DENYWR       30.36   31.20   31.43   32.03
 
READ            24.44   27.93   30.43   30.98
sh=             30.72   31.27   31.31   32.42
sh=COMPAT       15.37   22.98   29.46   29.96
sh=DENYNONE     20.12   25.37   30.04   30.06
sh=DENYRD       17.94   25.26   30.73   31.02
sh=DENYRW       30.68   31.35   30.32   31.46
sh=DENYWR       31.83   31.35   30.72   30.99
Grand Total     18.47   21.67   30.26   30.94

These results are the average of the 4 do_test results, as Mb per second based on either elapsed or cpu seconds. eg sh=COMPAT 0.45 6.25 27.95 30.67 this has an average of 0.45 mb per second performance, based on the reported elapsed time and 6.25 mb per second for reported CPU time. On my Win 7 pc, both these times and rates are similar, as there is no noticeable wait delay.

Bill, While your results show different performance between RAM and HDD, the delay event times are different, so I am still wondering about the cause of these delay events.

Still need to understand the nature of the delays being observed.

A solution is to avoid COMPAT, DENYNONE or DENYRD, which may not be a problem.

John

28 Jan 2015 4:42 #15512

John, yes, I am avoiding the 'bad boys'. Right now, I'm still performing conversion tasks on the software, bringing it in line with FTN95, and testing it thoroughly.

And, having said that, I'm putting this issue on my back burner. While I think this is important to understand, there's a limit to how deep down the rabbit hole I'm willing to go; there's only so much time with which to put out a product.

I am hoping that, sometime, there will be a root cause explanation, either one that offers a solution (like a policy setting), or, perhaps, something in the run-time system that needed a tweak and has now eliminated the problem.

If that doesn't happen, at least there is a workaround, and for that, I am grateful to the group here for answering my posting, and for asking more questions and offering things to try, and for taking to 'play' with settings.

Bill

1 Jul 2016 11:40 #17720

Bill,

Following your link to this, I reviewed what I had done and re-ran the tests. I get the following elapsed times on a 1tb HDD

 SUMMARY of 19mb write, write, read tests elapsed time

         SHARE            SEQUENTIAL          DIRECT
 SHARE =          test =     0.684200         0.722100    
 SHARE = DENYNONE test =     2.06150         18.2767    
 SHARE = DENYWR   test =     0.681900         0.714300    
 SHARE = DENYRD   test =     2.33870         18.4115    
 SHARE = DENYRW   test =     0.670002         0.705799    
 SHARE = COMPAT   test =     2.57771         17.8660    

These results show that SHARE= DENYNONE, DENYRD or COMPAT all have performance problems with DIRECT access files.

Based on this, COMPAT is not performing as I would expect from the documentation.

If you do not use SHARE= then there is no performance penalty, so the best plan is to be selective on how you share direct access files for allowing multiple write. I presume the consequence is that the file buffers are being constantly flushed. If this is the case the performance penalty is not surprising. Allowing other programs to write to this file while this program is creating and writing is a significant problem for managing the file integrity. Why would you consider the performance penalty a problem. Why would you do it ?

For SEQUENTIAL access, I don't think that multiple write would be an allowed possibility for that type of file, which is why it does not have a performance penalty.

Dismissing DIRECT access performance based on multiple write sharing is not a reasonable test.

John

Please login to reply.