- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Hello,
I am writing a code in which I need to use a derived data type that include another derived data type.
I've been able to follow the examples tu use the DT descriptor for user defined io within the first one, but in the second one I get an error from the compiler, namely
model.f90: error #8638: The type/rank signature for arguments of this specific subroutine is identical to another specific subroutine that shares the same defined I/O. [UDIO_WRITE_NODE] model.f90: error #8638: The type/rank signature for arguments of this specific subroutine is identical to another specific subroutine that shares the same defined I/O. [UDIO_WRITE_MODEL] model.f90: error #8638: The type/rank signature for arguments of this specific subroutine is identical to another specific subroutine that shares the same defined I/O. [UDIO_READ_NODE] compilation aborted for model.f90 (code 1)
I have to admit that I simply nested the two io procedures.
The inner derived data type works finely
module myNode
implicit none
type node
logical :: isIsotropic
real :: depth
real :: sigmaMean
real :: sigmaRatio
real :: betaS
end type node
interface write(formatted)
module procedure udio_write_node
end interface write(formatted)
interface read(formatted)
module procedure udio_read_node
end interface read(formatted)
contains
subroutine udio_read_node(dtv, unit, iotype, v_list, iostat, iomsg)
!
!
! ifort note: to enable reading int as logical the code must be compiled with the flag
!
! -assume old_logical_ldio
!
!
class(node), intent(inout) :: dtv
integer, intent(in) :: unit
character(*), intent(in) :: iotype
integer, intent(in) :: v_list(:)
integer, intent(out) :: iostat
character(*), intent(inout) :: iomsg
read(unit,fmt=*,iostat=iostat,iomsg=iomsg) dtv%isIsotropic, dtv%depth, dtv%sigmamean, dtv%sigmaratio, dtv%betas
end subroutine udio_read_node
subroutine udio_write_node(dtv, unit, iotype, v_list, iostat, iomsg)
class(node), intent(in) :: dtv
integer, intent(in) :: unit
character(*), intent(in) :: iotype
integer, intent(in) :: v_list(:)
integer, intent(out) :: iostat
character(*), intent(inout) :: iomsg
if(dtv%isIsotropic)then
write(unit, fmt=*, iostat=iostat, iomsg=iomsg) 1, dtv%depth, dtv%sigmamean, dtv%sigmaratio, dtv%betas
else
write(unit, fmt=*, iostat=iostat, iomsg=iomsg) 0, dtv%depth, dtv%sigmamean, dtv%sigmaratio, dtv%betas
end if
end subroutine udio_write_node
end module myNode
program test1
use myNode
implicit none
integer :: i
type(node),dimension(4) :: n
!!$ do i = 1,4
!!$ n(i)%isIsotropic = .true.
!!$ n(i)%depth = real(i)*1.1
!!$ n(i)%sigmamean = real(i) * 0.5
!!$ n(i)%sigmaratio = real(i) * 1.0
!!$ n(i)%betas = real(i) * 15.0
!!$ end do
open(1,file='iotest.txt',form='formatted',recl=2048)
read(1,"(4(dt))") n
close(1)
do i = 1,4
write(*,"(dt)") n(i)
end do
end program test1
but when I try to use the same with another type that contains an array of type(node) i get the compilation error.
module model
use mynode
implicit none
integer, private, parameter :: kmax = 32
type model
integer :: k = 1
real :: logL = 0.
real :: logPr = 0.
real :: h_par = 1.
type(node), dimension (kmax) :: par
end type model
interface write(formatted)
module procedure udio_write_model
end interface write(formatted)
interface read(formatted)
module procedure udio_read_model
end interface read(formatted)
contains
subroutine udio_read_model(dtvv, unit, iotype, v_list, iostat, iomsg)
!
!
! ifort note: to enable reading int as logical the code must be compiled with the flag
!
! -assume old_logical_ldio
!
!
class(model), intent(inout) :: dtvv
integer, intent(in) :: unit
character(*), intent(in) :: iotype
integer, intent(in) :: v_list(:)
integer, intent(out) :: iostat
character(*), intent(inout) :: iomsg
read(unit,fmt=*,iostat=iostat,iomsg=iomsg) dtvv%k, dtvv%logL, dtvv%logPr, dtvv%h_par, dtvv%par(1:dtvv%k)
end subroutine udio_read_model
subroutine udio_write_model(dtv, unit, iotype, v_list, iostat, iomsg)
class(model), intent(in) :: dtv
integer, intent(in) :: unit
character(*), intent(in) :: iotype
integer, intent(in) :: v_list(:)
integer, intent(out) :: iostat
character(*), intent(inout) :: iomsg
write(unit, fmt=*, iostat=iostat, iomsg=iomsg) dtv%k, dtv%logL, dtv%logPr, dtv%h_par, dtv%par(1:dtv%k)
end subroutine udio_write_model
end module model
program test1
use mtmodel
use mynode
implicit none
type(model) :: m
integer :: i
open(1,file='iotest.txt',form='formatted',recl=2048)
read(1,"(dt)") m
close(1)
write(*,"(dt)") m
do i = 1,4
write(*,"(dt)") m%par(i)
end do
end program test1
What's the proper way to chain the user defined io procedure?
Thanks in advance for any help.
Eric
Link Copied
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I believe that your code is correct, but apparently, the compiler is getting confused by the interface declarations.
I changed the type declarations to have type-bound procedures instead, and removed the generic interfaces, and the program compiled.
More specifically, I changed the declaration of node to:
type node logical :: isIsotropic real :: depth real :: sigmaMean real :: sigmaRatio real :: betaS contains procedure :: udio_read_node procedure :: udio_write_node generic :: write(formatted) => udio_write_node generic :: read(formatted) => udio_read_node end type node
Similar edit for type model.
I hope this helps -
--Lorri
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I have escalated this as issue DPD200411713. I also note that the error messages lack "locator" information to tell you where in the source file the error (allegedly) occurred.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Even modifying the code I still get runtime errors.
As workaround, there is a simple way to overload read a write?
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Please show a complete test case with the modified code.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
The node.f90 module stays the same
module myNode
implicit none
type node
logical :: isIsotropic
real :: depth
real :: sigmaMean
real :: sigmaRatio
real :: betaS
contains
procedure :: udio_read_node
procedure :: udio_write_node
generic :: read(formatted) => udio_read_node
generic :: write(formatted) => udio_write_node
end type node
!!$ interface write(formatted)
!!$ module procedure udio_write_node
!!$ end interface write(formatted)
!!$
!!$ interface read(formatted)
!!$ module procedure udio_read_node
!!$ end interface read(formatted)
contains
subroutine udio_read_node(dtv, unit, iotype, v_list, iostat, iomsg)
!
!
! ifort note: to enable reading int as logical the code must be compiled with the flag
!
! -assume old_logical_ldio
!
!
class(node), intent(inout) :: dtv
integer, intent(in) :: unit
character(*), intent(in) :: iotype
integer, intent(in) :: v_list(:)
integer, intent(out) :: iostat
character(*), intent(inout) :: iomsg
read(unit,fmt=*,iostat=iostat,iomsg=iomsg) dtv%isIsotropic, dtv%depth, dtv%sigmamean, dtv%sigmaratio, dtv%betas
end subroutine udio_read_node
subroutine udio_write_node(dtv, unit, iotype, v_list, iostat, iomsg)
class(node), intent(in) :: dtv
integer, intent(in) :: unit
character(*), intent(in) :: iotype
integer, intent(in) :: v_list(:)
integer, intent(out) :: iostat
character(*), intent(inout) :: iomsg
if(dtv%isIsotropic)then
write(unit, fmt=*, iostat=iostat, iomsg=iomsg) 1, dtv%depth, dtv%sigmamean, dtv%sigmaratio, dtv%betas
else
write(unit, fmt=*, iostat=iostat, iomsg=iomsg) 0, dtv%depth, dtv%sigmamean, dtv%sigmaratio, dtv%betas
end if
end subroutine udio_write_node
end module myNode
and works as before.
If I try to nest the node structure into another one I get
forrtl: severe (105): there is no data-edit-descriptor to match a data-item in the I/O list, unit 1, file /Users/eric/Src/greenTDMT/iotest_write.txt Image PC Routine Line Source test 0000000104292E5C Unknown Unknown Unknown test 00000001042BE122 Unknown Unknown Unknown test 000000010427C00E Unknown Unknown Unknown test 000000010427BB7E Unknown Unknown Unknown
explicitly I try to read/write na array of nodes and a bunch of other parameters
module mtmodel
use mynode
implicit none
integer, private, parameter :: kmax = 32
type model
integer :: k = 1
real :: logL = 0.
real :: logPr = 0.
real :: h_par = 1.
type(node), dimension (kmax) :: par
contains
procedure :: udio_read_model
procedure :: udio_write_model
generic :: read(formatted) => udio_read_model
generic :: write(formatted) => udio_write_model
end type model
!!$ interface read(formatted)
!!$ module procedure udio_read_model
!!$ end interface read(formatted)
!!$
!!$ interface write(formatted)
!!$ module procedure udio_write_model
!!$ end interface write(formatted)
contains
subroutine udio_read_model(dtv, unit, iotype, v_list, iostat, iomsg)
!
!
! ifort note: to enable reading int as logical the code must be compiled with the flag
!
! -assume old_logical_ldio
!
!
class(model), intent(inout) :: dtv
integer, intent(in) :: unit
character(*), intent(in) :: iotype
integer, intent(in) :: v_list(:)
integer, intent(out) :: iostat
character(*), intent(inout) :: iomsg
read(unit,fmt=*,iostat=iostat,iomsg=iomsg) dtv%k, dtv%logL, dtv%logPr, dtv%h_par, dtv%par(1:dtv%k)
end subroutine udio_read_model
subroutine udio_write_model(dtv, unit, iotype, v_list, iostat, iomsg)
class(model), intent(in) :: dtv
integer, intent(in) :: unit
character(*), intent(in) :: iotype
integer, intent(in) :: v_list(:)
integer, intent(out) :: iostat
character(*), intent(inout) :: iomsg
write(unit, fmt=*, iostat=iostat, iomsg=iomsg) dtv%k, dtv%logL, dtv%logPr, dtv%h_par, dtv%par(1:dtv%k)
end subroutine udio_write_model
!!$ function forward(m,period) result(z)
!!$ implicit none
!!$ type(model), intent(in) :: m
!!$ real, intent(in) :: period
!!$ complex, dimension(2,2) :: z
!!$
!!$ call z1anis()
end module mtmodel
program test1
use mtmodel
use mynode, only : node
implicit none
type(model) :: m
type(node), dimension(4) :: n
integer :: i
do i = 1,4
n(i)%isIsotropic = .true.
n(i)%depth = real(i)*1.1
n(i)%sigmamean = real(i) * 0.5
n(i)%sigmaratio = real(i) * 1.0
n(i)%betas = real(i) * 15.0
end do
m%par(1:4) = n
open(1,file='iotest_write.txt',form='formatted',recl=2048)
write(1,113) m
close(1)
! write(*,113) m
!!$ do i = 1,4
!!$ write(*,"(dt)") m%par(i)
!!$ end do
113 format(dt)
end program test1
I think that the problem could be that I use the * descriptor in both the node and model i/o subroutine, but I am not sure about that.
- Subscribe to RSS Feed
- Mark Topic as New
- Mark Topic as Read
- Float this Topic for Current User
- Bookmark
- Subscribe
- Printer Friendly Page