Ignore:
Timestamp:
Jun 16, 2014, 4:33:38 PM (10 years ago)
Author:
Ehouarn Millour
Message:

Preparatory stuff to fix and improve the slab ocean model.
FC

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/phylmd/limit_slab.F90

    r1907 r2057  
    11! $Header$
    22
    3 SUBROUTINE limit_slab(itime, dtime, jour, lmt_bils, lmt_foce, diff_sst)
     3SUBROUTINE limit_slab(itime, dtime, jour, lmt_bils, diff_sst)
    44
    55  USE dimphy
     
    2020  INTEGER, INTENT(IN) :: jour    ! jour a lire dans l'annee
    2121  REAL   , INTENT(IN) :: dtime   ! pas de temps de la physique (en s)
    22   REAL, DIMENSION(klon), INTENT(OUT) :: lmt_bils, lmt_foce, diff_sst
     22  REAL, DIMENSION(klon), INTENT(OUT) :: lmt_bils, diff_sst
    2323
    2424! Locals variables with attribute SAVE
    2525!****************************************************************************************
    26   REAL, DIMENSION(:), ALLOCATABLE, SAVE :: bils_save, foce_save
    27 !$OMP THREADPRIVATE(bils_save, foce_save)
     26  REAL, DIMENSION(:), ALLOCATABLE, SAVE :: bils_save, diff_sst_save
     27!$OMP THREADPRIVATE(bils_save, diff_sst_save)
    2828
    2929! Locals variables
     
    3232  INTEGER                  :: nvarid, nid, ierr, i
    3333  INTEGER, DIMENSION(2)    :: start, epais
    34   REAL, DIMENSION(klon_glo):: bils_glo, foce_glo, sst_l_glo, sst_lp1_glo, diff_sst_glo
     34  REAL, DIMENSION(klon_glo):: bils_glo, sst_l_glo, sst_lp1_glo, diff_sst_glo
    3535  CHARACTER (len = 20)     :: modname = 'limit_slab'
     36  LOGICAL                  :: read_bils,read_sst
    3637
    3738! End declaration
     
    4142  lmt_pas = NINT(86400./dtime)
    4243 
     44  ! F. Codron 5/14: add defaults for bils, diff_sst (0)
    4345  IF (MOD(itime-1, lmt_pas) == 0) THEN   ! time to read
    4446     !$OMP MASTER  ! Only master thread
    4547     IF (is_mpi_root) THEN ! Only master processus
    4648        print*,'in limit_slab time to read, itime=',itime
     49        read_bils=.TRUE.
     50        read_sst=.TRUE.
    4751       
    4852        ierr = NF90_OPEN ('limit_slab.nc', NF90_NOWRITE, nid)
    49         IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,&
    50              'Pb in opening file limit_slab.nc',1)
     53        IF (ierr /= NF90_NOERR) THEN
     54            read_bils=.FALSE.
     55            read_sst=.FALSE.
     56        ELSE ! read file
    5157       
    5258        ! La tranche de donnees a lire:
     
    5763
    5864!****************************************************************************************
    59 ! 2) Read bils and ocean fraction
     65! 2) Read bils and SST tendency
    6066!
    6167!****************************************************************************************
     
    6369! Read bils_glo
    6470        ierr = NF90_INQ_VARID(nid, 'BILS_OCE', nvarid)
    65         IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'The variable <BILS_OCE> is abstent',1)
    66 
    67         ierr = NF90_GET_VAR(nid,nvarid,bils_glo,start,epais)
    68         IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'Reading of <BILS_OCE> failed',1)
    69 !
    70 ! Read foce_glo
    71         ierr = NF90_INQ_VARID(nid, 'FOCE', nvarid)
    72         IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'The variable <FOCE> is abstent',1)
    73 
    74         ierr = NF90_GET_VAR(nid,nvarid,foce_glo,start,epais)
    75         IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'Reading of <FOCE> failed',1)
    76 !
     71        IF (ierr /= NF90_NOERR) THEN
     72            read_bils=.FALSE.
     73        ELSE
     74            ierr = NF90_GET_VAR(nid,nvarid,bils_glo,start,epais)
     75            IF (ierr /= NF90_NOERR) read_bils=.FALSE.
     76        END IF
    7777! Read sst_glo for this day
    7878        ierr = NF90_INQ_VARID(nid, 'SST', nvarid)
    79         IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'The variable <SST> is abstent',1)
    80 
    81         ierr = NF90_GET_VAR(nid,nvarid,sst_l_glo,start,epais)
    82         IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'Reading of <SST> failed',1)
    83 
     79        IF (ierr /= NF90_NOERR)  THEN
     80            read_sst=.FALSE.
     81        ELSE
     82            ierr = NF90_GET_VAR(nid,nvarid,sst_l_glo,start,epais)
     83            IF (ierr /= NF90_NOERR) read_sst=.FALSE.
    8484! Read sst_glo for one day ahead
    85         start(2) = jour + 1
    86         IF (start(2) > 360) start(2)=1
    87         ierr = NF90_GET_VAR(nid,nvarid,sst_lp1_glo,start,epais)
    88         IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'Reading of <SST> day+1 failed',1)
    89 
    90 ! Calculate difference in temperature between this day and one ahead
    91         DO i=1, klon_glo-1
    92            diff_sst_glo(i) = sst_lp1_glo(i) - sst_l_glo(i)
    93         END DO
    94         diff_sst_glo(klon_glo) = sst_lp1_glo(klon_glo) - sst_l_glo(1)
     85            start(2) = jour + 1
     86            IF (start(2) > 360) start(2)=1
     87            ierr = NF90_GET_VAR(nid,nvarid,sst_lp1_glo,start,epais)
     88            IF (ierr /= NF90_NOERR) read_sst=.FALSE.
     89        END IF
    9590
    9691!****************************************************************************************
    97 ! 5) Close file and distribuate variables to all processus
     92! 5) Close file and distribute variables to all processus
    9893!
    9994!****************************************************************************************
    10095        ierr = NF90_CLOSE(nid)
    10196        IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'Pb when closing file', 1)
     97        END IF ! Read File
     98        IF (read_sst) THEN
     99! Calculate difference in temperature between this day and one ahead
     100!            DO i=1, klon_glo-1
     101!               diff_sst_glo(i) = sst_lp1_glo(i) - sst_l_glo(i)
     102!            END DO
     103!            diff_sst_glo(klon_glo) = sst_lp1_glo(klon_glo) - sst_l_glo(1)
     104            DO i=1, klon_glo
     105               diff_sst_glo(i) = sst_lp1_glo(i) - sst_l_glo(i)
     106            END DO
     107        END IF !read_sst
    102108     ENDIF ! is_mpi_root
    103109
     
    105111       
    106112     IF (.NOT. ALLOCATED(bils_save)) THEN
    107         ALLOCATE(bils_save(klon), foce_save(klon), stat=ierr)
     113        ALLOCATE(bils_save(klon), diff_sst_save(klon), stat=ierr)
    108114        IF (ierr /= 0) CALL abort_gcm('limit_slab', 'pb in allocation',1)
    109115     END IF
    110116
    111      CALL Scatter(bils_glo, bils_save)
    112      CALL Scatter(foce_glo, foce_save)
    113      CALL Scatter(diff_sst_glo, diff_sst)
     117! Giveddefault values if needed
     118     IF (read_bils) THEN
     119         CALL Scatter(bils_glo, bils_save)
     120     ELSE
     121         bils_save(:)=0.
     122     END IF
     123     IF (read_sst) THEN
     124         CALL Scatter(diff_sst_glo, diff_sst_save)
     125     ELSE
     126         diff_sst_save(:)=0.
     127     END IF
    114128     
    115   ELSE ! not time to read
    116      diff_sst(:) = 0.
    117129  ENDIF ! time to read
    118130
    119131  lmt_bils(:) = bils_save(:)
    120   lmt_foce(:) = foce_save(:)
     132  diff_sst(:) = diff_sst_save(:)
    121133 
    122134END SUBROUTINE limit_slab
Note: See TracChangeset for help on using the changeset viewer.