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 4106 – NEMO

Changeset 4106


Ignore:
Timestamp:
2013-10-22T17:30:08+02:00 (10 years ago)
Author:
andrewryan
Message:

Applied naming convention to eliminate confusion with OFF_SRC, included relevant OPA_SRC files in OOO_SRC directory.

Location:
branches/2013/dev_r3987_UKMO4_OBS/NEMOGCM/NEMO
Files:
3 edited
1 copied
5 moved

Legend:

Unmodified
Added
Removed
  • branches/2013/dev_r3987_UKMO4_OBS/NEMOGCM/NEMO/OOO_SRC/nemo.f90

    r4101 r4106  
    11PROGRAM nemo 
    2    USE off_oper 
     2   USE ooomod 
    33   IMPLICIT NONE 
    44   !!---------------------------------------------------------------------- 
     
    88   !!              location. 
    99   !!---------------------------------------------------------------------- 
    10    CALL off_obs_oper 
     10   CALL offline_obs_oper 
    1111END PROGRAM nemo 
    1212 
  • branches/2013/dev_r3987_UKMO4_OBS/NEMOGCM/NEMO/OOO_SRC/nemogcm.F90

    r4102 r4106  
    101101CONTAINS 
    102102 
    103    SUBROUTINE nemo_gcm 
    104       !!---------------------------------------------------------------------- 
    105       !!                     ***  ROUTINE nemo_gcm  *** 
    106       !! 
    107       !! ** Purpose :   NEMO solves the primitive equations on an orthogonal 
    108       !!              curvilinear mesh on the sphere. 
    109       !! 
    110       !! ** Method  : - model general initialization 
    111       !!              - launch the time-stepping (stp routine) 
    112       !!              - finalize the run by closing files and communications 
    113       !! 
    114       !! References : Madec, Delecluse, Imbard, and Levy, 1997:  internal report, IPSL. 
    115       !!              Madec, 2008, internal report, IPSL. 
    116       !!---------------------------------------------------------------------- 
    117       INTEGER ::   istp       ! time step index 
    118       !!---------------------------------------------------------------------- 
    119       ! 
    120 #if defined key_agrif 
    121       CALL Agrif_Init_Grids()      ! AGRIF: set the meshes 
    122 #endif 
    123  
    124       !                            !-----------------------! 
    125       CALL nemo_init               !==  Initialisations  ==! 
    126       !                            !-----------------------! 
    127 #if defined key_agrif 
    128       CALL Agrif_Declare_Var_dom   ! AGRIF: set the meshes for DOM 
    129       CALL Agrif_Declare_Var       !  "      "   "   "      "  DYN/TRA  
    130 # if defined key_top 
    131       CALL Agrif_Declare_Var_top   !  "      "   "   "      "  TOP 
    132 # endif 
    133 # if defined key_lim2 
    134       CALL Agrif_Declare_Var_lim2  !  "      "   "   "      "  LIM 
    135 # endif 
    136 #endif 
    137       ! check that all process are still there... If some process have an error, 
    138       ! they will never enter in step and other processes will wait until the end of the cpu time! 
    139       IF( lk_mpp )   CALL mpp_max( nstop ) 
    140  
    141       IF(lwp) WRITE(numout,cform_aaa)   ! Flag AAAAAAA 
    142  
    143       !                            !-----------------------! 
    144       !                            !==   time stepping   ==! 
    145       !                            !-----------------------! 
    146       istp = nit000 
    147 #if defined key_c1d 
    148          DO WHILE ( istp <= nitend .AND. nstop == 0 ) 
    149             CALL stp_c1d( istp ) 
    150             istp = istp + 1 
    151          END DO 
    152 #else 
    153           IF( lk_asminc ) THEN 
    154              IF( ln_bkgwri ) CALL asm_bkg_wri( nit000 - 1 )    ! Output background fields 
    155              IF( ln_asmdin ) THEN                        ! Direct initialization 
    156                 IF( ln_trainc ) CALL tra_asm_inc( nit000 - 1 )    ! Tracers 
    157                 IF( ln_dyninc ) CALL dyn_asm_inc( nit000 - 1 )    ! Dynamics 
    158                 IF( ln_sshinc ) CALL ssh_asm_inc( nit000 - 1 )    ! SSH 
    159              ENDIF 
    160           ENDIF 
    161  
    162          DO WHILE ( istp <= nitend .AND. nstop == 0 ) 
    163 #if defined key_agrif 
    164             CALL Agrif_Step( stp )           ! AGRIF: time stepping 
    165 #else 
    166             CALL stp( istp )                 ! standard time stepping 
    167 #endif 
    168             istp = istp + 1 
    169             IF( lk_mpp )   CALL mpp_max( nstop ) 
    170          END DO 
    171 #endif 
    172  
    173       IF( lk_diaobs   )   CALL dia_obs_wri 
    174       ! 
    175       IF( ln_icebergs )   CALL icb_end( nitend ) 
    176  
    177       !                            !------------------------! 
    178       !                            !==  finalize the run  ==! 
    179       !                            !------------------------! 
    180       IF(lwp) WRITE(numout,cform_aaa)   ! Flag AAAAAAA 
    181       ! 
    182       IF( nstop /= 0 .AND. lwp ) THEN   ! error print 
    183          WRITE(numout,cform_err) 
    184          WRITE(numout,*) nstop, ' error have been found' 
    185       ENDIF 
    186       ! 
    187 #if defined key_agrif 
    188       CALL Agrif_ParentGrid_To_ChildGrid() 
    189       IF( lk_diaobs ) CALL dia_obs_wri 
    190       IF( nn_timing == 1 )   CALL timing_finalize 
    191       CALL Agrif_ChildGrid_To_ParentGrid() 
    192 #endif 
    193       IF( nn_timing == 1 )   CALL timing_finalize 
    194       ! 
    195       CALL nemo_closefile 
    196 #if defined key_iomput 
    197       CALL xios_finalize                ! end mpp communications with xios 
    198 # if defined key_oasis3 || defined key_oasis4 
    199       CALL cpl_prism_finalize           ! end coupling and mpp communications with OASIS 
    200 # endif 
    201 #else 
    202 # if defined key_oasis3 || defined key_oasis4 
    203       CALL cpl_prism_finalize           ! end coupling and mpp communications with OASIS 
    204 # else 
    205       IF( lk_mpp )   CALL mppstop       ! end mpp communications 
    206 # endif 
    207 #endif 
    208       ! 
    209    END SUBROUTINE nemo_gcm 
    210  
    211103 
    212104   SUBROUTINE nemo_init 
     
    335227      IF( ln_ctl        )   CALL prt_ctl_init   ! Print control 
    336228 
    337       IF( lk_obc        )   CALL     obc_init   ! Open boundaries 
    338  
    339229                            CALL  istate_init   ! ocean initial state (Dynamics and tracers) 
    340230 
    341       IF( lk_tide       )   CALL tide_init( nit000 )    ! Initialisation of the tidal harmonics 
    342  
    343       IF( lk_bdy        )   CALL     bdy_init       ! Open boundaries initialisation 
    344       IF( lk_bdy        )   CALL     bdy_dta_init   ! Open boundaries initialisation of external data arrays 
    345       IF( lk_bdy        )   CALL     bdytide_init   ! Open boundaries initialisation of tidal harmonic forcing 
    346  
    347                             CALL dyn_nept_init  ! simplified form of Neptune effect 
    348  
    349       !                                     ! Ocean physics 
    350                             CALL     sbc_init   ! Forcings : surface module 
    351       !                                         ! Vertical physics 
    352                             CALL     zdf_init      ! namelist read 
    353                             CALL zdf_bfr_init      ! bottom friction 
    354       IF( lk_zdfric     )   CALL zdf_ric_init      ! Richardson number dependent Kz 
    355       IF( lk_zdftke     )   CALL zdf_tke_init      ! TKE closure scheme 
    356       IF( lk_zdfgls     )   CALL zdf_gls_init      ! GLS closure scheme 
    357       IF( lk_zdfkpp     )   CALL zdf_kpp_init      ! KPP closure scheme 
    358       IF( lk_zdftmx     )   CALL zdf_tmx_init      ! tidal vertical mixing 
    359       IF( lk_zdfddm .AND. .NOT. lk_zdfkpp )   & 
    360          &                  CALL zdf_ddm_init      ! double diffusive mixing 
    361       !                                         ! Lateral physics 
    362                             CALL ldf_tra_init      ! Lateral ocean tracer physics 
    363                             CALL ldf_dyn_init      ! Lateral ocean momentum physics 
    364       IF( lk_ldfslp     )   CALL ldf_slp_init      ! slope of lateral mixing 
    365  
    366       !                                     ! Active tracers 
    367                             CALL tra_qsr_init   ! penetrative solar radiation qsr 
    368                             CALL tra_bbc_init   ! bottom heat flux 
    369       IF( lk_trabbl     )   CALL tra_bbl_init   ! advective (and/or diffusive) bottom boundary layer scheme 
    370       IF( ln_tradmp     )   CALL tra_dmp_init   ! internal damping trends 
    371                             CALL tra_adv_init   ! horizontal & vertical advection 
    372                             CALL tra_ldf_init   ! lateral mixing 
    373                             CALL tra_zdf_init   ! vertical mixing and after tracer fields 
    374  
    375       !                                     ! Dynamics 
    376                             CALL dyn_adv_init   ! advection (vector or flux form) 
    377                             CALL dyn_vor_init   ! vorticity term including Coriolis 
    378                             CALL dyn_ldf_init   ! lateral mixing 
    379                             CALL dyn_hpg_init   ! horizontal gradient of Hydrostatic pressure 
    380                             CALL dyn_zdf_init   ! vertical diffusion 
    381                             CALL dyn_spg_init   ! surface pressure gradient 
    382  
    383       !                                     ! Misc. options 
    384       IF( nn_cla == 1   )   CALL cla_init       ! Cross Land Advection 
    385                             CALL icb_init( rdt, nit000)   ! initialise icebergs instance 
    386        
    387 #if defined key_top 
    388       !                                     ! Passive tracers 
    389                             CALL     trc_init 
    390 #endif 
    391       !                                     ! Diagnostics 
    392       IF( lk_floats     )   CALL     flo_init   ! drifting Floats 
    393       IF( lk_diaar5     )   CALL dia_ar5_init   ! ar5 diag 
    394                             CALL dia_ptr_init   ! Poleward TRansports initialization 
    395       IF( lk_diadct     )   CALL dia_dct_init   ! Sections tranports 
    396                             CALL dia_hsb_init   ! heat content, salt content and volume budgets 
    397                             CALL trd_mod_init   ! Mixed-layer/Vorticity/Integral constraints trends 
    398231      IF( lk_diaobs     ) THEN                  ! Observation & model comparison 
    399232                            CALL dia_obs_init            ! Initialize observational data 
    400233                            CALL dia_obs( nit000 - 1 )   ! Observation operator for restart 
    401234      ENDIF 
    402       !                                     ! Assimilation increments 
    403       IF( lk_asminc     )   CALL asm_inc_init   ! Initialize assimilation increments 
    404       IF(lwp) WRITE(numout,*) 'Euler time step switch is ', neuler 
    405       ! 
    406235   END SUBROUTINE nemo_init 
    407236 
  • branches/2013/dev_r3987_UKMO4_OBS/NEMOGCM/NEMO/OOO_SRC/obs_fbm.F90

    r4100 r4106  
    15701570      !!---------------------------------------------------------------------- 
    15711571      USE dom_oce, ONLY: narea 
    1572       USE off_write 
    1573       USE off_data 
     1572      USE ooo_write 
     1573      USE ooo_data 
    15741574      IMPLICIT NONE 
    15751575      !! * Arguments 
     
    17341734 
    17351735         ! Initialise class 4 file 
    1736          CALL off_wri_init(cconf, csys, ckind, cversion, ccont, cinst, cdate, & 
     1736         CALL ooo_wri_init(cconf, csys, ckind, cversion, ccont, cinst, cdate, & 
    17371737                         & kproc, kobs, kvars, kdeps, kfcst, & 
    17381738                         & clfilename) 
    17391739 
    17401740         ! Write standard variables 
    1741          CALL off_wri_default(clfilename, kobs, kvars, kfcst, kdeps, & 
     1741         CALL ooo_wri_default(clfilename, kobs, kvars, kfcst, kdeps, & 
    17421742                            & ctype, cwmo, cunit, cvarname, & 
    17431743                            & plam, pphi, pdep, ptim, pob, plead, & 
     
    17481748              (TRIM(cdtmp) == "persistence") ) THEN 
    17491749            !! 4D variables 
    1750             CALL off_wri_extra(clfilename, TRIM(cdtmp), kdeps, kfcst, & 
     1750            CALL ooo_wri_extra(clfilename, TRIM(cdtmp), kdeps, kfcst, & 
    17511751                            &  kvars, kobs, (/ 1,ij,1,1 /), (/ kdeps,1,kvars,kobs /), pmod) 
    17521752         ELSE 
    17531753            !! 3D variables 
    1754             CALL off_wri_extra(clfilename, TRIM(cdtmp), kdeps, & 
     1754            CALL ooo_wri_extra(clfilename, TRIM(cdtmp), kdeps, & 
    17551755                            &  kvars, kobs, (/ 1,1,1 /), (/ kdeps,kvars,kobs /), pmod) 
    17561756         ENDIF 
  • branches/2013/dev_r3987_UKMO4_OBS/NEMOGCM/NEMO/OOO_SRC/ooo_data.F90

    r4100 r4106  
    1 MODULE off_data 
     1MODULE ooo_data 
    22   USE par_kind, ONLY: lc 
    33   IMPLICIT NONE 
     
    3434      & alt_file                       !: altimeter file 
    3535CONTAINS 
    36    SUBROUTINE off_data_init( ld_cl4 ) 
     36   SUBROUTINE ooo_data_init( ld_cl4 ) 
    3737      !!---------------------------------------------------------------------- 
    38       !!                    ***  SUBROUTINE off_data_init *** 
     38      !!                    ***  SUBROUTINE ooo_data_init *** 
    3939      !! 
    4040      !! ** Purpose : To read namelists and initialise offline_oper run. 
     
    131131      END IF 
    132132 
    133    END SUBROUTINE off_data_init 
     133   END SUBROUTINE ooo_data_init 
    134134 
    135 END MODULE off_data 
     135END MODULE ooo_data 
    136136 
  • branches/2013/dev_r3987_UKMO4_OBS/NEMOGCM/NEMO/OOO_SRC/ooo_netcdf.F90

    r4100 r4106  
    1 MODULE off_netcdf 
     1MODULE ooo_netcdf 
    22   USE obs_utils, ONLY: chkerr 
    33   USE obs_const, ONLY: obfillflt 
     
    102102   END SUBROUTINE inst_converter 
    103103 
    104 END MODULE off_netcdf 
     104END MODULE ooo_netcdf 
  • branches/2013/dev_r3987_UKMO4_OBS/NEMOGCM/NEMO/OOO_SRC/ooo_read.F90

    r4100 r4106  
    11 
    2 MODULE off_read 
     2MODULE ooo_read 
    33   !!====================================================================== 
    4    !!                      *** MODULE off_read *** 
     4   !!                      *** MODULE ooo_read *** 
    55   !! Read routines : I/O for offline obs_oper 
    66   !!====================================================================== 
     
    1616USE obs_fbm, ONLY: fbimdi, fbrmdi, fbsp, fbdp 
    1717 
    18 USE off_data 
     18USE ooo_data 
    1919!! * Routine accessibility 
    2020PRIVATE 
    2121 
    22 PUBLIC off_rea_dri 
     22PUBLIC ooo_rea_dri 
    2323 
    2424CONTAINS 
    25    SUBROUTINE off_rea_dri(kfile) 
     25   SUBROUTINE ooo_rea_dri(kfile) 
    2626      IMPLICIT NONE 
    2727      !!------------------------------------------------------------------------ 
    28       !!             *** off_rea_dri *** 
     28      !!             *** ooo_rea_dri *** 
    2929      !! 
    3030      !! Purpose : To choose appropriate read method 
     
    5656         & (TRIM(cmatchname) == 'best_estimate').OR. & 
    5757         & (TRIM(cmatchname) == '') ) THEN 
    58          CALL off_read_file(TRIM(cdfilename), kindex) 
    59          CALL off_read_juld(TRIM(cdfilename), kindex, cl4_modjuld) 
     58         CALL ooo_read_file(TRIM(cdfilename), kindex) 
     59         CALL ooo_read_juld(TRIM(cdfilename), kindex, cl4_modjuld) 
    6060      ELSE IF (TRIM(cmatchname) == 'climatology') THEN 
    6161         WRITE(numout,*) 'Interpolating climatologies' 
    6262      ELSE IF (TRIM(cmatchname) == 'altimeter') THEN 
    63          CALL off_read_altbias(TRIM(cdfilename)) 
    64          CALL off_read_juld(TRIM(cdfilename), kindex, cl4_modjuld) 
     63         CALL ooo_read_altbias(TRIM(cdfilename)) 
     64         CALL ooo_read_juld(TRIM(cdfilename), kindex, cl4_modjuld) 
    6565      END IF 
    6666 
    67    END SUBROUTINE off_rea_dri 
    68  
    69    SUBROUTINE off_read_altbias(filename) 
     67   END SUBROUTINE ooo_rea_dri 
     68 
     69   SUBROUTINE ooo_read_altbias(filename) 
    7070      IMPLICIT NONE 
    7171      !!------------------------------------------------------------------------ 
    72       !!                      *** off_read_altbias *** 
     72      !!                      *** ooo_read_altbias *** 
    7373      !! 
    7474      !! Purpose : To read altimeter bias and set tn,sn to missing values 
     
    140140      END IF 
    141141    
    142    END SUBROUTINE off_read_altbias 
    143  
    144    SUBROUTINE off_read_file(filename, ifcst) 
     142   END SUBROUTINE ooo_read_altbias 
     143 
     144   SUBROUTINE ooo_read_file(filename, ifcst) 
    145145      IMPLICIT NONE 
    146146      !!------------------------------------------------------------------------ 
    147       !!             *** off_read_file *** 
     147      !!             *** ooo_read_file *** 
    148148      !! 
    149149      !! Purpose : To fill tn and sn with dailymean field from netcdf files 
     
    268268         istat = nf90_close(ncid) 
    269269      END IF 
    270    END SUBROUTINE off_read_file 
    271  
    272    SUBROUTINE off_read_juld(filename, ifcst, julian) 
     270   END SUBROUTINE ooo_read_file 
     271 
     272   SUBROUTINE ooo_read_juld(filename, ifcst, julian) 
    273273      USE calendar 
    274274      IMPLICIT NONE 
    275275      !!-------------------------------------------------------------------- 
    276       !!                 *** off_read_juld *** 
     276      !!                 *** ooo_read_juld *** 
    277277      !! 
    278278      !!   Purpose : To read model julian day information from file 
     
    346346      DEALLOCATE(r_sec) 
    347347       
    348    END SUBROUTINE off_read_juld 
    349  
    350 END MODULE off_read  
    351  
     348   END SUBROUTINE ooo_read_juld 
     349 
     350END MODULE ooo_read  
     351 
  • branches/2013/dev_r3987_UKMO4_OBS/NEMOGCM/NEMO/OOO_SRC/ooo_write.F90

    r4100 r4106  
    1 MODULE off_write 
     1MODULE ooo_write 
    22   !!====================================================================== 
    3    !!                       ***  MODULE off_write  *** 
     3   !!                       ***  MODULE ooo_write  *** 
    44   !!====================================================================== 
    55   USE netcdf 
    66   USE obs_utils, ONLY: chkerr 
    7    USE off_netcdf, ONLY: date_format, inst_converter, yyyymmdd_to_ref_date 
    8    USE off_data 
     7   USE ooo_netcdf, ONLY: date_format, inst_converter, yyyymmdd_to_ref_date 
     8   USE ooo_data 
    99   IMPLICIT NONE 
    1010   PRIVATE 
    1111 
    12    PUBLIC off_wri_init 
    13    PUBLIC off_wri_default 
    14    PUBLIC off_wri_extra 
     12   PUBLIC ooo_wri_init 
     13   PUBLIC ooo_wri_default 
     14   PUBLIC ooo_wri_extra 
    1515 
    1616   ! Type kinds for class 4 data. 
     
    2222   REAL(clsp), PARAMETER :: clrmdi =  99999   !: Reals 
    2323 
    24    INTERFACE off_wri_extra 
    25       MODULE PROCEDURE off_wri_extra_3d_index, off_wri_extra_4d, off_wri_extra_4d_index 
     24   INTERFACE ooo_wri_extra 
     25      MODULE PROCEDURE ooo_wri_extra_3d_index, ooo_wri_extra_4d, ooo_wri_extra_4d_index 
    2626   END INTERFACE 
    2727 
    2828   CONTAINS 
    2929 
    30       SUBROUTINE off_wri_extra_3d_index(cdfilename, cdvarname, ndeps, nvars, & 
     30      SUBROUTINE ooo_wri_extra_3d_index(cdfilename, cdvarname, ndeps, nvars, & 
    3131                               &  nobs, kstart, kcount, pdata) 
    3232         !!---------------------------------------------------------------------- 
    33          !!                    ***  ROUTINE off_wri_extra_3d  *** 
     33         !!                    ***  ROUTINE ooo_wri_extra_3d  *** 
    3434         !! 
    3535         !! ** Purpose : Write 3d variables to class 4 file. 
     
    5252                 & dimid, &      !: 
    5353                 & varid         !: 
    54          CHARACTER(len=16), PARAMETER :: cpname = 'off_wri_extra_3d' 
     54         CHARACTER(len=16), PARAMETER :: cpname = 'ooo_wri_extra_3d' 
    5555         ! Open netcdf file 
    5656         CALL chkerr(nf90_open(trim(cdfilename), nf90_write, ncid), cpname, __LINE__ ) 
     
    6060         ! Close netcdf file 
    6161         CALL chkerr(nf90_close(ncid), cpname, __LINE__ ) 
    62       END SUBROUTINE off_wri_extra_3d_index 
    63  
    64       SUBROUTINE off_wri_extra_4d_index(cdfilename, cdvarname, ndeps, nfcst, & 
     62      END SUBROUTINE ooo_wri_extra_3d_index 
     63 
     64      SUBROUTINE ooo_wri_extra_4d_index(cdfilename, cdvarname, ndeps, nfcst, & 
    6565                               &  nvars, nobs, kstart, kcount, pdata) 
    6666         !!---------------------------------------------------------------------- 
    67          !!                    ***  ROUTINE off_wri_extra_4d  *** 
     67         !!                    ***  ROUTINE ooo_wri_extra_4d  *** 
    6868         !! 
    6969         !! ** Purpose : Write 4d variables to class 4 file. 
     
    8787                 & dimid, &      !: 
    8888                 & varid         !: 
    89          CHARACTER(len=22), PARAMETER :: cpname = 'off_wri_extra_4d_index' 
     89         CHARACTER(len=22), PARAMETER :: cpname = 'ooo_wri_extra_4d_index' 
    9090         ! Open netcdf file 
    9191         CALL chkerr(nf90_open(trim(cdfilename), nf90_write, ncid), cpname, __LINE__ ) 
     
    9595         ! Close netcdf file 
    9696         CALL chkerr(nf90_close(ncid), cpname, __LINE__ ) 
    97       END SUBROUTINE off_wri_extra_4d_index 
    98  
    99       SUBROUTINE off_wri_extra_4d(cdfilename, cdvarname, ndeps, nfcst, & 
     97      END SUBROUTINE ooo_wri_extra_4d_index 
     98 
     99      SUBROUTINE ooo_wri_extra_4d(cdfilename, cdvarname, ndeps, nfcst, & 
    100100                               &  nvars, nobs, pdata) 
    101101         !!---------------------------------------------------------------------- 
    102          !!                    ***  ROUTINE off_wri_extra_4d  *** 
     102         !!                    ***  ROUTINE ooo_wri_extra_4d  *** 
    103103         !! 
    104104         !! ** Purpose : Write 4d variables to class 4 file. 
     
    119119                 & dimid, &      !: 
    120120                 & varid         !: 
    121          CHARACTER(len=16), PARAMETER :: cpname = 'off_wri_extra_4d' 
     121         CHARACTER(len=16), PARAMETER :: cpname = 'ooo_wri_extra_4d' 
    122122         ! Open netcdf file 
    123123         CALL chkerr(nf90_open(trim(cdfilename), nf90_write, ncid), cpname, __LINE__ ) 
     
    127127         ! Close netcdf file 
    128128         CALL chkerr(nf90_close(ncid), cpname, __LINE__ ) 
    129       END SUBROUTINE off_wri_extra_4d 
    130  
    131       SUBROUTINE off_wri_default(cdfilename, nobs, nvars, nfcst, ndeps, &  
     129      END SUBROUTINE ooo_wri_extra_4d 
     130 
     131      SUBROUTINE ooo_wri_default(cdfilename, nobs, nvars, nfcst, ndeps, &  
    132132                             &   cdtyp, cdwmo, cunit, cvnam, & 
    133133                             &   plam, pphi, pdep, ptim, pob, plead, & 
    134134                             &   kqc, pmjuld) 
    135135         !!---------------------------------------------------------------------- 
    136          !!                    ***  ROUTINE off_wri_default  *** 
     136         !!                    ***  ROUTINE ooo_wri_default  *** 
    137137         !! 
    138138         !! ** Purpose : Write standard variables to class 4 file. 
     
    189189                 & dimid, & !: 
    190190                 & varid    !: 
    191          CHARACTER(len=15), PARAMETER :: cpname = 'off_wri_default' 
     191         CHARACTER(len=15), PARAMETER :: cpname = 'ooo_wri_default' 
    192192         ! Open netcdf file 
    193193         CALL chkerr(nf90_open(trim(cdfilename), nf90_write, ncid), cpname, __LINE__ ) 
     
    250250         ! Close netcdf file 
    251251         CALL chkerr(nf90_close(ncid), cpname, __LINE__ ) 
    252       END SUBROUTINE off_wri_default 
    253  
    254       SUBROUTINE off_wri_init(cconf, csys, ckind, cversion, ccont, & 
     252      END SUBROUTINE ooo_wri_default 
     253 
     254      SUBROUTINE ooo_wri_init(cconf, csys, ckind, cversion, ccont, & 
    255255                            & cinst, cdate, nproc, nobs, nvars, & 
    256256                            & ndeps, nfcst, cdfilename) 
    257257         !!---------------------------------------------------------------------- 
    258          !!                    ***  ROUTINE off_wri_init  *** 
     258         !!                    ***  ROUTINE ooo_wri_init  *** 
    259259         !! 
    260260         !! ** Purpose : Initialise a class 4 file. 
     
    310310         INTEGER, DIMENSION(4) :: & 
    311311                 & dim4a         !: 4 dimensional settings 
    312          CHARACTER(len=12), PARAMETER :: cpname = 'off_wri_init' 
     312         CHARACTER(len=12), PARAMETER :: cpname = 'ooo_wri_init' 
    313313         ! Global att variables 
    314314         CHARACTER(len=40) :: date_str 
     
    613613            CALL chkerr(nf90_close(ncid), cpname, __LINE__ ) 
    614614         END IF 
    615       END SUBROUTINE off_wri_init 
    616  
    617  
    618 END MODULE off_write 
     615      END SUBROUTINE ooo_wri_init 
     616 
     617 
     618END MODULE ooo_write 
  • branches/2013/dev_r3987_UKMO4_OBS/NEMOGCM/NEMO/OOO_SRC/ooomod.F90

    r4100 r4106  
    1 MODULE off_oper 
     1MODULE ooomod 
    22   !!---------------------------------------------------------------------- 
    3    !!                    ***  MODULE off_oper *** 
     3   !!                    ***  MODULE ooo *** 
    44   !! ** Purpose : Run NEMO observation operator in offline mode 
    55   !!---------------------------------------------------------------------- 
     
    1111   USE obs_fbm, ONLY: ln_cl4 
    1212   !! Offline obs_oper modules 
    13    USE off_data 
    14    USE off_read 
     13   USE ooo_data 
     14   USE ooo_read 
    1515   CONTAINS 
    16       SUBROUTINE off_oper_init 
     16      SUBROUTINE ooo_init 
    1717         !!---------------------------------------------------------------------- 
    18          !!                    ***  SUBROUTINE off_oper_init *** 
     18         !!                    ***  SUBROUTINE ooo_init *** 
    1919         !! 
    2020         !! ** Purpose : To initialise the model as if it were running online. 
     
    2525         CALL nemo_init 
    2626         !! Initialise Offline obs_oper data 
    27          CALL off_data_init( ln_cl4 ) 
    28       END SUBROUTINE off_oper_init 
     27         CALL ooo_data_init( ln_cl4 ) 
     28      END SUBROUTINE ooo_init 
    2929 
    30       SUBROUTINE off_obs_oper 
     30      SUBROUTINE offline_obs_oper 
    3131         !!---------------------------------------------------------------------- 
    32          !!                    ***  SUBROUTINE off_obs_oper *** 
     32         !!                    ***  SUBROUTINE offline_obs_oper *** 
    3333         !! 
    3434         !! ** Purpose : To use NEMO components to interpolate model fields 
     
    3838         IMPLICIT NONE 
    3939         !! Initialise offline obs_oper 
    40          CALL off_oper_init 
     40         CALL ooo_init 
    4141         !! Loop over various model counterparts 
    4242         DO jimatch = 1, cl4_match_len 
     
    4646            END IF 
    4747            !! Interpolate to observation space 
    48             CALL off_oper_interp 
     48            CALL ooo_interp 
    4949            !! Pipe to output files 
    5050            CALL dia_obs_wri 
     
    5353         END DO 
    5454         !! Safely stop MPI 
    55          CALL off_oper_stop 
    56       END SUBROUTINE off_obs_oper 
     55         CALL ooo_stop 
     56      END SUBROUTINE offline_obs_oper 
    5757 
    58       SUBROUTINE off_oper_interp 
     58      SUBROUTINE ooo_interp 
    5959         !!---------------------------------------------------------------------- 
    60          !!                    ***  SUBROUTINE off_oper_interp *** 
     60         !!                    ***  SUBROUTINE ooo_interp *** 
    6161         !! 
    6262         !! ** Purpose : To interpolate the model as if it were running online. 
     
    7474               IF ( MOD(istp, nn_off_freq) == nit000 ) THEN 
    7575                  !! Read next model counterpart 
    76                   CALL off_rea_dri(jifile) 
     76                  CALL ooo_rea_dri(jifile) 
    7777                  jifile = jifile + 1 
    7878               ENDIF 
     
    8383            istp = istp + 1 
    8484         END DO 
    85       END SUBROUTINE off_oper_interp 
     85      END SUBROUTINE ooo_interp 
    8686 
    87       SUBROUTINE off_oper_stop 
     87      SUBROUTINE ooo_stop 
    8888         !!---------------------------------------------------------------------- 
    89          !!                    ***  SUBROUTINE off_oper_stop *** 
     89         !!                    ***  SUBROUTINE ooo_stop *** 
    9090         !! 
    9191         !! ** Purpose : To finalise the model as if it were running online. 
     
    9494         IMPLICIT NONE 
    9595         IF(lk_mpp) CALL mppstop  ! end mpp communications 
    96       END SUBROUTINE off_oper_stop 
     96      END SUBROUTINE ooo_stop 
    9797 
    98 END MODULE off_oper 
     98END MODULE ooomod 
  • branches/2013/dev_r3987_UKMO4_OBS/NEMOGCM/NEMO/OPA_SRC/OBS/obs_fbm.F90

    r4091 r4106  
    15701570      !!---------------------------------------------------------------------- 
    15711571      USE dom_oce, ONLY: narea 
    1572       USE off_write 
    1573       USE off_data 
     1572      USE ooo_write 
     1573      USE ooo_data 
    15741574      IMPLICIT NONE 
    15751575      !! * Arguments 
     
    17341734 
    17351735         ! Initialise class 4 file 
    1736          CALL off_wri_init(cconf, csys, ckind, cversion, ccont, cinst, cdate, & 
     1736         CALL ooo_wri_init(cconf, csys, ckind, cversion, ccont, cinst, cdate, & 
    17371737                         & kproc, kobs, kvars, kdeps, kfcst, & 
    17381738                         & clfilename) 
    17391739 
    17401740         ! Write standard variables 
    1741          CALL off_wri_default(clfilename, kobs, kvars, kfcst, kdeps, & 
     1741         CALL ooo_wri_default(clfilename, kobs, kvars, kfcst, kdeps, & 
    17421742                            & ctype, cwmo, cunit, cvarname, & 
    17431743                            & plam, pphi, pdep, ptim, pob, plead, & 
     
    17481748              (TRIM(cdtmp) == "persistence") ) THEN 
    17491749            !! 4D variables 
    1750             CALL off_wri_extra(clfilename, TRIM(cdtmp), kdeps, kfcst, & 
     1750            CALL ooo_wri_extra(clfilename, TRIM(cdtmp), kdeps, kfcst, & 
    17511751                            &  kvars, kobs, (/ 1,ij,1,1 /), (/ kdeps,1,kvars,kobs /), pmod) 
    17521752         ELSE 
    17531753            !! 3D variables 
    1754             CALL off_wri_extra(clfilename, TRIM(cdtmp), kdeps, & 
     1754            CALL ooo_wri_extra(clfilename, TRIM(cdtmp), kdeps, & 
    17551755                            &  kvars, kobs, (/ 1,1,1 /), (/ kdeps,kvars,kobs /), pmod) 
    17561756         ENDIF 
Note: See TracChangeset for help on using the changeset viewer.