LinuxQuestions.org

LinuxQuestions.org (/questions/)
-   Programming (https://www.linuxquestions.org/questions/programming-9/)
-   -   Derived Type in GFortran (https://www.linuxquestions.org/questions/programming-9/derived-type-in-gfortran-4175540810/)

AlexBB 04-26-2015 01:31 PM

Derived Type in GFortran
 
My environment is Ubuntu 14.04. I have this Fortran-90 routine:

Code:

subroutine fillThetaBounds (ThetaBounds,NN)
  ...............
  TYPE TripleType
    REAL*8 :: phi,thetaLower,thetaUpper
  END TYPE TripleType
  TYPE (TripleType), DIMENSION (:), intent (inout) :: ThetaBounds
  Integer*4, intent (IN) :: NN
  ................


In the calling routine there is a similar definition:

Code:

TYPE TripleType
    REAL*8 :: phi,thetaLower,thetaUpper
  END TYPE TripleType
  TYPE (TripleType), DIMENSION (:), POINTER :: ThetaBounds

You see, it is an allocatable type. I need it to store triplets of numbers.

I was also forced to put this definition in my interface:

Code:

subroutine fillThetaBounds (ThetaBounds,NN)
      integer, intent (in) :: NN
      TYPE TripleType
        REAL*8 :: phi,thetaLower,thetaUpper
      END TYPE TripleType
      TYPE (TripleType), DIMENSION (NN), intent (inout) :: ThetaBounds
    end subroutine fillThetaBounds

Then the trouble starts:

Code:

call fillThetaBounds (ThetaBounds,NN)
I get this compile error:

Code:

call fillThetaBounds (ThetaBounds,NN)
                        1
Error: Type mismatch in argument 'thetabounds' at (1); passed TYPE(tripletype) to TYPE(tripletype)

How do you like that?

Without this call everything compiles.

What is it? An error in the compiler?

Thanks, - Alex

Ragnathok 04-27-2015 09:29 AM

There is a difference between the type of the argument that is passed to the subroutine, and what the subroutine expects to receive. It happened in my case for instance when I passed an integer when the subroutine expected a real number, or when I passed a single-precision real number and the subroutine expected a double-precision real number.

Could it be because in the calling program, ThetaBounds is defined as a pointer while in the subroutine it is not? Maybe declaring both of them as a pointer, or none of them as a pointer, could solve the problem.

Also, if this does not work, in the calling program, do you allocate ThetaBounds before calling the subroutine?

AlexBB 04-27-2015 02:35 PM

Thanks, Ragnathok. I am away from that laptop now, so my response might be somewhat flawed. Answering the second question which is easier, YES, the array is allocatable in the calling routine. There are two other Double precision complex arrays also declared in the MAIN program, not the calling routine (I think) and they are also POINTER and allocated with the standard ALLOCATE (...) command. They are all declared as pointers. I found through trial and error that in the subroutine that is called, the same arrays cannot be declared as POINTER. They also must be declared in the interface without the POINTER keyword and in the interface they must be declared not as dummy variables but as ThetaBounds (N).

Yesterday afternoon I spent hours trying to make it work and finally dropped the idea. I finally declared ThetaBounds via a COMMON statement and the subroutine is now able to fill the array and I can access the result in the calling routine with no problem. Everything is still allocatable.

In the end I still was getting an error message saying that the COMMON statement missed SEQUENCE keyword. I obliged and the error message changed saying that the SEQUENCE should not be there. Acting as a blind kitten I was looking for the place to drop the SEQUENCE. Sure, when I put it in the TYPE definition as a separate line, the program finally compiled. Go figure.

The Fortran pointers are weird. Theoretically I have to define a "target" with => operator. I don't do it and everything seems to work fine.

Thanks, - Alex

suicidaleggroll 04-27-2015 04:17 PM

You've posted one calling routine and two different definitions of the routine. What are you actually using? Please post one pair of codes, the definition of the routine, and the caller of that routine.

As near as I can tell from your first post, you're allocating the array in the caller, and then you have a fixed size of the array (NN) in the routine. This is bad joo joo. Declare it as a pointer on both sides and allocate it in one.

caller:
Code:

double precision, dimension(:), pointer :: array => NULL()

allocate(array(num))
call routine(array)
! Do something with array
deallocate(array)

routine:
Code:

subroutine routine(array)
  double precision, dimension(:), pointer :: array

  ! Do something with array
end subroutine routine

Quote:

Originally Posted by AlexBB
I found through trial and error that in the subroutine that is called, the same arrays cannot be declared as POINTER. They also must be declared in the interface without the POINTER keyword and in the interface they must be declared not as dummy variables but as ThetaBounds (N).

The information you "found" through trial and error is wrong.

AlexBB 04-28-2015 06:08 PM

hello suicidal egg roll. The second routine is just a skeletal definition in the interface. As I tried to explain the compiler does not accept POINTER keyword in both calling and called routines. I am still at work and the code is home. I will post exact working (!) code in a few hours. However as I mentioned now I have a somewhat different arrangement. The called routine does not have the the same calling sequence. I was forced to place the allocatable array into a COMMON block.

suicidaleggroll 04-28-2015 07:14 PM

Did you try putting the type definition in a loadable module so it's common to all routines?

Also - you're never "forced" to use a common block. Common blocks are the lazy way out and should be avoided at all costs.


Eg (compilable, runable)
subs.f90
Code:

module subs

type TripleType
  real*8 :: phi,thetaLower,thetaUpper
end type TripleType

contains

subroutine fillThetaBounds(ThetaBounds)
  type(TripleType), dimension(:), pointer :: ThetaBounds

  ThetaBounds(1)phi = 6
end subroutine fillThetaBounds

end module subs

main.f90
Code:

use subs

type (TripleType), dimension(:), pointer :: ThetaBounds
integer :: num=10

allocate(ThetaBounds(num))
ThetaBounds(:)%phi = 2
ThetaBounds(:)%thetaLower = 3
ThetaBounds(:)%thetaUpper = 4
call fillThetaBounds(ThetaBounds)
ThetaBounds(3)%phi = 1

print *,ThetaBounds(:)%phi
print *,ThetaBounds(:)%thetaLower
print *,ThetaBounds(:)%thetaUpper
deallocate(ThetaBounds)

end


Code:

$ gfortran -c subs.f90
$ gfortran main.f90 subs.o
$ ./a.out
  6.0000000000000000        2.0000000000000000        1.0000000000000000        2.0000000000000000        2.0000000000000000        2.0000000000000000        2.0000000000000000        2.0000000000000000        2.0000000000000000        2.0000000000000000   
  3.0000000000000000        3.0000000000000000        3.0000000000000000        3.0000000000000000        3.0000000000000000        3.0000000000000000        3.0000000000000000        3.0000000000000000        3.0000000000000000        3.0000000000000000   
  4.0000000000000000        4.0000000000000000        4.0000000000000000        4.0000000000000000        4.0000000000000000        4.0000000000000000        4.0000000000000000        4.0000000000000000        4.0000000000000000        4.0000000000000000


AlexBB 04-28-2015 09:25 PM

OK, egg roll, here is the irrefutable truth :-)

This is how I define now three of my allocatable arrays. Two of them are double precision, complex, the third one is an array of triples.

Code:

TYPE TripleType
    SEQUENCE
    REAL*8 :: phi,thetaLower,thetaUpper
  END TYPE TripleType
  TYPE (TripleType), DIMENSION (:), POINTER :: ThetaBounds !!
  TYPE (TripleType) :: probe
  COMMON /SET8/ ThetaBounds
  DOUBLE COMPLEX, DIMENSION (:), POINTER :: Input
  DOUBLE COMPLEX, DIMENSION (:), POINTER :: Output
  NN = Narray (4)                                  !! NN is in fact = 128 in this run
  ALLOCATE (Input(NN),Output(NN),ThetaBounds(NN))

At the end of this subroutine (and this is subroutine) I deallocate them:

Code:

DEALLOCATE (Input,Output,ThetaBounds)
At one point inside of this routine there is a call to subroutine Forward.
Code:

call Forward (Input,Output,NN)
Subroutine Forward is, in fact, a FFT Librow routine. The code can be found at this website but it is in C and I had to convert it to Fortran because I could not debug the interoperability of Fortran and C. I had to convert the whole package of about 6 subroutines.

This is how subroutine Forward looks in its entirety:

Code:

subroutine Forward (Input, Output, N)
  implicit none
  Integer, intent(IN) :: N
  DOUBLE COMPLEX, DIMENSION (:), Intent (IN) :: Input
  DOUBLE COMPLEX, DIMENSION (:), Intent (OUT) :: Output
  call Rearrange (Input, Output, N)  !  Initialize data
  call Perform (Output, N, .false.)  !  Call FFT implementation
 end subroutine Forward

It is Fortran, not C. Note that the word POINTER is absent!!!

Subroutine Forward calls subroutine Rearrange and you will find the same arrangement there:

Code:

subroutine Rearrange (Input, Output, N)
  implicit none
  DOUBLE COMPLEX, DIMENSION (N), Intent (IN) :: Input
  DOUBLE COMPLEX, DIMENSION (N), Intent (OUT) :: Output
  Integer, intent (IN) :: N
  Integer :: Position1 = 1, Mask, Target1 = 1
  do while (Position1 < N)
    ........................

Please note that POINTER keyword is absent.

Then I have this module with an interface. I am posting it in its entirety.

Code:

MODULE fft_vect_mod

  interface

    subroutine Forward (Input, Output, N)
      Integer :: N
      DOUBLE COMPLEX, DIMENSION (N), intent (IN) :: Input
      DOUBLE COMPLEX, DIMENSION (N), intent (OUT) :: Output
    end subroutine Forward

    subroutine Rearrange (Input, Output, N)
      DOUBLE COMPLEX, DIMENSION (N), Intent (IN) :: Input
      DOUBLE COMPLEX, DIMENSION (N), Intent (OUT) :: Output
      Integer, intent (IN) :: N
    end subroutine Rearrange

    subroutine Perform (Data1, N, scaled)
      Integer :: N
      DOUBLE COMPLEX, DIMENSION (N), Intent (INOUT) :: Data1
      logical :: scaled
    end subroutine Perform
   
    subroutine fillThetaBounds (NN)
      integer, intent (in) :: NN
    end subroutine fillThetaBounds

  end interface

 end module

The POINTER keyword is likewise absent.

Now we are going to deal with the ThetaBounds array.

As I said, I got a weird error message when I tried to do a similar arrangement and was forced to consider alternatives. I finally put it in a COMMON block and this solved the problem. The declaration for ThetaBounds is posted above and also below in the subroutine. The array ThetaBounds is used in subroutine fllThetaBounds

Code:

subroutine fillThetaBounds (NN)
  implicit none
  TYPE TripleType
    SEQUENCE
    REAL*8 :: phi,thetaLower,thetaUpper
  END TYPE TripleType
  TYPE (TripleType), DIMENSION (:), POINTER :: ThetaBounds !!
  COMMON /SET8/ ThetaBounds
  Integer*4, intent (IN) :: NN
  .............................

Well your dislike of COMMON blocks is well known in the community, I mean not your personal dislike but people like you. Unfortunately in this case with this enormous program where I have to handle thousands of variables (FFT is very small part of it) placing them all into calling sequence for the procedures would have been a logistic nightmare. Just one example, zeroes and weights for Gauss-Legendre quadrature have two arrays of 1024 size each, and there are many more.

You can see that for some reason the called routine here accepted the POINTER keyword and I think it is because the triplets array is not in the calling sequence and the subroutine does not deal with dummy variables. Could be?

This is all for now. Everything compiles and runs. Thanks.

AlexBB 04-29-2015 08:51 AM

Suicidaleggroll, you've helped me in the past and I respect you very much but I think this time you may be wrong, at least partially, but I will still have to read your post a few more times to make complete sense out of it. Thanks, - Alex

suicidaleggroll 04-29-2015 10:03 AM

Quote:

Originally Posted by AlexBB (Post 5354807)
This is how subroutine Forward looks in its entirety:

Code:

subroutine Forward (Input, Output, N)
  implicit none
  Integer, intent(IN) :: N
  DOUBLE COMPLEX, DIMENSION (:), Intent (IN) :: Input
  DOUBLE COMPLEX, DIMENSION (:), Intent (OUT) :: Output
  call Rearrange (Input, Output, N)  !  Initialize data
  call Perform (Output, N, .false.)  !  Call FFT implementation
 end subroutine Forward

It is Fortran, not C. Note that the word POINTER is absent!!!

Why? You ported the code, why don't you add it?

Quote:

Originally Posted by AlexBB (Post 5354807)
As I said, I got a weird error message when I tried to do a similar arrangement and was forced to consider alternatives.

As I mentioned above, you're re-declaring the TripleType type everywhere you use it, this will lead to a conflict. Instead you should define it in a module, once, then just use that module everywhere you need that type.

Quote:

Originally Posted by AlexBB (Post 5354807)
Well your dislike of COMMON blocks is well known in the community, I mean not your personal dislike but people like you.

"People like me"? What does that mean? People who care about usable, readable, and maintainable code? There's a reason we dislike common blocks - they're terrible 99.999% of the time. They make the code unreadable and unmaintainable, and lead to massive memory problems VERY easily. They're also COMPLETELY unnecessary 99.999% of the time, this being one of them.

Quote:

Originally Posted by AlexBB (Post 5354807)
Unfortunately in this case with this enormous program where I have to handle thousands of variables (FFT is very small part of it) placing them all into calling sequence for the procedures would have been a logistic nightmare. Just one example, zeroes and weights for Gauss-Legendre quadrature have two arrays of 1024 size each, and there are many more.

So group them together using types.



Here's a working example passing pointers between caller and function with pointer declared on both ends, using both standard arrays as well as types, and no common blocks:
subs.f90
Code:

module subs

type TripleType
  real*8 :: phi,thetaLower,thetaUpper
end type TripleType

contains

subroutine fillThetaBounds(ThetaBounds, otherarray)
  type(TripleType), dimension(:), pointer :: ThetaBounds
  real, dimension(:), pointer :: otherarray

  ThetaBounds(1)%phi = 6
  otherarray(2) = 4
end subroutine fillThetaBounds

end module subs

main.f90
Code:

use subs

type (TripleType), dimension(:), pointer :: ThetaBounds
real, dimension(:), pointer :: otherarray
integer :: num=10

allocate(ThetaBounds(num))
allocate(otherarray(num))
ThetaBounds(:)%phi = 2
ThetaBounds(:)%thetaLower = 3
ThetaBounds(:)%thetaUpper = 4
otherarray(:) = 5
call fillThetaBounds(ThetaBounds,otherarray)
ThetaBounds(3)%phi = 1
otherarray(7) = 2

print *,ThetaBounds(:)%phi
print *,ThetaBounds(:)%thetaLower
print *,ThetaBounds(:)%thetaUpper
print *,otherarray
deallocate(ThetaBounds)
deallocate(otherarray)
end

Code:

$ gfortran -Wall -fbounds-check -c subs.f90
$ gfortran -Wall -fbounds-check main.f90 subs.o
$ ./a.out
  6.0000000000000000        2.0000000000000000        1.0000000000000000        2.0000000000000000        2.0000000000000000        2.0000000000000000        2.0000000000000000        2.0000000000000000        2.0000000000000000        2.0000000000000000   
  3.0000000000000000        3.0000000000000000        3.0000000000000000        3.0000000000000000        3.0000000000000000        3.0000000000000000        3.0000000000000000        3.0000000000000000        3.0000000000000000        3.0000000000000000   
  4.0000000000000000        4.0000000000000000        4.0000000000000000        4.0000000000000000        4.0000000000000000        4.0000000000000000        4.0000000000000000        4.0000000000000000        4.0000000000000000        4.0000000000000000   
  5.0000000      4.0000000      5.0000000      5.0000000      5.0000000      5.0000000      2.0000000      5.0000000      5.0000000      5.0000000

What am I missing? Where is the problem?

AlexBB 04-29-2015 10:53 AM

Thank you very much, egg roll. It is a food for thought. Very interesting. I will be able to read it carefully and absorb in a day or two, on Friday. Today is Wednesday. Too busy at work. - Alex

AlexBB 05-01-2015 12:39 PM

Suicidaleggroll, I want to answer issues raised in your last post partially.

(1) The COMMON blocks. I don't know if you do a lot of numerical simulations. I think, for anyone who does it, using common blocks is an unavoidable option. I tried to place some of the massive arrays in a module and interface them but when I tried to use them in the main file with the main program and all other subroutines, I found that the array names are recognized but the values all came out to be zeros, when I ran ./a.out. I think this is another issue with the compiler.

The Stanford Fortran website does not condemn common blocks as you do but suggests that their usage should be minimized.

Also I have a question about this sentence:

Quote:

Why? You ported the code, why don't you add it?
What did you mean by that?

As I said, this is a partial response. I will try to review and answer other issues you raised.

Thanks, - Alex

suicidaleggroll 05-01-2015 12:50 PM

A big chunk of what I do is large numerical modeling and simulation. Most programs are well over 50k lines, most closer to 100k. None of them use common blocks. It is most certainly not necessary or unavoidable, far from it.

It sounds like you just messed up the syntax, or aren't implementing it correctly. I gave you examples above for declaring a type in a module, using it in the main program, and passing it to a subroutine. That type only had three doubles, but there's no reason it can't have tens or hundreds of fields, some scalars, some arrays, etc.

As for the porting comment - you said that you ported the code from C, and then you pointed out that it doesn't have "pointer" in the declaration. The only reason it doesn't have "pointer" in the declaration is because you didn't put "pointer" in the declaration. I was confused why you were pointing out that it didn't say "pointer" when the only reason it didn't say "pointer" is because that's how you wrote it.

AlexBB 05-01-2015 05:37 PM

Wow, my respect for you just gone up significantly. So, you are a fellow numerical "modeller?" Is it the correct word? It is very interesting. I may need some time to really digest it all, everything you posted, perhaps even during this weekend. Reworking a code drastically is not something unknown to me. Thanks much. - Alex

AlexBB 05-01-2015 06:27 PM

OK, I tried to implement one of your suggestions, namely to get rid of one of the COMMON statements because it contains massive arrays for Gauss-Legendre quadratures. The numbers which I again borrowed from C code blocks contain 25 significant digits. It is quadruple precision. So, I placed the arrays containing the abscissas and weights into a module. If you recalled I stated in one one of the previous posts that I got zeroes out of them but I had a different arrangement. Then I placed them in a subroutine and the subroutine inside an interface. Now there is no subroutine and no interface.

Still it does not really work. It is weird but I get only 8 (eight!) significant digits when I try to print the values in the main program. Can you explain why? Perhaps I am doing something wrong? In a situation like this I still cannot use them unless they are in a COMMON block.

Thanks, - Alex

AlexBB 05-01-2015 06:46 PM

It is not working. Strange, weird things happen. I did not notice first but I also posted in the module along with the arrays, a COMMON statement with the array names. It compiled but gave me what I consider single precision output which is unacceptable. When I commented out the COMMON statement it did not even compile and gave me this error:

Code:

sphere_perspective.f90:(.text+0x56fa): undefined reference to `__sph_persp_mod_MOD_x64'
x64 array is array of abscissas for 128 point Gauss-Legendre quadrature.

The strange thing is: the compiler seems to recognise that the x64 array is located in sph_persp_mod.f90 but still claims that it is not referenced.

On the other hand when I uncomment out the COMMON statement in the module it works but the main routine does NOT have this COMMON block. What does it have to do with the block?

It is frustrating. I don't know what kind of numerical simulations you do but you must have encountered something like this, how else? Where is your wisdom and experience?

Thanks, - Alex

P.S. Again I want to remind that I have Ubuntu 14.04.


All times are GMT -5. The time now is 11:49 PM.