/[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/libf/IOIPSL/Histcom/histbeg_totreg.f90 revision 61 by guez, Fri Apr 20 14:58:43 2012 UTC trunk/IOIPSL/Histcom/histbeg_totreg.f90 revision 335 by guez, Thu Sep 12 21:22:46 2019 UTC
# Line 2  MODULE histbeg_totreg_m Line 2  MODULE histbeg_totreg_m
2    
3    ! From histcom.f90, version 2.1 2004/04/21 09:27:10    ! From histcom.f90, version 2.1 2004/04/21 09:27:10
4    
5    ! Some confusing vocabulary in this code !    ! Some confusing vocabulary in this code!
6    
7    ! A REGULAR grid is a grid which is i, j indices    ! A regular grid is a grid with i, j indices and thus it is
8    ! and thus it is stored in a 2D matrix.    ! stored in a 2D matrix. This is opposed to an irregular grid which
9    ! This is opposed to an IRREGULAR grid which is only in a vector    ! is in a vector and where we do not know which neighbours we
10    ! and where we do not know which neighbors we have.    ! have. As a consequence we need the bounds for each grid-cell.
11    ! As a consequence we need the bounds for each grid-cell.  
12      ! A rectilinear grid is a special case of a regular grid in which
13    ! A RECTILINEAR grid is a special case of a regular grid    ! all longitudes for i constant are equal and all latitudes for j
14    ! in which all longitudes for i constant are equal    ! constant are equal. In other words we do not need the full 2D
15    ! and all latitudes for j constant.    ! matrix to describe the grid, just two vectors.
   ! In other words we do not need the full 2D matrix  
   ! to describe the grid, just two vectors.  
16    
17    IMPLICIT NONE    USE histcom_var, only: nb_files_max
18    
19  CONTAINS    IMPLICIT NONE
20    
21    SUBROUTINE histbeg_totreg(pfilename, plon_1d, plat_1d, par_orix, par_szx, &    INTEGER:: nb_files = 0
22         par_oriy, par_szy, pitau0, pdate0, pdeltat, phoriid, pfileid)    double precision, SAVE:: date0(nb_files_max)
23      REAL, SAVE:: deltat(nb_files_max)
24      LOGICAL:: regular(nb_files_max) = .TRUE.
25    
26      ! The user provides "plon_1d" and "plat_1d" as vectors. Obviously    private nb_files_max
     ! this can only be used for very regular grids.  
     ! This subroutine initializes a netcdf file and returns the ID.  
     ! It will set up the geographical space on which the data will be  
     ! stored and offers the possibility of seting a zoom.  
     ! It also gets the global parameters into the I/O subsystem.  
   
     ! INPUT  
   
     ! pfilename: Name of the netcdf file to be created  
     ! pim: Size of arrays in longitude direction  
     ! plon_1d: Coordinates of points in longitude  
     ! pjm: Size of arrays in latitude direction  
     ! plat_1d: Coordinates of points in latitude  
   
     ! The next 4 arguments allow to define a horizontal zoom  
     ! for this file. It is assumed that all variables to come  
     ! have the same index space. This can not be assumed for  
     ! the z axis and thus we define the zoom in histdef.  
   
     ! par_orix: Origin of the slab of data within the X axis (pim)  
     ! par_szx: Size of the slab of data in X  
     ! par_oriy: Origin of the slab of data within the Y axis (pjm)  
     ! par_szy: Size of the slab of data in Y  
   
     ! pitau0: time step at which the history tape starts  
     ! pdate0: The Julian date at which the itau was equal to 0  
     ! pdeltat: Time step in seconds. Time step of the counter itau  
     !             used in histwrt for instance  
27    
28      ! OUTPUT  CONTAINS
29    
30      ! phoriid: ID of the horizontal grid    SUBROUTINE histbeg_totreg(filename, lon_1d, lat_1d, orix, szx, oriy, szy, &
31      ! pfileid: ID of the netcdf file         pitau0, pdate0, pdeltat, horiid, fileid)
32    
33      ! We assume the grid is rectilinear.      ! We assume the grid is rectilinear. The user provides "lon_1d"
34        ! and "lat_1d" as vectors. This subroutine initializes a NetCDF
35        ! file and returns the ID. It sets up the geographical space on
36        ! which the data will be stored and offers the possibility of
37        ! setting a zoom. It also gets the global parameters into the
38        ! 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, nb_files_max, nb_hax, nb_tax, &           model_name, nb_hax, nb_tax, nb_var, nb_zax, ncdf_ids, slab_ori, &
43           nb_var, 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_create, nf90_def_dim, &      USE netcdf, ONLY: nf90_clobber, nf90_global
46           nf90_global, nf90_put_att      use netcdf95, only: nf95_create, nf95_def_dim, nf95_put_att
47    
48        CHARACTER(len=*), INTENT(IN):: filename
49        ! name of the netcdf file to be created
50    
51        REAL, INTENT(IN):: lon_1d(:) ! coordinates of points in longitude
52        REAL, INTENT(IN):: lat_1d(:) ! coordinates of points in latitude
53    
54        ! The next 4 arguments allow to define a horizontal zoom for this
55        ! file. It is assumed that all variables to come have the same
56        ! index space. This can not be assumed for the z axis and thus we
57        ! define the zoom in histdef.
58        INTEGER, INTENT(IN):: orix ! origin of the slab of data within the X axis
59        INTEGER, INTENT(IN):: szx ! size of the slab of data in X
60        INTEGER, INTENT(IN):: oriy ! origin of the slab of data within the Y axis
61        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
64        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
66    
67      CHARACTER (len=*), INTENT (IN):: pfilename      INTEGER, INTENT(OUT):: horiid ! ID of the horizontal grid
68      REAL, DIMENSION (:), INTENT (IN):: plon_1d      INTEGER, INTENT(OUT):: fileid ! ID of the netcdf file
     REAL, DIMENSION (:), INTENT (IN):: plat_1d  
     INTEGER, INTENT (IN):: par_orix, par_szx, par_oriy, par_szy  
     INTEGER, INTENT (IN):: pitau0  
     REAL, INTENT (IN):: pdate0, pdeltat  
     INTEGER, INTENT (OUT):: pfileid, phoriid  
69    
70      ! Variables local to the procedure:      ! Variables local to the procedure:
71      REAL, DIMENSION (size(plon_1d), size(plat_1d)):: plon, plat      REAL, DIMENSION(size(lon_1d), size(lat_1d)):: lon, lat
72      INTEGER:: pim, pjm      INTEGER im ! size of arrays in longitude direction
73      INTEGER:: ncid, iret      integer jm ! size of arrays in latitude direction
74      INTEGER:: lengf, lenga      INTEGER ncid
75      CHARACTER (len=120):: file, tfile      INTEGER lengf, lenga
76        CHARACTER(len=120) file
77    
78      !---------------------------------------------------------------------      !---------------------------------------------------------------------
79    
80      pim = size(plon_1d)      im = size(lon_1d)
81      pjm = size(plat_1d)      jm = size(lat_1d)
82    
83      plon = spread(plon_1d, 2, pjm)      lon = spread(lon_1d, 2, jm)
84      plat = spread(plat_1d, 1, pim)      lat = spread(lat_1d, 1, im)
85    
86      nb_files = nb_files + 1      nb_files = nb_files + 1
87      pfileid = nb_files      fileid = nb_files
88    
89      ! 1.0 Transfering into the common for future use      ! 1. Transfer into module variables for future use
90    
91      itau0(pfileid) = pitau0      itau0(fileid) = pitau0
92      date0(pfileid) = pdate0      date0(fileid) = pdate0
93      deltat(pfileid) = pdeltat      deltat(fileid) = pdeltat
94    
95      ! 2.0 Initializes all variables for this file      ! 2. Initialize all variables for this file
96    
97      IF (nb_files>nb_files_max) THEN      IF (nb_files > nb_files_max) CALL histerr(3, 'histbeg', &
98         CALL histerr(3, 'histbeg', &           'Table of files too small. You should increase nb_files_max', &
99              'Table of files too small. You should increase nb_files_max', &           'in M_HISTCOM.f90 in order to accomodate all these files', ' ')
             'in M_HISTCOM.f90 in order to accomodate all these files', ' ')  
     END IF  
100    
101      nb_var(pfileid) = 0      nb_var(fileid) = 0
102      nb_tax(pfileid) = 0      nb_tax(fileid) = 0
103      nb_hax(pfileid) = 0      nb_hax(fileid) = 0
104      nb_zax(pfileid) = 0      nb_zax(fileid) = 0
   
     slab_ori(pfileid, 1:2) = (/ par_orix, par_oriy/)  
     slab_sz(pfileid, 1:2) = (/ par_szx, par_szy/)  
   
     ! 3.0 Opening netcdf file and defining dimensions  
   
     tfile = pfilename  
     lengf = len_trim(tfile)  
     IF (tfile(lengf-2:lengf)/='.nc') THEN  
        file = tfile(1:lengf) // '.nc'  
     ELSE  
        file = tfile(1:lengf)  
     END IF  
105    
106      ! Add PE number in file name on MPP      slab_ori(fileid, :) = (/orix, oriy/)
107        slab_sz(fileid, :) = (/szx, szy/)
108    
109      CALL ioipslmpp_file(file)      ! 3. Open NetCDF file and define dimensions
110    
111        lengf = len_trim(filename)
112        IF (filename(lengf-2:lengf)/='.nc') THEN
113           file = filename(:lengf) // '.nc'
114        ELSE
115           file = filename(:lengf)
116        END IF
117    
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)
121      lenga = len_trim(assc_file)      lenga = len_trim(assc_file)
122      IF (nb_files==1) THEN      IF (nb_files==1) THEN
123         assc_file = file(1:lengf)         assc_file = file(:lengf)
124      ELSE IF ((lenga+lengf)<500) THEN      ELSE IF ((lenga+lengf)<500) THEN
125         assc_file = assc_file(1:lenga) // ' ' // file(1:lengf)         assc_file = assc_file(:lenga) // ' ' // file(:lengf)
126      ELSE IF (((lenga+7)<500) .AND. (index(assc_file(1:lenga), &      ELSE IF (lenga + 7 < 500 .AND. index(assc_file(:lenga), 'et.al.') < 1) THEN
127           'et.al.')<1)) THEN         assc_file = assc_file(:lenga) // ' et.al.'
        assc_file = assc_file(1:lenga) // ' et.al.'  
128      ELSE      ELSE
129         CALL histerr(2, 'histbeg', &         CALL histerr(2, 'histbeg', &
130              'The file names do not fit into the associate_file attribute.', &              'The file names do not fit into the associate_file attribute.', &
131              'Use shorter names if you wish to keep the information.', ' ')              'Use shorter names if you wish to keep the information.', ' ')
132      END IF      END IF
133    
134      iret = nf90_create(file, nf90_clobber, ncid)      call nf95_create(file, nf90_clobber, ncid)
135      iret = nf90_def_dim(ncid, 'lon', par_szx, xid(nb_files))      call nf95_def_dim(ncid, 'lon', szx, xid(nb_files))
136      iret = nf90_def_dim(ncid, 'lat', par_szy, yid(nb_files))      call nf95_def_dim(ncid, 'lat', szy, yid(nb_files))
137    
138      ! 4.0 Declaring the geographical coordinates and other attributes      ! 4. Declare the geographical coordinates and other attributes
139    
140      ! 4.3 Global attributes      ! 4.3 Global attributes
141    
142      iret = nf90_put_att(ncid, nf90_global, 'Conventions', 'GDT 1.3')      call nf95_put_att(ncid, nf90_global, 'Conventions', 'GDT 1.3')
143      iret = nf90_put_att(ncid, nf90_global, 'file_name', trim(file))      call nf95_put_att(ncid, nf90_global, 'file_name', trim(file))
144      iret = nf90_put_att(ncid, nf90_global, 'production', trim(model_name))      call nf95_put_att(ncid, nf90_global, 'production', trim(model_name))
145      lock_modname = .TRUE.      lock_modname = .TRUE.
146    
147      ! 5.0 Saving some important information on this file in the common      ! 5. Save some important information on this file in the module variables
148        ncdf_ids(fileid) = ncid
149      ncdf_ids(pfileid) = ncid      full_size(fileid, :) = (/im, jm/)
     full_size(pfileid, 1:2) = (/ pim, pjm/)  
150    
151      ! 6.0 storing the geographical coordinates      ! 6. Store the geographical coordinates
152    
153      IF ((pim/=par_szx) .OR. (pjm/=par_szy)) zoom(pfileid) = .TRUE.      IF ((im /= szx) .OR. (jm /= szy)) zoom(fileid) = .TRUE.
154      regular(pfileid) = .TRUE.      regular(fileid) = .TRUE.
155    
156      CALL histhori_regular(pfileid, pim, plon, pjm, plat, ' ', 'Default grid', &      CALL histhori_regular(fileid, im, lon, jm, lat, ' ', 'Default grid', horiid)
          phoriid)  
157    
158    END SUBROUTINE histbeg_totreg    END SUBROUTINE histbeg_totreg
159    

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

  ViewVC Help
Powered by ViewVC 1.1.21