source: dynamico_lmdz/simple_physics/phyparam/DYNAMICO/icosa_phyparam_mod.F90 @ 4237

Last change on this file since 4237 was 4237, checked in by dubos, 5 years ago

simple_physics : update DYNAMICO interface

File size: 6.3 KB
Line 
1MODULE icosa_phyparam_mod
2#include "use_logging.h"
3
4! FCM gets confused when external modules are USEd at module level
5! => USE statements to DYNAMICO modules go into subroutines
6
7  IMPLICIT NONE
8  PRIVATE
9  SAVE
10
11  LOGICAL :: firstcall = .TRUE.
12  LOGICAL, PARAMETER :: lastcall = .FALSE.
13
14  REAL, PARAMETER :: oneday = 86400. ! hard-coded                                                                                                                                                         
15  INTEGER, PARAMETER :: log_unit = 15
16
17  PUBLIC :: init_physics, physics
18
19  CONTAINS
20
21    SUBROUTINE init_physics
22      ! DYNAMICO
23      USE mpipara,  ONLY : is_mpi_master
24      USE icosa,    ONLY : llm
25
26      USE icosa,     ONLY : g, radius, cpp, kappa
27      USE getin_mod, ONLY : getin
28      USE physics_interface_mod, ONLY : inout => physics_inout
29      ! phyparam
30      USE logging, ONLY : flush_plugin, dbtag, max_log_level
31      USE read_param_mod
32      USE comgeomfi
33      USE iniphyparam_mod
34      INTEGER, PARAMETER :: dayref=0
35      CHARACTER(10) :: physics_log_level
36      INTEGER :: ngrid, lev
37      REAL    :: timestep
38      REAL    :: unjours ! solar day in seconds
39
40      flush_plugin => flush_log_
41
42      physics_log_level='INF'
43      CALL getin('physics_log_level', physics_log_level)
44      DO lev=1, SIZE(dbtag)
45         IF(dbtag(lev)==TRIM(physics_log_level)) THEN
46            max_log_level = lev
47            EXIT
48         END IF
49      END DO
50
51      read_paramr_plugin => read_paramr
52      read_parami_plugin => read_parami
53      read_paramb_plugin => read_paramb
54
55      WRITELOG(*,*) 'init_physics called'
56      WRITELOG(*,*) 'physics log level set to ', dbtag(max_log_level)
57      LOG_INFO('phyparam')
58
59      ngrid = inout%ngrid
60      timestep = inout%dt_phys
61
62      unjours = 86400.
63      CALL getin('unjours', unjours)
64
65      CALL init_comgeomfi(ngrid, llm, inout%lon, inout%lat)
66      CALL iniphyparam(timestep, unjours, radius, g, cpp*kappa, cpp)
67
68    END SUBROUTINE init_physics
69
70    SUBROUTINE physics
71      USE mpipara,  ONLY : is_mpi_master
72      USE icosa,    ONLY : llm
73      USE physics_interface_mod, ONLY : inout => physics_inout
74      USE phyparam_mod
75      USE error_mod
76      REAL :: dps(inout%ngrid), play(inout%ngrid, llm), pphi(inout%ngrid, llm)
77      REAL :: timestep, time, jourvrai, gmtime
78      INTEGER :: l
79      IF(is_mpi_master) WRITE(log_unit,*) 'phyparam/physics called', SHAPE(inout%p), SHAPE(inout%pk)     
80
81      timestep = inout%dt_phys
82      time = timestep * inout%it
83      gmtime = time/oneday
84      jourvrai = FLOOR(gmtime)
85      gmtime   = gmtime - jourvrai
86
87      ! compute pressure and geopotential at full levels
88      CALL compute_play(inout%ngrid, llm, inout%p, play)
89      CALL compute_play(inout%ngrid, llm, inout%geopot, pphi)
90
91      ! substract surface geopotential
92      DO l=1,llm
93         pphi(:,l) = pphi(:,l) - inout%geopot(:,1)
94      END DO
95
96      IF(is_mpi_master) PRINT *, 'phyparam phi :', pphi(inout%ngrid/2+1, :)
97
98      CALL check_NaN('physics', 'ulon', inout%ulon)
99      CALL check_NaN('physics', 'ulat', inout%ulat)
100      CALL check_NaN('physics', 'temp', inout%temp)
101
102      ! go
103      CALL phyparam(inout%ngrid,llm,                       &
104           &        firstcall,lastcall,                    &
105           &        jourvrai, gmtime, timestep,            &
106           &        inout%p, play, pphi,                   &
107           &        inout%ulon,  inout%ulat,  inout%temp,  &
108           &        inout%dulon, inout%dulat, inout%dtemp, dps)
109
110      IF(is_mpi_master) PRINT *, 'phyparam dT :', inout%dtemp(inout%ngrid/2+1, :)
111
112      CALL check_NaN('physics', 'dulon', inout%dulon)
113      CALL check_NaN('physics', 'dulat', inout%dulat)
114      CALL check_NaN('physics', 'dtemp', inout%dtemp)
115
116      firstcall = .FALSE.
117    END SUBROUTINE physics
118
119    SUBROUTINE compute_play(ngrid, llm, plev, play)
120      INTEGER, INTENT(IN) :: ngrid, llm
121      REAL, INTENT(IN)    :: plev(ngrid, llm+1) ! pressure at interfaces (half-levels)
122      REAL, INTENT(OUT)   :: play(ngrid, llm)   ! pressure in layers (full levels)
123      INTEGER :: ij, l
124      DO l = 1,llm
125         DO ij = 1,ngrid
126            play(ij,l) = .5*(plev(ij,l)+plev(ij,l+1))
127         END DO
128      END DO
129    END SUBROUTINE compute_play
130
131!------------------------------------------------------------------------------------
132!------------------------------- Infrastructure plugins -----------------------------
133
134!--------------------------------------- Logging ------------------------------------
135
136    SUBROUTINE flush_log_(lev, taglen, tag, buflen, bufsize, buf) BIND(C)
137      USE mpipara, ONLY : is_mpi_master
138      USE logging, ONLY : dbtag
139      USE, INTRINSIC :: iso_c_binding, ONLY : c_char, c_null_char, c_int
140      INTEGER(c_int), INTENT(IN), VALUE :: lev, taglen, buflen, bufsize
141      CHARACTER(KIND=c_char), INTENT(IN) :: tag(taglen), buf(buflen, bufsize)
142      CHARACTER(buflen+1) :: line
143      !    SUBROUTINE flush_log_(lev, tag, buf)
144      !      INTEGER, INTENT(IN) :: lev
145      !      CHARACTER(*), INTENT(IN) :: tag, buf(:)
146      CHARACTER(100) :: prefix
147      INTEGER :: i
148     
149      IF(is_mpi_master) THEN
150         WRITE(prefix,*) '[', dbtag(lev), ' ', tag, ']'
151         DO i=1, bufsize
152            WRITE(line,*) buf(:,i)
153            WRITE(log_unit,*) TRIM(prefix), TRIM(line)
154         END DO
155         WRITE(log_unit, *) ''
156      END IF
157    END SUBROUTINE flush_log_
158
159!--------------------------------------- read_param ------------------------------------
160
161    SUBROUTINE read_paramr(name, defval, val, comment)
162      USE getin_mod, ONLY : getin
163      CHARACTER(*), INTENT(IN) :: name, comment
164      REAL, INTENT(IN)         :: defval
165      REAL, INTENT(OUT)        :: val
166      val = defval
167      CALL getin(name, val)
168    END SUBROUTINE read_paramr
169
170    SUBROUTINE read_parami(name, defval, val, comment)
171      USE getin_mod, ONLY : getin
172      CHARACTER(*), INTENT(IN) :: name, comment
173      INTEGER, INTENT(IN)      :: defval
174      INTEGER, INTENT(OUT)     :: val
175      val = defval
176      CALL getin(name, val)
177    END SUBROUTINE read_parami
178   
179    SUBROUTINE read_paramb(name, defval, val, comment)
180      USE getin_mod, ONLY : getin
181      CHARACTER(*), INTENT(IN) :: name, comment
182      LOGICAL, INTENT(IN)      :: defval
183      LOGICAL, INTENT(OUT)     :: val
184      val = defval
185      CALL getin(name, val)
186    END SUBROUTINE read_paramb
187
188END MODULE icosa_phyparam_mod
Note: See TracBrowser for help on using the repository browser.