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 4600 for branches – NEMO

Changeset 4600 for branches


Ignore:
Timestamp:
2014-03-27T11:25:15+01:00 (10 years ago)
Author:
pabouttier
Message:

Allow to initialize direct model from nemogcm_tam, see Ticket #1286

Location:
branches/2012/dev_v3_4_STABLE_2012/NEMOGCM/NEMO
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • branches/2012/dev_v3_4_STABLE_2012/NEMOGCM/NEMO/OPATAM_SRC/mt19937ar.f90

    r4598 r4600  
    271271      l_mtinit = .TRUE. 
    272272 
    273    END SUBROUTINE mtrand_seedre 
     273   END SUBROUTINE mtrand_seedread 
    274274    
    275275END MODULE mt19937ar 
  • branches/2012/dev_v3_4_STABLE_2012/NEMOGCM/NEMO/OPATAM_SRC/nemogcm_tam.F90

    r3658 r4600  
    3838   !!   nemo_init      : initialization of the NEMO system 
    3939   !!   nemo_ctl       : initialisation of the contol print 
    40    !!   nemo_closefile : close remaining open files 
    4140   !!   nemo_alloc     : dynamical allocation 
    4241   !!   nemo_partition : calculate MPP domain decomposition 
     
    8887   USE tamctl 
    8988   USE lib_mpp_tam 
     89   USE paresp 
    9090   !USE tamtrj 
    9191   USE trj_tam 
     
    123123      !                            !-----------------------! 
    124124      !                            !==  Initialisations  ==! 
    125       CALL nemo_init_tam           !-----------------------! 
     125      CALL nemo_init               !-----------------------! 
     126      CALL nemo_init_tam          
    126127      ! 
    127128      ! check that all process are still there... If some process have an error, 
     
    185186      !!---------------------------------------------------------------------- 
    186187      ! 
    187       cltxt = '' 
    188       ! 
    189       !                             ! open Namelist file 
    190       CALL ctl_opn( numnam, 'namelist', 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE. ) 
    191       !! 
    192       READ( numnam, namctl )        ! Namelist namctl : Control prints & Benchmark 
    193       ! 
    194       !                             !--------------------------------------------! 
    195       !                             !  set communicator & select the local node  ! 
    196       !                             !--------------------------------------------! 
    197       ilocal_comm = 0 
    198       narea = mynode( cltxt, numnam, nstop )                 ! Nodes selection (control print return in cltxt) 
    199       narea = narea + 1                                     ! mynode return the rank of proc (0 --> jpnij -1 ) 
    200  
    201       lwp = (narea == 1) .OR. ln_ctl                        ! control of all listing output print 
    202  
    203       ! If dimensions of processor grid weren't specified in the namelist file 
    204       ! then we calculate them here now that we have our communicator size 
    205       IF( (jpni < 1) .OR. (jpnj < 1) )THEN 
    206 #if   defined key_mpp_mpi 
    207          IF( Agrif_Root() ) CALL nemo_partition(mppsize) 
    208 #else 
    209          jpni  = 1 
    210          jpnj  = 1 
    211          jpnij = jpni*jpnj 
    212 #endif 
    213       END IF 
    214  
    215       ! Calculate domain dimensions given calculated jpni and jpnj 
    216       ! This used to be done in par_oce.F90 when they were parameters rather 
    217       ! than variables 
    218       IF( Agrif_Root() ) THEN 
    219          jpi = ( jpiglo-2*jpreci + (jpni-1) ) / jpni + 2*jpreci   ! first  dim. 
    220          jpj = ( jpjglo-2*jprecj + (jpnj-1) ) / jpnj + 2*jprecj   ! second dim. 
    221          jpk = jpkdta                                             ! third dim 
    222          jpim1 = jpi-1                                            ! inner domain indices 
    223          jpjm1 = jpj-1                                            !   "           " 
    224          jpkm1 = jpk-1                                            !   "           " 
    225          jpij  = jpi*jpj                                          !  jpi x j 
    226       ENDIF 
    227  
    228       IF(lwp) THEN                            ! open listing units 
    229          ! 
    230          CALL ctl_opn( numout, 'ocean.output', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE., narea ) 
    231          ! 
    232          WRITE(numout,*) 
    233          WRITE(numout,*) '   CNRS - NERC - Met OFFICE - MERCATOR-ocean - INGV - CMCC' 
    234          WRITE(numout,*) '                       NEMO team' 
    235          WRITE(numout,*) '            Ocean General Circulation Model' 
    236          WRITE(numout,*) '                  version 3.4  (2011) ' 
    237          WRITE(numout,*) '                      NEMOTAM ' 
    238          WRITE(numout,*) 
    239          WRITE(numout,*) 
    240          DO ji = 1, SIZE(cltxt) 
    241             IF( TRIM(cltxt(ji)) /= '' )   WRITE(numout,*) cltxt(ji)      ! control print of mynode 
    242          END DO 
    243          WRITE(numout,cform_aaa)                                         ! Flag AAAAAAA 
    244          ! 
    245       ENDIF 
    246  
    247       ! Now we know the dimensions of the grid and numout has been set we canhttp://forge.ipsl.jussieu.fr/nemo/changeset/3640 
    248       ! allocate arrays 
    249       CALL nemo_alloc() 
    250  
    251       !                                      ! Domain decomposition 
    252       IF( jpni*jpnj == jpnij ) THEN   ;   CALL mpp_init      ! standard cutting out 
    253       ELSE                            ;   CALL mpp_init2     ! eliminate land processors 
    254       ENDIF 
    255       ! 
    256       IF( nn_timing == 1 )  CALL timing_init 
    257       ! 
    258       !                                      ! General initialization 
    259                             CALL     phy_cst    ! Physical constants 
    260                             CALL     eos_init   ! Equation of state 
    261                             CALL     dom_cfg    ! Domain configuration 
    262                             CALL     dom_init   ! Domain 
    263  
    264       IF( ln_nnogather )    CALL nemo_northcomms   ! Initialise the northfold neighbour lists (must be done after the masks are defined) 
    265  
    266       IF( ln_ctl        )   CALL prt_ctl_init   ! Print control 
    267  
    268       IF( lk_obc        )   CALL     obc_init   ! Open boundaries 
    269       IF( lk_bdy        )   CALL     bdy_init       ! Open boundaries initialisation 
    270       IF( lk_bdy        )   CALL     bdy_dta_init   ! Open boundaries initialisation of external data arrays 
    271       IF( lk_bdy        )   CALL     tide_init      ! Open boundaries initialisation of tidal harmonic forcing 
    272  
    273                             CALL flush(numout) 
    274                             CALL dyn_nept_init  ! simplified form of Neptune effect 
    275                             CALL flush(numout) 
    276  
    277                             CALL  istate_init   ! ocean initial state (Dynamics and tracers) 
    278  
    279       !                                     ! Ocean physics 
    280                             CALL     sbc_init   ! Forcings : surface module 
    281       !                                         ! Vertical physics 
    282                             CALL     zdf_init      ! namelist read 
    283                             CALL zdf_bfr_init      ! bottom friction 
    284       IF( lk_zdfric     )   CALL zdf_ric_init      ! Richardson number dependent Kz 
    285       IF( lk_zdftke     )   CALL zdf_tke_init      ! TKE closure scheme 
    286       IF( lk_zdfgls     )   CALL zdf_gls_init      ! GLS closure scheme 
    287       IF( lk_zdfkpp     )   CALL zdf_kpp_init      ! KPP closure scheme 
    288       IF( lk_zdftmx     )   CALL zdf_tmx_init      ! tidal vertical mixing 
    289       IF( lk_zdfddm .AND. .NOT. lk_zdfkpp )   & 
    290          &                  CALL zdf_ddm_init      ! double diffusive mixing 
    291       !                                         ! Lateral physics 
    292                             CALL ldf_tra_init      ! Lateral ocean tracer physics 
    293                             CALL ldf_dyn_init      ! Lateral ocean momentum physics 
    294       IF( lk_ldfslp     )   CALL ldf_slp_init      ! slope of lateral mixing 
    295  
    296       !                                     ! Active tracers 
    297                             CALL tra_qsr_init   ! penetrative solar radiation qsr 
    298                             CALL tra_bbc_init   ! bottom heat flux 
    299       IF( lk_trabbl     )   CALL tra_bbl_init   ! advective (and/or diffusive) bottom boundary layer scheme 
    300       IF( ln_tradmp     )   CALL tra_dmp_init   ! internal damping trends 
    301                             CALL tra_adv_init   ! horizontal & vertical advection 
    302                             CALL tra_ldf_init   ! lateral mixing 
    303                             CALL tra_zdf_init   ! vertical mixing and after tracer fields 
    304  
    305       !                                     ! Dynamics 
    306                             CALL dyn_adv_init   ! advection (vector or flux form) 
    307                             CALL dyn_vor_init   ! vorticity term including Coriolis 
    308                             CALL dyn_ldf_init   ! lateral mixing 
    309                             CALL dyn_hpg_init   ! horizontal gradient of Hydrostatic pressure 
    310                             CALL dyn_zdf_init   ! vertical diffusion 
    311                             CALL dyn_spg_init   ! surface pressure gradient 
    312  
    313       !                                     ! Misc. options 
    314       IF( nn_cla == 1   )   CALL cla_init       ! Cross Land Advection 
    315  
    316 #if defined key_top 
    317       !                                     ! Passive tracers 
    318                             CALL     trc_init 
    319 #endif 
    320       !                                     ! Diagnostics 
    321       IF( lk_floats     )   CALL     flo_init   ! drifting Floats 
    322                             CALL     iom_init   ! iom_put initialization 
    323       IF( lk_diaar5     )   CALL dia_ar5_init   ! ar5 diag 
    324                             CALL dia_ptr_init   ! Poleward TRansports initialization 
    325       IF( lk_diadct     )   CALL dia_dct_init   ! Sections tranports 
    326                             CALL dia_hsb_init   ! heat content, salt content and volume budgets 
    327                             CALL trd_mod_init   ! Mixed-layer/Vorticity/Integral constraints trends 
    328       IF( lk_diaobs     ) THEN                  ! Observation & model comparison 
    329                             CALL dia_obs_init            ! Initialize observational data 
    330                             CALL dia_obs( nit000 - 1 )   ! Observation operator for restart 
    331       ENDIF 
    332       !                                     ! Assimilation increments 
    333       IF( lk_asminc     )   CALL asm_inc_init   ! Initialize assimilation increments 
    334       ! 
    335188      IF( ln_rnf        )   CALL sbc_rnf_init 
    336189      !!!!!!!!!!!!! TAM initialisation !!!!!!!!!!!!!!!!!!!!!!!!!!! 
     
    343196                            CALL     sbc_init_tam   ! Forcings : surface module 
    344197                            CALL     sbc_ssr_ini_tam   ! Forcings : surface module 
    345       !                                         ! Vertical physics 
    346       !                      CALL     zdf_init_tam      ! namelist read 
    347       !IF( lk_zdfric     )   CALL zdf_ric_init      ! Richardson number dependent Kz 
    348       !IF( lk_zdftke     )   CALL zdf_tke_init      ! TKE closure scheme 
    349       !IF( lk_zdfgls     )   CALL zdf_gls_init      ! GLS closure scheme 
    350       !IF( lk_zdfkpp     )   CALL zdf_kpp_init      ! KPP closure scheme 
    351       !IF( lk_zdftmx     )   CALL zdf_tmx_init      ! tidal vertical mixing 
    352       !IF( lk_zdfddm .AND. .NOT. lk_zdfkpp )   & 
    353          !&                  CALL zdf_ddm_init      ! double diffusive mixing 
    354       !                                         ! Lateral physics 
    355                             !CALL ldf_tra_init      ! Lateral ocean tracer physics 
    356                             !CALL ldf_dyn_init      ! Lateral ocean momentum physics 
    357       !IF( lk_ldfslp     )   CALL ldf_slp_init      ! slope of lateral mixing 
    358  
    359       !                                     ! Active tracers 
     198            !                                     ! Active tracers 
    360199                            CALL tra_qsr_init_tam   ! penetrative solar radiation qsr 
    361200      IF( lk_trabbl     )   CALL tra_bbl_init_tam   ! advective (and/or diffusive) bottom boundary layer scheme 
     
    376215      IF( nn_cla == 1   )   CALL cla_init_tam       ! Cross Land Advection 
    377216                            CALL sbc_rnf_init_tam 
    378 !#if defined key_top 
    379       !!                                     ! Passive tracers 
    380                             !CALL     trc_init 
    381 !#endif 
    382       !!                                     ! Diagnostics 
    383       !IF( lk_floats     )   CALL     flo_init   ! drifting Floats 
    384                             !CALL     iom_init   ! iom_put initialization 
    385       !IF( lk_diaar5     )   CALL dia_ar5_init   ! ar5 diag 
    386                             !CALL dia_ptr_init   ! Poleward TRansports initialization 
    387       !IF( lk_diadct     )   CALL dia_dct_init   ! Sections tranports 
    388                             !CALL dia_hsb_init   ! heat content, salt content and volume budgets 
    389                             !CALL trd_mod_init   ! Mixed-layer/Vorticity/Integral constraints trends 
    390       !IF( lk_diaobs     ) THEN                  ! Observation & model comparison 
    391                             !CALL dia_obs_init            ! Initialize observational data 
    392                             !CALL dia_obs( nit000 - 1 )   ! Observation operator for restart 
    393       !ENDIF 
    394       !!                                     ! Assimilation increments 
    395       !IF( lk_asminc     )   CALL asm_inc_init   ! Initialize assimilation increments 
    396       !IF(lwp) WRITE(numout,*) 'Euler time step switch is ', neuler 
    397       ! 
    398       CALL tam_trj_init 
     217 
    399218      CALL tam_tst_init 
    400219      CALL tl_trj_ini 
    401220   END SUBROUTINE nemo_init_tam 
    402  
    403221 
    404222   SUBROUTINE nemo_ctl_tam 
     
    488306   END SUBROUTINE nemo_ctl_tam 
    489307 
    490  
    491    SUBROUTINE nemo_closefile 
    492       !!---------------------------------------------------------------------- 
    493       !!                     ***  ROUTINE nemo_closefile  *** 
    494       !! 
    495       !! ** Purpose :   Close the files 
    496       !!---------------------------------------------------------------------- 
    497       ! 
    498       IF( lk_mpp )   CALL mppsync 
    499       ! 
    500       CALL iom_close                                 ! close all input/output files managed by iom_* 
    501       ! 
    502       IF( numstp      /= -1 )   CLOSE( numstp      )   ! time-step file 
    503       IF( numsol      /= -1 )   CLOSE( numsol      )   ! solver file 
    504       IF( numnam      /= -1 )   CLOSE( numnam      )   ! oce namelist 
    505       IF( numnam_ice  /= -1 )   CLOSE( numnam_ice  )   ! ice namelist 
    506       IF( numevo_ice  /= -1 )   CLOSE( numevo_ice  )   ! ice variables (temp. evolution) 
    507       IF( numout      /=  6 )   CLOSE( numout      )   ! standard model output file 
    508       IF( numdct_vol  /= -1 )   CLOSE( numdct_vol  )   ! volume transports 
    509       IF( numdct_heat /= -1 )   CLOSE( numdct_heat )   ! heat transports 
    510       IF( numdct_salt /= -1 )   CLOSE( numdct_salt )   ! salt transports 
    511       ! 
    512       numout = 6                                     ! redefine numout in case it is used after this point... 
    513       ! 
    514    END SUBROUTINE nemo_closefile 
    515  
    516  
    517308   SUBROUTINE nemo_alloc_tam 
    518309      !!---------------------------------------------------------------------- 
     
    539330      ! 
    540331   END SUBROUTINE nemo_alloc_tam 
    541  
    542  
    543    SUBROUTINE nemo_partition( num_pes ) 
    544       !!---------------------------------------------------------------------- 
    545       !!                 ***  ROUTINE nemo_partition  *** 
    546       !! 
    547       !! ** Purpose : 
    548       !! 
    549       !! ** Method  : 
    550       !!---------------------------------------------------------------------- 
    551       INTEGER, INTENT(in) :: num_pes ! The number of MPI processes we have 
    552       ! 
    553       INTEGER, PARAMETER :: nfactmax = 20 
    554       INTEGER :: nfact ! The no. of factors returned 
    555       INTEGER :: ierr  ! Error flag 
    556       INTEGER :: ji 
    557       INTEGER :: idiff, mindiff, imin ! For choosing pair of factors that are closest in value 
    558       INTEGER, DIMENSION(nfactmax) :: ifact ! Array of factors 
    559       !!---------------------------------------------------------------------- 
    560  
    561       ierr = 0 
    562  
    563       CALL factorise( ifact, nfactmax, nfact, num_pes, ierr ) 
    564  
    565       IF( nfact <= 1 ) THEN 
    566          WRITE (numout, *) 'WARNING: factorisation of number of PEs failed' 
    567          WRITE (numout, *) '       : using grid of ',num_pes,' x 1' 
    568          jpnj = 1 
    569          jpni = num_pes 
    570       ELSE 
    571          ! Search through factors for the pair that are closest in value 
    572          mindiff = 1000000 
    573          imin    = 1 
    574          DO ji = 1, nfact-1, 2 
    575             idiff = ABS( ifact(ji) - ifact(ji+1) ) 
    576             IF( idiff < mindiff ) THEN 
    577                mindiff = idiff 
    578                imin = ji 
    579             ENDIF 
    580          END DO 
    581          jpnj = ifact(imin) 
    582          jpni = ifact(imin + 1) 
    583       ENDIF 
    584       ! 
    585       jpnij = jpni*jpnj 
    586       ! 
    587    END SUBROUTINE nemo_partition 
    588  
    589332 
    590333   SUBROUTINE factorise( kfax, kmaxfax, knfax, kn, kerr ) 
  • branches/2012/dev_v3_4_STABLE_2012/NEMOGCM/NEMO/OPA_SRC/nemogcm.F90

    r3604 r4600  
    8484   PUBLIC   nemo_init   ! needed by AGRIF 
    8585   PUBLIC   nemo_alloc  ! needed by TAM 
     86   PUBLIC   nemo_closefile ! Needed by NEMOTAM 
     87   PUBLIC   nemo_partition ! needed by NEMOTAM 
    8688 
    8789   CHARACTER(lc) ::   cform_aaa="( /, 'AAAAAAAA', / ) "     ! flag for output listing 
Note: See TracChangeset for help on using the changeset viewer.