Changeset 1328 for LMDZ4


Ignore:
Timestamp:
Mar 18, 2010, 2:26:23 PM (14 years ago)
Author:
Laurent Fairhead
Message:

Continent/ocean mask was transformed incorrectly from o2a.nc file
Change of unit for seaice depending on whether the initial data is from
climatology or model results


Erreur sur la transformation vers la grille physique du masque lu dans o2a.nc
Pas de division par 100 de la glace océanique si on lit des champs du modèle
couplé

Location:
LMDZ4/trunk/libf
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • LMDZ4/trunk/libf/dyn3d/etat0_netcdf.F90

    r1323 r1328  
    214214    WRITE(lunout,fmt)int(ocemask)
    215215    ocemask_fi(1)=ocemask(1,1)
    216     DO j=2,jjm; ocemask_fi((j-2)*iim+1:iim+1)=ocemask(1:iim,j); END DO
     216    DO j=2,jjm; ocemask_fi((j-2)*iim+2:(j-1)*iim+1)=ocemask(1:iim,j); END DO
    217217    ocemask_fi(klon)=ocemask(1,jjp1)
    218218    zmasq=1.-ocemask_fi
  • LMDZ4/trunk/libf/dyn3d/limit_netcdf.F90

    r1323 r1328  
    8181  INTEGER :: NF90_FORMAT
    8282  LOGICAL :: lCPL                    !--- T: IPCC-IPSL cpl model output files
    83 
    84 !--- MICS (PHYSICAL KEYS, TIME) ------------------------------------------------
    85 !  INTEGER, PARAMETER        :: longcles=20
    86 !  REAL, DIMENSION(longcles) :: clesphy0
    87   INTEGER                   :: ndays
    88  
     83  INTEGER :: ndays                   !--- Depending on the output calendar
     84
    8985!--- INITIALIZATIONS -----------------------------------------------------------
    9086#ifdef NC_DOUBLE
     
    9490#endif
    9591
    96 !  CALL conf_gcm(99, .TRUE., clesphy0)
    9792  pi    = 4.*ATAN(1.)
    9893  rad   = 6371229.
     
    129124  WRITE(lunout,*)'Pour la glace de mer a ete choisi un fichier '//TRIM(dumstr)
    130125
    131   CALL get_2Dfield(icefile,'SIC',interbar,ndays,phy_ice,flag=oldice)
     126  CALL get_2Dfield(icefile,'SIC',interbar,ndays,phy_ice,flag=oldice,lCPL=lCPL)
    132127
    133128  ALLOCATE(pctsrf_t(klon,nbsrf,ndays))
     
    139134      pctsrf_t(:,is_ter,k)=pctsrf(:,is_ter)       ! land soil
    140135      pctsrf_t(:,is_lic,k)=pctsrf(:,is_lic)       ! land ice
    141       IF(lCPL) THEN                              ! SIC=pICE*(1-LIC-TER)
     136      IF(lCPL) THEN                               ! SIC=pICE*(1-LIC-TER)
    142137        pctsrf_t(:,is_sic,k)=fi_ice*(1-pctsrf(:,is_lic)-pctsrf(:,is_ter))
    143138      ELSE                                        ! SIC=pICE-LIC
     
    233228
    234229  !--- Variables creation
    235   ierr=NF90_DEF_VAR(nid,"TEMPS",NF90_FORMAT,dims,id_tim)
     230  ierr=NF90_DEF_VAR(nid,"TEMPS",NF90_FORMAT,(/ntim/),id_tim)
    236231  ierr=NF90_DEF_VAR(nid,"FOCE", NF90_FORMAT,dims,id_FOCE)
    237232  ierr=NF90_DEF_VAR(nid,"FSIC", NF90_FORMAT,dims,id_FSIC)
     
    257252
    258253  !--- Variables saving
    259   ierr=NF90_PUT_VAR(nid,id_tim,(/(DBLE(k),k=1,ndays)/))
     254  ierr=NF90_PUT_VAR(nid,id_tim,(/(REAL(k),k=1,ndays)/))
    260255  ierr=NF90_PUT_VAR(nid,id_FOCE,pctsrf_t(:,is_oce,:),(/1,1/),(/klon,ndays/))
    261256  ierr=NF90_PUT_VAR(nid,id_FSIC,pctsrf_t(:,is_sic,:),(/1,1/),(/klon,ndays/))
     
    284279!-------------------------------------------------------------------------------
    285280!
    286 SUBROUTINE get_2Dfield(fnam, mode, ibar, ndays, champo, flag, mask)
     281SUBROUTINE get_2Dfield(fnam, mode, ibar, ndays, champo, flag, mask, lCPL)
    287282!
    288283!-------------------------------------------------------------------------------
     
    312307  INTEGER,           INTENT(IN)     :: ndays    ! current year number of days
    313308  REAL,    POINTER,  DIMENSION(:,:) :: champo   ! output field = f(t)
    314   LOGICAL, OPTIONAL,                      INTENT(IN) :: flag
    315 ! flag=T means:   extrapolation (SST case)  or  old ice (SIC case)
     309  LOGICAL, OPTIONAL, INTENT(IN)     :: flag     ! extrapol. (SST)  old ice (SIC)
    316310  REAL,    OPTIONAL, DIMENSION(iim,jjp1), INTENT(IN) :: mask
     311  LOGICAL, OPTIONAL, INTENT(IN)     :: lCPL     ! Coupled model flag (for ICE)
    317312!-------------------------------------------------------------------------------
    318313! Local variables:
     
    397392  timeyear=mid_months(anneeref,cal_in,lmdep)
    398393  IF(lmdep/=12) WRITE(lunout,'(a,i3,a)')'Note: les fichiers de '//TRIM(mode)   &
    399     //' ne comportent pas 12, mais ',lmdep,' renregistrements.'
     394    //' ne comportent pas 12, mais ',lmdep,' enregistrements.'
    400395
    401396!--- GETTING THE FIELD AND INTERPOLATING IT ------------------------------------
     
    480475  IF(mode=='SIC') THEN
    481476    WRITE(lunout,*) 'Filtrage de la SIC: 0.0 < Sea-ice < 1.0'
    482     champan(:,:,:)=champan(:,:,:)/100.
     477    IF(.NOT.lCPL) champan(:,:,:)=champan(:,:,:)/100.
    483478    champan(iip1,:,:)=champan(1,:,:)
    484479    WHERE(champan>1.0) champan=1.0
     
    486481  END IF
    487482
    488 write(*,*)'coin1'
    489483!--- DYNAMICAL TO PHYSICAL GRID ------------------------------------------------
    490484  ALLOCATE(champo(klon,ndays))
     
    492486    CALL gr_dyn_fi(1,iip1,jjp1,klon,champan(1,1,k),champo(1,k))
    493487  END DO
    494 write(*,*)'coin2'
    495488  DEALLOCATE(champan)
    496 write(*,*)'coin3'
     489
    497490END SUBROUTINE get_2Dfield
    498491!
  • LMDZ4/trunk/libf/dyn3dpar/etat0_netcdf.F90

    r1323 r1328  
    214214    WRITE(lunout,fmt)int(ocemask)
    215215    ocemask_fi(1)=ocemask(1,1)
    216     DO j=2,jjm; ocemask_fi((j-2)*iim+1:iim+1)=ocemask(1:iim,j); END DO
     216    DO j=2,jjm; ocemask_fi((j-2)*iim+2:(j-1)*iim+1)=ocemask(1:iim,j); END DO
    217217    ocemask_fi(klon)=ocemask(1,jjp1)
    218218    zmasq=1.-ocemask_fi
  • LMDZ4/trunk/libf/dyn3dpar/limit_netcdf.F90

    r1323 r1328  
    8181  INTEGER :: NF90_FORMAT
    8282  LOGICAL :: lCPL                    !--- T: IPCC-IPSL cpl model output files
    83 
    84 !--- MICS (PHYSICAL KEYS, TIME) ------------------------------------------------
    85 !  INTEGER, PARAMETER        :: longcles=20
    86 !  REAL, DIMENSION(longcles) :: clesphy0
    87   INTEGER                   :: ndays
    88  
     83  INTEGER :: ndays                   !--- Depending on the output calendar
     84
    8985!--- INITIALIZATIONS -----------------------------------------------------------
    9086#ifdef NC_DOUBLE
     
    9490#endif
    9591
    96 !  CALL conf_gcm(99, .TRUE., clesphy0)
    9792  pi    = 4.*ATAN(1.)
    9893  rad   = 6371229.
     
    129124  WRITE(lunout,*)'Pour la glace de mer a ete choisi un fichier '//TRIM(dumstr)
    130125
    131   CALL get_2Dfield(icefile,'SIC',interbar,ndays,phy_ice,flag=oldice)
     126  CALL get_2Dfield(icefile,'SIC',interbar,ndays,phy_ice,flag=oldice,lCPL=lCPL)
    132127
    133128  ALLOCATE(pctsrf_t(klon,nbsrf,ndays))
     
    139134      pctsrf_t(:,is_ter,k)=pctsrf(:,is_ter)       ! land soil
    140135      pctsrf_t(:,is_lic,k)=pctsrf(:,is_lic)       ! land ice
    141       IF(lCPL) THEN                              ! SIC=pICE*(1-LIC-TER)
     136      IF(lCPL) THEN                               ! SIC=pICE*(1-LIC-TER)
    142137        pctsrf_t(:,is_sic,k)=fi_ice*(1-pctsrf(:,is_lic)-pctsrf(:,is_ter))
    143138      ELSE                                        ! SIC=pICE-LIC
     
    233228
    234229  !--- Variables creation
    235   ierr=NF90_DEF_VAR(nid,"TEMPS",NF90_FORMAT,dims,id_tim)
     230  ierr=NF90_DEF_VAR(nid,"TEMPS",NF90_FORMAT,(/ntim/),id_tim)
    236231  ierr=NF90_DEF_VAR(nid,"FOCE", NF90_FORMAT,dims,id_FOCE)
    237232  ierr=NF90_DEF_VAR(nid,"FSIC", NF90_FORMAT,dims,id_FSIC)
     
    257252
    258253  !--- Variables saving
    259   ierr=NF90_PUT_VAR(nid,id_tim,(/(DBLE(k),k=1,ndays)/))
     254  ierr=NF90_PUT_VAR(nid,id_tim,(/(REAL(k),k=1,ndays)/))
    260255  ierr=NF90_PUT_VAR(nid,id_FOCE,pctsrf_t(:,is_oce,:),(/1,1/),(/klon,ndays/))
    261256  ierr=NF90_PUT_VAR(nid,id_FSIC,pctsrf_t(:,is_sic,:),(/1,1/),(/klon,ndays/))
     
    284279!-------------------------------------------------------------------------------
    285280!
    286 SUBROUTINE get_2Dfield(fnam, mode, ibar, ndays, champo, flag, mask)
     281SUBROUTINE get_2Dfield(fnam, mode, ibar, ndays, champo, flag, mask, lCPL)
    287282!
    288283!-------------------------------------------------------------------------------
     
    312307  INTEGER,           INTENT(IN)     :: ndays    ! current year number of days
    313308  REAL,    POINTER,  DIMENSION(:,:) :: champo   ! output field = f(t)
    314   LOGICAL, OPTIONAL,                      INTENT(IN) :: flag
    315 ! flag=T means:   extrapolation (SST case)  or  old ice (SIC case)
     309  LOGICAL, OPTIONAL, INTENT(IN)     :: flag     ! extrapol. (SST)  old ice (SIC)
    316310  REAL,    OPTIONAL, DIMENSION(iim,jjp1), INTENT(IN) :: mask
     311  LOGICAL, OPTIONAL, INTENT(IN)     :: lCPL     ! Coupled model flag (for ICE)
    317312!-------------------------------------------------------------------------------
    318313! Local variables:
     
    397392  timeyear=mid_months(anneeref,cal_in,lmdep)
    398393  IF(lmdep/=12) WRITE(lunout,'(a,i3,a)')'Note: les fichiers de '//TRIM(mode)   &
    399     //' ne comportent pas 12, mais ',lmdep,' renregistrements.'
     394    //' ne comportent pas 12, mais ',lmdep,' enregistrements.'
    400395
    401396!--- GETTING THE FIELD AND INTERPOLATING IT ------------------------------------
     
    480475  IF(mode=='SIC') THEN
    481476    WRITE(lunout,*) 'Filtrage de la SIC: 0.0 < Sea-ice < 1.0'
    482     champan(:,:,:)=champan(:,:,:)/100.
     477    IF(.NOT.lCPL) champan(:,:,:)=champan(:,:,:)/100.
    483478    champan(iip1,:,:)=champan(1,:,:)
    484479    WHERE(champan>1.0) champan=1.0
     
    486481  END IF
    487482
    488 write(*,*)'coin1'
    489483!--- DYNAMICAL TO PHYSICAL GRID ------------------------------------------------
    490484  ALLOCATE(champo(klon,ndays))
     
    492486    CALL gr_dyn_fi(1,iip1,jjp1,klon,champan(1,1,k),champo(1,k))
    493487  END DO
    494 write(*,*)'coin2'
    495488  DEALLOCATE(champan)
    496 write(*,*)'coin3'
     489
    497490END SUBROUTINE get_2Dfield
    498491!
Note: See TracChangeset for help on using the changeset viewer.