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

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

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

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

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

  ViewVC Help
Powered by ViewVC 1.1.21