New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
Changeset 5462 for branches/UKMO/restart_datestamp/NEMOGCM/NEMO/OPA_SRC/TRA/trabbc.F90 – NEMO

Ignore:
Timestamp:
2015-06-22T16:40:58+02:00 (9 years ago)
Author:
davestorkey
Message:

Update UKMO/restart_datestamp branch to revision 5442 of trunk. Also clear the SVN keywords again - necessary after the update step.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/restart_datestamp/NEMOGCM/NEMO/OPA_SRC/TRA/trabbc.F90

    r5420 r5462  
    2121   USE trdtra          ! trends manager: tracers  
    2222   USE in_out_manager  ! I/O manager 
     23   USE iom             ! I/O manager 
     24   USE fldread         ! read input fields 
     25   USE lbclnk            ! ocean lateral boundary conditions (or mpp link) 
     26   USE lib_mpp           ! distributed memory computing library 
    2327   USE prtctl          ! Print control 
    2428   USE wrk_nemo        ! Memory Allocation 
     
    3741 
    3842   REAL(wp), PUBLIC, DIMENSION(:,:), ALLOCATABLE ::   qgh_trd0   ! geothermal heating trend 
     43   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_qgh              ! structure of input qgh (file informations, fields read) 
    3944  
    4045   !! * Substitutions 
     
    9297      END DO 
    9398      ! 
     99      CALL lbc_lnk( tsa(:,:,:,jp_tem) , 'T', 1. ) 
     100      ! 
    94101      IF( l_trdtra ) THEN        ! Save the geothermal heat flux trend for diagnostics 
    95102         ztrdt(:,:,:) = tsa(:,:,:,jp_tem) - ztrdt(:,:,:) 
     
    125132      INTEGER  ::   inum                ! temporary logical unit 
    126133      INTEGER  ::   ios                 ! Local integer output status for namelist read 
    127       ! 
    128       NAMELIST/nambbc/ln_trabbc, nn_geoflx, rn_geoflx_cst  
     134      INTEGER  ::   ierror              ! local integer 
     135      ! 
     136      TYPE(FLD_N)        ::   sn_qgh    ! informations about the geotherm. field to be read 
     137      CHARACTER(len=256) ::   cn_dir    ! Root directory for location of ssr files 
     138      ! 
     139      NAMELIST/nambbc/ln_trabbc, nn_geoflx, rn_geoflx_cst, sn_qgh, cn_dir  
    129140      !!---------------------------------------------------------------------- 
    130141 
     
    161172         CASE ( 2 )                          !* variable geothermal heat flux : read the geothermal fluxes in mW/m2 
    162173            IF(lwp) WRITE(numout,*) '      *** variable geothermal heat flux' 
    163             CALL iom_open ( 'geothermal_heating.nc', inum ) 
    164             CALL iom_get  ( inum, jpdom_data, 'heatflow', qgh_trd0 ) 
    165             CALL iom_close( inum ) 
    166             qgh_trd0(:,:) = r1_rau0_rcp * qgh_trd0(:,:) * 1.e-3     ! conversion in W/m2 
     174            ! 
     175            ALLOCATE( sf_qgh(1), STAT=ierror ) 
     176            IF( ierror > 0 ) THEN 
     177               CALL ctl_stop( 'tra_bbc_init: unable to allocate sf_qgh structure' )   ; 
     178               RETURN 
     179            ENDIF 
     180            ALLOCATE( sf_qgh(1)%fnow(jpi,jpj,1)   ) 
     181            IF( sn_qgh%ln_tint )ALLOCATE( sf_qgh(1)%fdta(jpi,jpj,1,2) ) 
     182            ! fill sf_chl with sn_chl and control print 
     183            CALL fld_fill( sf_qgh, (/ sn_qgh /), cn_dir, 'tra_bbc_init',   & 
     184               &          'bottom temperature boundary condition', 'nambbc' ) 
     185 
     186            CALL fld_read( nit000, 1, sf_qgh )                         ! Read qgh data 
     187            qgh_trd0(:,:) = r1_rau0_rcp * sf_qgh(1)%fnow(:,:,1) * 1.e-3 ! conversion in W/m2 
    167188            ! 
    168189         CASE DEFAULT 
Note: See TracChangeset for help on using the changeset viewer.