- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Hi,
I want to define a derived type PM consisting of an integer array ng(n1,n2) and a double vector zg(n3).
I wrote
:TYPE PM
INTEGER,ALLOCATABLE::ng(:,:)
DOUBLE PRECISION,ALLOCATABLE::zg(:)
END TYPE PM
n1, n2 and n3 are defined run time.
Then I finally want to allocate an array PMA with n4 of PM derived types.
n4 is defined at run time.
How do I allocate PM and PMA?
Best regards
Anders S
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
You have an error in your programming:
... CALL sub(PMA) ! *** 1 argument ... SUBROUTINE sub(n1,n2,n3,n4,PMA) ! *** 5 arguments
If you select the compile time check to generate and warn for interface mismatch you will receive a warning
Additionally:
SUBROUTINE sub(n1,n2,n3,n4,PMA) IMPLICIT NONE INTEGER,INTENT(IN)::n1,n2,n3,n4 TYPE PM INTEGER ng(n1,n2) DOUBLE PRECISION zg(n3) END TYPE PM
Your type PM, as written, cannot use an undefined value for the array dimension values (not defined until run time).
While (after fixing arguments) you could possibly use a Parameterized Derive-Type Statement:
In your situation it is not recommended. Something like the following could be used:
MODULE YourModuleName TYPE PM INTEGER,ALLOCATABLE::ng(:,:) DOUBLE PRECISION,ALLOCATABLE::zg(:) END TYPE PM contains SUBROUTINE sub(PMA) IMPLICIT NONE TYPE(PM), DIMENSION(:), ALLOCATABLE, INTENT(IN)::PMA ! following assunmes (requires) PMA is allocated, has index including 1, PMA(1)%zg is allocated and has index of 1 ! place tests and error actions here PRINT *,PMA(1)%zg(1) END SUBROUTINE sub END MODULE YourModuleName PROGRAM test USE YourModuleName IMPLICIT NONE INTEGER i,n1,n2,n3,n4 Type(PM),ALLOCATABLE::PMA(:) n1=20 n2=2 n3=1000 n4=5 ALLOCATE(PMA(n4)) DO i=1,n4 ALLOCATE(PMA(i)%ng(n1,n2)) ALLOCATE(PMA(i)%zg(n3)) ENDDO PMA(1)%zg(1)=3.14D0 CALL sub(PMA) DEALLOCATE(PMA) END PROGRAM test
Jim Dempsey
Link Copied
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
You can't allocate PM, it's a type.
First you allocate PMA:
type(PM), allocatable :: PMA(:) ... allocate (PMA(n4))
This doesn't allocate the ng and zg components of each element - you'll need to loop through the elements of PMA and allocate those separately, if desired.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Looks good. Note that when you deallocate PMA, all the subcomponents get deallocated automatically.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
when mecej4 set up the allocatable in MAGNI -- he used stat=err? Is this still a good idea?
INTEGER ERR INTEGER, ALLOCATABLE :: A(:), B(:) ... ALLOCATE(A(10:25), B(SIZE(A)), STAT=ERR) ! A is invalid as an argument to function SIZE
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Hi,
It may be interesting to use the derived type PMA as a subroutine argument. I have checked this in various sources but
did not find any "clear advice". I made a "best effort guess" in the supplied code but I know it is wrong. I would be most grateful to have this
matter clarified. Is there any best practice when it comes to defining derived types, e.g. using modules?
Best regards
Anders S
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Anders S. wrote:.. I have checked this in various sources but did not find any "clear advice". .. Is there any best practice when it comes to defining derived types, e.g. using modules?
Re: sources, have you looked at these?
https://www.amazon.com/FORTRAN-SCIENTISTS-ENGINEERS-Stephen-Chapman/dp/0073385891
https://www.amazon.com/Modern-Fortran-Style-Norman-Clerman/dp/052173052X
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
>>
INTEGER ERR
INTEGER, ALLOCATABLE :: A(:), B(:)
...
ALLOCATE(A(10:25), B(SIZE(A)), STAT=ERR) ! A is invalid as an argument to function SIZE
<<
As to which of A or B is allocated first, it is ambiguous at least to use SIZE(A) in this case. I think that the error message in the compiler version that you are using is inadequate. In Version 2020
error #6500: A bound in an allocate-shape-spec involves array inquiry about allocate-object in same ALLOCATE statement.
Jim Dempsey
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Anders,
When you supply code examples, please use the {...} code button to paste the text of the source code (select as Fortran format from the pull-down).
Pasting a screenshot makes it difficult for the readers to test your code.
Jim Dempsey
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
PROGRAM test IMPLICIT NONE INTEGER i,n1,n2,n3,n4 TYPE PM INTEGER,ALLOCATABLE::ng(:,:) DOUBLE PRECISION,ALLOCATABLE::zg(:) END TYPE PM Type(PM),ALLOCATABLE::PMA(:) n1=20 n2=2 n3=1000 n4=5 ALLOCATE(PMA(n4)) DO i=1,n4 ALLOCATE(PMA(i)%ng(n1,n2)) ALLOCATE(PMA(i)%zg(n3)) ENDDO PMA(1)%zg(1)=3.14D0 CALL sub(PMA) DEALLOCATE(PMA) STOP END !------------------------------------------ SUBROUTINE sub(n1,n2,n3,n4,PMA) IMPLICIT NONE INTEGER,INTENT(IN)::n1,n2,n3,n4 TYPE PM INTEGER ng(n1,n2) DOUBLE PRECISION zg(n3) END TYPE PM TYPE(PM),DIMENSION(n4)::PMA PRINT *,PMA(1)%zg(1) RETURN END
Hi,
FortranFan:
Which of the books do you prefer?
Jim:
Sorry for my screen copy! I have now supplied the code example in the right format.
Best regards
Anders S
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Anders S. wrote:..
FortranFan:
Which of the books do you prefer? ..
@Anders S.,
I recommend both of above books. I strongly recommend you get the first book by Stephen Chapman and go through it fully first. You can also consider a couple of other books but my suggestion will be to look at these after reviewing the book by Chapman:
https://www.amazon.com/Numerical-Computing-Fortran-Applied-Mathematics/dp/1611973112
Here's another reference:
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
You have an error in your programming:
... CALL sub(PMA) ! *** 1 argument ... SUBROUTINE sub(n1,n2,n3,n4,PMA) ! *** 5 arguments
If you select the compile time check to generate and warn for interface mismatch you will receive a warning
Additionally:
SUBROUTINE sub(n1,n2,n3,n4,PMA) IMPLICIT NONE INTEGER,INTENT(IN)::n1,n2,n3,n4 TYPE PM INTEGER ng(n1,n2) DOUBLE PRECISION zg(n3) END TYPE PM
Your type PM, as written, cannot use an undefined value for the array dimension values (not defined until run time).
While (after fixing arguments) you could possibly use a Parameterized Derive-Type Statement:
In your situation it is not recommended. Something like the following could be used:
MODULE YourModuleName TYPE PM INTEGER,ALLOCATABLE::ng(:,:) DOUBLE PRECISION,ALLOCATABLE::zg(:) END TYPE PM contains SUBROUTINE sub(PMA) IMPLICIT NONE TYPE(PM), DIMENSION(:), ALLOCATABLE, INTENT(IN)::PMA ! following assunmes (requires) PMA is allocated, has index including 1, PMA(1)%zg is allocated and has index of 1 ! place tests and error actions here PRINT *,PMA(1)%zg(1) END SUBROUTINE sub END MODULE YourModuleName PROGRAM test USE YourModuleName IMPLICIT NONE INTEGER i,n1,n2,n3,n4 Type(PM),ALLOCATABLE::PMA(:) n1=20 n2=2 n3=1000 n4=5 ALLOCATE(PMA(n4)) DO i=1,n4 ALLOCATE(PMA(i)%ng(n1,n2)) ALLOCATE(PMA(i)%zg(n3)) ENDDO PMA(1)%zg(1)=3.14D0 CALL sub(PMA) DEALLOCATE(PMA) END PROGRAM test
Jim Dempsey
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Hi Jim,
Thank you for your rapid and complete answer!
I had meanwhile searched the web and found a very similar problem and
rewritten the code, which resembled your answer. After a few corrections by looking
at your code, I arrived at the code below. I want to move the subroutine sub outside
the module as sub in the real case is a few hundred lines long. Compilation gives one error
which I have depicted. The error maybe come from moving sub outside the module?
Best regards
Anders S
MODULE PMd TYPE PM INTEGER,ALLOCATABLE::ng(:,:) DOUBLE PRECISION,ALLOCATABLE::zg(:) END TYPE PM END MODULE PMd !---------------------------------------------------------- PROGRAM test USE PMd IMPLICIT NONE INTEGER i,n1,n2,n3,n4 TYPE(PM),ALLOCATABLE::PMA(:) INTERFACE SUBROUTINE sub(PMA) USE PMd TYPE(PM) PMA END SUBROUTINE sub END INTERFACE n1=20; n2=2; n3=1000; n4=5 ALLOCATE(PMA(n4)) DO i=1,n4 ALLOCATE(PMA(i)%ng(n1,n2)); ALLOCATE(PMA(i)%zg(n3)) ENDDO PMA(1)%zg(1)=3.14D0 CALL sub(PMA) <--------------------------------------error #6634 DEALLOCATE(PMA) STOP END PROGRAM test !------------------------------------------------------------ SUBROUTINE sub(PMA) USE PMd IMPLICIT NONE TYPE(PM),DIMENSION(:),ALLOCATABLE,INTENT(IN)::PMA PRINT *,PMA(1)%zg(1) RETURN END SUBROUTINE sub test.f90(27): error #6634: The shape matching rules of actual arguments and dummy arguments have been violated. [PMA] pmd.mod : \
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
The following has error actions:
MODULE YourModuleName TYPE PM INTEGER,ALLOCATABLE::ng(:,:) DOUBLE PRECISION,ALLOCATABLE::zg(:) END TYPE PM contains SUBROUTINE sub(PMA) IMPLICIT NONE TYPE(PM), DIMENSION(:), ALLOCATABLE, INTENT(IN)::PMA if(.not. allocated(PMA)) then print *,"PMA not allocated" return endif if(size(PMA) < 1) then print *,"PMA must have size >= 1" return endif if((lbound(PMA,DIM=1) > 1) .or. (ubound(PMA,DIM=1) < 1)) then print *,"PMA(1) does not exist" return endif if(.not. allocated(PMA(1)%zg)) then print *,"PMA(1)%zg not allocated" return endif if(size(PMA(1)%zg) < 1) then print *,"PMA(1)%zg must have size >= 1" return endif if((lbound(PMA(1)%zg,DIM=1) > 1) .or. (ubound(PMA(1)%zg,DIM=1) < 1)) then print *,"PMA(1)%zg(1) does not exist" return endif PRINT *,PMA(1)%zg(1) END SUBROUTINE sub END MODULE YourModuleName PROGRAM test USE YourModuleName IMPLICIT NONE INTEGER i,n1,n2,n3,n4 Type(PM),ALLOCATABLE::PMA(:) n1=20 n2=2 n3=1000 n4=5 ALLOCATE(PMA(n4)) DO i=1,n4 ALLOCATE(PMA(i)%ng(n1,n2)) ALLOCATE(PMA(i)%zg(n3)) ENDDO PMA(1)%zg(1)=3.14D0 CALL sub(PMA) DEALLOCATE(PMA) CALL sub(PMA) ! "PMA not allocated" ALLOCATE(PMA(0)) CALL sub(PMA) ! "PMA must have size >= 1" DEALLOCATE(PMA) ALLOCATE(PMA(2:3)) CALL sub(PMA) ! "PMA(1) does not exist" DEALLOCATE(PMA) ALLOCATE(PMA(4)) CALL sub(PMA) ! "PMA(1)%zg not allocated" ALLOCATE(PMA(1)%zg(0)) CALL sub(PMA) ! "PMA(1)%zg must have size >= 1" DEALLOCATE(PMA(1)%zg) ALLOCATE(PMA(1)%zg(2:3)) CALL sub(PMA) ! "PMA(1)%zg(1) does not exist" DEALLOCATE(PMA) END PROGRAM test
For an unexplained reason I had to include ",DIM=1" on the lbound and ubound intrinsic functions.
Steve L, perhaps you can shed light on this requirement. DIM=1 should have been implicit
Anders,
Note that sub requires PMA to be an allocatable array. There would be an issue if your code requires sub to be called with a non-allocatable array as well as allocatable. I will let you address this issue.
Jim Dempsey
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Hi Jim,
PMA will always be allocatable in order to adjust to the actual dimensions of the problem, e.g. the number of subgroups when
the MPI communicator has been split.
Hi FortranFan,
Thanks again for your advice. I have found that working on a physical problem, physics, mathematics and numerics takes a lot of
gunpowder leading to little left to dive in writing nice code that use all functionality of Fortran. I guess you have already noticed that...
Therefore, the IDZ support is invaluable!
Best regards
Anders S
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
In your post #13, line 17 or the interface to SUB states PMA is a scalar (single) as opposed to an array.
Further, it is bad practice to place the INTERFACE in the caller's code as opposed to the preferred location of being in a MODULE. Locating the interface within a module reduces potential errors later as interface checking is always assured.
Jim Demspey
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Hi Jim,
I think with your final comment I have got my problem solved!
Thanks all contributors!
Best regards
Anders S
- Subscribe to RSS Feed
- Mark Topic as New
- Mark Topic as Read
- Float this Topic for Current User
- Bookmark
- Subscribe
- Printer Friendly Page