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 508 for trunk/NEMO/OPA_SRC/istate.F90 – NEMO

Ignore:
Timestamp:
2006-10-03T17:58:55+02:00 (18 years ago)
Author:
opalod
Message:

nemo_v1_update_071:RB: add iom for restart and reorganization of restart

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMO/OPA_SRC/istate.F90

    r479 r508  
    44   !! Ocean state   :  initial state setting 
    55   !!===================================================================== 
     6   !! History :   4.0  !  89-12  (P. Andrich)  Original code 
     7   !!             5.0  !  91-11  (G. Madec)  rewritting 
     8   !!             6.0  !  96-01  (G. Madec)  terrain following coordinates 
     9   !!             8.0  !  01-09  (M. Levy, M. Ben Jelloul)  istate_eel 
     10   !!             8.0  !  01-09  (M. Levy, M. Ben Jelloul)  istate_uvg 
     11   !!             9.0  !  03-08  (G. Madec)  F90: Free form, modules 
     12   !!             9.0  !  03-09  (G. Madec, C. Talandier)  add EEL R5 
     13   !!             9.0  !  04-05  (A. Koch-Larrouy)  istate_gyre  
     14   !!             9.0  !  06-07  (S. Masson)  distributed restart using iom 
     15   !!---------------------------------------------------------------------- 
    616 
    717   !!---------------------------------------------------------------------- 
     
    1323   !!   istate_uvg    : initial velocity in geostropic balance 
    1424   !!---------------------------------------------------------------------- 
    15    !! * Modules used 
    1625   USE oce             ! ocean dynamics and active tracers  
    1726   USE dom_oce         ! ocean space and time domain  
     
    1928   USE ldftra_oce      ! ocean active tracers: lateral physics 
    2029   USE zdf_oce         ! ocean vertical physics 
    21    USE in_out_manager  ! I/O manager 
    2230   USE phycst          ! physical constants 
    2331   USE wzvmod          ! verctical velocity               (wzv     routine) 
     
    2634   USE restart         ! ocean restart                   (rst_read routine) 
    2735   USE solisl          ! ??? 
    28  
     36   USE in_out_manager  ! I/O manager 
     37   USE iom 
     38    
    2939   IMPLICIT NONE 
    3040   PRIVATE 
    3141 
    32    !! * Routine accessibility 
    33    PUBLIC istate_init   ! routine called by step.F90 
     42   PUBLIC   istate_init   ! routine called by step.F90 
    3443 
    3544   !! * Substitutions 
     
    3746#  include "vectopt_loop_substitute.h90" 
    3847   !!---------------------------------------------------------------------- 
    39    !!   OPA 9.0 , LOCEAN-IPSL (2005)  
     48   !!   OPA 9.0 , LOCEAN-IPSL (2006)  
    4049   !! $Header$  
    41    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
     50   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    4251   !!---------------------------------------------------------------------- 
    4352 
     
    4857      !!                   ***  ROUTINE istate_init  *** 
    4958      !!  
    50       !! ** Purpose :   Initialization of the dynamics and tracers. 
    51       !! 
    52       !! ** Method  : 
    53       !! 
    54       !! History : 
    55       !!   4.0  !  91-03  ()  Original code 
    56       !!        !  91-11  (G. Madec) 
    57       !!   9.0  !  03-09  (G. Madec)  F90: Free form, modules, orthogonality 
    58       !!---------------------------------------------------------------------- 
    59       USE iom 
    60       !! * Local declarations 
    61       !CT INTEGER ::   inum 
    62       !!---------------------------------------------------------------------- 
    63  
    64  
    65       ! Initialization to zero 
    66       ! ---------------------- 
    67  
    68       !     before fields       !       now fields        !      after fields       ! 
    69       ;   ub   (:,:,:) = 0.e0   ;   un   (:,:,:) = 0.e0   ;   ua   (:,:,:) = 0.e0 
    70       ;   vb   (:,:,:) = 0.e0   ;   vn   (:,:,:) = 0.e0   ;   va   (:,:,:) = 0.e0 
    71       ;                         ;   wn   (:,:,:) = 0.e0   ; 
    72       ;   rotb (:,:,:) = 0.e0   ;   rotn (:,:,:) = 0.e0   ; 
    73       ;   hdivb(:,:,:) = 0.e0   ;   hdivn(:,:,:) = 0.e0   ; 
    74  
    75       ;   tb   (:,:,:) = 0.e0   ;   tn   (:,:,:) = 0.e0   ;   ta   (:,:,:) = 0.e0 
    76       ;   sb   (:,:,:) = 0.e0   ;   sn   (:,:,:) = 0.e0   ;   sa   (:,:,:) = 0.e0 
     59      !! ** Purpose :   Initialization of the dynamics and tracer fields. 
     60      !!---------------------------------------------------------------------- 
     61 
     62      IF(lwp) WRITE(numout,*) 
     63      IF(lwp) WRITE(numout,*) 'istate_ini : Initialization of the dynamics and tracers' 
     64      IF(lwp) WRITE(numout,*) '~~~~~~~~~~' 
    7765 
    7866      rhd  (:,:,:) = 0.e0 
    7967      rhop (:,:,:) = 0.e0 
    8068      rn2  (:,:,:) = 0.e0  
    81  
    82 #if defined key_dynspg_rl 
    83       ! rigid-lid formulation 
    84       bsfb(:,:) = 0.e0      ! before barotropic stream-function 
    85       bsfn(:,:) = 0.e0      ! now    barotropic stream-function 
    86       bsfd(:,:) = 0.e0      ! barotropic stream-function trend 
    87 #endif 
    88       ! free surface formulation 
    89       sshb(:,:) = 0.e0      ! before sea-surface height 
    90       sshn(:,:) = 0.e0      ! now    sea-surface height 
    91  
    9269 
    9370      IF( ln_rstart ) THEN                    ! Restart from a file 
     
    10077         neuler = 0                              ! Set time-step indicator at nit000 (euler forward) 
    10178         adatrj = 0._wp 
     79         !                                       ! Initialization of ocean to zero 
     80         !     before fields       !       now fields           
     81         ;   ub   (:,:,:) = 0.e0   ;   un   (:,:,:) = 0.e0    
     82         ;   vb   (:,:,:) = 0.e0   ;   vn   (:,:,:) = 0.e0     
     83         ;   rotb (:,:,:) = 0.e0   ;   rotn (:,:,:) = 0.e0   
     84         ;   hdivb(:,:,:) = 0.e0   ;   hdivn(:,:,:) = 0.e0   
     85         ! 
    10286         IF( cp_cfg == 'eel' ) THEN 
    10387            CALL istate_eel                      ! EEL   configuration : start from pre-defined 
     
    10791            !                                    !                       and salinity fields  
    10892         ELSE 
    109          !                                       ! Other configurations: Initial temperature and salinity fields 
    110  
    111          !CT CALL iom_open ('ssh', inum)  
    112          !CT CALL iom_get( inum, jpdom_local, 'sshb', sshb )     ! free surface formulation (ssh) 
    113          !CT sshn(:,:) = sshb(:,:) 
    114          !CT CALL iom_close (inum) 
    115  
     93            !                                    ! Other configurations: Initial temperature and salinity fields 
    11694#if defined key_dtatem 
    11795            CALL dta_tem( nit000 )                  ! read 3D temperature data 
     
    12098#else 
    12199            IF(lwp) WRITE(numout,*)                 ! analytical temperature profile 
    122             IF(lwp) WRITE(numout,*)' Temperature initialization using an analytic profile' 
     100            IF(lwp) WRITE(numout,*)'             Temperature initialization using an analytic profile' 
    123101            CALL istate_tem 
    124102#endif 
     
    130108            ! No salinity data 
    131109            IF(lwp)WRITE(numout,*)                  ! analytical salinity profile 
    132             IF(lwp)WRITE(numout,*)' Salinity initialisation using a constant value' 
     110            IF(lwp)WRITE(numout,*)'             Salinity initialisation using a constant value' 
    133111            CALL istate_sal 
    134112#endif 
     
    139117      !                                       ! ----------------- 
    140118      CALL wzv( nit000 )                         ! from horizontal divergence 
    141  
     119      ! 
    142120   END SUBROUTINE istate_init 
    143121 
     
    153131      !! 
    154132      !! References :  Philander ??? 
    155       !! 
    156       !! History : 
    157       !!   4.0  !  89-12  (P. Andrich)  Original code 
    158       !!   6.0  !  96-01  (G. Madec)  terrain following coordinates 
    159       !!   9.0  !  02-09  (G. Madec)  F90: Free form 
    160       !!---------------------------------------------------------------------- 
    161       !! * Local declarations 
     133      !!---------------------------------------------------------------------- 
    162134      INTEGER :: ji, jj, jk 
    163135      !!---------------------------------------------------------------------- 
    164  
     136      ! 
    165137      IF(lwp) WRITE(numout,*) 
    166138      IF(lwp) WRITE(numout,*) 'istate_tem : initial temperature profile' 
     
    181153         &                 1     , jpi   , 5     , 1     , jpk   ,   & 
    182154         &                 1     , 1.    , numout                  ) 
    183  
     155      ! 
    184156   END SUBROUTINE istate_tem 
    185157 
     
    194166      !!               
    195167      !! ** Action  :   Initialize sn and sb 
    196       !! 
    197       !! History : 
    198       !!   4.0  !  89-12  (P. Andrich)  Original code 
    199       !!   8.5  !  02-09  (G. Madec)  F90: Free form 
    200       !!---------------------------------------------------------------------- 
    201       !! * Local declarations 
     168      !!---------------------------------------------------------------------- 
    202169      REAL(wp) ::   zsal = 35.50_wp 
    203170      !!---------------------------------------------------------------------- 
     
    224191      !!              - set velocity field including horizontal divergence 
    225192      !!                and relative vorticity fields 
    226       !! 
    227       !! History : 
    228       !!   8.0  !  01-09  (M. Levy, M. Ben Jelloul)  read file for EEL 2 & 6 
    229       !!   9.0  !  03-09  (G. Madec, C. Talandier)  EEL 5 
    230       !!   9.0  !  05-11  (V. Garnier) Surface pressure gradient organization 
    231       !!---------------------------------------------------------------------- 
    232       !! * Modules used 
     193      !!---------------------------------------------------------------------- 
    233194      USE eosbn2     ! eq. of state, Brunt Vaisala frequency (eos     routine) 
    234195      USE divcur     ! hor. divergence & rel. vorticity      (div_cur routine) 
    235196      USE iom 
    236197  
    237       !! * Local declarations 
    238198      INTEGER  ::   inum              ! temporary logical unit 
    239199      INTEGER  ::   ji, jj, jk        ! dummy loop indices 
    240200      INTEGER  ::   ijloc 
    241       REAL(wp) ::   & 
    242          zh1, zh2, zslope, zcst,   &  ! temporary scalars 
    243          zfcor 
    244       REAL(wp) ::   & 
    245          zt1  = 12._wp,            &  ! surface temperature value (EEL R5) 
    246          zt2  =  2._wp,            &  ! bottom  temperature value (EEL R5) 
    247          zsal = 35.5_wp,           &  ! constant salinity (EEL R2, R5 and R6) 
    248          zueel = 0.1_wp               ! constant uniform zonal velocity (EEL R5) 
     201      REAL(wp) ::   zh1, zh2, zslope, zcst, zfcor   ! temporary scalars 
     202      REAL(wp) ::   zt1  = 12._wp,               &  ! surface temperature value (EEL R5) 
     203         &          zt2  =  2._wp,               &  ! bottom  temperature value (EEL R5) 
     204         &          zsal = 35.5_wp,              &  ! constant salinity (EEL R2, R5 and R6) 
     205         &          zueel = 0.1_wp                  ! constant uniform zonal velocity (EEL R5) 
    249206# if ! defined key_dynspg_rl 
    250       REAL(wp), DIMENSION(jpiglo,jpjglo) ::   & 
    251          zssh                         ! initial ssh over the global domain 
     207      REAL(wp), DIMENSION(jpiglo,jpjglo) ::   zssh  ! initial ssh over the global domain 
    252208# endif 
    253209      !!---------------------------------------------------------------------- 
     
    389345      !! ** Method  : - set temprature field 
    390346      !!              - set salinity field 
    391       !! 
    392       !! ** History :                                      
    393       !!      9.0  !  04-05  (A. Koch-Larrouy)  Original code  
    394       !!---------------------------------------------------------------------- 
    395       !! * Modules used 
    396       USE iom 
    397  
    398       !! * Local variables 
    399       INTEGER  ::   inum              ! temporary logical unit 
    400       INTEGER, PARAMETER ::   & 
    401          ntsinit = 0         ! (0/1) (analytical/input data files) T&S initialization 
    402  
     347      !!---------------------------------------------------------------------- 
    403348      INTEGER :: ji, jj, jk  ! dummy loop indices 
     349      INTEGER            ::   inum          ! temporary logical unit 
     350      INTEGER, PARAMETER ::   ntsinit = 0   ! (0/1) (analytical/input data files) T&S initialization 
    404351      !!---------------------------------------------------------------------- 
    405352 
     
    469416      ENDIF 
    470417 
    471       
    472418   END SUBROUTINE istate_gyre 
    473  
    474419 
    475420 
     
    484429      !!      surface to the bottom. 
    485430      !!                 p=integral [ rau*g dz ] 
    486       !! 
    487       !! History : 
    488       !!   8.1  !  01-09  (M. Levy, M. Ben Jelloul)  Original code 
    489       !!   8.5  !  02-09  (G. Madec)  F90: Free form 
    490       !!   9.0  !  05-11  (V. Garnier) Surface pressure gradient organization 
    491       !!---------------------------------------------------------------------- 
    492       !! * Modules used 
     431      !!---------------------------------------------------------------------- 
    493432      USE eosbn2          ! eq. of state, Brunt Vaisala frequency (eos     routine) 
    494433      USE dynspg          ! surface pressure gradient             (dyn_spg routine) 
     
    496435      USE lbclnk          ! ocean lateral boundary condition (or mpp link) 
    497436 
    498       !! * Local declarations 
    499437      INTEGER ::   ji, jj, jk        ! dummy loop indices 
    500438      INTEGER ::   indic             ! ??? 
    501       REAL(wp) ::   & 
    502          zmsv, zphv, zmsu, zphu,  &  ! temporary scalars 
    503          zalfg 
    504       REAL(wp), DIMENSION (jpi,jpj,jpk) ::   & 
    505          zprn                        ! workspace 
     439      REAL(wp) ::   zmsv, zphv, zmsu, zphu, zalfg     ! temporary scalars 
     440      REAL(wp), DIMENSION (jpi,jpj,jpk) ::   zprn     ! workspace 
    506441      !!---------------------------------------------------------------------- 
    507442 
     
    514449 
    515450      zalfg = 0.5 * grav * rau0 
    516       ! Surface value 
    517       zprn(:,:,1) = zalfg * fse3w(:,:,1) * ( 1 + rhd(:,:,1) ) 
    518  
    519       ! Vertical integration from the surface 
    520       DO jk = 2, jpkm1 
     451       
     452      zprn(:,:,1) = zalfg * fse3w(:,:,1) * ( 1 + rhd(:,:,1) )       ! Surface value 
     453 
     454      DO jk = 2, jpkm1                                              ! Vertical integration from the surface 
    521455         zprn(:,:,jk) = zprn(:,:,jk-1)   & 
    522456            &         + zalfg * fse3w(:,:,jk) * ( 2. + rhd(:,:,jk) + rhd(:,:,jk-1) ) 
     
    525459      ! Compute geostrophic balance 
    526460      ! --------------------------- 
    527  
    528461      DO jk = 1, jpkm1 
    529462         DO jj = 2, jpjm1 
     
    571504      ! after initializing u and v, we need to calculate the initial streamfunction bsf. 
    572505      ! Otherwise, only the trend will be computed and the model will blow up (inconsistency). 
    573        
    574506      ! to do that, we call dyn_spg with a special trick: 
    575       ! we fill ua and va with the velocities divided by dt, 
    576       ! and the streamfunction will be brought to the right 
    577       ! value assuming the velocities have been set up in 
    578       ! one time step. 
    579       ! we then set bsfd to zero (first guess for next step 
    580       ! is d(psi)/dt = 0.) 
    581  
    582       !  sets up s false trend to calculate the barotropic 
    583       !  streamfunction. 
     507      ! we fill ua and va with the velocities divided by dt, and the streamfunction will be brought to the 
     508      ! right value assuming the velocities have been set up in one time step. 
     509      ! we then set bsfd to zero (first guess for next step is d(psi)/dt = 0.) 
     510      !  sets up s false trend to calculate the barotropic streamfunction. 
    584511 
    585512      ua(:,:,:) = ub(:,:,:) / rdt 
     
    612539      hdivb(:,:,:) = hdivn(:,:,:)       ! set the before to the now value 
    613540      rotb (:,:,:) = rotn (:,:,:)       ! set the before to the now value 
    614  
     541      ! 
    615542   END SUBROUTINE istate_uvg 
    616543 
Note: See TracChangeset for help on using the changeset viewer.