source: LMDZ6/branches/LMDZ-COSP/libf/phylmd/lmdz_wake_first.f90 @ 5918

Last change on this file since 5918 was 5894, checked in by Sebastien Nguyen, 12 days ago

rephase LMDZISO with 5864 version of phylmd + bug fixes in physiq_mod + other bugs in isoverif sections. Code now compiles and runs with -debug -isotopes true -isoverif. There are still isoverif error messages for Dexcess getting greater than 1000 on some points at some moments.

File size: 723 bytes
Line 
1MODULE lmdz_wake_first
2  LOGICAL            :: first_call=.true.
3  !$OMP THREADPRIVATE(first_call)
4PUBLIC wake_first
5CONTAINS
6
7SUBROUTINE wake_first(klev, dtime)           
8USE lmdz_wake_ini , ONLY : CPPKEY_IOPHYS_WK
9USE lmdz_wake_ini , ONLY : phys_sub
10USE lmdz_wake_ini , ONLY : wk_nsub
11IMPLICIT NONE 
12  INTEGER, INTENT(IN) :: klev
13  REAL, INTENT(IN)    :: dtime
14  REAL                :: dtimesub
15
16  dtimesub = dtime/wk_nsub
17  !
18  IF (first_call) THEN
19    IF (CPPKEY_IOPHYS_WK) THEN
20      IF (phys_sub) THEN
21        call iophys_ini(dtimesub,klev)
22      ELSE
23        call iophys_ini(dtime,klev)
24      ENDIF
25    END IF
26    first_call = .false.
27  ENDIF   !(first_call)
28
29END SUBROUTINE wake_first
30END MODULE lmdz_wake_first
Note: See TracBrowser for help on using the repository browser.