Silverfrost Forums

Welcome to our forums

%ss and browse_for_folder@ under 64bit

11 Jun 2016 8:49 #17627

Hello I'm transferring now all my programs to 64bit, they will be faster and I can allocate memory up to 12 GB unter 16GB RAM. I have only problems with browse_for_folder@, it always produce an arror. I get an Silverfrost exception report, RPC server is unavailable within KERNELBASE.dll. On the other hand, I can't read with %ss any prarameters from the .INI file and also, I can't write to the .INI file. What I have made wrong?

Thanks for Help

Chemie

11 Jun 2016 4:08 #17630

In both cases a short sample program would help to identify reasons for the failure. browse_for_folder@ should be OK. There might be problems with %ss concerning protected folders. Post some samples and I will check them out.

12 Jun 2016 12:07 #17637

Hi Paul, here are the two sample programs: browse_for_folder@:

  winapp 
  program suchefolder
  use mswin
  implicit none
  character*80 title,path
  logical folder
  title='Suche Folder'
  call browse_for_folder@(title,path) 

! folder=browse_for_folder@(title,path) end

In both cases of call there will be the exception report.

%ss:

  winapp 
  program sstest
  use mswin
  implicit none
  integer*4 ssctrl,testvalue,a,openctrl
 testvalue=0
  ssctrl=-1
  a=winio@('%ss[SSTest/SSTest]&',ssctrl)
  a=winio@('%ww[invisible]&')
  a=winio@('%nlTestvalue: %rd&',testvalue)
  a=winio@('%lw',openctrl)
  call sleep@(0.01)
  openctrl=0
  call window_update@(openctrl)
  a=winio@('%ca[Result]&')
  a=winio@('%nlResult: %wd&',testvalue)
  a=winio@('%2nl%cn%9`bt[OK]')
  end

The File SSTEST.INI contains:

[SSTest] Testvalue=1000

When I build with win32, testvalue is 1000, with x64 testvalue is 0. Thank you for looking. Chemie

13 Jun 2016 5:13 #17642

I can confirm that both of these need fixing for 64 bits and I made a note of this.

13 Jun 2016 10:49 #17648

I'm getting the same problem. It opens the browse-for-folder dialog window but fails when I click on almost anything - though did actually create a new folder when I simply clicked on 'Make new folder' (in the default location)

13 Jun 2016 12:58 #17651

The %ss issue has now been fixed.

For me, browse_for_folder@ does not even get started (Exception: RPC server not available).

14 Jun 2016 8:34 #17660

Quoted from PaulLaidler The %ss issue has now been fixed.

For me, browse_for_folder@ does not even get started (Exception: RPC server not available).

Thank you for fixing the %ss issue. When I get an exception report, how can I see the line number, which is generating the error? When I use CheckMatex64 I get the building error: error 1205: - /CHECK is not available in FTN95/64 when I use Debugx64 or Releasex64 I get only error adresses, but no line numbers. Thanks for Help Chemie

14 Jun 2016 11:08 #17663

64 bit browse_for_folder@ has now been fixed for the next release.

Use /debug and try launching SDBG64.exe using your exe and step through the program or click on 'continue'.

18 Jun 2016 3:39 #17680

Quoted from PaulLaidler 64 bit browse_for_folder@ has now been fixed for the next release.

Use /debug and try launching SDBG64.exe using your exe and step through the program or click on 'continue'.

Hello

Sorry, but I don't use the command line. I use only Plato under Windows, its more uncomplicated for me. Here I have found, when I use the new Plato, no differenz between 'Release win32' and 'Debug32', always I get the debug-version. When I use 'Debugx64' and 'release64' I get always the same, in this case the Release-version.

Another Problem I have found with the intrinsic subroutine ichar. For example I get under x64 negativ values, for my opinion I can't get negativ values, specially, when I transfer the Pixelvalues from an 24bit grahic area. The example program runs corect under win32 and give back the values 100 and 200, the win64 programs gives 100 and -56, this is not corect.

  winapp 

  program ichartest
  use mswin
  implicit none

  integer*4 a,iclow,ichigh

character*1 charlow,charhigh
iclow=0
    ichigh=0
charlow=char(100)
charhigh=char(200)
iclow=ichar(charlow)
  ichigh=ichar(charhigh)

  a=winio@('%ca[Result]&')
  a=winio@('%nllow: %wd  high: %wd&',iclow,ichigh)
  a=winio@('%2nl%cn%9`bt[OK]')

  end

Chemie

19 Jun 2016 1:37 #17681

The problem appears to be with the result of ichar for characters with the 8th bit set. /64 gives the wrong result. Looks as if ichar is giving integer1 result then equated to I4. See the following code for /32 and /64 integer4 i,j integer1 k(4) character c equivalence (j,k) ! do i = 92,206,20 c = char (i) j = ichar (c) write (,) c,i,j,k end do ! do i = 92,206,20 c = char (i) j = ichar (c) j = iand (j,255) write (,) c,i,j,k end do ! end

19 Jun 2016 2:09 #17683

Hello

Sure, it works with iand(ichar(c),255) instead of ichar(c) but unfortunately, I have do change all my programs.

But, sorry, I have found 2 more problems:

  winapp 

  program timetest
  use mswin
  implicit none

  integer*4 a
real*8 zeitanf,zeitend

  zeitanf=HIGH_RES_CLOCK@(.TRUE.)
call sleep@(1.0)
  zeitend=HIGH_RES_CLOCK@(.FALSE.)

  a=winio@('%ca[Meldung]&')
  a=winio@('%cnCPU-Zeit!&')
  a=winio@('%2nlDie CPU-Zeit beträgt: %wf sec&',zeitend-zeitanf)
  a=winio@('%2nl%cn%9`bt[OK]')

  end

gives absurd values for the cputime, always different, when I start once more. Win32 works normal.

The other problem is the reading of jpeg-files. get_dib_size@ and get_dib-block@ are not working with some (in my case photos from my digitalcamera, I can't send here an example) jpegfiles. I don't know, what is the difference between my photos and other 'normal' jpegfiles. The error occurs also with Win32.

Chemie

19 Jun 2016 4:18 #17684

The diffrence between my digitalcamera jpegs and normal jpegs is that there are missing the JFIF-notation. When I insert at position 3 the sequenz

FF E0 00 10 4A 46 49 46 00 01 01 01 00 B4 00 B4 00 FF E1

then I have a normal jpeg.

Chemie

20 Jun 2016 1:31 #17685

Chemie,

HIGH_RES_CLOCK@ is VERY badly named, as it does not work in /64 and works very badly in 32 bit.

Preferable /64 routines for elapsed time are: SYSTEM_CLOCK intrinsic, STDCALL QUERYPERFORMANCECOUNTER 'QueryPerformanceCounter' (REF):LOGICAL*4, or INTEGER(KIND=4) FUNCTION RDTSC_VAL@()

The clock tick rate is an issue. For these last 2 timers is found by: STDCALL QUERYPERFORMANCEFREQUENCY 'QueryPerformanceFrequency' (REF):LOGICAL*4 From my recent testing, RDTSC_RATE@ = QueryPerformanceFrequency * 1024.

All these timers appear to be based on RDTSC

My recommendation is to use SYSTEM_CLOCK (ease of use), or RDTSC_VAL@() (most accurate)

Note: The function cpu_clock@ is not available for 64 bit applications and has been replaced by rdtsc_val@... INTEGER(KIND=4) FUNCTION RDTSC_VAL@()

winapp 

 program timetest 
 use mswin 
 implicit none 

 integer*4 a 
 real*8    zeitanf,zeitend 
 real*8    system_clock_sec
 external  system_clock_sec

! zeitanf=HIGH_RES_CLOCK@(.TRUE.) 
 zeitanf = system_clock_sec ()
 call sleep@ (1.0) 
! zeitend=HIGH_RES_CLOCK@(.FALSE.) 
 zeitend = system_clock_sec ()

 a=winio@('%ca[Meldung]&') 
 a=winio@('%cnCPU-Zeit!&') 
 a=winio@('%2nlDie CPU-Zeit beträgt: %wf sec&',zeitend-zeitanf) 
 a=winio@('%2nl%cn%9`bt[OK]') 

 end 

!====  System Clock  ============================================================
   real*8 function system_clock_sec ()
      integer*8 :: tick
      integer*8 :: tick_start = -1
      real*8    :: tick_rate  = -1
      integer*8 clock_tick_rate, clock_tick
      external  clock_tick_rate, clock_tick
!
      tick             = clock_tick ()
      if (tick_rate < 0) then
        tick_rate      = clock_tick_rate ()
        tick_start     = tick
      end if
      system_clock_sec = dble(tick-tick_start) / tick_rate
   end function system_clock_sec

   integer*8 function clock_tick ()
      integer*8 :: count
!
      call system_clock (count)
!
      clock_tick = count
   end function clock_tick
 
   integer*8 function clock_tick_rate ()
      integer*8 :: count_start
      integer*8 :: count_rate = -1
!
      if ( count_rate < 0) then
        call system_clock (count_start, count_rate)
      end if
!
      clock_tick_rate = count_rate
   end function clock_tick_rate
20 Jun 2016 1:35 #17686

As a more extensive comparison of preferred elapsed time timers, all based on RDTSC and working for /32 or /64, the following example is a approach I have adopted and works on all recent pc's I have. winapp

 program timetest 
 use mswin 
 implicit none 

 integer*4 a, i
 real*8    zeitanf,zeitend 
 real*8    test_sec
 external  test_sec

do i = 1,10
! zeitanf=HIGH_RES_CLOCK@(.TRUE.) 
 zeitanf = test_sec (i)
 call sleep@ (1.0) 
! zeitend=HIGH_RES_CLOCK@(.FALSE.) 
 zeitend = test_sec (i)
 write (*,*) zeitend-zeitanf
end do

 a=winio@('%ca[Meldung]&') 
 a=winio@('%cnCPU-Zeit!&') 
 a=winio@('%2nlDie CPU-Zeit beträgt: %wf sec&',zeitend-zeitanf) 
 a=winio@('%2nl%cn%9`bt[OK]') 

 end 

 real*8 function test_sec (i)
 integer*4 i
 real*8    system_clock_sec, QueryPerformance_sec, RDTSC_sec
 external  system_clock_sec, QueryPerformance_sec, RDTSC_sec
!
  select case ( mod(i,3) )
    case (0) 
     test_sec =  system_clock_sec ()
    case (1)
     test_sec =  QueryPerformance_sec ()
    case (2)
     test_sec =  RDTSC_sec ()
  end select

  end function test_sec
  
!====  System Clock  ============================================================
   real*8 function system_clock_sec ()
      integer*8 :: tick
      integer*8 :: tick_start = -1
      real*8    :: tick_rate  = -1
      integer*8 clock_tick_rate, clock_tick
      external  clock_tick_rate, clock_tick
!
      tick             = clock_tick ()
      if (tick_rate < 0) then
        tick_rate      = clock_tick_rate ()
        tick_start     = tick
      end if
      system_clock_sec = dble(tick-tick_start) / tick_rate
   end function system_clock_sec

   integer*8 function clock_tick ()
      integer*8 :: count
!
      call system_clock (count)
!
      clock_tick = count
   end function clock_tick
 
   integer*8 function clock_tick_rate ()
      integer*8 :: count_start
      integer*8 :: count_rate = -1
!
      if ( count_rate < 0) then
        call system_clock (count_start, count_rate)
        write (*,*) 'System_Clock', count_rate,' ticks per second'
      end if
!
      clock_tick_rate = count_rate
   end function clock_tick_rate

!====  Query Perform  ===========================================================
! QueryPerformanceCounter   Windows API routine
   real*8 function QueryPerformance_sec ()
      integer*8 :: tick
      real*8    :: tick_rate = -1
      integer*8 QueryPerformance_rate, QueryPerformance_tick
      external  QueryPerformance_rate, QueryPerformance_tick
!
      if (tick_rate < 0)  &
      tick_rate            = QueryPerformance_rate ()
      tick                 = QueryPerformance_tick ()
      QueryPerformance_sec = dble (tick) / tick_rate
   end function QueryPerformance_sec

    integer*8 function QueryPerformance_tick ()
      STDCALL   QUERYPERFORMANCECOUNTER 'QueryPerformanceCounter' (REF):LOGICAL*4
      logical*4 ll
      integer*8 tick
!
      ll    = QUERYPERFORMANCECOUNTER (tick)
      QueryPerformance_tick = tick
    end function QueryPerformance_tick

    integer*8 function QueryPerformance_rate ()
      STDCALL   QUERYPERFORMANCEFREQUENCY 'QueryPerformanceFrequency' (REF):LOGICAL*4
      logical*4 ll
      integer*8 :: tick_rate = -1
!
      if ( tick_rate < 0 ) then
        ll    = QUERYPERFORMANCEFREQUENCY (tick_rate)
        write (*,*) 'QueryPerformance', tick_rate,' ticks per second'
      end if
      QueryPerformance_rate = tick_rate
    end function QueryPerformance_rate
20 Jun 2016 1:42 #17687
! .ctd
!====  RDTSC  ============================================================
   real*8 function RDTSC_sec ()
      integer*8 :: tick
      integer*8 :: tick_start = -1
      real*8    :: tick_rate  = -1
      integer*8 RDTSC_tick_rate, RDTSC_tick
      external  RDTSC_tick_rate, RDTSC_tick
!
      tick             = RDTSC_tick ()
      if (tick_rate < 0) then
        tick_rate      = RDTSC_tick_rate ()
        tick_start     = tick
      end if
      RDTSC_sec = dble(tick-tick_start) / tick_rate
   end function RDTSC_sec

   integer*8 function RDTSC_tick ()
      RDTSC_tick = RDTSC_VAL@()
   end function RDTSC_tick
 
   integer*8 function RDTSC_tick_rate ()
      STDCALL   QUERYPERFORMANCEFREQUENCY 'QueryPerformanceFrequency' (REF):LOGICAL*4
      logical*4 ll
      integer*8 :: tick_rate = -1
!
      if ( tick_rate < 0 ) then
        ll    = QUERYPERFORMANCEFREQUENCY (tick_rate)
        tick_rate = tick_rate * 1024
        write (*,*) 'RDTSC_tick', tick_rate,' ticks per second'
      end if
!
      RDTSC_tick_rate = tick_rate
   end function RDTSC_tick_rate

RDTSC_VAL@() is a 64 bit replacement for REAL10 CPU_CLOCK@ and appears to work for 32 bit also. As INTEGER8, I find this is a better option.

RDTSC rate is not documented and appears to be the processor rate. My approach for RDTSC_tick_rate works on all pc's I have available to test. (I do not know what happens on processors that have a turbo boost or are over-clocked. If someone can test this I would like to know)

Unfortunately, for processor usage time, the CPU_TIME intrinsic is the best available, which has a refresh rate of only 1/64 second. I would recommend to avoid all other timer routines.

20 Jun 2016 7:29 #17688

The ichar failure has now been fixed but probably not in time for the impending new release.

high_res_clock@ seems to work OK for me. The documentation is out of date but it should be OK if used as in the documented sample. You must declare the type of the return as REAL(2). For both 32 bit and 64 bits it uses QueryPerformanceFrequency which is also used by SYSTEM_CLOCK. So the results should be similar. However, for safety I have made the internal code for 64 bit high_res_clock@ to be the same as that for SYSTEM_CLOCK.

Note that high_res_clock@ is provided so that legacy code can be ported. For future portability, something like SYSTEM_CLOCK is preferred assuming it provides sufficient accuracy.

6 Jul 2016 8:41 #17745

Now I'm using FTN95 8.05. When linking some programs, I get an error in SALFLIBC64DLL, there were missing or not defined __ALLOCATE$ and __DEALLOCATE@

What can I do?

Thanks

Chemie

6 Jul 2016 9:41 #17746

FTN95 makes calls to __ALLOCATE$ and __DEALLOCATE@ and these are currently located in clearwin64.dll.

It is possible that you have an old clearwin64.dll on your machine that is getting in the way.

8 Jul 2016 10:38 #17753

Sorry, but I have found an other problem.

  winapp 

  program alloctest
  use mswin
  implicit none 

  integer*4 a,i3,aerror,xpix,ypix
  character*1, dimension(:,:,:), allocatable :: picture

i3=3

xpix=73728
  ypix=81920
allocate(picture(i3,xpix,ypix),stat=aerror)
  a=winio@('%ca[Meldung]&amp;')
  a=winio@('%2nlaerror= %wd x,y %wd %wd&amp;',aerror,xpix,ypix)
  a=winio@('%2nl%cn%9`bt[OK]')
if (aerror.gt.0) goto 1

picture(1,1,1)='a'
  picture(3,73728,81920)='a'

1 end

In this example, I get no Error (aerror=0), when allocating ca. 17 GB (3 x 73728 x 81920), my PC has only 16 GB, this can't go. When I alter the values for xpix and ypix, sometimes aerror will be 1, other times 0.

Thanks Chemie

8 Jul 2016 4:52 #17756

ALLOCATE calls upon the Windows API function HeapAlloc so any associated problems probably relate to HeapAlloc. My first thought is that HeapAlloc will not restrict the size to the amount of RAM and secondly that the result may depend on what else is running at the time.

The FTN95/ClearWin+ library function GlobalMemoryStatus@ may be useful in this context. See topic 368 in the ClearWin+ enhancements file cwplus.enh.

Please login to reply.