source: LMDZ6/branches/Amaury_dev/libf/phylmd/phyaqua_mod.F90 @ 5099

Last change on this file since 5099 was 5099, checked in by abarral, 4 months ago

Replace most uses of CPP_DUST by the corresponding logical defined in lmdz_cppkeys_wrapper.F90
Convert several files from .F to .f90 to allow Dust to compile w/o rrtm/ecrad
Create lmdz_yoerad.f90
(lint) Remove "!" on otherwise empty line

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
  • Property svn:keywords set to Id
File size: 30.1 KB
RevLine 
[5099]1
[3540]2! $Id: phyaqua_mod.F90 5099 2024-07-22 19:29:09Z abarral $
[5099]3
[1992]4MODULE phyaqua_mod
5  ! Routines complementaires pour la physique planetaire.
6  IMPLICIT NONE
[1529]7
[1992]8CONTAINS
[1529]9
[3579]10  SUBROUTINE iniaqua(nlon,year_len,iflag_phys)
[1529]11
[1992]12    ! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
13    ! Creation d'un etat initial et de conditions aux limites
14    ! (resp startphy.nc et limit.nc) pour des configurations idealisees
15    ! du modele LMDZ dans sa version terrestre.
16    ! iflag_phys est un parametre qui controle
17    ! iflag_phys = N
18    ! de 100 a 199 : aqua planetes avec SST forcees
19    ! N-100 determine le type de SSTs
20    ! de 200 a 299 : terra planetes avec Ts calcule
[1529]21
[1992]22    ! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
[1529]23
[1992]24    USE dimphy, ONLY: klon
[2351]25    USE geometry_mod, ONLY : latitude
[1992]26    USE surface_data, ONLY: type_ocean, ok_veget
27    USE pbl_surface_mod, ONLY: pbl_surface_init
28    USE fonte_neige_mod, ONLY: fonte_neige_init
29    USE phys_state_var_mod
[2344]30    USE time_phylmdz_mod, ONLY: day_ref, ndays, pdtphys, &
31                                day_ini,day_end
[1992]32    USE indice_sol_mod
[2344]33    USE nrtype, ONLY: pi
[3435]34!    USE ioipsl
35    USE mod_phys_lmdz_para, ONLY: is_master
36    USE mod_phys_lmdz_transfert_para, ONLY: bcast
37    USE mod_grid_phy_lmdz
38    USE ioipsl_getin_p_mod, ONLY : getin_p
[3579]39    USE phys_cal_mod , ONLY: calend, year_len_phy => year_len
[1992]40    IMPLICIT NONE
[1529]41
[2344]42    include "YOMCST.h"
[1992]43    include "clesphys.h"
44    include "dimsoil.h"
[1671]45
[3579]46    INTEGER, INTENT (IN) :: nlon, year_len, iflag_phys
[1992]47    ! IM ajout latfi, lonfi
[2351]48!    REAL, INTENT (IN) :: lonfi(nlon), latfi(nlon)
[1529]49
[1992]50    INTEGER type_profil, type_aqua
[1529]51
[1992]52    ! Ajouts initialisation des surfaces
53    REAL :: run_off_lic_0(nlon)
54    REAL :: qsolsrf(nlon, nbsrf), snsrf(nlon, nbsrf)
55    REAL :: tsoil(nlon, nsoilmx, nbsrf)
56    REAL :: tslab(nlon), seaice(nlon)
[2243]57    REAL fder(nlon)
[1529]58
59
60
[1992]61    ! Arguments :
62    ! -----------
[1529]63
[1992]64    ! integer radpas
65    INTEGER it, unit, i, k, itap
[1529]66
[1992]67    REAL rugos, albedo
68    REAL tsurf
69    REAL time, timestep, day, day0
[2243]70    REAL qsol_f
[1992]71    REAL rugsrel(nlon)
72    LOGICAL alb_ocean
[1529]73
[1992]74    CHARACTER *80 ans, file_forctl, file_fordat, file_start
75    CHARACTER *100 file, var
76    CHARACTER *2 cnbl
[1529]77
[3540]78    REAL phy_nat(nlon, year_len)
79    REAL phy_alb(nlon, year_len)
80    REAL phy_sst(nlon, year_len)
81    REAL phy_bil(nlon, year_len)
82    REAL phy_rug(nlon, year_len)
83    REAL phy_ice(nlon, year_len)
84    REAL phy_fter(nlon, year_len)
85    REAL phy_foce(nlon, year_len)
86    REAL phy_fsic(nlon, year_len)
87    REAL phy_flic(nlon, year_len)
[1529]88
[1992]89    INTEGER, SAVE :: read_climoz = 0 ! read ozone climatology
[3435]90!$OMP THREADPRIVATE(read_climoz)
[1529]91
[1992]92    ! -------------------------------------------------------------------------
93    ! declaration pour l'appel a phyredem
94    ! -------------------------------------------------------------------------
[1529]95
[1992]96    ! real pctsrf(nlon,nbsrf),ftsol(nlon,nbsrf)
97    REAL falbe(nlon, nbsrf), falblw(nlon, nbsrf)
98    ! real pbl_tke(nlon,llm,nbsrf)
99    ! real rain_fall(nlon),snow_fall(nlon)
100    ! real solsw(nlon), sollw(nlon),radsol(nlon)
101    ! real t_ancien(nlon,llm),q_ancien(nlon,llm),rnebcon(nlon,llm)
102    ! real ratqs(nlon,llm)
103    ! real clwcon(nlon,llm)
[1529]104
[1992]105    INTEGER longcles
106    PARAMETER (longcles=20)
107    REAL clesphy0(longcles)
[1529]108
109
[1992]110    ! -----------------------------------------------------------------------
111    ! dynamial tendencies :
112    ! ---------------------
[1529]113
[1992]114    INTEGER l, ierr, aslun
[1529]115
[1992]116    REAL paire
[1529]117
[3531]118    ! Local
119    CHARACTER (LEN=20) :: modname='phyaqua'
120    CHARACTER (LEN=80) :: abort_message
[1529]121
[3531]122
[1992]123    ! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
124    ! INITIALISATIONS
125    ! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
[1529]126
[1992]127    ! -----------------------------------------------------------------------
128    ! Initialisations  des constantes
129    ! -------------------------------
[1529]130
[3579]131    !IF (calend .EQ. "earth_360d") Then
132      year_len_phy = year_len
133    !END IF
134   
[5073]135    if (year_len/=360) then
[3579]136      write (*,*) year_len
[4463]137      call abort_physic("iniaqua", 'iniaqua: 360 day calendar is required !', 1)
[3540]138    endif
139
[1992]140    type_aqua = iflag_phys/100
141    type_profil = iflag_phys - type_aqua*100
142    PRINT *, 'iniaqua:type_aqua, type_profil', type_aqua, type_profil
[1529]143
[1992]144    IF (klon/=nlon) THEN
145      WRITE (*, *) 'iniaqua: klon=', klon, ' nlon=', nlon
[3531]146      abort_message= 'probleme de dimensions dans iniaqua'
147      CALL abort_physic(modname,abort_message,1)
[1992]148    END IF
149    CALL phys_state_var_init(read_climoz)
[1529]150
151
[1992]152    read_climoz = 0
153    day0 = 217.
154    day = day0
155    it = 0
156    time = 0.
[1529]157
[1992]158    ! -----------------------------------------------------------------------
159    ! initialisations de la physique
160    ! -----------------------------------------------------------------------
[1529]161
[2344]162    day_ini = day_ref
163    day_end = day_ini + ndays
[1759]164
[3435]165    nbapp_rad = 24
166    CALL getin_p('nbapp_rad', nbapp_rad)
167
[1992]168    ! ---------------------------------------------------------------------
169    ! Creation des conditions aux limites:
170    ! ------------------------------------
171    ! Initialisations des constantes
172    ! Ajouter les manquants dans planete.def... (albedo etc)
[3435]173    co2_ppm = 348.
174    CALL getin_p('co2_ppm', co2_ppm)
175
176    solaire = 1365.
177    CALL getin_p('solaire', solaire)
178 
[1992]179    ! CALL getin('albedo',albedo) ! albedo is set below, depending on
180    ! type_aqua
[3435]181    alb_ocean = .TRUE.
182    CALL getin_p('alb_ocean', alb_ocean)
183
[1992]184    WRITE (*, *) 'iniaqua: co2_ppm=', co2_ppm
185    WRITE (*, *) 'iniaqua: solaire=', solaire
186    WRITE (*, *) 'iniaqua: alb_ocean=', alb_ocean
[1529]187
[1992]188    radsol = 0.
189    qsol_f = 10.
[1529]190
[1992]191    ! Conditions aux limites:
192    ! -----------------------
[1529]193
[1992]194    qsol(:) = qsol_f
195    rugsrel = 0.0 ! (rugsrel = rugoro)
196    rugoro = 0.0
197    u_ancien = 0.0
198    v_ancien = 0.0
199    agesno = 50.0
200    ! Relief plat
201    zmea = 0.
202    zstd = 0.
203    zsig = 0.
204    zgam = 0.
205    zthe = 0.
206    zpic = 0.
207    zval = 0.
[1529]208
[1992]209    ! Une seule surface
210    pctsrf = 0.
211    IF (type_aqua==1) THEN
212      rugos = 1.E-4
213      albedo = 0.19
214      pctsrf(:, is_oce) = 1.
215    ELSE IF (type_aqua==2) THEN
216      rugos = 0.03
217      albedo = 0.1
218      pctsrf(:, is_ter) = 1.
219    END IF
[1529]220
[3435]221    CALL getin_p('rugos', rugos)
222
[1992]223    WRITE (*, *) 'iniaqua: rugos=', rugos
[2209]224    zmasq(:) = pctsrf(:, is_ter)
[1529]225
[1992]226    ! pctsrf_pot(:,is_oce) = 1. - zmasq(:)
227    ! pctsrf_pot(:,is_sic) = 1. - zmasq(:)
[1529]228
[1992]229    ! Si alb_ocean on calcule un albedo oceanique moyen
230    ! if (alb_ocean) then
231    ! Voir pourquoi on avait ca.
232    ! CALL ini_alb_oce(phy_alb)
233    ! else
234    phy_alb(:, :) = albedo ! albedo land only (old value condsurf_jyg=0.3)
235    ! endif !alb_ocean
[1529]236
[3540]237    DO i = 1, year_len
[1992]238      ! IM Terraplanete   phy_sst(:,i) = 260.+50.*cos(rlatd(:))**2
239      ! IM ajout calcul profil sst selon le cas considere (cf. FBr)
[1529]240
[1992]241      phy_nat(:, i) = 1.0 ! 0=ocean libre, 1=land, 2=glacier, 3=banquise
242      phy_bil(:, i) = 1.0 ! ne sert que pour les slab_ocean
243      phy_rug(:, i) = rugos ! longueur rugosite utilisee sur land only
244      phy_ice(:, i) = 0.0 ! fraction de glace (?)
245      phy_fter(:, i) = pctsrf(:, is_ter) ! fraction de glace (?)
246      phy_foce(:, i) = pctsrf(:, is_oce) ! fraction de glace (?)
247      phy_fsic(:, i) = pctsrf(:, is_sic) ! fraction de glace (?)
248      phy_flic(:, i) = pctsrf(:, is_lic) ! fraction de glace (?)
249    END DO
250    ! IM calcul profil sst
[2351]251    CALL profil_sst(nlon, latitude, type_profil, phy_sst)
[1529]252
[3435]253    IF (grid_type==unstructured) THEN
254      CALL writelim_unstruct(klon, phy_nat, phy_alb, phy_sst, phy_bil, phy_rug, phy_ice, &
255                             phy_fter, phy_foce, phy_flic, phy_fsic)
256    ELSE
257     
258       CALL writelim(klon, phy_nat, phy_alb, phy_sst, phy_bil, phy_rug, phy_ice, &
259                     phy_fter, phy_foce, phy_flic, phy_fsic)
260    ENDIF
[1529]261
[1992]262    ! ---------------------------------------------------------------------
263    ! Ecriture de l'etat initial:
264    ! ---------------------------
[1529]265
266
[1992]267    ! Ecriture etat initial physique
[1529]268
[2344]269    timestep = pdtphys
270    radpas = nint(rday/timestep/float(nbapp_rad))
[1529]271
[1992]272    DO i = 1, longcles
273      clesphy0(i) = 0.
274    END DO
275    clesphy0(1) = float(iflag_con)
276    clesphy0(2) = float(nbapp_rad)
277    ! IF( cycle_diurne  ) clesphy0(3) =  1.
278    clesphy0(3) = 1. ! cycle_diurne
279    clesphy0(4) = 1. ! soil_model
280    clesphy0(5) = 1. ! new_oliq
281    clesphy0(6) = 0. ! ok_orodr
282    clesphy0(7) = 0. ! ok_orolf
283    clesphy0(8) = 0. ! ok_limitvrai
[1529]284
285
[1992]286    ! =======================================================================
287    ! Profils initiaux
288    ! =======================================================================
[1529]289
[1992]290    ! On initialise les temperatures de surfaces comme les sst
291    DO i = 1, nlon
292      ftsol(i, :) = phy_sst(i, 1)
293      tsoil(i, :, :) = phy_sst(i, 1)
294      tslab(i) = phy_sst(i, 1)
295    END DO
[1529]296
[1992]297    falbe(:, :) = albedo
298    falblw(:, :) = albedo
299    rain_fall(:) = 0.
300    snow_fall(:) = 0.
301    solsw(:) = 0.
302    sollw(:) = 0.
303    radsol(:) = 0.
[1529]304
[1992]305    ! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
306    ! intialisation bidon mais pas grave
307    t_ancien(:, :) = 0.
308    q_ancien(:, :) = 0.
309    ! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
310    rnebcon = 0.
311    ratqs = 0.
312    clwcon = 0.
313    pbl_tke = 1.E-8
[1529]314
[1992]315    ! variables supplementaires pour appel a plb_surface_init
316    fder(:) = 0.
317    seaice(:) = 0.
318    run_off_lic_0 = 0.
[2243]319    fevap = 0.
[1529]320
321
[1992]322    ! Initialisations necessaires avant phyredem
323    type_ocean = 'force'
324    CALL fonte_neige_init(run_off_lic_0)
325    qsolsrf(:, :) = qsol(1) ! humidite du sol des sous surface
326    snsrf(:, :) = 0. ! couverture de neige des sous surface
[2243]327    z0m(:, :) = rugos ! couverture de neige des sous surface
328    z0h=z0m
[1530]329
330
[2243]331    CALL pbl_surface_init(fder, snsrf, qsolsrf, tsoil)
[1529]332
[1992]333    PRINT *, 'iniaqua: before phyredem'
[1529]334
[3435]335    pbl_tke(:,:,:) = 1.e-8
[1992]336    falb1 = albedo
337    falb2 = albedo
338    zmax0 = 0.
339    f0 = 0.
340    sig1 = 0.
341    w01 = 0.
342    wake_deltat = 0.
343    wake_deltaq = 0.
344    wake_s = 0.
[3435]345    wake_dens = 0.
[1992]346    wake_cstar = 0.
347    wake_pe = 0.
348    wake_fip = 0.
349    fm_therm = 0.
350    entr_therm = 0.
351    detr_therm = 0.
[2827]352    ale_bl = 0.
353    ale_bl_trig =0.
354    alp_bl =0.
[2979]355    treedrg(:,:,:)=0.
[1529]356
[3579]357    u10m = 0.
358    v10m = 0.
359
360    ql_ancien   = 0.
361    qs_ancien   = 0.
[4523]362    qbs_ancien  = 0.
[3579]363    u_ancien    = 0.
364    v_ancien    = 0.
365    prw_ancien  = 0.
366    prlw_ancien = 0.
367    prsw_ancien = 0. 
[4523]368    prbsw_ancien= 0.
[3579]369
370    ale_wake    = 0.
371    ale_bl_stat = 0. 
372
373
[3435]374!ym error : the sub surface dimension is the third not second : forgotten for iniaqua
375!    falb_dir(:,is_ter,:)=0.08; falb_dir(:,is_lic,:)=0.6
376!    falb_dir(:,is_oce,:)=0.5;  falb_dir(:,is_sic,:)=0.6
377    falb_dir(:,:,is_ter)=0.08; falb_dir(:,:,is_lic)=0.6
378    falb_dir(:,:,is_oce)=0.5;  falb_dir(:,:,is_sic)=0.6
[1529]379
[3435]380!ym falb_dif has been forgotten, initialize with defaukt value found in phyetat0 or 0 ?
381!ym probably the uninitialized value was 0 for standard (regular grid) case
382    falb_dif(:,:,:)=0
383
384
[1992]385    CALL phyredem('startphy.nc')
[1529]386
[1992]387    PRINT *, 'iniaqua: after phyredem'
388    CALL phys_state_var_end
[1529]389
[1992]390    RETURN
391  END SUBROUTINE iniaqua
[1529]392
393
[1992]394  ! ====================================================================
395  ! ====================================================================
396  SUBROUTINE zenang_an(cycle_diurne, gmtime, rlat, rlon, rmu0, fract)
397    USE dimphy
398    IMPLICIT NONE
399    ! ====================================================================
400    ! =============================================================
401    ! CALL zenang(cycle_diurne,gmtime,rlat,rlon,rmu0,fract)
402    ! Auteur : A. Campoy et F. Hourdin
403    ! Objet  : calculer les valeurs moyennes du cos de l'angle zenithal
404    ! et l'ensoleillement moyen entre gmtime1 et gmtime2
405    ! connaissant la declinaison, la latitude et la longitude.
[1529]406
[1992]407    ! Dans cette version particuliere, on calcule le rayonnement
408    ! moyen sur l'année à chaque latitude.
409    ! angle zenithal calculé pour obtenir un
410    ! Fit polynomial de  l'ensoleillement moyen au sommet de l'atmosphere
411    ! en moyenne annuelle.
412    ! Spécifique de la terre. Utilisé pour les aqua planetes.
[1529]413
[1992]414    ! Rque   : Different de la routine angle en ce sens que zenang
415    ! fournit des moyennes de pmu0 et non des valeurs
416    ! instantanees, du coup frac prend toutes les valeurs
417    ! entre 0 et 1.
418    ! Date   : premiere version le 13 decembre 1994
419    ! revu pour  GCM  le 30 septembre 1996
420    ! ===============================================================
421    ! longi----INPUT : la longitude vraie de la terre dans son plan
422    ! solaire a partir de l'equinoxe de printemps (degre)
423    ! gmtime---INPUT : temps universel en fraction de jour
424    ! pdtrad---INPUT : pas de temps du rayonnement (secondes)
425    ! lat------INPUT : latitude en degres
426    ! long-----INPUT : longitude en degres
427    ! pmu0-----OUTPUT: angle zenithal moyen entre gmtime et gmtime+pdtrad
428    ! frac-----OUTPUT: ensoleillement moyen entre gmtime et gmtime+pdtrad
429    ! ================================================================
430    include "YOMCST.h"
431    ! ================================================================
432    LOGICAL cycle_diurne
433    REAL gmtime
434    REAL rlat(klon), rlon(klon), rmu0(klon), fract(klon)
435    ! ================================================================
436    INTEGER i
437    REAL gmtime1, gmtime2
438    REAL pi_local
[1529]439
440
[1992]441    REAL rmu0m(klon), rmu0a(klon)
[1529]442
443
[1992]444    pi_local = 4.0*atan(1.0)
[1529]445
[1992]446    ! ================================================================
447    ! Calcul de l'angle zenithal moyen sur la journee
448    ! ================================================================
449
450    DO i = 1, klon
451      fract(i) = 1.
452      ! Calcule du flux moyen
453      IF (abs(rlat(i))<=28.75) THEN
454        rmu0m(i) = (210.1924+206.6059*cos(0.0174533*rlat(i))**2)/1365.
455      ELSE IF (abs(rlat(i))<=43.75) THEN
456        rmu0m(i) = (187.4562+236.1853*cos(0.0174533*rlat(i))**2)/1365.
457      ELSE IF (abs(rlat(i))<=71.25) THEN
458        rmu0m(i) = (162.4439+284.1192*cos(0.0174533*rlat(i))**2)/1365.
[1529]459      ELSE
[1992]460        rmu0m(i) = (172.8125+183.7673*cos(0.0174533*rlat(i))**2)/1365.
461      END IF
462    END DO
[1529]463
[1992]464    ! ================================================================
465    ! Avec ou sans cycle diurne
466    ! ================================================================
[1529]467
[1992]468    IF (cycle_diurne) THEN
[1529]469
[1992]470      ! On redecompose flux  au sommet suivant un cycle diurne idealise
471      ! identique a toutes les latitudes.
[1671]472
[1992]473      DO i = 1, klon
474        rmu0a(i) = 2.*rmu0m(i)*sqrt(2.)*pi_local/(4.-pi_local)
475        rmu0(i) = rmu0a(i)*abs(sin(pi_local*gmtime+pi_local*rlon(i)/360.)) - &
476          rmu0a(i)/sqrt(2.)
477      END DO
[1671]478
[1992]479      DO i = 1, klon
480        IF (rmu0(i)<=0.) THEN
481          rmu0(i) = 0.
482          fract(i) = 0.
483        ELSE
484          fract(i) = 1.
485        END IF
486      END DO
[1671]487
[1992]488      ! Affichage de l'angel zenitale
489      ! print*,'************************************'
490      ! print*,'************************************'
491      ! print*,'************************************'
492      ! print*,'latitude=',rlat(i),'longitude=',rlon(i)
493      ! print*,'rmu0m=',rmu0m(i)
494      ! print*,'rmu0a=',rmu0a(i)
495      ! print*,'rmu0=',rmu0(i)
[1529]496
[1992]497    ELSE
[1671]498
[1992]499      DO i = 1, klon
500        fract(i) = 0.5
501        rmu0(i) = rmu0m(i)*2.
502      END DO
503
504    END IF
505
506    RETURN
507  END SUBROUTINE zenang_an
508
509  ! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
510
[3435]511  SUBROUTINE writelim_unstruct(klon, phy_nat, phy_alb, phy_sst, phy_bil, phy_rug, &
512      phy_ice, phy_fter, phy_foce, phy_flic, phy_fsic)
513
514    USE mod_phys_lmdz_para, ONLY: is_omp_master, klon_mpi
515    USE mod_phys_lmdz_transfert_para, ONLY: gather_omp
[4619]516    USE lmdz_xios
[3435]517    IMPLICIT NONE
518
519    INTEGER, INTENT (IN) :: klon
520    REAL, INTENT (IN) :: phy_nat(klon, 360)
521    REAL, INTENT (IN) :: phy_alb(klon, 360)
522    REAL, INTENT (IN) :: phy_sst(klon, 360)
523    REAL, INTENT (IN) :: phy_bil(klon, 360)
524    REAL, INTENT (IN) :: phy_rug(klon, 360)
525    REAL, INTENT (IN) :: phy_ice(klon, 360)
526    REAL, INTENT (IN) :: phy_fter(klon, 360)
527    REAL, INTENT (IN) :: phy_foce(klon, 360)
528    REAL, INTENT (IN) :: phy_flic(klon, 360)
529    REAL, INTENT (IN) :: phy_fsic(klon, 360)
530
531    REAL :: phy_mpi(klon_mpi, 360) ! temporary variable, to store phy_***(:)
532      ! on the whole physics grid
533 
[4619]534    IF (using_xios) THEN
535      PRINT *, 'writelim: Ecriture du fichier limit'
[3435]536
[4619]537      CALL gather_omp(phy_foce, phy_mpi)
538      IF (is_omp_master) CALL xios_send_field('foce_limout',phy_mpi)
[3435]539
[4619]540      CALL gather_omp(phy_fsic, phy_mpi)
541      IF (is_omp_master) CALL xios_send_field('fsic_limout',phy_mpi)
[3435]542     
[4619]543      CALL gather_omp(phy_fter, phy_mpi)
544      IF (is_omp_master) CALL xios_send_field('fter_limout',phy_mpi)
[3435]545     
[4619]546      CALL gather_omp(phy_flic, phy_mpi)
547      IF (is_omp_master) CALL xios_send_field('flic_limout',phy_mpi)
[3435]548
[4619]549      CALL gather_omp(phy_sst, phy_mpi)
550      IF (is_omp_master) CALL xios_send_field('sst_limout',phy_mpi)
[3435]551
[4619]552      CALL gather_omp(phy_bil, phy_mpi)
553      IF (is_omp_master) CALL xios_send_field('bils_limout',phy_mpi)
[3435]554
[4619]555      CALL gather_omp(phy_alb, phy_mpi)
556      IF (is_omp_master) CALL xios_send_field('alb_limout',phy_mpi)
[3435]557
[4619]558      CALL gather_omp(phy_rug, phy_mpi)
559      IF (is_omp_master) CALL xios_send_field('rug_limout',phy_mpi)
560    ENDIF
[3435]561  END SUBROUTINE writelim_unstruct
562
563
564
[1992]565  SUBROUTINE writelim(klon, phy_nat, phy_alb, phy_sst, phy_bil, phy_rug, &
566      phy_ice, phy_fter, phy_foce, phy_flic, phy_fsic)
567
[3435]568    USE mod_phys_lmdz_para, ONLY: is_master
[1992]569    USE mod_grid_phy_lmdz, ONLY: klon_glo
570    USE mod_phys_lmdz_transfert_para, ONLY: gather
[3540]571    USE phys_cal_mod, ONLY: year_len
[5088]572    USE netcdf, ONLY: nf90_def_var, nf90_put_var, nf90_get_var, nf90_strerror, nf90_close, &
573            nf90_enddef, nf90_put_att, nf90_unlimited, nf90_noerr, nf90_global, nf90_clobber, &
574            nf90_64bit_offset, nf90_def_dim, nf90_create
[5090]575    USE lmdz_cppkeys_wrapper, ONLY: nf90_format
[1992]576    IMPLICIT NONE
577
578    INTEGER, INTENT (IN) :: klon
[3540]579    REAL, INTENT (IN) :: phy_nat(klon, year_len)
580    REAL, INTENT (IN) :: phy_alb(klon, year_len)
581    REAL, INTENT (IN) :: phy_sst(klon, year_len)
582    REAL, INTENT (IN) :: phy_bil(klon, year_len)
583    REAL, INTENT (IN) :: phy_rug(klon, year_len)
584    REAL, INTENT (IN) :: phy_ice(klon, year_len)
585    REAL, INTENT (IN) :: phy_fter(klon, year_len)
586    REAL, INTENT (IN) :: phy_foce(klon, year_len)
587    REAL, INTENT (IN) :: phy_flic(klon, year_len)
588    REAL, INTENT (IN) :: phy_fsic(klon, year_len)
[1992]589
[3540]590    REAL :: phy_glo(klon_glo, year_len) ! temporary variable, to store phy_***(:)
[1992]591      ! on the whole physics grid
592    INTEGER :: k
593    INTEGER ierr
594    INTEGER dimfirst(3)
595    INTEGER dimlast(3)
596
597    INTEGER nid, ndim, ntim
598    INTEGER dims(2), debut(2), epais(2)
599    INTEGER id_tim
600    INTEGER id_nat, id_sst, id_bils, id_rug, id_alb
601    INTEGER id_fter, id_foce, id_fsic, id_flic
602
[3435]603    IF (is_master) THEN
[1992]604
605      PRINT *, 'writelim: Ecriture du fichier limit'
606
[5088]607      ierr = nf90_create('limit.nc', IOR(nf90_clobber,nf90_64bit_offset), nid)
[1992]608
[5088]609      ierr = nf90_put_att(nid, nf90_global, 'title', &
[1992]610        'Fichier conditions aux limites')
[5088]611      ! !        ierr = nf90_def_dim (nid, "points_physiques", klon, ndim)
612      ierr = nf90_def_dim(nid, 'points_physiques', klon_glo, ndim)
613      ierr = nf90_def_dim(nid, 'time', nf90_unlimited, ntim)
[1992]614
615      dims(1) = ndim
616      dims(2) = ntim
617
[5088]618      ierr = nf90_def_var(nid, 'TEMPS', nf90_format, [ntim], id_tim)
619      ierr = nf90_put_att(nid, id_tim, 'title', 'Jour dans l annee')
[2198]620
[5088]621      ierr = nf90_def_var(nid, 'NAT', nf90_format, dims, id_nat)
622      ierr = nf90_put_att(nid, id_nat, 'title', &
[1992]623        'Nature du sol (0,1,2,3)')
[2198]624
[5088]625      ierr = nf90_def_var(nid, 'SST', nf90_format, dims, id_sst)
626      ierr = nf90_put_att(nid, id_sst, 'title', &
[1992]627        'Temperature superficielle de la mer')
[2198]628
[5088]629      ierr = nf90_def_var(nid, 'BILS', nf90_format, dims, id_bils)
630      ierr = nf90_put_att(nid, id_bils, 'title', &
[1992]631        'Reference flux de chaleur au sol')
[2198]632
[5088]633      ierr = nf90_def_var(nid, 'ALB', nf90_format, dims, id_alb)
634      ierr = nf90_put_att(nid, id_alb, 'title', 'Albedo a la surface')
[2198]635
[5088]636      ierr = nf90_def_var(nid, 'RUG', nf90_format, dims, id_rug)
637      ierr = nf90_put_att(nid, id_rug, 'title', 'Rugosite')
[1992]638
[5088]639      ierr = nf90_def_var(nid, 'FTER', nf90_format, dims, id_fter)
640      ierr = nf90_put_att(nid, id_fter, 'title','Frac. Land')
641      ierr = nf90_def_var(nid, 'FOCE', nf90_format, dims, id_foce)
642      ierr = nf90_put_att(nid, id_foce, 'title','Frac. Ocean')
643      ierr = nf90_def_var(nid, 'FSIC', nf90_format, dims, id_fsic)
644      ierr = nf90_put_att(nid, id_fsic, 'title','Frac. Sea Ice')
645      ierr = nf90_def_var(nid, 'FLIC', nf90_format, dims, id_flic)
646      ierr = nf90_put_att(nid, id_flic, 'title','Frac. Land Ice')
[1992]647
[5088]648      ierr = nf90_enddef(nid)
649      IF (ierr/=nf90_noerr) THEN
[1992]650        WRITE (*, *) 'writelim error: failed to end define mode'
[5088]651        WRITE (*, *) nf90_strerror(ierr)
[1992]652      END IF
653
654
655      ! write the 'times'
[3540]656      DO k = 1, year_len
[5073]657        ierr = nf90_put_var(nid, id_tim, k, [k])
[5088]658        IF (ierr/=nf90_noerr) THEN
[1992]659          WRITE (*, *) 'writelim error with temps(k),k=', k
[5088]660          WRITE (*, *) nf90_strerror(ierr)
[1992]661        END IF
662      END DO
[1529]663
[3435]664    END IF ! of if (is_master)
[1671]665
[1992]666    ! write the fields, after having collected them on master
[1671]667
[1992]668    CALL gather(phy_nat, phy_glo)
[3435]669    IF (is_master) THEN
[5073]670      ierr = nf90_put_var(nid, id_nat, phy_glo)
[5088]671      IF (ierr/=nf90_noerr) THEN
[1992]672        WRITE (*, *) 'writelim error with phy_nat'
[5088]673        WRITE (*, *) nf90_strerror(ierr)
[1992]674      END IF
675    END IF
[1671]676
[1992]677    CALL gather(phy_sst, phy_glo)
[3435]678    IF (is_master) THEN
[5073]679      ierr = nf90_put_var(nid, id_sst, phy_glo)
[5088]680      IF (ierr/=nf90_noerr) THEN
[1992]681        WRITE (*, *) 'writelim error with phy_sst'
[5088]682        WRITE (*, *) nf90_strerror(ierr)
[1992]683      END IF
684    END IF
[1671]685
[1992]686    CALL gather(phy_bil, phy_glo)
[3435]687    IF (is_master) THEN
[5073]688      ierr = nf90_put_var(nid, id_bils, phy_glo)
[5088]689      IF (ierr/=nf90_noerr) THEN
[1992]690        WRITE (*, *) 'writelim error with phy_bil'
[5088]691        WRITE (*, *) nf90_strerror(ierr)
[1992]692      END IF
693    END IF
[1671]694
[1992]695    CALL gather(phy_alb, phy_glo)
[3435]696    IF (is_master) THEN
[5073]697      ierr = nf90_put_var(nid, id_alb, phy_glo)
[5088]698      IF (ierr/=nf90_noerr) THEN
[1992]699        WRITE (*, *) 'writelim error with phy_alb'
[5088]700        WRITE (*, *) nf90_strerror(ierr)
[1992]701      END IF
702    END IF
[1671]703
[1992]704    CALL gather(phy_rug, phy_glo)
[3435]705    IF (is_master) THEN
[5073]706      ierr = nf90_put_var(nid, id_rug, phy_glo)
[5088]707      IF (ierr/=nf90_noerr) THEN
[1992]708        WRITE (*, *) 'writelim error with phy_rug'
[5088]709        WRITE (*, *) nf90_strerror(ierr)
[1992]710      END IF
711    END IF
[1671]712
[1992]713    CALL gather(phy_fter, phy_glo)
[3435]714    IF (is_master) THEN
[5073]715      ierr = nf90_put_var(nid, id_fter, phy_glo)
[5088]716      IF (ierr/=nf90_noerr) THEN
[1992]717        WRITE (*, *) 'writelim error with phy_fter'
[5088]718        WRITE (*, *) nf90_strerror(ierr)
[1992]719      END IF
720    END IF
[1671]721
[1992]722    CALL gather(phy_foce, phy_glo)
[3435]723    IF (is_master) THEN
[5073]724      ierr = nf90_put_var(nid, id_foce, phy_glo)
[5088]725      IF (ierr/=nf90_noerr) THEN
[1992]726        WRITE (*, *) 'writelim error with phy_foce'
[5088]727        WRITE (*, *) nf90_strerror(ierr)
[1992]728      END IF
729    END IF
[1671]730
[1992]731    CALL gather(phy_fsic, phy_glo)
[3435]732    IF (is_master) THEN
[5073]733      ierr = nf90_put_var(nid, id_fsic, phy_glo)
[5088]734      IF (ierr/=nf90_noerr) THEN
[1992]735        WRITE (*, *) 'writelim error with phy_fsic'
[5088]736        WRITE (*, *) nf90_strerror(ierr)
[1992]737      END IF
738    END IF
[1671]739
[1992]740    CALL gather(phy_flic, phy_glo)
[3435]741    IF (is_master) THEN
[5073]742      ierr = nf90_put_var(nid, id_flic, phy_glo)
[5088]743      IF (ierr/=nf90_noerr) THEN
[1992]744        WRITE (*, *) 'writelim error with phy_flic'
[5088]745        WRITE (*, *) nf90_strerror(ierr)
[1992]746      END IF
747    END IF
[1671]748
[1992]749    ! close file:
[3435]750    IF (is_master) THEN
[5088]751      ierr = nf90_close(nid)
[1992]752    END IF
[1671]753
[1992]754  END SUBROUTINE writelim
[1529]755
[1992]756  ! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
[1671]757
[1992]758  SUBROUTINE profil_sst(nlon, rlatd, type_profil, phy_sst)
759    USE dimphy
[3540]760    USE phys_cal_mod , ONLY: year_len
[1992]761    IMPLICIT NONE
[1529]762
[1992]763    INTEGER nlon, type_profil, i, k, j
[3540]764    REAL :: rlatd(nlon), phy_sst(nlon, year_len)
[1992]765    INTEGER imn, imx, amn, amx, kmn, kmx
766    INTEGER p, pplus, nlat_max
767    PARAMETER (nlat_max=72)
768    REAL x_anom_sst(nlat_max)
[3531]769    CHARACTER (LEN=20) :: modname='profil_sst'
770    CHARACTER (LEN=80) :: abort_message
[1529]771
[3531]772    IF (klon/=nlon) THEN
773       abort_message='probleme de dimensions dans profil_sst'
774       CALL abort_physic(modname,abort_message,1)
775    ENDIF
[1992]776    WRITE (*, *) ' profil_sst: type_profil=', type_profil
[3540]777    DO i = 1, year_len
[1992]778      ! phy_sst(:,i) = 260.+50.*cos(rlatd(:))**2
[1529]779
[1992]780      ! Rajout fbrlmd
[1529]781
[1992]782      IF (type_profil==1) THEN
783        ! Méthode 1 "Control" faible plateau à l'Equateur
784        DO j = 1, klon
785          phy_sst(j, i) = 273. + 27.*(1-sin(1.5*rlatd(j))**2)
786          ! PI/3=1.047197551
787          IF ((rlatd(j)>1.0471975) .OR. (rlatd(j)<-1.0471975)) THEN
788            phy_sst(j, i) = 273.
789          END IF
790        END DO
791      END IF
792      IF (type_profil==2) THEN
793        ! Méthode 2 "Flat" fort plateau à l'Equateur
794        DO j = 1, klon
795          phy_sst(j, i) = 273. + 27.*(1-sin(1.5*rlatd(j))**4)
796          IF ((rlatd(j)>1.0471975) .OR. (rlatd(j)<-1.0471975)) THEN
797            phy_sst(j, i) = 273.
798          END IF
799        END DO
800      END IF
[1529]801
802
[1992]803      IF (type_profil==3) THEN
804        ! Méthode 3 "Qobs" plateau réel à l'Equateur
805        DO j = 1, klon
806          phy_sst(j, i) = 273. + 0.5*27.*(2-sin(1.5*rlatd(j))**2-sin(1.5* &
807            rlatd(j))**4)
808          IF ((rlatd(j)>1.0471975) .OR. (rlatd(j)<-1.0471975)) THEN
809            phy_sst(j, i) = 273.
810          END IF
811        END DO
812      END IF
[1529]813
[1992]814      IF (type_profil==4) THEN
815        ! Méthode 4 : Méthode 3 + SST+2 "Qobs" plateau réel à l'Equateur
816        DO j = 1, klon
817          phy_sst(j, i) = 273. + 0.5*29.*(2-sin(1.5*rlatd(j))**2-sin(1.5* &
818            rlatd(j))**4)
819          IF ((rlatd(j)>1.0471975) .OR. (rlatd(j)<-1.0471975)) THEN
820            phy_sst(j, i) = 273.
821          END IF
822        END DO
823      END IF
[1529]824
[1992]825      IF (type_profil==5) THEN
826        ! Méthode 5 : Méthode 3 + +2K "Qobs" plateau réel à l'Equateur
827        DO j = 1, klon
828          phy_sst(j, i) = 273. + 2. + 0.5*27.*(2-sin(1.5*rlatd(j))**2-sin(1.5 &
829            *rlatd(j))**4)
830          IF ((rlatd(j)>1.0471975) .OR. (rlatd(j)<-1.0471975)) THEN
831            phy_sst(j, i) = 273. + 2.
832          END IF
[1529]833
[1992]834        END DO
835      END IF
[1529]836
[1992]837      IF (type_profil==6) THEN
838        ! Méthode 6 "cst" valeur constante de SST
839        DO j = 1, klon
840          phy_sst(j, i) = 288.
841        END DO
842      END IF
[1529]843
844
[1992]845      IF (type_profil==7) THEN
846        ! Méthode 7 "cst" valeur constante de SST +2
847        DO j = 1, klon
848          phy_sst(j, i) = 288. + 2.
849        END DO
850      END IF
[1529]851
[1992]852      p = 0
853      IF (type_profil==8) THEN
854        ! Méthode 8 profil anomalies SST du modèle couplé AR4
855        DO j = 1, klon
856          IF (rlatd(j)==rlatd(j-1)) THEN
857            phy_sst(j, i) = 273. + x_anom_sst(pplus) + &
858              0.5*27.*(2-sin(1.5*rlatd(j))**2-sin(1.5*rlatd(j))**4)
859            IF ((rlatd(j)>1.0471975) .OR. (rlatd(j)<-1.0471975)) THEN
860              phy_sst(j, i) = 273. + x_anom_sst(pplus)
861            END IF
862          ELSE
863            p = p + 1
864            pplus = 73 - p
865            phy_sst(j, i) = 273. + x_anom_sst(pplus) + &
866              0.5*27.*(2-sin(1.5*rlatd(j))**2-sin(1.5*rlatd(j))**4)
867            IF ((rlatd(j)>1.0471975) .OR. (rlatd(j)<-1.0471975)) THEN
868              phy_sst(j, i) = 273. + x_anom_sst(pplus)
869            END IF
870            WRITE (*, *) rlatd(j), x_anom_sst(pplus), phy_sst(j, i)
871          END IF
872        END DO
873      END IF
[1529]874
[1992]875      IF (type_profil==9) THEN
876        ! Méthode 5 : Méthode 3 + -2K "Qobs" plateau réel à l'Equateur
877        DO j = 1, klon
878          phy_sst(j, i) = 273. - 2. + 0.5*27.*(2-sin(1.5*rlatd(j))**2-sin(1.5 &
879            *rlatd(j))**4)
880          IF ((rlatd(j)>1.0471975) .OR. (rlatd(j)<-1.0471975)) THEN
881            phy_sst(j, i) = 273. - 2.
882          END IF
883        END DO
884      END IF
[1529]885
886
[1992]887      IF (type_profil==10) THEN
888        ! Méthode 10 : Méthode 3 + +4K "Qobs" plateau réel à l'Equateur
889        DO j = 1, klon
890          phy_sst(j, i) = 273. + 4. + 0.5*27.*(2-sin(1.5*rlatd(j))**2-sin(1.5 &
891            *rlatd(j))**4)
892          IF ((rlatd(j)>1.0471975) .OR. (rlatd(j)<-1.0471975)) THEN
893            phy_sst(j, i) = 273. + 4.
894          END IF
895        END DO
896      END IF
[1529]897
[1992]898      IF (type_profil==11) THEN
899        ! Méthode 11 : Méthode 3 + 4CO2 "Qobs" plateau réel à l'Equateur
900        DO j = 1, klon
901          phy_sst(j, i) = 273. + 0.5*27.*(2-sin(1.5*rlatd(j))**2-sin(1.5* &
902            rlatd(j))**4)
903          IF ((rlatd(j)>1.0471975) .OR. (rlatd(j)<-1.0471975)) THEN
904            phy_sst(j, i) = 273.
905          END IF
906        END DO
907      END IF
[1529]908
[1992]909      IF (type_profil==12) THEN
910        ! Méthode 12 : Méthode 10 + 4CO2 "Qobs" plateau réel à l'Equateur
911        DO j = 1, klon
912          phy_sst(j, i) = 273. + 4. + 0.5*27.*(2-sin(1.5*rlatd(j))**2-sin(1.5 &
913            *rlatd(j))**4)
914          IF ((rlatd(j)>1.0471975) .OR. (rlatd(j)<-1.0471975)) THEN
915            phy_sst(j, i) = 273. + 4.
916          END IF
917        END DO
918      END IF
[1529]919
[1992]920      IF (type_profil==13) THEN
921        ! Méthode 13 "Qmax" plateau réel à l'Equateur augmenté !
922        DO j = 1, klon
923          phy_sst(j, i) = 273. + 0.5*29.*(2-sin(1.5*rlatd(j))**2-sin(1.5* &
924            rlatd(j))**4)
925          IF ((rlatd(j)>1.0471975) .OR. (rlatd(j)<-1.0471975)) THEN
926            phy_sst(j, i) = 273.
927          END IF
928        END DO
929      END IF
[1529]930
[1992]931      IF (type_profil==14) THEN
932        ! Méthode 13 "Qmax2K" plateau réel à l'Equateur augmenté +2K !
933        DO j = 1, klon
934          phy_sst(j, i) = 273. + 2. + 0.5*29.*(2-sin(1.5*rlatd(j))**2-sin(1.5 &
935            *rlatd(j))**4)
936          IF ((rlatd(j)>1.0471975) .OR. (rlatd(j)<-1.0471975)) THEN
937            phy_sst(j, i) = 273.
938          END IF
939        END DO
940      END IF
[1529]941
[5073]942      if (type_profil==20) then
[2107]943      print*,'Profile SST 20'
[5093]944!     Méthode 13 "Qmax2K" plateau réel é|  l'Equateur augmenté +2K
[2107]945
946      do j=1,klon
947        phy_sst(j,i)=248.+55.*(1-sin(rlatd(j))**2)
948      enddo
949      endif
950
[5073]951      if (type_profil==21) then
[2107]952      print*,'Profile SST 21'
[5093]953!     Méthode 13 "Qmax2K" plateau réel é|  l'Equateur augmenté +2K
[2107]954      do j=1,klon
955        phy_sst(j,i)=252.+55.*(1-sin(rlatd(j))**2)
956      enddo
957      endif
958
959
960
[1992]961    END DO
962
963    ! IM beg : verif profil SST: phy_sst
964    amn = min(phy_sst(1,1), 1000.)
965    amx = max(phy_sst(1,1), -1000.)
966    imn = 1
967    kmn = 1
968    imx = 1
969    kmx = 1
[3540]970    DO k = 1, year_len
[1992]971      DO i = 2, nlon
972        IF (phy_sst(i,k)<amn) THEN
973          amn = phy_sst(i, k)
974          imn = i
975          kmn = k
976        END IF
977        IF (phy_sst(i,k)>amx) THEN
978          amx = phy_sst(i, k)
979          imx = i
980          kmx = k
981        END IF
982      END DO
983    END DO
984
985    PRINT *, 'profil_sst: imn, kmn, phy_sst(imn,kmn) ', imn, kmn, amn
986    PRINT *, 'profil_sst: imx, kmx, phy_sst(imx,kmx) ', imx, kmx, amx
987    ! IM end : verif profil SST: phy_sst
988
989    RETURN
990  END SUBROUTINE profil_sst
991
992END MODULE phyaqua_mod
Note: See TracBrowser for help on using the repository browser.