Ignore:
Timestamp:
Mar 29, 2023, 3:14:27 PM (22 months ago)
Author:
lguez
Message:

Sync latest trunk changes to branch LMDZ_ECRad

Location:
LMDZ6/branches/LMDZ_ECRad
Files:
9 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/LMDZ_ECRad

  • LMDZ6/branches/LMDZ_ECRad/libf/dynphy_lonlat/calfis.F

    r4056 r4482  
    186186         write(lunout,*) '  ngridmx  jjm   iim   '
    187187         write(lunout,*) ngridmx,jjm,iim
    188          STOP
     188         call abort_gcm("calfis", "", 1)
    189189        ENDIF
    190190      ELSE
  • LMDZ6/branches/LMDZ_ECRad/libf/dynphy_lonlat/calfis_loc.F

    r4056 r4482  
    262262          write(lunout,*) '  ngridmx  jjm   iim   '
    263263          write(lunout,*) ngridmx,jjm,iim
    264           STOP
     264          call abort_gcm("calfis_loc", "", 1)
    265265        ENDIF
    266266c$OMP MASTER
     
    12181218
    12191219#else
    1220       write(lunout,*)
    1221      & "calfis_p: for now can only work with parallel physics"
    1222       stop
     1220      call abort_gcm("calfis_loc",
     1221     & "calfis_p: for now can only work with parallel physics", 1)
    12231222#endif
    12241223! of #ifdef CPP_PHYS
  • LMDZ6/branches/LMDZ_ECRad/libf/dynphy_lonlat/gr_dyn_fi.F

    r2239 r4482  
    2222c   -------
    2323
    24       IF(ngrid.NE.2+(jm-2)*(im-1)) STOP 'probleme de dim'
     24      IF (ngrid.NE.2+(jm-2)*(im-1)) then
     25         call abort_gcm("gr_dyn_fi", 'probleme de dim', 1)
     26      end if
    2527c   traitement des poles
    2628      CALL SCOPY(nfield,pdyn,im*jm,pfi,ngrid)
  • LMDZ6/branches/LMDZ_ECRad/libf/dynphy_lonlat/inigeomphy_mod.F90

    r3895 r4482  
    2525  USE nrtype, ONLY: pi
    2626  USE comvert_mod, ONLY: preff, ap, bp, aps, bps, presnivs, &
    27                          scaleheight, pseudoalt
     27                         scaleheight, pseudoalt, presinter
    2828  USE vertical_layers_mod, ONLY: init_vertical_layers
    2929  IMPLICIT NONE
     
    233233  ! copy over preff , ap(), bp(), etc
    234234  CALL init_vertical_layers(nlayer,preff,scaleheight, &
    235                             ap,bp,aps,bps,presnivs,pseudoalt)
     235                            ap,bp,aps,bps,presnivs,presinter,pseudoalt)
    236236
    237237!$OMP END PARALLEL
  • LMDZ6/branches/LMDZ_ECRad/libf/dynphy_lonlat/phylmd/ce0l.F90

    r3815 r4482  
    2323  USE netcdf,         ONLY: NF90_OPEN, NF90_NOWRITE, NF90_CLOSE, NF90_NOERR,    &
    2424         NF90_INQUIRE_DIMENSION, NF90_INQ_DIMID, NF90_INQ_VARID, NF90_GET_VAR
    25   USE infotrac,       ONLY: type_trac, infotrac_init
     25  USE infotrac,       ONLY: init_infotrac
    2626  USE dimphy,         ONLY: klon
    2727  USE test_disvert_m, ONLY: test_disvert
     
    108108  calnd='gregorian'
    109109  SELECT CASE(calend)
    110     CASE('earth_360d');CALL ioconf_calendar('360d');   calnd='with 360 days/year'
     110    CASE('earth_360d');CALL ioconf_calendar('360_day');   calnd='with 360 days/year'
    111111    CASE('earth_365d');CALL ioconf_calendar('noleap'); calnd='with no leap year'
    112112    CASE('earth_366d');CALL ioconf_calendar('366d');   calnd='with leap years only'
     
    132132
    133133!--- Tracers initializations
    134   CALL infotrac_init()
     134  CALL init_infotrac()
    135135
    136136  CALL inifilr()
  • LMDZ6/branches/LMDZ_ECRad/libf/dynphy_lonlat/phylmd/iniphysiq_mod.F90

    r4140 r4482  
    1616  USE mod_phys_lmdz_para, ONLY: klon_omp ! number of columns (on local omp grid)
    1717  USE vertical_layers_mod, ONLY : init_vertical_layers
    18   USE infotrac, ONLY: nbtr,nqCO2,tracers,isotopes,type_trac,conv_flg,pbl_flg,nqtottr
     18  USE infotrac, ONLY: nbtr, type_trac
    1919#ifdef CPP_StratAer
    2020  USE infotrac_phy, ONLY: nbtr_bin, nbtr_sulgas, id_OCS_strat, &
     
    3030  USE mod_phys_lmdz_omp_data, ONLY: klon_omp
    3131#endif
    32   USE control_mod, ONLY: dayref,anneeref,day_step,nday,offline, iphysiq, config_inca
     32  USE control_mod, ONLY: dayref,anneeref,day_step,nday,offline, iphysiq
    3333  USE inifis_mod, ONLY: inifis
    3434  USE time_phylmdz_mod, ONLY: init_time
     
    137137
    138138  ! Initialize tracer names, numbers, etc. for physics
    139   CALL init_infotrac_phy(type_trac, tracers, isotopes, nqtottr, nqCO2, pbl_flg, conv_flg)
     139  CALL init_infotrac_phy
    140140
    141141  ! Initializations for Reprobus
     
    166166  END IF
    167167
    168   IF (type_trac == 'inca' .OR. type_trac == 'inco') THEN
     168  IF (ANY(type_trac == ['inca','inco'])) THEN
    169169#ifdef INCA
    170170     CALL init_inca_dim_reg(nbp_lon, nbp_lat - 1, &
  • LMDZ6/branches/LMDZ_ECRad/libf/dynphy_lonlat/phylmd/init_ssrf_m.F90

    r2798 r4482  
    33!*******************************************************************************
    44
    5   USE indice_sol_mod, ONLY: is_ter, is_oce, is_oce, is_lic, epsfra
     5  USE indice_sol_mod,     ONLY: is_ter, is_oce, is_oce, is_lic, epsfra
    66  USE dimphy,             ONLY: klon, zmasq
    77  USE phys_state_var_mod, ONLY: pctsrf
    8   USE geometry_mod, ONLY : longitude_deg, latitude_deg
     8  USE geometry_mod,       ONLY : longitude_deg, latitude_deg
    99  USE grid_atob_m,        ONLY: grille_m
    1010  USE ioipsl,             ONLY: flininfo, flinopen, flinget, flinclo
    1111  USE ioipsl_getin_p_mod, ONLY: getin_p
    12   USE comconst_mod, ONLY: im, pi
     12  USE comconst_mod,       ONLY: im, pi
     13  USE surface_data,       ONLY: landice_opt
    1314
    1415  CHARACTER(LEN=256), PARAMETER :: icefname="landiceref.nc", icevar="landice"
     
    5859! Sub-surfaces initialization
    5960!*******************************************************************************
    60 !--- Read and interpolate on model T-grid soil fraction and soil ice fraction.
    61   CALL flininfo(icefname, iml_lic, jml_lic, llm_tmp, ttm_tmp, fid)
    62   ALLOCATE(lat_lic(iml_lic,jml_lic),lon_lic(iml_lic,jml_lic))
    63   ALLOCATE(fraclic(iml_lic,jml_lic))
    64   CALL flinopen(icefname, .FALSE., iml_lic, jml_lic, llm_tmp,  &
    65  &               lon_lic, lat_lic, lev, ttm_tmp, itaul, date, dt, fid)
    66   CALL flinget(fid, icevar, iml_lic, jml_lic, llm_tmp, ttm_tmp, 1,1, fraclic)
    67   CALL flinclo(fid)
    68   WRITE(lunout,*)'landice dimensions: iml_lic, jml_lic : ',iml_lic,jml_lic
     61  IF (landice_opt .LT. 2) THEN
     62     ! Continue with reading landice.nc file
     63     WRITE(lunout,*)"Read landice.nc file to attribute is_lic fraction"
    6964
    70   ALLOCATE(dlon_lic(iml_lic),dlat_lic(jml_lic))
    71   dlon_lic(:)=lon_lic(:,1); IF(MAXVAL(dlon_lic)>pi) dlon_lic=dlon_lic*pi/180.
    72   dlat_lic(:)=lat_lic(1,:); IF(MAXVAL(dlat_lic)>pi) dlat_lic=dlat_lic*pi/180.
    73   DEALLOCATE(lon_lic,lat_lic); ALLOCATE(flic_tmp(iip1,jjp1))
    74   CALL grille_m(dlon_lic,dlat_lic,fraclic,rlonv(1:iim),rlatu,flic_tmp(1:iim,:))
    75   flic_tmp(iip1,:)=flic_tmp(1,:)
    76 
    77 !--- To the physical grid
    78   pctsrf(:,:) = 0.
    79   CALL gr_dyn_fi(1, iip1, jjp1, klon, flic_tmp, pctsrf(:,is_lic))
    80   DEALLOCATE(flic_tmp)
    81 
    82 !--- Adequation with soil/sea mask
    83   WHERE(pctsrf(:,is_lic)<EPSFRA) pctsrf(:,is_lic)=0.
    84   WHERE(zmasq(:)<EPSFRA)         pctsrf(:,is_lic)=0.
    85   pctsrf(:,is_ter)=zmasq(:)
    86   DO ji=1,klon
    87     IF(zmasq(ji)>EPSFRA) THEN
    88       IF(pctsrf(ji,is_lic)>=zmasq(ji)) THEN
    89         pctsrf(ji,is_lic)=zmasq(ji)
    90         pctsrf(ji,is_ter)=0.
    91       ELSE
    92         pctsrf(ji,is_ter)=zmasq(ji)-pctsrf(ji,is_lic)
    93         IF(pctsrf(ji,is_ter)<EPSFRA) THEN
    94           pctsrf(ji,is_ter)=0.
    95           pctsrf(ji,is_lic)=zmasq(ji)
    96         END IF
    97       END IF
    98     END IF
    99   END DO
    100 
    101 
    102   !--- Option no_ter_antartique removes all land fractions souther than 60S.
    103   !--- Land ice is set instead of the land fractions on these latitudes.
    104   !--- The ocean and sea-ice fractions are not changed.
    105   no_ter_antartique=.FALSE.
    106   CALL getin_p('no_ter_antartique',no_ter_antartique)
    107   WRITE(lunout,*)"no_ter_antartique=",no_ter_antartique
    108   IF (no_ter_antartique) THEN
    109      ! Remove all land fractions souther than 60S and set land-ice instead
    110      WRITE(lunout,*) "Remove land fractions souther than 60deg south by increasing"
    111      WRITE(lunout,*) "the continental ice fractions. No land can now be found at Antartic."
    112      DO ji=1, klon
    113         IF (latitude_deg(ji)<-60.0) THEN
    114            pctsrf(ji,is_lic) = pctsrf(ji,is_lic) + pctsrf(ji,is_ter)
    115            pctsrf(ji,is_ter) = 0
     65     !--- Read and interpolate on model T-grid soil fraction and soil ice fraction.
     66     CALL flininfo(icefname, iml_lic, jml_lic, llm_tmp, ttm_tmp, fid)
     67     ALLOCATE(lat_lic(iml_lic,jml_lic),lon_lic(iml_lic,jml_lic))
     68     ALLOCATE(fraclic(iml_lic,jml_lic))
     69     CALL flinopen(icefname, .FALSE., iml_lic, jml_lic, llm_tmp,  &
     70          &               lon_lic, lat_lic, lev, ttm_tmp, itaul, date, dt, fid)
     71     CALL flinget(fid, icevar, iml_lic, jml_lic, llm_tmp, ttm_tmp, 1,1, fraclic)
     72     CALL flinclo(fid)
     73     WRITE(lunout,*)'landice dimensions: iml_lic, jml_lic : ',iml_lic,jml_lic
     74     
     75     ALLOCATE(dlon_lic(iml_lic),dlat_lic(jml_lic))
     76     dlon_lic(:)=lon_lic(:,1); IF(MAXVAL(dlon_lic)>pi) dlon_lic=dlon_lic*pi/180.
     77     dlat_lic(:)=lat_lic(1,:); IF(MAXVAL(dlat_lic)>pi) dlat_lic=dlat_lic*pi/180.
     78     DEALLOCATE(lon_lic,lat_lic); ALLOCATE(flic_tmp(iip1,jjp1))
     79     CALL grille_m(dlon_lic,dlat_lic,fraclic,rlonv(1:iim),rlatu,flic_tmp(1:iim,:))
     80     flic_tmp(iip1,:)=flic_tmp(1,:)
     81     
     82     !--- To the physical grid
     83     pctsrf(:,:) = 0.
     84     CALL gr_dyn_fi(1, iip1, jjp1, klon, flic_tmp, pctsrf(:,is_lic))
     85     DEALLOCATE(flic_tmp)
     86     
     87     !--- Adequation with soil/sea mask
     88     WHERE(pctsrf(:,is_lic)<EPSFRA) pctsrf(:,is_lic)=0.
     89     WHERE(zmasq(:)<EPSFRA)         pctsrf(:,is_lic)=0.
     90     pctsrf(:,is_ter)=zmasq(:)
     91     DO ji=1,klon
     92        IF(zmasq(ji)>EPSFRA) THEN
     93           IF(pctsrf(ji,is_lic)>=zmasq(ji)) THEN
     94              pctsrf(ji,is_lic)=zmasq(ji)
     95              pctsrf(ji,is_ter)=0.
     96           ELSE
     97              pctsrf(ji,is_ter)=zmasq(ji)-pctsrf(ji,is_lic)
     98              IF(pctsrf(ji,is_ter)<EPSFRA) THEN
     99                 pctsrf(ji,is_ter)=0.
     100                 pctsrf(ji,is_lic)=zmasq(ji)
     101              END IF
     102           END IF
    116103        END IF
    117104     END DO
     105     
     106     
     107     !--- Option no_ter_antartique removes all land fractions souther than 60S.
     108     !--- Land ice is set instead of the land fractions on these latitudes.
     109     !--- The ocean and sea-ice fractions are not changed.
     110     no_ter_antartique=.FALSE.
     111     CALL getin_p('no_ter_antartique',no_ter_antartique)
     112     WRITE(lunout,*)"no_ter_antartique=",no_ter_antartique
     113     IF (no_ter_antartique) THEN
     114        ! Remove all land fractions souther than 60S and set land-ice instead
     115        WRITE(lunout,*) "Remove land fractions souther than 60deg south by increasing"
     116        WRITE(lunout,*) "the continental ice fractions. No land can now be found at Antartic."
     117        DO ji=1, klon
     118           IF (latitude_deg(ji)<-60.0) THEN
     119              pctsrf(ji,is_lic) = pctsrf(ji,is_lic) + pctsrf(ji,is_ter)
     120              pctsrf(ji,is_ter) = 0
     121           END IF
     122        END DO
     123     END IF
     124     
     125  ELSE
     126     ! landice_opt=2 and higher
     127     WRITE(lunout,*) 'No landice is attributed is_lic sub-surface because landice_opt=2 or higher.'
     128     WRITE(lunout,*) 'This means that the land model will handel land ice as well as all other land areas.'
     129     pctsrf(:,is_ter) = zmasq(:)
     130     pctsrf(:,is_lic) = 0.0
    118131  END IF
    119 
    120132
    121133!--- Sub-surface ocean and sea ice (sea ice set to zero for start).
  • LMDZ6/branches/LMDZ_ECRad/libf/dynphy_lonlat/phylmd/limit_netcdf.F90

    r3803 r4482  
    424424  IF(NF90_GET_ATT(ncid, varid, 'calendar', cal_in)/=NF90_NOERR) THEN
    425425    SELECT CASE(mode)
    426       CASE('RUG', 'ALB'); cal_in='360d'
     426      CASE('RUG', 'ALB'); cal_in='360_day'
    427427      CASE('SIC', 'SST'); cal_in='gregorian'
    428428    END SELECT
     
    492492      !--- DROPPED FOR BCS DATA (FRACTIONS CAN BE HIGHER THAN 1)
    493493      IF(ll.AND.ix_sic/=1.AND.mode=='SIC') &
    494         CALL abort_physic(mode,'unrealistic '//TRIM(mode)//' found: '//TRIM(str))
     494        CALL abort_physic(mode,'unrealistic '//TRIM(mode)//' found: '//TRIM(str), 1)
    495495
    496496    END IF
     
    599599         CALL pchfe_95(timeyear, champtime(i, j, :), yder, skip, &
    600600              arth(0.5, real(ndays_in) / ndays, ndays), champan(i, j, :), ierr)
    601          if (ierr < 0) stop 1
     601         if (ierr < 0) call abort_physic("get_2Dfield", "", 1)
    602602         n_extrap = n_extrap + ierr
    603603       END DO
     
    641641  ALLOCATE(champo(klon, ndays))
    642642  DO k=1, ndays
    643     CALL gr_dyn_fi(1, iip1, jjp1, klon, champan(1, 1, k), champo(1, k))
     643    CALL gr_dyn_fi(1, iip1, jjp1, klon, champan(1, 1, k), champo(:, k))
    644644  END DO
    645645  DEALLOCATE(champan)
Note: See TracChangeset for help on using the changeset viewer.