/[lmdze]/trunk/IOIPSL/Histcom/histbeg_totreg.f90
ViewVC logotype

Diff of /trunk/IOIPSL/Histcom/histbeg_totreg.f90

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

trunk/Sources/IOIPSL/Histcom/histbeg_totreg.f revision 138 by guez, Fri May 22 23:13:19 2015 UTC trunk/IOIPSL/Histcom/histbeg_totreg.f90 revision 335 by guez, Thu Sep 12 21:22:46 2019 UTC
# Line 14  MODULE histbeg_totreg_m Line 14  MODULE histbeg_totreg_m
14    ! constant are equal. In other words we do not need the full 2D    ! constant are equal. In other words we do not need the full 2D
15    ! matrix to describe the grid, just two vectors.    ! matrix to describe the grid, just two vectors.
16    
17      USE histcom_var, only: nb_files_max
18    
19    IMPLICIT NONE    IMPLICIT NONE
20    
21    INTEGER:: nb_files = 0    INTEGER:: nb_files = 0
22      double precision, SAVE:: date0(nb_files_max)
23      REAL, SAVE:: deltat(nb_files_max)
24      LOGICAL:: regular(nb_files_max) = .TRUE.
25    
26      private nb_files_max
27    
28  CONTAINS  CONTAINS
29    
# Line 30  CONTAINS Line 37  CONTAINS
37      ! setting a zoom. It also gets the global parameters into the      ! setting a zoom. It also gets the global parameters into the
38      ! input-output subsystem.      ! input-output subsystem.
39    
     USE ioipslmpp, ONLY: ioipslmpp_file  
40      USE errioipsl, ONLY: histerr      USE errioipsl, ONLY: histerr
41      USE histcom_var, ONLY: assc_file, date0, deltat, full_size, itau0, &      USE histcom_var, ONLY: assc_file, full_size, itau0, lock_modname, &
42           lock_modname, model_name, nb_files_max, nb_hax, nb_tax, nb_var, &           model_name, nb_hax, nb_tax, nb_var, nb_zax, ncdf_ids, slab_ori, &
43           nb_zax, ncdf_ids, regular, slab_ori, slab_sz, xid, yid, zoom           slab_sz, xid, yid, zoom
44      use histhori_regular_m, only: histhori_regular      use histhori_regular_m, only: histhori_regular
45      USE netcdf, ONLY: nf90_clobber, nf90_global      USE netcdf, ONLY: nf90_clobber, nf90_global
46      use netcdf95, only: nf95_create, nf95_def_dim, nf95_put_att      use netcdf95, only: nf95_create, nf95_def_dim, nf95_put_att
# Line 55  CONTAINS Line 61  CONTAINS
61      INTEGER, INTENT(IN):: szy ! size of the slab of data in Y      INTEGER, INTENT(IN):: szy ! size of the slab of data in Y
62    
63      INTEGER, INTENT(IN):: pitau0 ! time step at which the history tape starts      INTEGER, INTENT(IN):: pitau0 ! time step at which the history tape starts
64      REAL, INTENT(IN):: pdate0 ! the Julian date at which the itau was equal to 0      double precision, INTENT(IN):: pdate0 ! the Julian date at which the itau was equal to 0
65      REAL, INTENT(IN):: pdeltat ! time step of the counter itau, in seconds      REAL, INTENT(IN):: pdeltat ! time step of the counter itau, in seconds
66    
     INTEGER, INTENT(OUT):: fileid ! ID of the netcdf file  
67      INTEGER, INTENT(OUT):: horiid ! ID of the horizontal grid      INTEGER, INTENT(OUT):: horiid ! ID of the horizontal grid
68        INTEGER, INTENT(OUT):: fileid ! ID of the netcdf file
69    
70      ! Variables local to the procedure:      ! Variables local to the procedure:
71      REAL, DIMENSION(size(lon_1d), size(lat_1d)):: lon, lat      REAL, DIMENSION(size(lon_1d), size(lat_1d)):: lon, lat
# Line 109  CONTAINS Line 115  CONTAINS
115         file = filename(:lengf)         file = filename(:lengf)
116      END IF      END IF
117    
     ! Add PE number in file name on MPP  
   
     CALL ioipslmpp_file(file)  
   
118      ! Keep track of the name of the files opened      ! Keep track of the name of the files opened
119    
120      lengf = len_trim(file)      lengf = len_trim(file)

Legend:
Removed from v.138  
changed lines
  Added in v.335

  ViewVC Help
Powered by ViewVC 1.1.21