From: Arjan on
Hi!

Many of my user-defined types look like a X-mas-tree and new types are
built on top of the old ones. Some of them have allocatable
components. In certain occasions, I would like to just dump such a
beast to file/screen, and maybe read it back from file later. Below is
a sample that is not accepted by g95:

WRITE(*,*) y
1
Error: Data transfer element at (1) cannot have ALLOCATABLE components

My colleague complains about gfortran not accepting something similar
when reading a variable of similar type.

--> What is the easiest way to dump variables of user-defined type
with allocatable components to file and read it back later, without
worrying about the exact structure and components of the variable?
Binary would be okay (even preferable).

Arjan


PROGRAM Test
!
TYPE MyType
INTEGER, DIMENSION(:,:), ALLOCATABLE :: x
END TYPE MyType
!
TYPE(MyType) :: y
!
ALLOCATE(y%x(3,4))
y%x = 7
WRITE(*,*) y ! <-- Here I try to dump the variable, but
in vain...
!
DEALLOCATE(y%x)
!
END PROGRAM Test
From: Paul van Delst on
Hello,

My reply is likely of limited use to you: my approach has been to create an "inspect"
procedure (modeled after the ruby inspect method) whenever I create a datatype. For nested
datatypes, they simply call the "child" datatype inspect function.

E.g. I have the atmosphere datatype which itself contains the cloud and aerosol datatypes:

TYPE :: CRTM_Atmosphere_type
! Dimension values
INTEGER :: n_Layers = 0 ! K dimension
INTEGER :: n_Absorbers = 0 ! J dimension
INTEGER :: n_Clouds = 0 ! Nc dimension
INTEGER :: n_Aerosols = 0 ! Na dimension
! Profile LEVEL and LAYER quantities
REAL(fp), ALLOCATABLE :: Level_Pressure(:) ! 0:K
REAL(fp), ALLOCATABLE :: Pressure(:) ! K
REAL(fp), ALLOCATABLE :: Temperature(:) ! K
REAL(fp), ALLOCATABLE :: Absorber(:,:) ! K x J
! Clouds associated with each profile
TYPE(CRTM_Cloud_type), ALLOCATABLE :: Cloud(:) ! Nc
! Aerosols associated with each profile
TYPE(CRTM_Aerosol_type), ALLOCATABLE :: Aerosol(:) ! Na
END TYPE CRTM_Atmosphere_type

with the associated "inspect" routine:

SUBROUTINE CRTM_Atmosphere_Inspect( Atm )
TYPE(CRTM_Atmosphere_type), INTENT(IN) :: Atm
INTEGER :: j, k
INTEGER :: nc, na
IF ( .NOT. CRTM_Atmosphere_Associated(Atm) ) RETURN
WRITE(*, '(1x,"ATMOSPHERE OBJECT")')
! Profile information
k = Atm%n_Layers
WRITE(*, '(3x,"Level pressure:")')
WRITE(*, '(5(1x,es13.6,:))') Atm%Level_Pressure(0:k)
WRITE(*, '(3x,"Layer pressure:")')
WRITE(*, '(5(1x,es13.6,:))') Atm%Pressure(1:k)
WRITE(*, '(3x,"Layer temperature:")')
WRITE(*, '(5(1x,es13.6,:))') Atm%Temperature(1:k)
WRITE(*, '(3x,"Layer absorber:")')
DO j = 1, Atm%n_Absorbers
WRITE(*, '(5(1x,es13.6,:))') Atm%Absorber(1:k,j)
END DO
! Cloud information
IF ( Atm%n_Clouds > 0 ) THEN
DO nc = 1, Atm%n_Clouds
CALL CRTM_Cloud_Inspect(Atm%Cloud(nc))
END DO
END IF
! Aerosol information
IF ( Atm%n_Aerosols > 0 ) THEN
DO na = 1, Atm%n_Aerosols
CALL CRTM_Aerosol_Inspect(Atm%Aerosol(na))
END DO
END IF
END SUBROUTINE CRTM_Atmosphere_Inspect

Following this convention, it's easy for me to dump the contents of a datatype with
allocated components for any level of nesting. For file I/O I create separate modules (for
"binary" as well as netCDF I/O) but I could also use a variant of the above.

Anyway....

cheers,

paulv


Arjan wrote:
> Hi!
>
> Many of my user-defined types look like a X-mas-tree and new types are
> built on top of the old ones. Some of them have allocatable
> components. In certain occasions, I would like to just dump such a
> beast to file/screen, and maybe read it back from file later. Below is
> a sample that is not accepted by g95:
>
> WRITE(*,*) y
> 1
> Error: Data transfer element at (1) cannot have ALLOCATABLE components
>
> My colleague complains about gfortran not accepting something similar
> when reading a variable of similar type.
>
> --> What is the easiest way to dump variables of user-defined type
> with allocatable components to file and read it back later, without
> worrying about the exact structure and components of the variable?
> Binary would be okay (even preferable).
>
> Arjan
>
>
> PROGRAM Test
> !
> TYPE MyType
> INTEGER, DIMENSION(:,:), ALLOCATABLE :: x
> END TYPE MyType
> !
> TYPE(MyType) :: y
> !
> ALLOCATE(y%x(3,4))
> y%x = 7
> WRITE(*,*) y ! <-- Here I try to dump the variable, but
> in vain...
> !
> DEALLOCATE(y%x)
> !
> END PROGRAM Test
From: Richard Maine on
Arjan <arjan.van.dijk(a)rivm.nl> wrote:

> --> What is the easiest way to dump variables of user-defined type
> with allocatable components to file and read it back later, without
> worrying about the exact structure and components of the variable?
> Binary would be okay (even preferable).

I'm afraid you can't do it without at least some attention to the
structure if you have allocatable (or pointer) components.

I was slightly surprised to find that it doesn't work with a formatted
write, but indeed that's what the standard says. I forget exactly why
the limitation is there for formatted output unless it was just a
simplification. For input, either formatted or unformatted, there is the
problem of allocating to the corect size. For unformated I/O, there is
the problem of the data in the structure not being continguous in memory
and containing internal pointers to memory elsewhere; this means that
the simple unformatted I/O model of transferring the next n bits of
memory without interpretation doesn't work.

I assume that you mean unformatted whan you say "binary". The term
"binary" gets regularly misused in I/O contexts. In addition to my usual
gripe that "binary" means "base 2" and thus has little to do with
formatted versus unformatted output, there is the problem that different
people misuse the term in different ways. Some people just take it to
mean "unformatted", while others also take it to imply lack of record
structure.

In any case, the issues for formatted and unformatted are simillar here
and there is no distinction in stream versus record for this issue.

One way or another, you end up having to write out the code to handle
the allocatable (or pointer) components. You might find it less
inconvenient (I deliberately say that instead of "more convenient") to
write a subroutine to handle I/O of the derived type so that you can do
it just once for each type instead of once for each usage.

If you have an f2003 compiler that implements user-defined derived-type
I/O, you could take advantage of that. You'd still have to write the
subroutines, but it would integrate better with other I/O (particularly
in cases where you might want to have a record with multiple items in
it.) However, you probably don't have such a compiler. This seems to be
one of the last things implemented in f2003 compilers, probably because
of poor cost/benefit.

--
Richard Maine | Good judgment comes from experience;
email: last name at domain . net | experience comes from bad judgment.
domain: summertriangle | -- Mark Twain
From: Arjan on
Thanks for the suggestions!

A.