source: LMDZ6/trunk/libf/phylmd/perturb_radlwsw.f90 @ 5308

Last change on this file since 5308 was 5301, checked in by abarral, 39 hours ago

Turn tsoilnudge.h fcg_gcssold.h flux_arp.h into module

File size: 642 bytes
Line 
1      SUBROUTINE perturb_radlwsw(zxtsol,iflag_radia)
2!
3!Case-specific radiative setup
4!
5USE flux_arp_mod_h
6            use dimphy
7      IMPLICIT none
8!
9! Arguments :
10!------------
11      REAL,DIMENSION(klon), INTENT(INOUT) :: zxtsol
12      INTEGER, INTENT(IN)                 :: iflag_radia
13!
14!======================================================================
15!
16      IF (iflag_radia == 2) THEN
17!
18! Iflag_radia = 2 : DICE case :
19!               on force zxtsol=tg pour le rayonnement (MPL 20130806)
20!Sonia : Cas dice lmdz1d force en flux : on impose Tg pour imposer le LWUP
21!
22        zxtsol(:) =  tg
23      ENDIF
24!
25      RETURN
26      END
27
Note: See TracBrowser for help on using the repository browser.