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 11455 for branches/UKMO/dev_r5518_obs_oper_update_addclim/NEMOGCM/NEMO/OPA_SRC/OBS/diaobs.F90 – NEMO

Ignore:
Timestamp:
2019-08-19T17:36:23+02:00 (5 years ago)
Author:
mattmartin
Message:

Commit version which compiles and runs. Not fully tested that it is producing the correct answer yet though.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/dev_r5518_obs_oper_update_addclim/NEMOGCM/NEMO/OPA_SRC/OBS/diaobs.F90

    r11449 r11455  
    5050   LOGICAL :: ln_diaobs            !: Logical switch for the obs operator 
    5151   LOGICAL :: ln_sstnight          !: Logical switch for night mean SST obs 
    52    LOGICAL :: ln_output_clim       !: Logical switch for interpolating and outputting T/S climatology 
    5352   LOGICAL :: ln_default_fp_indegs !: T=> Default obs footprint size specified in degrees, F=> in metres 
    5453   LOGICAL :: ln_sla_fp_indegs     !: T=>     SLA obs footprint size specified in degrees, F=> in metres 
     
    5655   LOGICAL :: ln_sss_fp_indegs     !: T=>     SSS obs footprint size specified in degrees, F=> in metres 
    5756   LOGICAL :: ln_sic_fp_indegs     !: T=> sea-ice obs footprint size specified in degrees, F=> in metres 
     57   LOGICAL :: ln_output_clim       !: Logical switch for interpolating and writing T/S climatology 
    5858 
    5959   REAL(wp) :: rn_default_avglamscl !: Default E/W diameter of observation footprint 
     
    235235      LOGICAL :: ltype_fp_indegs ! Local version of ln_*_fp_indegs 
    236236      LOGICAL :: ltype_night     ! Local version of ln_sstnight (false for other variables) 
     237      LOGICAL :: ltype_clim      ! Local version of ln_output_clim 
    237238 
    238239      REAL(wp), POINTER, DIMENSION(:,:,:) :: & 
     
    728729 
    729730         DO jtype = 1, nproftypes 
    730  
     731             
     732            ltype_clim = .FALSE.  
     733             
    731734            IF ( TRIM(cobstypesprof(jtype)) == 'prof' ) THEN 
    732735               nvarsprof(jtype) = 2 
    733736               nextrprof(jtype) = 1 
     737               IF ( ln_output_clim ) ltype_clim = .TRUE.               
    734738               ALLOCATE(llvar(nvarsprof(jtype))) 
    735739               CALL wrk_alloc( jpi, jpj,      nvarsprof(jtype), zglam ) 
     
    777781               &               nvarsprof(jtype), nextrprof(jtype), nitend-nit000+2, & 
    778782               &               rn_dobsini, rn_dobsend, llvar, & 
    779                &               ln_ignmis, ln_s_at_t, .FALSE., & 
     783               &               ln_ignmis, ln_s_at_t, .FALSE., ltype_clim, & 
    780784               &               kdailyavtypes = nn_profdavtypes ) 
    781785 
     
    813817            nvarssurf(jtype) = 1 
    814818            nextrsurf(jtype) = 0 
     819            ltype_clim = .FALSE. 
    815820            IF ( TRIM(cobstypessurf(jtype)) == 'sla' ) nextrsurf(jtype) = 2 
     821            IF ( ln_output_clim .AND. & 
     822               & ( ( TRIM(cobstypessurf(jtype)) == 'sst' ) .OR. & 
     823               &   ( TRIM(cobstypessurf(jtype)) == 'sss' ) ) ) & 
     824               & ltype_clim = .TRUE. 
    816825 
    817826            !Read in surface obs types 
     
    819828               &               clsurffiles(jtype,1:ifilessurf(jtype)), & 
    820829               &               nvarssurf(jtype), nextrsurf(jtype), nitend-nit000+2, & 
    821                &               rn_dobsini, rn_dobsend, ln_ignmis, .FALSE., llnightav(jtype) ) 
     830               &               rn_dobsini, rn_dobsend, ln_ignmis, .FALSE., & 
     831               &               llnightav(jtype), ltype_clim ) 
    822832 
    823833            CALL obs_pre_surf( surfdata(jtype), surfdataqc(jtype), ln_nea, ln_bound_reject ) 
     
    928938         & jp_spm 
    929939#endif 
     940      USE tradmp, ONLY: & 
     941         & tclim, & 
     942         & sclim 
    930943 
    931944      IMPLICIT NONE 
     
    956969         & pco2_3d                 ! 3D pCO2 from FABM 
    957970#endif 
    958       REAL(wp), POINTER, DIMENSION(:,:,:,:) ::  zts_dta  
    959971       
    960972      IF(lwp) THEN 
     
    966978 
    967979      idaystp = NINT( rday / rdt ) 
    968  
    969       ! Get the climatological T & S fields on this time step 
    970       IF ( ln_output_clim ) CALL dta_tsd( kstp, zts_dta ) 
    971980 
    972981      !----------------------------------------------------------------------- 
     
    9981007               zprofvar(:,:,:,1) = tsn(:,:,:,jp_tem) 
    9991008               zprofvar(:,:,:,2) = tsn(:,:,:,jp_sal) 
    1000                IF ( ln_output_clim ) THEN                
    1001                   zprofclim(:,:,:,1) = zts_dta(:,:,:,jp_tem) 
    1002                   zprofclim(:,:,:,2) = zts_dta(:,:,:,jp_sal) 
     1009               IF ( ln_output_clim ) THEN           
     1010                  zprofclim(:,:,:,1) = tclim(:,:,:) 
     1011                  zprofclim(:,:,:,2) = sclim(:,:,:) 
    10031012               ENDIF 
    10041013                
     
    12191228            CASE('sst') 
    12201229               zsurfvar(:,:) = tsn(:,:,1,jp_tem) 
    1221                IF ( ln_output_clim ) zsurfclim(:,:) = zts_dta(:,:,1,jp_tem) 
     1230               IF ( ln_output_clim ) zsurfclim(:,:) = tclim(:,:,1) 
    12221231            CASE('sla') 
    12231232               zsurfvar(:,:)  = sshn(:,:) 
    12241233            CASE('sss') 
    12251234               zsurfvar(:,:) = tsn(:,:,1,jp_sal) 
    1226                IF ( ln_output_clim ) zsurfclim(:,:) = zts_dta(:,:,1,jp_sal)                
     1235               IF ( ln_output_clim ) zsurfclim(:,:) = sclim(:,:,1)               
    12271236            CASE('sic') 
    12281237               IF ( kstp == 0 ) THEN 
Note: See TracChangeset for help on using the changeset viewer.