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

Changeset 1359


Ignore:
Timestamp:
2009-03-31T14:36:28+02:00 (15 years ago)
Author:
smasson
Message:

first implementation of iom_put, see ticket:387

Location:
trunk
Files:
2 added
11 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMO/LIM_SRC_2/limwri_2.F90

    r1347 r1359  
    2727   USE dianam          ! build name of file (routine) 
    2828   USE in_out_manager 
     29   USE iom 
    2930   USE ioipsl 
    3031 
     
    9394      !!------------------------------------------------------------------- 
    9495 
     96      CALL iom_setkt( kt + nn_fsbc - 1 ) 
    9597      !                                          !--------------------! 
    9698      IF( kt == nit000 ) THEN                    !   Initialisation   ! 
     
    179181          
    180182         IF( nc(jf) == 1 )   CALL histwrite( nice, nam(jf), niter, zfield, ndim, ndex51 ) 
     183         CALL iom_put( nam(jf), zfield ) 
    181184          
    182185      END DO 
     
    184187      IF( ( nn_fsbc * niter ) >= nitend )   CALL histclo( nice )  
    185188      ! 
     189      CALL iom_setkt( kt ) 
     190 
    186191   END SUBROUTINE lim_wri_2 
    187192    
  • trunk/NEMO/OPA_SRC/DIA/diawri.F90

    r1334 r1359  
    2727   USE in_out_manager  ! I/O manager 
    2828   USE diadimg         ! dimg direct access file format output 
     29   USE iom 
    2930   USE ioipsl 
    3031 
     
    411412         WRITE(numout,*) '~~~~~~ ' 
    412413      ENDIF 
     414       
     415!--------------------------------------------------------------------------- 
     416 
     417      CALL iom_put("votemper",tn) 
     418      CALL iom_put("vosaline",sn) 
     419      CALL iom_put("sosstsst",tn(:,:,1))   ! sea surface temperature 
     420      CALL iom_put("sosaline",sn(:,:,1))   ! sea surface salinity 
     421#if defined key_dynspg_rl 
     422      CALL iom_put("sobarstf",bsfn)   ! barotropic streamfunction 
     423#else 
     424      CALL iom_put("sossheig",sshn)   ! sea surface height 
     425#endif 
     426 
     427      CALL iom_put("sowaflup",emp )   ! upward water flux 
     428      CALL iom_put("sowaflcd",emps)   ! c/d water flux 
     429      zw2d(:,:) = emps(:,:) * sn(:,:,1) * tmask(:,:,1) 
     430      CALL iom_put("sosalflx",zw2d)   ! c/d salt flux 
     431      CALL iom_put("sohefldo",qns + qsr )   ! total heat flux 
     432      CALL iom_put("soshfldo",qsr)   ! solar heat flux 
     433      CALL iom_put("somxl010",hmlp)   ! mixed layer depth 
     434      CALL iom_put("somixhgt",hmld)   ! turbocline depth 
     435      CALL iom_put("soicecov",fr_i)   ! ice fraction  
     436#if ! defined key_coupled 
     437      CALL iom_put("sohefldp",qrp)   ! heat flux damping 
     438      CALL iom_put("sowafldp",erp)   ! freshwater flux damping 
     439      zw2d(:,:) = erp(:,:) * sn(:,:,1) * tmask(:,:,1) 
     440      CALL iom_put("sosafldp", zw2d)   ! salt flux damping 
     441#endif 
     442 
     443#if ( defined key_coupled && ! defined key_lim3 && ! defined key_lim2 )  
     444      CALL iom_put("sohefldp",qrp)   ! heat flux damping 
     445      CALL iom_put("sowafldp",erp)   ! freshwater flux damping 
     446         zw2d(:,:) = erp(:,:) * sn(:,:,1) * tmask(:,:,1) 
     447      CALL iom_put("sosafldp",zw2d)   ! salt flux damping 
     448#endif 
     449#if defined key_diaspr 
     450      CALL iom_put("sosurfps",gps)   ! surface pressure 
     451#endif 
     452         zw2d(:,:) = FLOAT( nmln(:,:) ) * tmask(:,:,1) 
     453      CALL iom_put("sobowlin",zw2d)   ! ??? 
     454 
     455#if defined key_diahth 
     456      CALL iom_put("sothedep",hth)   ! depth of the thermocline 
     457      CALL iom_put("so20chgt",hd20)   ! depth of the 20 isotherm 
     458      CALL iom_put("so28chgt",hd28)   ! depth of the 28 isotherm 
     459      CALL iom_put("sohtc300",htc3)   ! first 300m heaat content 
     460#endif 
     461 
     462#if defined key_coupled  
     463#  if defined key_lim3 
     464      Must be adapted for LIM3 
     465#  else 
     466      CALL iom_put("soicetem",tn_ice)   ! surf. ice temperature 
     467      CALL iom_put("soicealb",alb_ice)   ! ice albedo 
     468#  endif 
     469#endif 
     470         ! Write fields on U grid 
     471      CALL iom_put("vozocrtx",un)    ! i-current 
     472#if defined key_diaeiv 
     473      CALL iom_put("vozoeivu",u_eiv)    ! i-eiv current 
     474#endif 
     475      CALL iom_put("sozotaux",utau)   ! i-wind stress 
     476#if defined key_dynspg_rl 
     477      CALL lbc_lnk( spgu, 'U', -1. ) 
     478      CALL iom_put("sozospgx",spgu)   ! i-surf. press. grad. 
     479#endif 
     480 
     481         ! Write fields on V grid 
     482      CALL iom_put("vomecrty",vn)   ! j-current 
     483#if defined key_diaeiv 
     484      CALL iom_put("vomeeivv",v_eiv)   ! j-eiv current 
     485#endif 
     486      CALL iom_put("sometauy", vtau)   ! j-wind stress 
     487#if defined key_dynspg_rl 
     488      CALL lbc_lnk( spgv, 'V', -1. ) 
     489      CALL iom_put("somespgy",spgv)   ! j-surf. pressure grad. 
     490#endif 
     491 
     492         ! Write fields on W grid 
     493      CALL iom_put("vovecrtz",wn)    ! vert. current 
     494#   if defined key_diaeiv 
     495      CALL iom_put("voveeivw",w_eiv)    ! vert. eiv current 
     496#   endif 
     497      CALL iom_put("votkeavt",avt)    ! T vert. eddy diff. coef. 
     498      CALL iom_put("votkeevd",avt_evd)    ! T enhan. vert. eddy diff. coef. 
     499      CALL iom_put("votkeavm",avmu)    ! T vert. eddy visc. coef. 
     500      CALL iom_put("votkeevm",avmu_evd)    ! T enhan. vert. eddy visc. coef. 
     501      IF( lk_zdfddm ) THEN 
     502         CALL iom_put("voddmavs",fsavs(:,:,:) )    ! S vert. eddy diff. coef. 
     503      ENDIF 
     504#if defined key_traldf_c2d 
     505      CALL iom_put("soleahtw",ahtw)   ! lateral eddy diff. coef. 
     506# if defined key_traldf_eiv 
     507      CALL iom_put("soleaeiw",aeiw)   ! EIV coefficient at w-point 
     508# endif 
     509#endif 
     510!--------------------------------------------------------------------------- 
    413511 
    414512      ! Write fields on T grid 
  • trunk/NEMO/OPA_SRC/IOM/iom.F90

    r1341 r1359  
    2626   USE iom_rstdimg     ! restarts access direct format "dimg" style... 
    2727 
     28#if defined key_ioserver 
     29   USE mod_event_client 
     30# endif 
     31 
    2832   IMPLICIT NONE 
    2933   PUBLIC   !   must be public to be able to access iom_def through iom 
    3034    
    31    PUBLIC iom_open, iom_close, iom_varid, iom_get, iom_gettime, iom_rstput 
     35   PUBLIC iom_init, iom_open, iom_close, iom_setkt, iom_varid, iom_get, iom_gettime, iom_rstput, iom_put 
    3236 
    3337   PRIVATE iom_rp0d, iom_rp1d, iom_rp2d, iom_rp3d 
    3438   PRIVATE iom_g0d, iom_g1d, iom_g2d, iom_g3d, iom_get_123d 
     39   PRIVATE iom_p2d, iom_p3d 
     40#if defined key_ioserver 
     41   PRIVATE iom_init_chkcpp 
     42   PRIVATE set_grid 
     43# endif 
    3544 
    3645   INTERFACE iom_get 
     
    4049      MODULE PROCEDURE iom_rp0d, iom_rp1d, iom_rp2d, iom_rp3d 
    4150   END INTERFACE 
     51  INTERFACE iom_put 
     52     MODULE PROCEDURE iom_p2d, iom_p3d 
     53  END INTERFACE 
     54#if defined key_ioserver 
     55   INTERFACE iom_setkt 
     56      MODULE PROCEDURE event__set_timestep 
     57   END INTERFACE 
     58# endif 
    4259 
    4360   !!---------------------------------------------------------------------- 
     
    4865 
    4966CONTAINS 
     67 
     68   SUBROUTINE iom_init( pjulian ) 
     69      !!---------------------------------------------------------------------- 
     70      !!                     ***  ROUTINE   *** 
     71      !! 
     72      !! ** Purpose :    
     73      !! 
     74      !!---------------------------------------------------------------------- 
     75      REAL(wp), INTENT(in) ::  pjulian   !: julian day at nit000 = 0 
     76#if defined key_ioserver 
     77      !!---------------------------------------------------------------------- 
     78      ! read the xml file 
     79      CALL event__parse_xml_file( 'iodef.xml' )   ! <- to get from the nameliste (namrun)... 
     80 
     81      ! calendar parameters 
     82      CALL event__set_time_parameters( nit000 - 1, pjulian, rdt ) 
     83 
     84      ! horizontal grid definition 
     85      CALL set_grid( "grid_T", glamt, gphit ) 
     86      CALL set_grid( "grid_U", glamu, gphiu ) 
     87      CALL set_grid( "grid_V", glamv, gphiv ) 
     88      CALL set_grid( "grid_W", glamt, gphit ) 
     89 
     90      ! vertical grid definition 
     91      CALL event__set_vert_axis( "deptht", gdept_0 ) 
     92      CALL event__set_vert_axis( "depthu", gdept_0 ) 
     93      CALL event__set_vert_axis( "depthv", gdept_0 ) 
     94      CALL event__set_vert_axis( "depthw", gdepw_0 ) 
     95 
     96      ! consistency regarding CPP keys... 
     97      CALL iom_init_chkcpp 
     98 
     99      ! end file definition 
     100      CALL event__close_io_definition 
     101#endif 
     102 
     103   END SUBROUTINE iom_init 
     104 
    50105 
    51106   SUBROUTINE iom_open( cdname, kiomid, ldwrt, kdom, kiolib, ldstop, ldiof ) 
     
    92147      ! if iom_open is called for the first time: initialize iom_file(:)%nfid to 0 
    93148      ! (could be done when defining iom_file in f95 but not in f90) 
    94       IF( iom_init == 0 ) THEN 
     149      IF( iom_open_init == 0 ) THEN 
    95150         iom_file(:)%nfid = 0 
    96          iom_init = 1 
     151         iom_open_init = 1 
    97152      ENDIF 
    98153      ! do we read or write the file? 
     
    244299         i_s = 1 
    245300         i_e = jpmax_files 
     301#if defined key_ioserver 
     302         CALL event__stop_ioserver 
     303#endif 
    246304      ENDIF 
    247305 
     
    822880      ENDIF 
    823881   END SUBROUTINE iom_rp3d 
     882 
     883 
    824884   !!---------------------------------------------------------------------- 
     885   !!                   INTERFACE iom_rstput 
     886   !!---------------------------------------------------------------------- 
     887   SUBROUTINE iom_p2d( cdname, pfield2d ) 
     888      CHARACTER(LEN=*)            , INTENT(in) ::   cdname 
     889      REAL(wp), DIMENSION(jpi,jpj), INTENT(in) ::   pfield2d 
     890#if defined key_ioserver 
     891      CALL event__write_field2D( cdname, pfield2d(nldi:nlei, nldj:nlej) ) 
     892#endif 
     893   END SUBROUTINE iom_p2d 
     894 
     895   SUBROUTINE iom_p3d( cdname, pfield3d ) 
     896      CHARACTER(LEN=*)                , INTENT(in) ::   cdname 
     897      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(in) ::   pfield3d 
     898#if defined key_ioserver 
     899      CALL event__write_field3D( cdname, pfield3d(nldi:nlei, nldj:nlej, :) ) 
     900#endif 
     901   END SUBROUTINE iom_p3d 
     902   !!---------------------------------------------------------------------- 
     903 
     904 
     905#if defined key_ioserver 
     906 
     907   SUBROUTINE set_grid( cdname, plon, plat ) 
     908      !!---------------------------------------------------------------------- 
     909      !!                     ***  ROUTINE   *** 
     910      !! 
     911      !! ** Purpose :    
     912      !! 
     913      !!---------------------------------------------------------------------- 
     914      CHARACTER(LEN=*)            , INTENT(in) ::   cdname 
     915      REAL(wp), DIMENSION(jpi,jpj), INTENT(in) ::   plon 
     916      REAL(wp), DIMENSION(jpi,jpj), INTENT(in) ::   plat 
     917 
     918      CALL event__set_grid_dimension( cdname, jpiglo, jpjglo) 
     919      CALL event__set_grid_domain( cdname, nlei-nldi+1, nlej-nldj+1, nimpp+nldi-1, njmpp+nldj-1, & 
     920         &                         plon(nldi:nlei, nldj:nlej), plat(nldi:nlei, nldj:nlej) ) 
     921      CALL event__set_grid_type_nemo( cdname ) 
     922 
     923   END SUBROUTINE set_grid 
     924 
     925 
     926   SUBROUTINE iom_init_chkcpp 
     927      !!--------------------------------------------------------------------- 
     928      !!                   ***  SUBROUTINE    *** 
     929      !! 
     930      !! ** Purpose :   
     931      !!--------------------------------------------------------------------- 
     932      USE zdfddm, ONLY :   lk_zdfddm      ! vertical  physics: double diffusion 
     933       
     934#if defined key_dynspg_rl 
     935      CALL event__disable_field( "sossheig" ) 
     936#else 
     937      CALL event__disable_field( "sobarstf" ) 
     938#endif 
     939 
     940      !!#if ! ( ! defined key_dynspg_rl && defined key_ice_lim) 
     941      !!        CALL disable_field( "iowaflup" ) 
     942      !!         CALL disable_field( "sowaflep" ) 
     943      !!#endif 
     944 
     945#if ! defined key_coupled 
     946      CALL event__enable_field( "sohefldp" ) 
     947      CALL event__enable_field( "sowafldp" ) 
     948      CALL event__enable_field( "sosafldp" ) 
     949#endif 
     950 
     951#if ( defined key_coupled && ! defined key_lim3 && ! defined key_lim2 )  
     952      CALL event__enable_field( "sohefldp" ) 
     953      CALL event__enable_field( "sowafldp" ) 
     954      CALL event__enable_field( "sosafldp" ) 
     955#endif 
     956 
     957#if ! defined key_diaspr 
     958      CALL event__disable_field( "sosurfps" ) 
     959#endif 
     960 
     961#if ! defined key_diahth 
     962      CALL event__disable_field( "sothedep" ) 
     963      CALL event__disable_field( "so20chgt" ) 
     964      CALL event__disable_field( "so28chgt" ) 
     965      CALL event__disable_field( "sohtc300" ) 
     966#endif 
     967 
     968#if defined key_coupled  
     969# if defined key_lim3 
     970      Must be adapted to LIM3 
     971# else 
     972      CALL event__enable_field( "soicetem" ) 
     973      CALL event__enable_field( "soicealb" ) 
     974# endif  
     975#endif  
     976 
     977#if ! defined key_diaeiv 
     978      CALL event__disable_field( "vozoeivu" ) 
     979      CALL event__disable_field( "vomeeivv" ) 
     980      CALL event__disable_field( "voveeivw" ) 
     981#endif 
     982 
     983#if ! defined key_dynspg_rl 
     984      CALL event__disable_field( "sozospgx" ) 
     985      CALL event__disable_field( "somespgy" ) 
     986#endif 
     987 
     988      IF( lk_zdfddm ) CALL event__enable_field( "voddmavs" ) 
     989 
     990#if ! defined key_traldf_c2d 
     991      CALL event__disable_field( "soleahtw" ) 
     992#endif 
     993 
     994#if ! defined key_traldf_eiv  
     995      CALL event__disable_field( "soleaeiw" ) 
     996#endif 
     997 
     998   END SUBROUTINE iom_init_chkcpp 
     999 
     1000#else 
     1001 
     1002   SUBROUTINE iom_setkt( kt ) 
     1003      INTEGER, INTENT(in   )::   kt  
     1004   END SUBROUTINE iom_setkt 
     1005 
     1006#endif 
    8251007 
    8261008 
  • trunk/NEMO/OPA_SRC/IOM/iom_def.F90

    r1152 r1359  
    4949 
    5050!$AGRIF_DO_NOT_TREAT 
    51    INTEGER, PUBLIC            ::   iom_init = 0        !: used to initialize iom_file(:)%nfid to 0 
     51   INTEGER, PUBLIC            ::   iom_open_init = 0   !: used to initialize iom_file(:)%nfid to 0 
    5252 
    5353   TYPE, PUBLIC ::   file_descriptor 
  • trunk/NEMO/OPA_SRC/daymod.F90

    r1213 r1359  
    3030   USE in_out_manager  ! I/O manager 
    3131   USE iom             !  
     32   USE ioipsl, ONLY :   ymds2ju        ! for calendar 
    3233   USE prtctl          ! Print control 
    3334   USE restart         !  
     
    4849   REAL(wp), PUBLIC ::   rsec_day    !: current time step counted in second since 00h of the current day 
    4950 
     51   REAL(wp), PUBLIC ::   fjulday     !: julian day  
    5052   REAL(wp), PUBLIC ::   adatrj      !: number of elapsed days since the begining of the run 
    5153   !                                 !: it is the accumulated duration of previous runs 
     
    101103      nday    =   ndastp - (nyear * 10000) - ( nmonth * 100 )  
    102104 
     105      CALL ymds2ju( nyear, nmonth, nday, 0.0, fjulday )  ! we assume that we start run at 00:00 
     106      fjulday = fjulday + 1.                             ! move back to the day at nit000 (and not at nit000 - 1) 
     107 
    103108      sec1jan000 = 0.e0 
    104109      CALL day_mth 
     
    207212      rsec_month = rsec_month + rdttra(1)                  
    208213      rsec_day   = rsec_day   + rdttra(1)                  
    209       adatrj = adatrj + rdttra(1) / rday 
     214      adatrj  = adatrj  + rdttra(1) / rday 
     215      fjulday = fjulday + rdttra(1) / rday 
    210216       
    211217      IF( rsec_day > rday ) THEN                        ! NEW day 
     
    300306            ! define ndastp and adatrj 
    301307            IF ( nrstdt == 2 ) THEN  
     308               ! read the parameters correspondting to nit000 - 1 (last time step of previous run) 
    302309               CALL iom_get( numror, 'ndastp', zndastp ) 
    303310               ndastp = NINT( zndastp ) 
    304311               CALL iom_get( numror, 'adatrj', adatrj  ) 
    305312            ELSE  
    306                ndastp = ndate0 - 1     ! ndate0 read in the namelist in dom_nam 
     313               ! parameters correspondting to nit000 - 1 (as we start the step loop with a call to day) 
     314               ndastp = ndate0 - 1     ! ndate0 read in the namelist in dom_nam, we assume that we start run at 00:00 
    307315               adatrj = ( REAL( nit000-1, wp ) * rdttra(1) ) / rday  
    308316               ! note this is wrong if time step has changed during run  
    309317            ENDIF 
    310318         ELSE 
    311             ndastp = ndate0 - 1        ! ndate0 read in the namelist in dom_nam 
     319            ! parameters correspondting to nit000 - 1 (as we start the step loop with a call to day) 
     320            ndastp = ndate0 - 1        ! ndate0 read in the namelist in dom_nam, we assume that we start run at 00:00 
    312321            adatrj = ( REAL( nit000-1, wp ) * rdttra(1) ) / rday  
    313322         ENDIF 
  • trunk/NEMO/OPA_SRC/lib_mpp.F90

    r1345 r1359  
    23642364      !!            08/04 :: R. Benshila, generalisation 
    23652365      !!--------------------------------------------------------------------- 
     2366#if defined key_ioserver 
     2367      USE io_interface 
     2368#endif 
    23662369      INTEGER                                 :: code, ierr 
    23672370      LOGICAL                                 :: mpi_was_called 
    23682371      !!--------------------------------------------------------------------- 
    23692372      ! 
     2373#if defined key_ioserver 
     2374      CALL init_ioserver(mpi_comm_opa,.TRUE.) 
     2375#else 
    23702376      CALL mpi_initialized( mpi_was_called, code )      ! MPI initialization 
    23712377      IF ( code /= MPI_SUCCESS ) THEN 
     
    23822388         ENDIF 
    23832389      ENDIF 
     2390#endif 
    23842391      ! 
    23852392      IF( nn_buffer > 0 ) THEN 
  • trunk/NEMO/OPA_SRC/opa.F90

    r1226 r1359  
    6868   USE step            ! OPA time-stepping                  (stp     routine) 
    6969#if defined key_oasis3 
    70    USE cpl_oasis3      ! OASIS3 coupling (to ECHAM5) 
     70   USE cpl_oasis3      ! OASIS3 coupling 
    7171#elif defined key_oasis4 
    72    USE cpl_oasis4      ! OASIS4 coupling (to ECHAM5) 
     72   USE cpl_oasis4      ! OASIS4 coupling (not working) 
    7373#endif 
    7474   USE dynspg_oce      ! Control choice of surface pressure gradient schemes 
     
    7979 
    8080   USE trcini          ! Initialization of the passive tracers 
     81   USE iom 
     82#if defined key_ioserver 
     83   USE io_interface 
     84#endif 
    8185 
    8286   IMPLICIT NONE 
     
    172176      !! 
    173177      !!---------------------------------------------------------------------- 
    174 #if defined key_oasis3 || defined key_oasis4 
     178#if defined key_oasis3 || defined key_oasis4 || defined key_ioserver 
    175179      INTEGER :: localComm 
    176180#endif 
     
    209213      call cpl_prism_init(localComm) 
    210214      ! Nodes selection 
     215      narea = mynode(localComm) 
     216#elif key_ioserver 
     217      CALL init_ioserver(localcomm, .FALSE.) 
    211218      narea = mynode(localComm) 
    212219#else 
     
    283290 
    284291#if defined key_top 
    285       CALL trc_ini                           ! Passive tracers 
     292      CALL trc_ini                          ! Passive tracers 
    286293#endif 
    287294 
    288295      CALL dia_ptr_init                     ! Poleward TRansports initialization 
     296 
     297      CALL iom_init( fjulday - adatrj )     ! iom_put initialization 
    289298 
    290299      !                                     ! =============== ! 
     
    437446      IF ( lk_mpp ) CALL mppsync 
    438447 
    439       ! 1. Unit close 
    440       ! ------------- 
    441  
    442448      CLOSE( numnam )           ! namelist 
    443449      CLOSE( numout )           ! standard model output file 
    444450 
    445451      IF(lwp) CLOSE( numstp )   ! time-step file 
    446       IF(lwp) CLOSE( numsol ) 
     452      IF(lwp) CLOSE( numsol )   ! solver file 
     453 
     454      CALL iom_close            ! close all input/output files 
    447455 
    448456   END SUBROUTINE opa_closefile 
  • trunk/NEMO/OPA_SRC/step.F90

    r1334 r1359  
    178178      CALL day( kstp )             ! Calendar 
    179179 
     180      CALL iom_setkt( kstp )       ! say to iom that we are at time step kstp 
     181       
    180182      CALL rst_opn( kstp )         ! Open the restart file 
    181183 
  • trunk/NVTK/INSTALL/JOBS/job_ORCA2_LIM.ksh

    r1301 r1359  
    8787# Sea-Ice namelist 
    8888get_namelist ${LOC_NAM} namelist_ice_lim2 ${MYO_EXP} namelist_ice 
     89 
     90# iom_put xml file 
     91get_namelist ${LOC_NAM} iodef.xml ${MYO_EXP} iodef.xml 
    8992 
    9093# Local function to find namelists parameters 
  • trunk/NVTK/fait_AA_make

    r1314 r1359  
    5757 
    5858# Target 
    59 all : diroce libioipsl key keyverif src_file_list libagrif \$(IOIPSL_LIB) \$(AGRIF_LIB) 
     59all : diroce libioipsl key keyverif src_file_list libioserver libagrif \$(IOIPSL_LIB) \$(AGRIF_LIB) 
    6060      @echo -------------------------------------------- 
    6161      time gmake \$(EXEC_BIN) -j \$(NBPRC) 
     
    8484\$(EXEC_BIN) :  \$(MODEL_LIB) agrif2model.o model.o 
    8585ifeq (\$(AGRIF),use) 
    86       \$(F_L) \$(L_X) -o \$(EXEC_BIN) model.o agrif2model.o \$(MODEL_LIB)/*.o \$(OASISMPI2_LIB) \$(IOIPSL_LIB) \$(AGRIF_LIB) \$(NCDF_LIB) \$(LIBMPI) \$(LIBMP) 
     86      \$(F_L) \$(L_X) -o \$(EXEC_BIN) model.o agrif2model.o \$(MODEL_LIB)/*.o \$(OASISMPI2_LIB) \$(IOIPSL_LIB) \$(AGRIF_LIB) \$(NCDF_LIB) \$(USER_LIB) \$(LIBMPI) \$(LIBMP) 
    8787else 
    88       \$(F_L) \$(L_X) -o \$(EXEC_BIN) model.o \$(MODEL_LIB)/*.o \$(OASISMPI2_LIB) \$(IOIPSL_LIB) \$(NCDF_LIB) \$(LIBMPI) \$(LIBMP) 
     88      \$(F_L) \$(L_X) -o \$(EXEC_BIN) model.o \$(MODEL_LIB)/*.o \$(OASISMPI2_LIB) \$(IOIPSL_LIB) \$(NCDF_LIB) \$(USER_LIB) \$(LIBMPI) \$(LIBMP) 
     89endif 
     90 
     91# ioserver library 
     92libioserver : 
     93ifeq (\$(IOSERVER),use) 
     94   (cd ../../../modeles/XMLF90; ./configure -arch \$(FCM_ARCH); fcm build; mkdir -p ../../lib/libxmlio_server  ; cd ../../lib/libxmlio_server ; ln -sf ../../modeles/XMLF90/lib/*.a .; ln -sf ../../modeles/XMLF90/inc/*.mod .) 
     95   (cd ../../../modeles/XMLIO_SERVER; ./configure -arch \$(FCM_ARCH); fcm build ; cd ../../lib/libxmlio_server ; ln -sf ../../modeles/XMLIO_SERVER/lib/*.a . ; ln -sf ../../modeles/XMLIO_SERVER/inc/* . ; cd \$(BINDIR) ; ln -sf ../modeles/XMLIO_SERVER/bin/server.exe ioserver) 
    8996endif 
    9097 
     
    224231echo '' 
    225232echo '#-Q- platine # Compiler options NEMO (CCRT Itanium Bull) ' 
    226 echo '#-Q- platine F_O = -O3 -i4 -r8 -module $(MODEL_LIB) -I $(MODDIR) -I$(MODEL_LIB) -I$(NCDF_INC) ' 
     233echo '#-Q- platine F_O = -O3 -i4 -r8 -module $(MODEL_LIB) -I $(MODDIR) -I$(MODEL_LIB) -I$(NCDF_INC) $(USER_INC) ' 
    227234echo '#-Q- platine L_X = $(L_O) ' 
    228235echo '#-Q- sx8mercure  # Compiler options NEMO (CEA SX8-NEC) ' 
    229 echo '#-Q- sx8mercure  F_O = -f2003 nocbind -size_t64 -dw -Wf\"-A dbl4\" -sx8 -C vopt -Wf"-P nh" -Wf',-pvctl noassume loopcnt=10000 shape=10000000 -L transform' -I $(MODDIR) -I $(MODEL_LIB) -I $(NCDF_INC)' 
     236echo '#-Q- sx8mercure  F_O = -f2003 nocbind -size_t64 -dw -Wf\"-A dbl4\" -sx8 -C vopt -Wf"-P nh" -Wf',-pvctl noassume loopcnt=10000 shape=10000000 -L transform' -I $(MODDIR) -I $(MODEL_LIB) -I $(NCDF_INC) $(USER_INC)' 
    230237echo '#-Q- sx8mercure  L_X = $(L_O)' 
    231238echo '#-Q- sx8brodie  # Compiler options NEMO (IDRIS SX8-NEC) ' 
    232 echo '#-Q- sx8brodie  F_O = -f2003 nocbind -dw -Wf\"-A idbl4\" -sx8 -C vopt -Wf"-init stack=nan" -Wl"-f nan" -Wf"-P nh -O overlap" -Wf,-pvctl noassume loopcnt=10000 -L transform -I $(MODDIR) -I $(MODEL_LIB) -I $(NCDF_INC)' 
     239echo '#-Q- sx8brodie  F_O = -f2003 nocbind -dw -Wf\"-A idbl4\" -sx8 -C vopt -Wf"-init stack=nan" -Wl"-f nan" -Wf"-P nh -O overlap" -Wf,-pvctl noassume loopcnt=10000 -L transform -I $(MODDIR) -I $(MODEL_LIB) -I $(NCDF_INC) $(USER_INC)' 
    233240echo '#-Q- sx8brodie  L_X = $(L_O)' 
    234241echo '#-Q- sxdkrz  # Compiler options for NEMO (DKRZ SX6-NEC) ' 
    235 echo '#-Q- sxdkrz  F_O =  -f2003 nocbind -ew -sx6 -ftrace -C vopt -Wf"-init stack=nan" -Wl"-f nan" -Wf"-P nh -O overlap" -Wf"-pvctl noassume loopcnt=10000" -L transform -I $(MODDIR) -I $(MODEL_LIB) -I $(NCDF_INC)' 
     242echo '#-Q- sxdkrz  F_O =  -f2003 nocbind -ew -sx6 -ftrace -C vopt -Wf"-init stack=nan" -Wl"-f nan" -Wf"-P nh -O overlap" -Wf"-pvctl noassume loopcnt=10000" -L transform -I $(MODDIR) -I $(MODEL_LIB) -I $(NCDF_INC) $(USER_INC)' 
    236243echo '#-Q- sxdkrz  L_X = $(L_O) -ftrace' 
    237244echo '#-Q- eshpux  # Compiler options for NEMO (Earth Simulator)' 
    238245echo '#-Q- eshpux  # for super perfs!' 
    239 echo '#-Q- eshpux  # F_O = -f2003 nocbind $(FTRACE) -pi nest=5 line=10000 expin=Fmpplib.F -Wf,-A idbl4 -C hopt -Wf"-P nh -O overlap" -Wf,-pvctl noassume loopcnt=10000 -L transform -I $(MODDIR) -I $(MODEL_LIB) -I $(NCDF_INC)' 
     246echo '#-Q- eshpux  # F_O = -f2003 nocbind $(FTRACE) -pi nest=5 line=10000 expin=Fmpplib.F -Wf,-A idbl4 -C hopt -Wf"-P nh -O overlap" -Wf,-pvctl noassume loopcnt=10000 -L transform -I $(MODDIR) -I $(MODEL_LIB) -I $(NCDF_INC) $(USER_INC)' 
    240247echo '#-Q- eshpux  # regular options!' 
    241 echo '#-Q- eshpux  F_O = -f2003 nocbind $(FTRACE) -Wf,-A idbl4 -C vopt -P stack -Wf"-P nh -O overlap" -Wf,-pvctl noassume loopcnt=10000 -L transform -Wf,-pvctl nomsg -Wf"-O nomsg" -I $(MODDIR) -I $(MODEL_LIB) -I $(NCDF_INC)' 
     248echo '#-Q- eshpux  F_O = -f2003 nocbind $(FTRACE) -Wf,-A idbl4 -C vopt -P stack -Wf"-P nh -O overlap" -Wf,-pvctl noassume loopcnt=10000 -L transform -Wf,-pvctl nomsg -Wf"-O nomsg" -I $(MODDIR) -I $(MODEL_LIB) -I $(NCDF_INC) $(USER_INC)' 
    242249echo '#-Q- eshpux  L_X = $(L_O)' 
    243250echo '#-Q- linux  # Compiler options for NEMO (pgf version)' 
    244 echo '#-Q- linux  F_O = -Mlist -O3 -byteswapio -r8  -I $(MODDIR) -I$(MODEL_LIB) -I $(NCDF_INC)' 
     251echo '#-Q- linux  F_O = -Mlist -O3 -byteswapio -r8  -I $(MODDIR) -I$(MODEL_LIB) -I $(NCDF_INC) $(USER_INC)' 
    245252echo '#-Q- linux  L_X = -r8 -O3' 
    246253echo '#-Q- lxiv7  # Compiler options for NEMO (ifc version)' 
    247 echo '#-Q- lxiv7  F_O = -O3 -r8  -I $(MODDIR) -I$(MODEL_LIB) -I $(NCDF_INC)' 
     254echo '#-Q- lxiv7  F_O = -O3 -r8  -I $(MODDIR) -I$(MODEL_LIB) -I $(NCDF_INC) $(USER_INC)' 
    248255echo '#-Q- lxiv7  L_X = -r8 -O3' 
    249256echo '#-Q- lxiv8  # Compiler options for NEMO (ifort version)' 
    250 echo '#-Q- lxiv8  F_O = -O3 -r8  -I $(MODDIR) -I$(MODEL_LIB) -I $(NCDF_INC)' 
     257echo '#-Q- lxiv8  F_O = -O3 -r8  -I $(MODDIR) -I$(MODEL_LIB) -I $(NCDF_INC) $(USER_INC)' 
    251258echo '#-Q- lxiv8  L_X = -r8 -O3' 
    252259echo '#-Q- g95  # Compiler options for NEMO (g95 version)' 
    253 echo '#-Q- g95  F_O = -O3 -fno-second-underscore -r8 -funroll-all-loops -I $(MODDIR) -I $(MODEL_LIB) -I $(NCDF_INC)' 
     260echo '#-Q- g95  F_O = -O3 -fno-second-underscore -r8 -funroll-all-loops -I $(MODDIR) -I $(MODEL_LIB) -I $(NCDF_INC) $(USER_INC)' 
    254261echo '#-Q- g95  L_X = -r8 -O3' 
    255262echo '#-Q- gfortran  # Compiler options for NEMO (gfortran version)' 
    256 echo '#-Q- gfortran  F_O = -fno-second-underscore -fdefault-real-8 -funroll-all-loops -I $(MODDIR) -I $(MODEL_LIB) -I $(NCDF_INC)' 
     263echo '#-Q- gfortran  F_O = -fno-second-underscore -fdefault-real-8 -funroll-all-loops -I $(MODDIR) -I $(MODEL_LIB) -I $(NCDF_INC) $(USER_INC)' 
    257264echo '#-Q- gfortran  L_X = -fdefault-real-8' 
    258265echo '#-Q- aix6  # Compiler options for NEMO (aix6 version)' 
    259 echo '#-Q- aix6  F_O = -O3 -qsave -qrealsize=8 -qsuffix=f=f90 -qsuffix=cpp=F90 -qextname -qsource -q64 -qlargepage -qmaxmem=-1 -I $(MODDIR) -I $(MODEL_LIB) -I $(NCDF_INC)'  
     266echo '#-Q- aix6  F_O = -O3 -qsave -qrealsize=8 -qsuffix=f=f90 -qsuffix=cpp=F90 -qextname -qsource -q64 -qlargepage -qmaxmem=-1 -I $(MODDIR) -I $(MODEL_LIB) -I $(NCDF_INC) $(USER_INC)'  
    260267echo '#-Q- aix6  L_O = $(F_P) -q64 -O3' 
    261268echo '#-Q- aix6  L_X = $(L_O)' 
    262269echo '#-Q- ax6_mono    # Compiler options for NEMO (aix6 version)' 
    263 echo '#-Q- ax6_mono    F_O = -O3 -qsave -qrealsize=8 -qsuffix=f=f90 -qsuffix=cpp=F90 -qextname -qsource -q64 -qlargepage -qmaxmem=-1 -I $(MODDIR) -I $(MODEL_LIB) -I $(NCDF_INC)'  
     270echo '#-Q- ax6_mono    F_O = -O3 -qsave -qrealsize=8 -qsuffix=f=f90 -qsuffix=cpp=F90 -qextname -qsource -q64 -qlargepage -qmaxmem=-1 -I $(MODDIR) -I $(MODEL_LIB) -I $(NCDF_INC) $(USER_INC)'  
    264271echo '#-Q- ax6_mono   L_O = $(F_P) -q64 -O3' 
    265272echo '#-Q- ax6_mono   L_X = $(L_O)' 
    266273echo '#-Q- babel  # Compiler options for NEMO (blue gene version)' 
    267 echo '#-Q- babel  F_O =  -O3 -qsave -qrealsize=8 -qsuffix=f=f90 -qsuffix=cpp=F90 -qsource -qextname=flush -qlargepage -qmaxmem=-1 -I $(MODDIR) -I $(MODEL_LIB) -I $(NCDF_INC)' 
     274echo '#-Q- babel  F_O =  -O3 -qsave -qrealsize=8 -qsuffix=f=f90 -qsuffix=cpp=F90 -qsource -qextname=flush -qlargepage -qmaxmem=-1 -I $(MODDIR) -I $(MODEL_LIB) -I $(NCDF_INC) $(USER_INC)' 
    268275echo '#-Q- babel  L_X = $(L_O)' 
    269276echo '#-Q- osxxlf    # Compiler options for NEMO (osxxlf version)' 
    270 echo '#-Q- osxxlf    F_O = -O3 -qsave -qrealsize=8 -qsuffix=f=f90 -qsuffix=cpp=F90 -qsource -qextname -qstrict -qmaxmem=-1 -I $(MODDIR) -I $(MODEL_LIB) -I $(NCDF_INC)'  
     277echo '#-Q- osxxlf    F_O = -O3 -qsave -qrealsize=8 -qsuffix=f=f90 -qsuffix=cpp=F90 -qsource -qextname -qstrict -qmaxmem=-1 -I $(MODDIR) -I $(MODEL_LIB) -I $(NCDF_INC) $(USER_INC)'  
    271278echo '#-Q- osxxlf    L_X = -qrealsize=8 -O3' 
    272279 
     
    317324echo 'else' 
    318325echo 'AGRIF_MPI=' 
     326echo 'endif' 
     327echo '' 
     328echo '# Some tests to define variables related to xmlioserver compilation' 
     329echo '# Please do not change ' 
     330echo 'ifneq (,$(findstring key_ioserver,$(P_P)))' 
     331echo 'IOSERVER=use' 
     332echo 'override USER_LIB += -L../../../lib/libxmlio_server -lioserver -lxmlio -lxmlf90' 
     333echo 'override USER_INC += -I../../../lib/libxmlio_server' 
     334echo 'else' 
     335echo 'IOSERVER=notuse' 
    319336echo 'endif' 
    320337 
  • trunk/UTIL/fait_AA_make

    r1330 r1359  
    6666      @if [ ! -d ../../../lib/oce ] ; then mkdir ../../../lib/oce ; fi 
    6767 
    68 \$(EXEC_BIN) : libioipsl firstagrif mpiagrif key keyverif src_file_list libagrif \$(MODEL_LIB) \$(IOIPSL_LIB) \$(AGRIF_LIB) agrif2model.o model.o 
     68\$(EXEC_BIN) : libioipsl libioserver firstagrif mpiagrif key keyverif src_file_list libagrif \$(MODEL_LIB) \$(IOIPSL_LIB) \$(AGRIF_LIB) agrif2model.o model.o 
    6969ifeq (\$(AGRIF),use) 
    7070      \$(F_L) \$(L_X) -o \$(EXEC_BIN) model.o agrif2model.o \$(SXMODEL_LIB) \$(USER_LIB) \$(IOIPSL_LIB) \$(AGRIF_LIB) \$(NCDF_LIB) \$(LIBMPI) \$(LIBMP) 
    7171else 
    7272      \$(F_L) \$(L_X) -o \$(EXEC_BIN) model.o \$(SXMODEL_LIB) \$(USER_LIB) \$(IOIPSL_LIB) \$(NCDF_LIB) \$(LIBMPI) \$(LIBMP) 
     73endif 
     74 
     75# ioserver library 
     76libioserver : 
     77ifeq (\$(IOSERVER),use) 
     78   (cd ../../XMLF90; ./configure -arch \$(FCM_ARCH); fcm build; mkdir -p ../../lib/libxmlio_server  ; cd ../../lib/libxmlio_server ; ln -sf ../../modeles/XMLF90/lib/*.a .; ln -sf ../../modeles/XMLF90/inc/*.mod .) 
     79   (cd ../../XMLIO_SERVER; ./configure -arch \$(FCM_ARCH); fcm build ; cd ../../lib/libxmlio_server ; ln -sf ../../modeles/XMLIO_SERVER/lib/*.a . ; ln -sf ../../modeles/XMLIO_SERVER/inc/* . ; cd \$(BINDIR) ; ln -sf ../modeles/XMLIO_SERVER/bin/server.exe ioserver) 
    7380endif 
    7481 
     
    284291echo 'AGRIF_MPI=' 
    285292echo 'endif' 
     293echo '' 
     294echo '# Some tests to define variables related to xmlioserver compilation' 
     295echo '# Please do not change ' 
     296echo 'ifneq (,$(findstring key_ioserver,$(P_P)))' 
     297echo 'IOSERVER=use' 
     298echo 'override USER_LIB += -L../../../lib/libxmlio_server -lioserver -lxmlio -lxmlf90' 
     299echo 'override USER_INC += -I../../../lib/libxmlio_server' 
     300echo 'else' 
     301echo 'IOSERVER=notuse' 
     302echo 'endif' 
    286303 
    287304echo '' 
Note: See TracChangeset for help on using the changeset viewer.