Ignore:
Timestamp:
Jul 15, 2015, 1:00:35 PM (9 years ago)
Author:
ymipsl
Message:

Add XIOS output for aquaplanet in LMDZ side

YM

Location:
dynamico_lmdz/aquaplanet/LMDZ5
Files:
1 added
1 deleted
6 edited

Legend:

Unmodified
Added
Removed
  • dynamico_lmdz/aquaplanet/LMDZ5/arch/arch-X64_CURIE.fcm

    r3809 r3849  
    99%PROD_FFLAGS         -O2
    1010%DEV_FFLAGS          -p -g -O2 -traceback -fp-stack-check
    11 %DEBUG_FFLAGS        -p -g -traceback -fp-stack-check -ftrapuv
     11%DEBUG_FFLAGS        -g -traceback
    1212%MPI_FFLAGS
    13 %OMP_FFLAGS          -openmp
     13%OMP_FFLAGS          -openmp -openmp-threadprivate compat
    1414%BASE_LD             -i4 -r8 -auto $MKL_LIBS
    1515%MPI_LD
    16 %OMP_LD              -openmp
     16%OMP_LD              -openmp -openmp-threadprivate compat
  • dynamico_lmdz/aquaplanet/LMDZ5/arch/arch-X64_CURIE.path

    r3809 r3849  
    11NETCDF_LIBDIR="-L$NETCDF_LIB_DIR -lnetcdff -lnetcdf"
    22NETCDF_INCDIR=-I$NETCDF_INC_DIR
    3 IOIPSL_INCDIR=$LMDGCM/../../lib
    4 IOIPSL_LIBDIR=$LMDGCM/../../lib
     3IOIPSL_INCDIR=$LMDGCM/../IOIPSL/src
     4IOIPSL_LIBDIR=$LMDGCM/../IOIPSL/src
    55ORCH_INCDIR=$LMDGCM/../../lib
    66ORCH_LIBDIR=$LMDGCM/../../lib
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/iophy.F90

    r3831 r3849  
    4545                                mpi_size, mpi_rank, klon_mpi, &
    4646                                is_sequential, is_south_pole
    47   USE mod_grid_phy_lmdz, only: nbp_lon, nbp_lat, klon_glo
     47  USE mod_grid_phy_lmdz, only: nbp_lon, nbp_lat, klon_glo, grid_type, unstructured
     48  USE print_control_mod, ONLY: prt_level, lunout
    4849#ifdef CPP_IOIPSL
    4950  USE ioipsl, only: flio_dom_set
    5051#endif
    5152#ifdef CPP_XIOS
    52   use wxios, only: wxios_domain_param
     53  use wxios, only: wxios_domain_param, wxios_domain_param_unstructured, wxios_context_init
    5354#endif
    5455  IMPLICIT NONE
     
    6970    INTEGER :: data_ibegin, data_iend
    7071
    71     CALL gather(rlat,rlat_glo)
    72     CALL bcast(rlat_glo)
    73     CALL gather(rlon,rlon_glo)
    74     CALL bcast(rlon_glo)
    75    
    76 !$OMP MASTER 
    77     ALLOCATE(io_lat(nbp_lat))
    78     io_lat(1)=rlat_glo(1)
    79     io_lat(nbp_lat)=rlat_glo(klon_glo)
    80     IF ((nbp_lon*nbp_lat) > 1) then
    81       DO i=2,nbp_lat-1
    82         io_lat(i)=rlat_glo(2+(i-2)*nbp_lon)
    83       ENDDO
     72#ifdef CPP_XIOS
     73      CALL wxios_context_init
     74#endif
     75   
     76
     77    IF (grid_type==unstructured) THEN
     78   
     79#ifdef CPP_XIOS
     80      CALL wxios_domain_param_unstructured
     81#endif
     82   
     83    ELSE
     84
     85      CALL gather(rlat,rlat_glo)
     86      CALL bcast(rlat_glo)
     87      CALL gather(rlon,rlon_glo)
     88      CALL bcast(rlon_glo)
     89   
     90  !$OMP MASTER 
     91      ALLOCATE(io_lat(nbp_lat))
     92      io_lat(1)=rlat_glo(1)
     93      io_lat(nbp_lat)=rlat_glo(klon_glo)
     94      IF ((nbp_lon*nbp_lat) > 1) then
     95        DO i=2,nbp_lat-1
     96          io_lat(i)=rlat_glo(2+(i-2)*nbp_lon)
     97        ENDDO
     98      ENDIF
     99
     100      ALLOCATE(io_lon(nbp_lon))
     101      IF (klon_glo == 1) THEN
     102        io_lon(1)=rlon_glo(1)
     103      ELSE
     104        io_lon(1:nbp_lon)=rlon_glo(2:nbp_lon+1)
     105      ENDIF
     106   
     107  !! (I) dtnb   : total number of domains
     108  !! (I) dnb    : domain number
     109  !! (I) did(:) : distributed dimensions identifiers
     110  !!              (up to 5 dimensions are supported)
     111  !! (I) dsg(:) : total number of points for each dimension
     112  !! (I) dsl(:) : local number of points for each dimension
     113  !! (I) dpf(:) : position of first local point for each dimension
     114  !! (I) dpl(:) : position of last local point for each dimension
     115  !! (I) dhs(:) : start halo size for each dimension
     116  !! (I) dhe(:) : end halo size for each dimension
     117  !! (C) cdnm   : Model domain definition name.
     118  !!              The names actually supported are :
     119  !!              "BOX", "APPLE", "ORANGE".
     120  !!              These names are case insensitive.
     121
     122      ddid=(/ 1,2 /)
     123      dsg=(/ nbp_lon, nbp_lat /)
     124      dsl=(/ nbp_lon, jj_nb /)
     125      dpf=(/ 1,jj_begin /)
     126      dpl=(/ nbp_lon, jj_end /)
     127      dhs=(/ ii_begin-1,0 /)
     128      IF (mpi_rank==mpi_size-1) THEN
     129        dhe=(/0,0/)
     130      ELSE
     131        dhe=(/ nbp_lon-ii_end,0 /) 
     132      ENDIF
     133
     134#ifndef CPP_IOIPSL_NO_OUTPUT   
     135      CALL flio_dom_set(mpi_size,mpi_rank,ddid,dsg,dsl,dpf,dpl,dhs,dhe, &
     136                        'APPLE',phys_domain_id)
     137#endif
     138#ifdef CPP_XIOS
     139      ! Set values for the mask:
     140      IF (mpi_rank == 0) THEN
     141          data_ibegin = 0
     142      ELSE
     143          data_ibegin = ii_begin - 1
     144      END IF
     145
     146      IF (mpi_rank == mpi_size-1) THEN
     147          data_iend = nbp_lon
     148      ELSE
     149          data_iend = ii_end + 1
     150      END IF
     151
     152      if (prt_level>=10) then
     153        write(lunout,*) "init_iophy_new: mpirank=",mpi_rank," iibegin=",ii_begin , " ii_end=",ii_end," jjbegin=",jj_begin," jj_nb=",jj_nb," jj_end=",jj_end
     154        write(lunout,*) "init_iophy_new: mpirank=",mpi_rank," nbp_lon=",nbp_lon," nbp_lat=",nbp_lat
     155        write(lunout,*) "init_iophy_new: mpirank=",mpi_rank," data_ibegin=",data_ibegin," data_iend=",data_iend
     156        write(lunout,*) "init_iophy_new: mpirank=",mpi_rank," data_ibegin=",data_ibegin," data_iend=",data_iend
     157        write(lunout,*) "init_iophy_new: mpirank=",mpi_rank," is_south_pole=",is_south_pole
     158      endif
     159
     160      ! Initialize the XIOS domain coreesponding to this process:
     161   
     162        CALL wxios_domain_param("dom_glo", is_sequential, nbp_lon, jj_nb, nbp_lon, nbp_lat, &
     163                                1, nbp_lon, ii_begin, ii_end, jj_begin, jj_end,             &
     164                                klon_mpi+2*(nbp_lon-1), data_ibegin, data_iend,             &
     165                               io_lat, io_lon,is_south_pole,mpi_rank)
     166#endif
     167!$OMP END MASTER
     168     
    84169    ENDIF
    85 
    86     ALLOCATE(io_lon(nbp_lon))
    87     IF (klon_glo == 1) THEN
    88       io_lon(1)=rlon_glo(1)
    89     ELSE
    90       io_lon(1:nbp_lon)=rlon_glo(2:nbp_lon+1)
    91     ENDIF
    92    
    93 !! (I) dtnb   : total number of domains
    94 !! (I) dnb    : domain number
    95 !! (I) did(:) : distributed dimensions identifiers
    96 !!              (up to 5 dimensions are supported)
    97 !! (I) dsg(:) : total number of points for each dimension
    98 !! (I) dsl(:) : local number of points for each dimension
    99 !! (I) dpf(:) : position of first local point for each dimension
    100 !! (I) dpl(:) : position of last local point for each dimension
    101 !! (I) dhs(:) : start halo size for each dimension
    102 !! (I) dhe(:) : end halo size for each dimension
    103 !! (C) cdnm   : Model domain definition name.
    104 !!              The names actually supported are :
    105 !!              "BOX", "APPLE", "ORANGE".
    106 !!              These names are case insensitive.
    107 
    108     ddid=(/ 1,2 /)
    109     dsg=(/ nbp_lon, nbp_lat /)
    110     dsl=(/ nbp_lon, jj_nb /)
    111     dpf=(/ 1,jj_begin /)
    112     dpl=(/ nbp_lon, jj_end /)
    113     dhs=(/ ii_begin-1,0 /)
    114     IF (mpi_rank==mpi_size-1) THEN
    115       dhe=(/0,0/)
    116     ELSE
    117       dhe=(/ nbp_lon-ii_end,0 /) 
    118     ENDIF
    119 
    120 #ifndef CPP_IOIPSL_NO_OUTPUT   
    121     CALL flio_dom_set(mpi_size,mpi_rank,ddid,dsg,dsl,dpf,dpl,dhs,dhe, &
    122                       'APPLE',phys_domain_id)
    123 #endif
    124 #ifdef CPP_XIOS
    125     ! Set values for the mask:
    126     IF (mpi_rank == 0) THEN
    127         data_ibegin = 0
    128     ELSE
    129         data_ibegin = ii_begin - 1
    130     END IF
    131 
    132     IF (mpi_rank == mpi_size-1) THEN
    133         data_iend = nbp_lon
    134     ELSE
    135         data_iend = ii_end + 1
    136     END IF
    137 
    138     if (prt_level>=10) then
    139       write(lunout,*) "init_iophy_new: mpirank=",mpi_rank," iibegin=",ii_begin , " ii_end=",ii_end," jjbegin=",jj_begin," jj_nb=",jj_nb," jj_end=",jj_end
    140       write(lunout,*) "init_iophy_new: mpirank=",mpi_rank," nbp_lon=",nbp_lon," nbp_lat=",nbp_lat
    141       write(lunout,*) "init_iophy_new: mpirank=",mpi_rank," data_ibegin=",data_ibegin," data_iend=",data_iend
    142       write(lunout,*) "init_iophy_new: mpirank=",mpi_rank," data_ibegin=",data_ibegin," data_iend=",data_iend
    143       write(lunout,*) "init_iophy_new: mpirank=",mpi_rank," is_south_pole=",is_south_pole
    144     endif
    145 
    146     ! Initialize the XIOS domain coreesponding to this process:
    147     CALL wxios_domain_param("dom_glo", is_sequential, nbp_lon, jj_nb, nbp_lon, nbp_lat, &
    148                             1, nbp_lon, ii_begin, ii_end, jj_begin, jj_end,             &
    149                             klon_mpi+2*(nbp_lon-1), data_ibegin, data_iend,             &
    150                             io_lat, io_lon,is_south_pole,mpi_rank)
    151 #endif
    152 !$OMP END MASTER
    153170     
    154171  END SUBROUTINE init_iophy_new
     
    454471                                   clef_stations, phys_out_filenames, lev_files, &
    455472                                   nid_files, nhorim, swaero_diag
     473    use print_control_mod, only: prt_level, lunout
    456474    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    457475#ifdef CPP_XIOS
     
    540558                                   levmax, nvertm
    541559  USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
     560  use print_control_mod, only: prt_level, lunout
     561
    542562#ifdef CPP_XIOS
    543563    use wxios, only: wxios_add_field_to_file
     
    774794                                 nfiles, vars_defined, clef_stations, &
    775795                                 nid_files
    776   USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
     796  USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat, grid_type, regular_lonlat, unstructured
    777797#ifdef CPP_XIOS
    778798  USE xios, only: xios_send_field
     
    838858    CALL Gather_omp(field,buffer_omp)
    839859!$OMP MASTER
    840     CALL grid1Dto2D_mpi(buffer_omp,Field2d)
     860    if (grid_type==regular_lonlat) CALL grid1Dto2D_mpi(buffer_omp,Field2d)
    841861
    842862! La boucle sur les fichiers:
     
    849869                             trim(var%name)                       
    850870          endif
    851           CALL xios_send_field(var%name, Field2d)
     871
     872          if (grid_type==regular_lonlat) THEN
     873            CALL xios_send_field(var%name, Field2d)
     874          else if (grid_type==unstructured) THEN
     875            CALL xios_send_field(var%name, buffer_omp)
     876          endif
     877         
    852878          if (prt_level >= 10) then
    853879             write(lunout,*)'Dans iophy histwrite2D,var%name apres xios_send ',&
     
    868894                     write(lunout,*)"histwrite2d_phy:.NOT.clef_stations(iff)and iff==iff_beg, call xios_send_field"
    869895                  endif
    870                   CALL xios_send_field(var%name, Field2d)
     896                  if (grid_type==regular_lonlat) THEN
     897                    CALL xios_send_field(var%name, Field2d)
     898                  else if (grid_type==unstructured) THEN
     899                    CALL xios_send_field(var%name, buffer_omp)
     900                 endif
     901     
    871902                  firstx=.false.
    872903               ENDIF
     
    933964                                 nfiles, vars_defined, clef_stations, &
    934965                                 nid_files
    935   USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
     966  USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat, grid_type, regular_lonlat, unstructured
    936967#ifdef CPP_XIOS
    937968  USE xios, only: xios_send_field
     
    9881019    CALL Gather_omp(field,buffer_omp)
    9891020!$OMP MASTER
    990     CALL grid1Dto2D_mpi(buffer_omp,field3d)
     1021    if (grid_type==regular_lonlat) CALL grid1Dto2D_mpi(buffer_omp,field3d)
    9911022
    9921023
     
    10001031                             trim(var%name)                       
    10011032          endif
    1002           CALL xios_send_field(var%name, Field3d(:,:,1:nlevx))
     1033          if (grid_type==regular_lonlat) THEN
     1034            CALL xios_send_field(var%name, Field3d(:,:,1:nlevx))
     1035          else if (grid_type==unstructured) THEN
     1036            CALL xios_send_field(var%name, buffer_omp(:,1:nlevx))
     1037          endif
    10031038#else
    10041039        CALL abort_physic ('iophy','cannot have ok_all_xml = .T. without CPP_XIOS defined' ,1)
     
    10181053                                  nbp_lon,jj_nb,nlevx
    10191054                endif
    1020                 CALL xios_send_field(var%name, Field3d(:,:,1:nlevx))
     1055                if (grid_type==regular_lonlat) THEN
     1056                  CALL xios_send_field(var%name, Field3d(:,:,1:nlevx))
     1057                else if (grid_type==unstructured) THEN
     1058                  CALL xios_send_field(var%name, buffer_omp(:,1:nlevx))
     1059                endif
    10211060                            firstx=.false.
    10221061              ENDIF
     
    10791118                                is_sequential, klon_mpi_begin, klon_mpi_end, &
    10801119                                jj_nb, klon_mpi
    1081   USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
     1120  USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat, grid_type, unstructured
    10821121  USE xios, only: xios_send_field
     1122  USE print_control_mod, ONLY: lunout, prt_level
    10831123
    10841124
     
    11021142    CALL Gather_omp(field,buffer_omp)   
    11031143!$OMP MASTER
    1104     CALL grid1Dto2D_mpi(buffer_omp,Field2d)
    1105    
    1106 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    1107 !ATTENTION, STATIONS PAS GEREES !
    1108 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    1109     !IF(.NOT.clef_stations(iff)) THEN
    1110     IF (.TRUE.) THEN
    1111         ALLOCATE(index2d(nbp_lon*jj_nb))
    1112         ALLOCATE(fieldok(nbp_lon*jj_nb))
    1113 
    1114 
    1115         CALL xios_send_field(field_name, Field2d)
    1116 
    1117     ELSE
    1118         ALLOCATE(fieldok(npstn))
    1119         ALLOCATE(index2d(npstn))
    1120 
    1121         IF (is_sequential) THEN
    1122             DO ip=1, npstn
    1123                 fieldok(ip)=buffer_omp(nptabij(ip))
    1124             ENDDO
    1125         ELSE
    1126             DO ip=1, npstn
    1127                 PRINT*,'histwrite2d_xios is_sequential npstn ip namenptabij',npstn,ip,field_name,nptabij(ip)
    1128                 IF(nptabij(ip).GE.klon_mpi_begin.AND. &
    1129                 nptabij(ip).LE.klon_mpi_end) THEN
     1144
     1145    IF (grid_type==unstructured) THEN
     1146
     1147      CALL xios_send_field(field_name, buffer_omp)
     1148
     1149    ELSE
     1150
     1151      CALL grid1Dto2D_mpi(buffer_omp,Field2d)
     1152   
     1153  !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     1154  !ATTENTION, STATIONS PAS GEREES !
     1155  !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     1156      !IF(.NOT.clef_stations(iff)) THEN
     1157      IF (.TRUE.) THEN
     1158
     1159          CALL xios_send_field(field_name, Field2d)
     1160
     1161      ELSE
     1162          ALLOCATE(fieldok(npstn))
     1163          ALLOCATE(index2d(npstn))
     1164
     1165          IF (is_sequential) THEN
     1166              DO ip=1, npstn
     1167                  fieldok(ip)=buffer_omp(nptabij(ip))
     1168              ENDDO
     1169          ELSE
     1170              DO ip=1, npstn
     1171                  PRINT*,'histwrite2d_xios is_sequential npstn ip namenptabij',npstn,ip,field_name,nptabij(ip)
     1172                  IF(nptabij(ip).GE.klon_mpi_begin.AND. &
     1173                    nptabij(ip).LE.klon_mpi_end) THEN
    11301174                    fieldok(ip)=buffer_omp(nptabij(ip)-klon_mpi_begin+1)
    1131                 ENDIF
    1132             ENDDO
    1133         ENDIF
    1134 
    1135     ENDIF
    1136                  
    1137     deallocate(index2d)
    1138     deallocate(fieldok)
     1175                  ENDIF
     1176              ENDDO
     1177          ENDIF
     1178          DEALLOCATE(index2d)
     1179          DEALLOCATE(fieldok)
     1180
     1181       ENDIF
     1182    ENDIF             
     1183
    11391184!$OMP END MASTER   
    11401185
     
    11501195                                jj_nb, klon_mpi
    11511196  USE xios, only: xios_send_field
    1152   USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
     1197  USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat, grid_type, unstructured
     1198  USE print_control_mod, ONLY: lunout, prt_level
    11531199
    11541200
     
    11731219    CALL Gather_omp(field,buffer_omp)
    11741220!$OMP MASTER
    1175     CALL grid1Dto2D_mpi(buffer_omp,field3d)
    1176 
    1177 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    1178 !ATTENTION, STATIONS PAS GEREES !
    1179 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    1180     !IF (.NOT.clef_stations(iff)) THEN
    1181     IF(.TRUE.)THEN
    1182         ALLOCATE(index3d(nbp_lon*jj_nb*nlev))
    1183         ALLOCATE(fieldok(nbp_lon*jj_nb,nlev))
    1184         CALL xios_send_field(field_name, Field3d(:,:,1:nlev))
     1221
     1222    IF (grid_type==unstructured) THEN
     1223
     1224      CALL xios_send_field(field_name, buffer_omp(:,1:nlev))
     1225
     1226    ELSE
     1227   
     1228      CALL grid1Dto2D_mpi(buffer_omp,field3d)
     1229
     1230  !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     1231  !ATTENTION, STATIONS PAS GEREES !
     1232  !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     1233      !IF (.NOT.clef_stations(iff)) THEN
     1234      IF(.TRUE.)THEN
     1235
     1236          CALL xios_send_field(field_name, Field3d(:,:,1:nlev))
    11851237                       
    1186     ELSE
    1187         nlev=size(field,2)
    1188         ALLOCATE(index3d(npstn*nlev))
    1189         ALLOCATE(fieldok(npstn,nlev))
    1190 
    1191         IF (is_sequential) THEN
    1192             DO n=1, nlev
    1193                 DO ip=1, npstn
    1194                     fieldok(ip,n)=buffer_omp(nptabij(ip),n)
    1195                 ENDDO
    1196             ENDDO
    1197         ELSE
    1198             DO n=1, nlev
    1199                 DO ip=1, npstn
    1200                     IF(nptabij(ip).GE.klon_mpi_begin.AND. &
    1201                     nptabij(ip).LE.klon_mpi_end) THEN
    1202                         fieldok(ip,n)=buffer_omp(nptabij(ip)-klon_mpi_begin+1,n)
    1203                     ENDIF
    1204                 ENDDO
    1205             ENDDO
    1206         ENDIF
     1238      ELSE
     1239          nlev=size(field,2)
     1240          ALLOCATE(index3d(npstn*nlev))
     1241          ALLOCATE(fieldok(npstn,nlev))
     1242
     1243          IF (is_sequential) THEN
     1244              DO n=1, nlev
     1245                  DO ip=1, npstn
     1246                      fieldok(ip,n)=buffer_omp(nptabij(ip),n)
     1247                  ENDDO
     1248              ENDDO
     1249          ELSE
     1250              DO n=1, nlev
     1251                 DO ip=1, npstn
     1252                      IF(nptabij(ip).GE.klon_mpi_begin.AND. &
     1253                       nptabij(ip).LE.klon_mpi_end) THEN
     1254                          fieldok(ip,n)=buffer_omp(nptabij(ip)-klon_mpi_begin+1,n)
     1255                       ENDIF
     1256                  ENDDO
     1257              ENDDO
     1258          ENDIF
     1259          DEALLOCATE(index3d)
     1260          DEALLOCATE(fieldok)
     1261      ENDIF
    12071262    ENDIF
    1208     deallocate(index3d)
    1209     deallocate(fieldok)
     1263
    12101264!$OMP END MASTER   
    12111265
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/phys_cal_mod.F90

    r3835 r3849  
    2929  REAL,SAVE    :: jD_ref  ! jour du demarage de la simulation (jour julien)
    3030!$OMP THREADPRIVATE(jD_ref)
     31 CHARACTER (len=10) :: calend ! type de calendrier
     32!$OMP THREADPRIVATE(calend)
    3133
    3234
     
    3436 
    3537  SUBROUTINE phys_cal_init(annee_ref,day_ref)
    36   USE IOIPSL, ONLY:  ymds2ju
     38  USE IOIPSL, ONLY:  ymds2ju, getin
     39  USE mod_phys_lmdz_para, ONLY:  is_master,bcast
    3740  IMPLICIT NONE
    3841    INTEGER,INTENT(IN) :: annee_ref
    3942    INTEGER,INTENT(IN) :: day_ref
     43
     44    !Config  Key  = calend
     45    !Config  Desc = type de calendrier utilise
     46    !Config  Def  = earth_360d
     47    !Config  Help = valeur possible: earth_360d, earth_365d, earth_366d
     48    !Config         
     49    calend = 'earth_360d'
     50
     51    IF (is_master) CALL getin('calend', calend)
     52    CALL bcast(calend)
    4053
    4154    CALL ymds2ju(annee_ref, 1, day_ref, 0., jD_ref)
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/phys_output_mod.F90

    r3831 r3849  
    3939    USE infotrac_phy
    4040    USE ioipsl
    41     USE phys_cal_mod, only : hour
     41    USE phys_cal_mod, only : hour, calend
    4242    USE mod_phys_lmdz_para
    4343    USE aero_mod, only : naero_spc,name_aero
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/phys_output_write_mod.F90

    r3831 r3849  
    245245    ! ug Pour les sorties XIOS
    246246    USE xios, ONLY: xios_update_calendar
    247     USE wxios, only: wxios_closedef
     247    USE wxios, only: wxios_closedef, wxios_set_context
    248248#endif
    249249    USE phys_cal_mod, only : mth_len
    250250    !USE temps_phy_mod
    251251    USE time_phylmdz_mod, ONLY: start_time, itau_phy
     252    USE print_control_mod, ONLY: lunout, prt_level
    252253
    253254    IMPLICIT NONE
     
    301302       iinitend = 1
    302303    ENDIF
     304
     305#ifdef CPP_XIOS
     306    CALL wxios_set_context
     307#endif
    303308
    304309    ! ug la boucle qui suit ne sert qu'une fois, pour l'initialisation, sinon il n'y a toujours qu'un seul passage:
Note: See TracChangeset for help on using the changeset viewer.