forums.silverfrost.com Forum Index forums.silverfrost.com
Welcome to the Silverfrost forums
 
 FAQFAQ   SearchSearch   MemberlistMemberlist   UsergroupsUsergroups   RegisterRegister 
 ProfileProfile   Log in to check your private messagesLog in to check your private messages   Log inLog in 

System exception 0x40010008: FormatMessage failed
Goto page 1, 2  Next
 
Post new topic   Reply to topic    forums.silverfrost.com Forum Index -> Support
View previous topic :: View next topic  
Author Message
narayanamoorthy_k



Joined: 19 Jun 2014
Posts: 142
Location: Chennai, IN

PostPosted: Thu Jan 25, 2018 7:16 pm    Post subject: System exception 0x40010008: FormatMessage failed Reply with quote

Dear All
I have this code as given below.
I compile using "Debug, Win32 mode in FTN95 V8.10 in VS2015 IDE.
I am unable to build and it shows the error as cited in topic.
The error happens at line 42 in subroutine extend_header().

Primarily, I want to assign values to a Header array type (info, comment), every time with new values and by incrementing the array size into +1 for every call. I have given the comments in the lines 42-45. I tried in Checkmate and Debug mode, but no use.
But the value of isize in Main program is correctly showing, but not in subroutine imax, where it is failing.
Can anyone help in knowing what is the error.

Code:
module mhead
          type header
             character(len=32) :: info   !format a80 col 2 to 81
             character(len=32) :: comment  !format a80 col 2 to 81
          end type header
   
   
          type (header), dimension(:), allocatable,save :: hdr
   end module mhead


program main
        use mhead
        implicit none
        integer :: hdrpar=1, allocstat, i, isize=1
        if (.not. allocated (hdr)) allocate (hdr(1:hdrpar), stat=allocstat)
        if(allocstat>0) stop "header parameters array dynamic allocation failed.."
 
        !array initialise
            do i = 1, size(hdr)             
                hdr(i)%info=''   !format a80 col 2 to 81
                hdr(i)%comment=''  !format a80 col 2 to 81         
            enddo
        hdr(1)%info="firstiteminfo"
        hdr(1)%comment = "firstitemcomment"
        isize=ubound(hdr,1)  !This shows the ubound as 1 correctly here.
        !    hdr array size = 1
        call extend_header(hdr) !call subroutine to extend hdr array to +1 and return the array
        !call extend_header(iaddr,isize)
        print*, ubound(hdr,1)  ! now ubound(hdr,1) = 2
        hdr(ubound(hdr,1))%info='Seconditeminfo'
        hdr(ubound(hdr,1))%comment = 'Seconditemcomment'
end program main


 subroutine extend_header(s)
        use mhead
         implicit none
          type (hdr), pointer :: s(:), tmp(:)
         integer*8 :: imax, istat=0
         if (allocated(s)) then
          imax = ubound(s,1)   !This shows wrong value and stops as 'access violation'
          !this should be 1 for the 1st call from main program.
        ! But this shows 8digit number which is wrong.
          ! I know, it is nothing but Pointer address from 1 to last of the array hdr.        
          if (.not. allocated(tmp)) allocate(tmp(1:imax),stat=istat)
          if (istat /= 0) stop 'extend_header():some problem in header tmp array allocation'
          tmp(1:imax) = s(1:imax)  ! this is also throws error as "access violation"
          deallocate(s)
          istat=0
          allocate(s(1:imax+1),stat=istat)
          if (istat /= 0) stop 'extend_header():some problem in extending header array allocation'
          s(1:imax) = tmp(1:imax)
          deallocate (tmp)
         
         else
          print*, 'extend_header(): header array ',s,' is not allocated.'
         end if
    end subroutine extend_header


But this code was running perfectly in earlier versions 7.10 and 7.20. But why it is failing here. The Pointer is used in subroutine for dynamically increase the array size on the orginal hdr arrays. But it is failing there in subroutine as unable to pickup ubound(s,1) ..

Is there any other betterway of doing this? Pls. suggest.

Thanks in advance,
_________________
Thanks and Regards
Moorthy
Back to top
View user's profile Send private message
narayanamoorthy_k



Joined: 19 Jun 2014
Posts: 142
Location: Chennai, IN

PostPosted: Thu Jan 25, 2018 7:20 pm    Post subject: Reply with quote

This also shows the following "Debug" errors before breaking the code.

Quote:
Loaded D:\A02\C03\Proj01\FDLFSoln\Winexample\Winexample\Debug\Win32\Winexample.exe @ z'00400000'
Loaded C:\Windows\SysWOW64\ntdll.dll @ z'77060000'
Loaded C:\Windows\SysWOW64\kernel32.dll @ z'76790000'
Loaded C:\Windows\SysWOW64\KernelBase.dll @ z'76660000'
Loaded C:\Windows\SysWOW64\sysfer.dll @ z'747a0000'
Loaded C:\Program Files (x86)\Silverfrost\FTN95\salflibc.dll @ z'10000000'
Loaded C:\Windows\SysWOW64\advapi32.dll @ z'76d90000'
Loaded C:\Windows\SysWOW64\shell32.dll @ z'75210000'
Loaded C:\Windows\SysWOW64\winmm.dll @ z'68300000'
Loaded C:\Windows\SysWOW64\hhctrl.ocx @ z'53e80000'
Loaded C:\Windows\SysWOW64\user32.dll @ z'74c60000'
Loaded C:\Windows\SysWOW64\gdi32.dll @ z'74890000'
Loaded C:\Windows\SysWOW64\comdlg32.dll @ z'74ee0000'
Loaded C:\Windows\WinSxS\x86_microsoft.windows.common-controls_6595b64144ccf1df_5.82.9600.17810_none_7c5b6194aa0716f1\comctl32.dll @ z'698d0000'
Loaded C:\Windows\SysWOW64\msvcrt.dll @ z'74dd0000'
Loaded C:\Windows\SysWOW64\sechost.dll @ z'74b70000'
Loaded C:\Windows\SysWOW64\rpcrt4.dll @ z'76ca0000'
Loaded C:\Windows\SysWOW64\combase.dll @ z'769f0000'
Loaded C:\Windows\SysWOW64\shlwapi.dll @ z'74e90000'
Loaded C:\Windows\SysWOW64\winmmbase.dll @ z'682e0000'
Loaded C:\Windows\SysWOW64\ole32.dll @ z'76b70000'
Loaded C:\Windows\SysWOW64\oleaut32.dll @ z'765b0000'
Loaded C:\Windows\SysWOW64\sspicli.dll @ z'74fe0000'
Loaded C:\Windows\SysWOW64\cfgmgr32.dll @ z'74c20000'
Loaded C:\Windows\SysWOW64\devobj.dll @ z'71cf0000'
Loaded C:\Windows\SysWOW64\cryptbase.dll @ z'74880000'
Loaded C:\Windows\SysWOW64\SHCore.dll @ z'71760000'
Loaded C:\Windows\SysWOW64\bcryptprimitives.dll @ z'74820000'
Loaded C:\Windows\SysWOW64\imm32.dll @ z'76d60000'
Loaded C:\Windows\SysWOW64\msctf.dll @ z'768d0000'
Loaded C:\Windows\katrack.dll @ z'746e0000'
Loaded C:\Windows\SysWOW64\uxtheme.dll @ z'6ecd0000'
Loaded C:\Windows\SysWOW64\dwmapi.dll @ z'6f0e0000'
Loaded C:\Windows\SysWOW64\kernel.appcore.dll @ z'746d0000'
Loaded C:\Windows\SysWOW64\wtsapi32.dll @ z'70af0000'
Unloaded C:\Windows\SysWOW64\wtsapi32.dll
System exception 0x40010008: FormatMessage failed

The program '[9732] Winexample.exe' has exited with code .

_________________
Thanks and Regards
Moorthy
Back to top
View user's profile Send private message
narayanamoorthy_k



Joined: 19 Jun 2014
Posts: 142
Location: Chennai, IN

PostPosted: Thu Jan 25, 2018 7:29 pm    Post subject: Reply with quote

Please see the Local constants values before breaking the Debug Run and the Error window herewith.

I have kept it in my Google Drive. Pls. click the below link to view the error files.

https://drive.google.com/drive/folders/1RZQb1Qt-yGznETP5EPr5qYxRH3FD_6wn?usp=sharing
_________________
Thanks and Regards
Moorthy
Back to top
View user's profile Send private message
PaulLaidler
Site Admin


Joined: 21 Feb 2005
Posts: 7912
Location: Salford, UK

PostPosted: Fri Jan 26, 2018 4:05 pm    Post subject: Reply with quote

The first error is on about line 39 where "hdr" should probably be "header".
Then ALLOCATED requires its argument be ALLOCATABLE.
Then you have a problem because s is a dummy argument and can't be ALLOCATABLE (at least not in the 95 Standard).
Back to top
View user's profile Send private message AIM Address
narayanamoorthy_k



Joined: 19 Jun 2014
Posts: 142
Location: Chennai, IN

PostPosted: Fri Jan 26, 2018 9:08 pm    Post subject: Reply with quote

The Error still exists.
I have changed the code as given below:

Code:
   module mhead
          type header
             character(len=32) :: info   !format a80 col 2 to 81
             character(len=32) :: comment  !format a80 col 2 to 81
          end type header
          type (header), dimension(:), allocatable,save :: hdr
          type (header), dimension(:), allocatable, save :: tmp
   end module mhead


program main
        use mhead
        implicit none
        integer :: hdrpar=1, allocstat=0, i=0, isize=1, istat=1
        if (.not. allocated (hdr)) allocate (hdr(1:hdrpar), stat=allocstat)
       
        if(allocstat>0) stop "header parameters array dynamic allocation failed.."
 
        !array initialise
            do i = 1, size(hdr)             
                hdr(i)%info=''   !format a80 col 2 to 81
                hdr(i)%comment=''  !format a80 col 2 to 81         
            enddo
        hdr(1)%info="firstiteminfo"
        hdr(1)%comment = "firstitemcomment"
        isize=ubound(hdr,1)  !This shows the ubound as 1 correctly here.
        !    hdr array size = 1
        !!call extend(hdr) !call subroutine to extend hdr array to +1 and return the array
        !call extend_header(iaddr,isize)

        call sayeesa(hdr,isize)

!         if (.not. allocated(tmp)) allocate(tmp(1:isize),stat=istat)
!         tmp = hdr
!       deallocate(hdr)
!       istat=0
!       allocate(hdr(1:isize+1), stat=allocstat)
!       hdr = tmp
!       deallocate(tmp)

      print*, ubound(hdr,1)  ! now ubound(hdr,1) = 2
        hdr(ubound(hdr,1))%info='Seconditeminfo'
        hdr(ubound(hdr,1))%comment = 'Seconditemcomment'
end program main


subroutine sayeesa(sarr,iarrcount)
    use mhead
    type (header), pointer :: sarr(:)
    integer, intent(INOUT) :: iarrcount
    integer :: K
    if (.not. allocated(tmp)) allocate(tmp(1:iarrcount),stat=istat)
    tmp(1:iarrcount) = sarr(1:iarrcount)
   deallocate(sarr)
   istat=0
    iarrcount=iarrcount+1
   allocate(sarr(1:iarrcount), stat=allocstat)
   sarr(1:iarrcount-1) = tmp(1:iarrcount-1)
   deallocate(tmp)

end subroutine sayeesa


But at Line 53,
Code:
tmp(1:iarrcount) = sarr(1:iarrcount)
the new error Access Violation is showing up now.

What I observe here during subroutine sayeesa() are:
1. the sarr array shows very high number of pointer addresses.
2. So, when copying the sarr array to tmp, it is not able copy the 2nd place onwards, which should not happen.
3. Here, I am copying the sarr values into tmp array and then extending the sarr array by 1 and then copying the old content from tmp to sarr.

Since the pointer array is more to copy into tmp array, the access violation error occurs. But how to control and correct this.

Primarily I want to do here, the below things.
1. Dynamically extended the array size
2. Create a temporary array to store the values from 1 to last exists from main array
3. now, extend the main array size by 1 (Ofcourse, you should deallocate the main array, to redefine)
4. then add the new value into the last position of the main array.
5. this process starts continuing, whenever, i want to add one more item values into the main array.

Can you inspect the code from these perspectives.

Mecej4, do you have any comments? Pls. let me know.
_________________
Thanks and Regards
Moorthy
Back to top
View user's profile Send private message
JohnCampbell



Joined: 16 Feb 2006
Posts: 2551
Location: Sydney

PostPosted: Sat Jan 27, 2018 1:59 am    Post subject: Reply with quote

In program main, you have declared hdr as an allocatable type (header), but in subroutine extend_header / sayeesa you declare it as a pointer.

To do what you are trying to do, I think you need TR 15581 to be implemented, which FTN95 does not support.
This can be overcome by having

subroutine extend_header
use mhead ! reference hdr direct from module
implicit none
type (header), allocatable :: tmp(:) ! note type name
integer*8 :: imax, istat=0
if (allocated(hdr)) then
imax = ubound(hdr,1) !This shows wrong value and stops as 'access violation'
...

ie, use hdr that is defined in the module and not pointer :: s(:)

I don't think you can write a general "subroutine extend_header (s)" then allocate a new array outside the module, without it going out of scope.

John
Back to top
View user's profile Send private message
JohnCampbell



Joined: 16 Feb 2006
Posts: 2551
Location: Sydney

PostPosted: Sat Jan 27, 2018 4:59 am    Post subject: Reply with quote

You could try something like this to overcome the array scope problem, by having a pool of allocatable target arrays in the module.
The following appears to work, you could possibly make poola and poolb private.
Code:
   module mhead
           type header
              character(len=32) :: info     ! format a80 col 2 to 81
              character(len=32) :: comment  ! format a80 col 2 to 81
           end type header

           type (header), dimension(:), allocatable, target :: poola, poolb
   contains

    subroutine extend_header (sarr)
     type (header), pointer :: sarr(:)
!
     integer :: iarrcount
     integer :: istat
!
     iarrcount = ubound (sarr,1)            ! This shows the ubound as 1 correctly here.

     if ( .not. allocated (poolb) ) then
        allocate(poolb(1:iarrcount+1),stat=istat)
        poolb(1:iarrcount) = sarr(1:iarrcount)
        sarr => poolb
        deallocate(poola,stat=istat)
        write (*,*) 'sarr => poolb ; size=',iarrcount+1
     else
        allocate(poola(1:iarrcount+1),stat=istat)
        poola(1:iarrcount) = sarr(1:iarrcount)
        sarr => poola
        deallocate(poolb,stat=istat)
        write (*,*) 'sarr => poola ; size=',iarrcount+1
     end if

     iarrcount = ubound (sarr,1)            ! This shows the ubound as 1 correctly here.
     sarr(iarrcount)%info=''             ! format a80 col 2 to 81
     sarr(iarrcount)%comment=''          ! format a80 col 2 to 81
     write (*,*) '  <extend_header> sarr size =',iarrcount       

    end subroutine extend_header

  end module mhead

 program main
         use mhead
         implicit none
         type (header), dimension(:), pointer :: hdr
         integer :: istat, i, isize=1, k

         allocate (poolb(0),stat=istat)
         hdr => poolb
!
         call extend_header (hdr)       ! call subroutine to extend hdr array to +1 and return the array

         hdr(1)%info    = "firstiteminfo"
         hdr(1)%comment = "firstitemcomment"
         isize = ubound(hdr,1)            ! This shows the ubound as 1 correctly here.
         write (*,*) 'ubound(hdr,1) = ',isize, '  loc(hdr) =',loc(hdr)       ! now ubound(hdr,1) = 1
!
        do k = 1,3
           call extend_header (hdr)       ! call subroutine to extend hdr array to +1 and return the array
           i = ubound(hdr,1)
           write (*,*) 'ubound(hdr,1) = ',i, '  loc(hdr) =',loc(hdr)       ! now ubound(hdr,1) = 2
           hdr(i)%info    = 'Seconditeminfo'
           hdr(i)%comment = 'Seconditemcomment'
        end do

 end program main


I rarely use local pointer arrays like "hdr", but work with allocatable arrays stored in a module.
It would be possible to make "extend_header" more general by increasing the pool of available arrays.

Is "type (header), dimension(:), pointer :: hdr" necessary ?
as I thought hdr would take the attributes from hdr => poolx
Back to top
View user's profile Send private message
JohnCampbell



Joined: 16 Feb 2006
Posts: 2551
Location: Sydney

PostPosted: Sat Jan 27, 2018 5:24 am    Post subject: Reply with quote

You would do better to extend in steps larger than 1, depending on how large you expect the system to be, perhaps increase size by max(size/2,1)
Code:
  module mhead

! supports 3 pools; only 2 used

     type header
       character(len=32) :: info
       character(len=32) :: comment
     end type header

     type (header), dimension(:), allocatable, target :: poola, poolb, poolc

   contains

    subroutine extend_header (sarr)
     type (header), pointer :: sarr(:)
!
     integer :: now, inc
     integer :: istat, ip
!
     ip = -1
     if ( allocated (poola) ) then
       if (loc(sarr) == loc(poola) ) ip = 1
     end if
     if ( allocated (poolb) ) then
       if (loc(sarr) == loc(poolb) ) ip = 2
     end if
     if ( allocated (poolc) ) then
       if (loc(sarr) == loc(poolc) ) ip = 3
     end if
     write (*,11) '  <extend_header> Sarr appears to be pointing to pool ',ip

     now = ubound (sarr,1)
     inc = max(now/2,1)

     if ( .not. allocated (poola) ) then
        allocate (poola(1:now+inc), stat=istat)
        poola(1:now) = sarr(1:now)
        sarr => poola
        write (*,11) '    sarr => poola ; size= ',ubound (sarr,1)

     else if ( .not. allocated (poolb) ) then
        allocate (poolb(1:now+inc), stat=istat)
        poolb(1:now) = sarr(1:now)
        sarr => poolb
        write (*,11) '    sarr => poolb ; size= ',ubound (sarr,1)

     else
        deallocate (poolc,stat=istat)
        allocate (poolc(1:now+inc), stat=istat)
        poolc(1:now) = sarr(1:now)
        sarr => poolc
        write (*,11) '    sarr => poolc ; size= ',ubound (sarr,1)
     end if

     if ( ip==1 ) deallocate (poola,stat=istat)
     if ( ip==2 ) deallocate (poolb,stat=istat)
     if ( ip==3 ) deallocate (poolc,stat=istat)

     now = ubound (sarr,1)
     sarr(now)%info=''
     sarr(now)%comment=''
!z     write (*,11) '  <extend_header> sarr size = ',now
  11 format (a,i0)       

    end subroutine extend_header

  end module mhead

 program main
         use mhead
         implicit none
         type (header), dimension(:), pointer :: hdr
         integer :: istat, i, isize=1, k

         allocate (poolc(0),stat=istat)
         hdr => poolc
!
         call extend_header (hdr)

         hdr(1)%info    = "first item info"
         hdr(1)%comment = "first item comment"
         isize = ubound(hdr,1)
         write (*,*) 'ubound(hdr,1) = ',isize, '  loc(hdr) =',loc(hdr)
!
        do k = 1,15
           call extend_header (hdr)
           i = ubound(hdr,1)
           write (*,*) 'ubound(hdr,1) = ',i, '  loc(hdr) =',loc(hdr)
           hdr(i)%info    = 'Next item info'
           hdr(i)%comment = 'Next item comment'
        end do

 end program main
Back to top
View user's profile Send private message
narayanamoorthy_k



Joined: 19 Jun 2014
Posts: 142
Location: Chennai, IN

PostPosted: Sat Jan 27, 2018 12:10 pm    Post subject: Re: Reply with quote

JohnCampbell wrote:
In program main, you have declared hdr as an allocatable type (header), but in subroutine extend_header / sayeesa you declare it as a pointer.

To do what you are trying to do, I think you need TR 15581 to be implemented, which FTN95 does not support.
This can be overcome by having

subroutine extend_header
use mhead ! reference hdr direct from module
implicit none
type (header), allocatable :: tmp(Smile ! note type name
integer*8 :: imax, istat=0
if (allocated(hdr)) then
imax = ubound(hdr,1) !This shows wrong value and stops as 'access violation'
...

ie, use hdr that is defined in the module and not pointer :: s(Smile

I don't think you can write a general "subroutine extend_header (s)" then allocate a new array outside the module, without it going out of scope.

John


Dear John

This is fantastic. Now, I realise the mistakes what I have done while coding.

The 2nd and 3rd example in using the target arrays poola,poolb, poolc is very effective way of extending this logic also. I have seen the 2nd code, including the logic of identification of deallocation of the poolx target arrays too. It was later included by you byediting the post..
That is very useful too. Thank you very much for your time and energy.

But I remember, this same code was working in V7.10 and V7.20 of FTN95. Not sure why.

Thank you very much.
_________________
Thanks and Regards
Moorthy
Back to top
View user's profile Send private message
narayanamoorthy_k



Joined: 19 Jun 2014
Posts: 142
Location: Chennai, IN

PostPosted: Tue Jan 30, 2018 7:24 pm    Post subject: Reply with quote

While I am going through these user-defined types, I get this question.

Let me take this example:

Code:
module mhead
 
    type header
       character(len=32) :: info
       character(len=32) :: comment
     end type header
 
    type bus
           real    :: voltpu  !to keep voltage in pu
           real    :: angle
      end type bus
   
    type load
           integer :: type     !format i1, 1 = pqbus, 2 pv bus, 3 slackbus col=2
           integer :: number   !format i5, col=3 to 7
           real    :: ldsmva    !format f8.2  col 80 to 87 to keep load power in mva
           real    :: ldpf      !format f8.2  col 88 to 95 to keep load power factor
      end type load      

         type trafo
            integer :: number     ! format i6, col 2 to 7
            character(len=8) :: name  ! format a8, col 8 to 15
            integer :: sbusno        ! format i5, col 16 to 20
            integer :: rbusno        ! format i5, col 21 to 25         
            real :: perloading        ! results: %loading
            real :: pycurrent         ! results: primary current in pu
            real :: sycurrent         ! results: secondary current in pu
         end type trafo

    
         type (header), dimension(:), allocatable, target :: poola, poolb, poolc
    type (bus), dimension(:), allocatable, target :: poold
    type (load), dimension(:), allocatable, target :: poole
    type (trafo), dimension(:), allocatable, target :: poolf

   end module mhead
   

   program main
         use mhead
         implicit none
         type (header), dimension(:), pointer :: hdr
         type (bus), dimension(:), pointer :: busa
         type (load), dimension(:), pointer :: loada
         type (trafo), dimension(:), pointer :: trafoa
      
         !integer :: istat, i, isize=1, k
         
         allocate (poolc(0),stat=istat)
         hdr => poolc
   allocate (poold(0), stat=istat)
   busa => poold
   end program main


The above code has 4 user-defined type and 2 of their pointers "hdr" and "busa" will be used further.

But how can I get to know that "hdr" belongs to the user-defined type "header" and "busa" is of user defined type "bus"

Is there any way to get this during run time of the code?

I am thinking of writing a overloading function, which does further activites based on its defined user-type it belongs to. Hence, I have the above question to check whether any method possible with FTN95 here. Please suggest.
_________________
Thanks and Regards
Moorthy
Back to top
View user's profile Send private message
JohnCampbell



Joined: 16 Feb 2006
Posts: 2551
Location: Sydney

PostPosted: Wed Jan 31, 2018 1:31 am    Post subject: Reply with quote

Quote:
But how can I get to know that "hdr" belongs to the user-defined type "header" and "busa" is of user defined type "bus"

I suspect that you don't need this approach, in that there are easier alternatives.
You need to investigate Generic procedures which are defined using an interface block, defined inside a MODULE.
My experience of "INTERFACE generic_name" is very limited, as I find I rarely need a generic procedure to cope with multiple types. I typically have a dataset that is for one type only. Also, I usually have generic types being intrinsic data types.

Your example has the following complications:
# your data type is a defined data type.
# your argument to the generic_procedure is a pointer.

I am not familiar with the possibilities as to what attributes can be transferred to a pointer via the statement:
xx_pointer => yy_target

Is it possible to associate rank or type ?
I am suggesting you should investigate these issues.

There are examples of defining generic procedures in an interface block and providing actual procedures for a range of intrinsic data types or a range of array rank.
I suggest you expand on this by first providing actual procedures for different derived types, then experimenting with pointers as arguments.

I have for a long time had a coding style that excludes using pointers. They just look to be an error prone concept.

Strangely, to some others condemnation, I insist on using non-standard coding approaches, like REAL*8, so I suggest you consider the coding style you are comfortable with. generic procedures using derived type pointers is not on my list.

John

PS: Also, why have a pool of 1 ? for the concept to work you need at least 2 alternatives for the switching and expand approach.
Back to top
View user's profile Send private message
narayanamoorthy_k



Joined: 19 Jun 2014
Posts: 142
Location: Chennai, IN

PostPosted: Wed Jan 31, 2018 8:37 am    Post subject: Reply with quote

JohnCampbell wrote:
There are examples of defining generic procedures in an interface block and providing actual procedures for a range of intrinsic data types or a range of array rank.
I suggest you expand on this by first providing actual procedures for different derived types, then experimenting with pointers as arguments.


Thanks John. Indeed, does our F77 tutorial (as part of FTN95) have those examples.

All are First order rank arrays "array(x)" here, which takes the user-defined types.

As each of the user-defined type matrices will be expanded during run-time, I am investigating the possibilities to check first on their user-defined type associated and then invoke the expanding that array dynamically, as we discussed earlier. The challenge here is that each type has different set of attributes associated, hence exclusive handling is necessary.

However, the nature of requirement is as I said earlier, check the associated user-defined type for the given array and then invoke them for expanding the dimensions during run time dynamically. It will be easier to keep a respective expand_array() routines separately, but the same code will be duplicated again and again for the respective user-defined type, which is also not a good way of coding. Hence exploring this possibility.

As far as the need is concerned, it is common-to-all here, I am trying to have a one common subroutine to do these two tasks together, including the OVERLOADING with a generic procedures.
_________________
Thanks and Regards
Moorthy
Back to top
View user's profile Send private message
narayanamoorthy_k



Joined: 19 Jun 2014
Posts: 142
Location: Chennai, IN

PostPosted: Wed Jan 31, 2018 1:23 pm    Post subject: Re: Reply with quote

Continuing...

Moorthy wrote:
As far as the need is concerned, it is common-to-all here, I am trying to have a one common subroutine to do these two tasks together, including the OVERLOADING with a generic procedures.


I am trying to look at making it very simple and effective. No need to bother about OVERLOADING features at all, as long as the identification of different user-defined types are done with simpler way.

Your views will help a lot. Please advise.
_________________
Thanks and Regards
Moorthy
Back to top
View user's profile Send private message
JohnCampbell



Joined: 16 Feb 2006
Posts: 2551
Location: Sydney

PostPosted: Fri Feb 02, 2018 5:21 am    Post subject: Reply with quote

Generic routines provide a single call, BUT you still need to write separate routines for all possible type/rank combinations.
It is just a verbose way of doing argument checking, which /CHECK can also do.
Not a fan of long winded verbose structures in F03/08. Just more opportunities to miss-type and provide coding errors.

John
Back to top
View user's profile Send private message
narayanamoorthy_k



Joined: 19 Jun 2014
Posts: 142
Location: Chennai, IN

PostPosted: Fri Feb 02, 2018 7:41 am    Post subject: Reply with quote

Thanks John

I was thinking this too, in writing separate subroutines to do, but wanted to cross check a better way of doing them.

On the other hand, if I introduce a index as an argument, in passing through to indicate the User-defined type passed on, I feel, all user-defined type structure should be made ALLOCATED, which may not optimal way, due to unused allocation would exists.

As each of these structures, will be a single dimensioned array "(x)", perhaps, writing a separate routines will be more effective way, which I agree with you.

Thanks for your time and suggestions, once again.
_________________
Thanks and Regards
Moorthy
Back to top
View user's profile Send private message
Display posts from previous:   
Post new topic   Reply to topic    forums.silverfrost.com Forum Index -> Support All times are GMT + 1 Hour
Goto page 1, 2  Next
Page 1 of 2

 
Jump to:  
You cannot post new topics in this forum
You cannot reply to topics in this forum
You cannot edit your posts in this forum
You cannot delete your posts in this forum
You cannot vote in polls in this forum


Powered by phpBB © 2001, 2005 phpBB Group