LMDZ
yom_phys_grid.F90
Go to the documentation of this file.
2 
3 USE parkind1 ,ONLY : jpim ,jprb
4 
5 IMPLICIT NONE
6 SAVE
7 
8 PRIVATE
11 
12 !-------------------------------------------------------------------------
13 ! Derived types for describing the coarse physics grid structure.
14 ! The descriptors themselves
15 ! (YGFL and YGFLC) can be found in module yom_ygfl.F90.
16 !-------------------------------------------------------------------------
17 ! Modifications:
18 
19 INTEGER(KIND=JPIM), PARAMETER :: jpmxnei=36 ! maximum number of neighbouring
20  ! points for averaging or
21  ! interpolation
22 
24  INTEGER(KIND=JPIM) :: ngptot ! number of physics points in the task
25  INTEGER(KIND=JPIM) :: ngptotg
26  INTEGER(KIND=JPIM) :: ndgsal, ndgenl
27  INTEGER(KIND=JPIM) :: ndgsag, ndgeng
28  INTEGER(KIND=JPIM), POINTER :: nloeng(:)
29  REAL(KIND=JPRB), POINTER :: rmu(:)
30  REAL(KIND=JPRB), POINTER :: rw(:)
31 
32  INTEGER(KIND=JPIM) :: nresol_id
33  INTEGER(KIND=JPIM) :: ngptotmx, nspec2, nsmax
34  INTEGER(KIND=JPIM) :: nptrfloff, nump, ndlon
35  INTEGER(KIND=JPIM) :: ndgsah, ndgenh
36  INTEGER(KIND=JPIM) :: ndglg, ndlsur
37  INTEGER(KIND=JPIM) :: nfrstloff, ndsur1,ndgsur
38  INTEGER(KIND=JPIM) :: myfrstactlat, mylstactlat
39  INTEGER(KIND=JPIM) :: ngpblks
40  INTEGER(KIND=JPIM) :: nproma
41 
42  INTEGER(KIND=JPIM), POINTER, DIMENSION(:) :: nrgri, nptrfrstlat, nfrstlat
43  INTEGER(KIND=JPIM), POINTER, DIMENSION(:) :: nlstlat, myms, nasm0
44  INTEGER(KIND=JPIM), POINTER, DIMENSION(:,:) :: nsta, nonl
45  INTEGER(KIND=JPIM), POINTER, DIMENSION(:) :: nstagp
46  REAL(KIND=JPRB), POINTER :: rsqm2(:), rlatig(:), rlati(:)
47  REAL(KIND=JPRB), POINTER :: ripi0(:), ripi1(:), ripi2(:)
48  INTEGER(KIND=JPIM), POINTER, DIMENSION(:) :: nptrlstlat
49 
50 END TYPE phys_grid_struct
51 
53 
55  INTEGER(KIND=JPIM),POINTER :: nslsta(:)
56  INTEGER(KIND=JPIM),POINTER :: nslonl(:)
57  INTEGER(KIND=JPIM),POINTER :: nsloff(:)
58  INTEGER(KIND=JPIM),POINTER :: nslext(:,:)
59  INTEGER(KIND=JPIM),POINTER :: nslsendpos(:)
60  INTEGER(KIND=JPIM),POINTER :: nslrecvpos(:)
61  INTEGER(KIND=JPIM),POINTER :: nslsendptr(:)
62  INTEGER(KIND=JPIM),POINTER :: nslrecvptr(:)
63  INTEGER(KIND=JPIM),POINTER :: nslcore(:)
64  INTEGER(KIND=JPIM),POINTER :: nslcomm(:)
65 
66  INTEGER(KIND=JPIM) :: naslb1
67  INTEGER(KIND=JPIM) :: nslprocs
68  INTEGER(KIND=JPIM) :: nslmpbufsz
69  INTEGER(KIND=JPIM) :: nslrpt
70  INTEGER(KIND=JPIM) :: nslspt
71  INTEGER(KIND=JPIM) :: nslwiden
72  INTEGER(KIND=JPIM) :: nslwides
73  INTEGER(KIND=JPIM) :: nslwidee
74  INTEGER(KIND=JPIM) :: nslwidew
75 END TYPE sl_struct
76 
77 TYPE(sl_struct) :: dyn_sl
79 
80 
81 TYPE type_phys_point ! Individual physics point characteristics
82 
83  REAL(KIND=JPRB) :: gelam, gelat, gemu
84  REAL(KIND=JPRB) :: geclo, geslo, gm, gaw
85  REAL(KIND=JPRB) :: gnordl, gnordm, gsqm2
86  REAL(KIND=JPRB) :: rcolon, rsilon
87  REAL(KIND=JPRB) :: rindx, rindy
88  REAL(KIND=JPRB) :: orog
89  INTEGER(KIND=JPIM) :: ngplat ! row number in the physics grid
90 
91  INTEGER(KIND=JPIM) :: neigh ! number of neighbours in the dynamics grid
92  ! for going from the dynamics to the physics grid
93  INTEGER(KIND=JPIM), POINTER :: nl0(:) ! indexes in the interpolation buffer of
94  ! the dynamics neighbours
95  REAL(KIND=JPRB), POINTER :: wgt(:) ! weights for every neighbouring
96  ! dynamics point
97 END TYPE type_phys_point
98 
99 TYPE(type_phys_point),ALLOCATABLE :: yphypoi(:)
100 
101 TYPE type_dyn_point ! Individual dynamics point characteristics
102  INTEGER(KIND=JPIM) :: neigh ! number of neighbours in the physics grid
103  ! for going from the physics to the dynamics grid
104  INTEGER(KIND=JPIM), POINTER :: nl0(:) ! indexes in the interpolation buffer of
105  ! the physics neighbours
106  REAL(KIND=JPRB), POINTER :: wgt(:) ! weights for every neighbouring
107  ! physics point
108 END TYPE type_dyn_point
109 
110 TYPE(type_dyn_point),ALLOCATABLE :: ydynpoi(:)
111 
112 !$OMP THREADPRIVATE(dyn_grid,dyn_sl,phys_grid,phys_sl)
113 !$OMP THREADPRIVATE(ydynpoi,yphypoi)
114 END MODULE yom_phys_grid
type(type_dyn_point), dimension(:), allocatable, public ydynpoi
type(sl_struct), public phys_sl
integer, parameter jprb
Definition: parkind1.F90:31
type(sl_struct), public dyn_sl
integer(kind=jpim), parameter, public jpmxnei
type(type_phys_point), dimension(:), allocatable, public yphypoi
integer, parameter jpim
Definition: parkind1.F90:13
type(phys_grid_struct), public phys_grid
type(phys_grid_struct), public dyn_grid