source: trunk/LMDZ.COMMON/libf/evolution/grid_conversion.F90 @ 3995

Last change on this file since 3995 was 3991, checked in by jbclement, 4 weeks ago

PEM:
Apply documentation template everywhere: standardized headers format with short description, separators between functions/subroutines, normalized code sections, aligned dependencies/arguments/variables declaration.
JBC

File size: 3.3 KB
Line 
1MODULE grid_conversion
2!-----------------------------------------------------------------------
3! NAME
4!     grid_conversion
5!
6! DESCRIPTION
7!     Provides tools to convert data between lon x lat grid format
8!     and vector format.
9!
10! AUTHORS & DATE
11!     JB Clement, 12/2025
12!
13! NOTES
14!     Handles pole duplication differences between the grid format
15!     and vector format.
16!-----------------------------------------------------------------------
17
18! DECLARATION
19! -----------
20implicit none
21
22contains
23!++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
24
25!=======================================================================
26SUBROUTINE lonlat2vect(nlon,nlat,ngrid,v_ll,v_vect)
27!-----------------------------------------------------------------------
28! NAME
29!     lonlat2vect
30!
31! DESCRIPTION
32!     Convert data from lon x lat grid (where values at the poles are
33!     duplicated) into a vector.
34!
35! AUTHORS & DATE
36!     JB Clement, 12/2025
37!
38! NOTES
39!     The longitudes -180 and +180 are not duplicated like in the PCM
40!     dynamics.
41!
42!-----------------------------------------------------------------------
43
44! DECLARATION
45! -----------
46implicit none
47
48! Arguments
49!----------
50integer,                    intent(in)  :: nlon, nlat, ngrid
51real, dimension(nlon,nlat), intent(in)  :: v_ll
52real, dimension(ngrid),     intent(out) :: v_vect
53
54! Local variables
55!----------------
56integer :: i, j
57
58! Code
59!-----
60! 1D case
61#ifdef CPP_1D
62    v_vect(1) = v_ll(1,1)
63    return
64#else
65    ! Check
66    if (ngrid /= nlon*(nlat - 2) + 2) error stop 'lonlat2vect: problem of dimensions!'
67
68    ! Initialization
69    v_vect = 0.
70
71    ! Treatment of the poles
72    v_vect(1) = v_ll(1,1)
73    v_vect(ngrid) = v_ll(1,nlat)
74
75    ! Treatment of regular points
76    do j = 2,nlat - 1
77        do i = 1,nlon
78            v_vect(1 + i + (j - 2)*nlon) = v_ll(i,j)
79        enddo
80    enddo
81#endif
82
83END SUBROUTINE lonlat2vect
84!=======================================================================
85
86!=======================================================================
87SUBROUTINE vect2lonlat(nlon,nlat,ngrid,v_vect,v_ll)
88!-----------------------------------------------------------------------
89! NAME
90!     vect2lonlat
91!
92! DESCRIPTION
93!     Convert data from a vector into lon x lat grid (where values
94!     at the poles are duplicated).
95!
96! AUTHORS & DATE
97!     JB Clement, 12/2025
98!
99! NOTES
100!     The longitudes -180 and +180 are not duplicated like in the PCM
101!     dynamics.
102!-----------------------------------------------------------------------
103
104! DECLARATION
105! -----------
106implicit none
107
108! Arguments
109!----------
110integer,                    intent(in)  :: nlon, nlat, ngrid
111real, dimension(ngrid),     intent(in)  :: v_vect
112real, dimension(nlon,nlat), intent(out) :: v_ll
113
114! Local variables
115!----------------
116integer :: i, j
117
118! Code
119!-----
120! 1D case
121#ifdef CPP_1D
122    v_ll(1,1) = v_vect(1)
123    return
124#else
125    ! Check
126    if (ngrid /= nlon*(nlat - 2) + 2) error stop 'vect2lonlat: problem of dimensions!'
127
128    ! Initialization
129    v_ll = 0.
130
131    ! Treatment of the poles
132    v_ll(:,1) = v_vect(1)
133    v_ll(:,nlat) = v_vect(ngrid)
134
135    ! Treatment of regular points
136    do j = 2,nlat - 1
137        do i = 1,nlon
138            v_ll(i,j) = v_vect(1 + i + (j - 2)*nlon)
139        enddo
140    enddo
141#endif
142
143END SUBROUTINE vect2lonlat
144!=======================================================================
145
146END MODULE grid_conversion
Note: See TracBrowser for help on using the repository browser.