Changeset 3448


Ignore:
Timestamp:
Jan 25, 2019, 5:48:33 PM (5 years ago)
Author:
oboucher
Message:

small changes for interactive CO2
cleaning up END IF statements

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmd/cpl_mod.F90

    r3435 r3448  
    204204
    205205! Allocate variable in carbon_cycle_mod
    206        ALLOCATE(fco2_ocn_day(klon), stat = error)
     206       IF (.NOT.ALLOCATED(fco2_ocn_day)) ALLOCATE(fco2_ocn_day(klon), stat = error)
    207207       sum_error = sum_error + error
    208     END IF
     208    ENDIF
    209209
    210210    IF (sum_error /= 0) THEN
     
    259259                "-",nbp_lon,nbp_lat,nhoridct,1,1,1,-99,32,"inst",dtime,dtime)
    260260         ENDIF
    261        END DO
     261       ENDDO
    262262       CALL histend(nidct)
    263263       CALL histsync(nidct)
     
    272272                "-",nbp_lon,nbp_lat,nhoridcs,1,1,1,-99,32,"inst",dtime,dtime)
    273273         ENDIF
    274        END DO
     274       ENDDO
    275275       CALL histend(nidcs)
    276276       CALL histsync(nidcs)
     
    286286       abort_message='carbon_cycle_cpl does not work with opa8'
    287287       CALL abort_physic(modname,abort_message,1)
    288     END IF
     288    ENDIF
    289289
    290290  END SUBROUTINE cpl_init
     
    356356                CALL histwrite(nidcs,inforecv(i)%name,itau_w,tab_read_flds(:,:,i),nbp_lon*(nbp_lat),ndexcs)
    357357            ENDIF
    358           END DO
     358          ENDDO
    359359       ENDIF
    360360
     
    415415       ENDDO
    416416
    417     END IF ! if time to receive
     417    ENDIF ! if time to receive
    418418
    419419  END SUBROUTINE cpl_receive_frac
     
    466466       DO i=1,klon
    467467          index(i)=i
    468        END DO
     468       ENDDO
    469469       CALL cpl2gath(read_co2, fco2_ocn_day, klon, index)
    470     END IF
     470    ENDIF
    471471
    472472!*************************************************************************************
     
    477477    DO i=1, knon
    478478       tsurf_new(i) = tsurf_new(i)/(1. - sic_new(i))
    479     END DO
     479    ENDDO
    480480
    481481  END SUBROUTINE cpl_receive_ocean_fields
     
    529529       tsurf_new(i) = tsurf_new(i) / sic_new(i)
    530530       alb_new(i)   = alb_new(i)   / sic_new(i)
    531     END DO
     531    ENDDO
    532532
    533533  END SUBROUTINE cpl_receive_seaice_fields
     
    637637          cpl_atm_co2(ig,cpl_index) = cpl_atm_co2(ig,cpl_index) + &
    638638               co2_send(knindex(ig))/ REAL(nexca)
    639        END IF
     639!!---OB: this is correct but why knindex ??
     640       ENDIF
    640641     ENDDO
    641642
     
    682683             ALLOCATE(cpl_atm_co22D(nbp_lon,jj_nb), stat=error)
    683684             sum_error = sum_error + error
    684           END IF
     685          ENDIF
    685686
    686687          IF (sum_error /= 0) THEN
     
    886887             ALLOCATE(cpl_atm_co22D(nbp_lon,jj_nb), stat=error)
    887888             sum_error = sum_error + error
    888           END IF
     889          ENDIF
    889890
    890891          IF (sum_error /= 0) THEN
     
    917918       DO ig = 1, knon
    918919          cpl_fder_tmp(knindex(ig))=cpl_fder(ig,cpl_index)
    919        END DO
     920       ENDDO
    920921       CALL gath2cpl(cpl_fder_tmp(:), cpl_fder2D(:,:,cpl_index), &
    921922            klon, unity)
     
    11391140       tab_flds(:,:,ids_runcoa) = cpl_rcoa2D(:,:)
    11401141       tab_flds(:,:,ids_rivflu) = cpl_rriv2D(:,:)
    1141     END IF
     1142    ENDIF
    11421143
    11431144!*************************************************************************************
     
    12521253                  cpl_tauy2D(:,:,2) * pctsrf2D(:,:,is_sic) / deno(:,:)
    12531254          ENDWHERE
    1254        END IF
     1255       ENDIF
    12551256
    12561257    ENDIF ! is_omp_root
     
    13361337       DEALLOCATE(cpl_atm_co22D, stat=error )
    13371338       sum_error = sum_error + error
    1338     END IF
     1339    ENDIF
    13391340
    13401341    IF (sum_error /= 0) THEN
Note: See TracChangeset for help on using the changeset viewer.