/[lmdze]/trunk/Sources/IOIPSL/Histcom/histdef.f
ViewVC logotype

Diff of /trunk/Sources/IOIPSL/Histcom/histdef.f

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

trunk/libf/IOIPSL/Histcom/histdef.f90 revision 67 by guez, Tue Oct 2 15:50:56 2012 UTC trunk/Sources/IOIPSL/Histcom/histdef.f revision 178 by guez, Fri Mar 11 18:47:26 2016 UTC
# Line 1  Line 1 
1  module histdef_m  module histdef_m
2    
3      USE histcom_var, ONLY: nb_files_max, nb_var_max
4    
5    implicit none    implicit none
6    
7      INTEGER:: buff_pos = 0
8      INTEGER, SAVE:: point(nb_files_max, nb_var_max)
9      private nb_files_max, nb_var_max
10    
11  contains  contains
12    
13    SUBROUTINE histdef(fileid, varname, ptitle, unit, xsize, ysize, &    SUBROUTINE histdef(fileid, varname, ptitle, unit, xsize, ysize, &
# Line 12  contains Line 18  contains
18      ! operation to be performed on the variable, the frequency of      ! operation to be performed on the variable, the frequency of
19      ! this operation and the frequency of the archiving.      ! this operation and the frequency of the archiving.
20    
21        USE buildop_m, ONLY: buildop
22      USE errioipsl, ONLY: histerr      USE errioipsl, ONLY: histerr
23      USE find_str_m, ONLY: find_str      USE find_str_m, ONLY: find_str
24      USE histcom_var, ONLY: buff_pos, deltat, freq_opp, freq_wrt, fullop, &      use histbeg_totreg_m, only: deltat
25           full_size, itau0, last_opp, last_opp_chk, last_wrt, last_wrt_chk, &      USE histcom_var, ONLY: freq_opp, freq_wrt, fullop, full_size, itau0, &
26           missing_val, name, name_length, nbopp, nbopp_max, nb_hax, nb_opp, &           last_opp, last_opp_chk, last_wrt, last_wrt_chk, missing_val, name, &
27           nb_tax, nb_var, nb_var_max, nb_wrt, nb_zax, point, scal, scsize, &           name_length, nbopp, nbopp_max, nb_hax, nb_opp, nb_tax, nb_var, &
28           slab_ori, slab_sz, sopps, tax_last, tax_name, tax_name_length, &           nb_wrt, nb_zax, scal, scsize, slab_ori, slab_sz, sopps, &
29           title, topp, unit_name, var_axid, var_haxid, var_zaxid, zax_name, &           tax_last, tax_name, tax_name_length, title, topp, unit_name, &
30           zax_size, zorig, zsize           var_axid, var_haxid, var_zaxid, zax_name, zax_size, zorig, zsize
31      USE ioget_calendar_m, ONLY: ioget_calendar      USE ioget_calendar_m, ONLY: ioget_calendar_real
     USE mathelp, ONLY: buildop  
32    
33      INTEGER, INTENT(IN):: fileid      INTEGER, INTENT(IN):: fileid
34      ! (ID of the file the variable should be archived in)      ! (ID of the file the variable should be archived in)
# Line 206  contains Line 212  contains
212    
213         IF (szz/=zax_size(fileid, zid)) THEN         IF (szz/=zax_size(fileid, zid)) THEN
214            str20 = zax_name(fileid, zid)            str20 = zax_name(fileid, zid)
           str70 = 'The size of the zoom does not correspond ' // &  
                'to the size of the chosen vertical axis'  
215            WRITE (str71, '("Size of zoom in z:", I4)') szz            WRITE (str71, '("Size of zoom in z:", I4)') szz
216            WRITE (str72, '("Size declared for axis ", a, ":", I4)') &            WRITE (str72, '("Size declared for axis ", a, ":", I4)') &
217                 trim(str20), zax_size(fileid, zid)                 trim(str20), zax_size(fileid, zid)
218            CALL histerr(3, 'histdef', str70, str71, str72)            CALL histerr(3, 'histdef', 'The size of the zoom does not ' &
219                   // 'correspond to the size of the chosen vertical axis', &
220                   str71, str72)
221         END IF         END IF
222    
223         ! Is the zoom smaler that the total size of the variable ?         ! Is the zoom smaler that the total size of the variable ?
# Line 255  contains Line 261  contains
261      freq_opp(fileid, iv) = pfreq_opp      freq_opp(fileid, iv) = pfreq_opp
262      freq_wrt(fileid, iv) = pfreq_wrt      freq_wrt(fileid, iv) = pfreq_wrt
263    
264      CALL ioget_calendar(un_an, un_jour)      CALL ioget_calendar_real(un_an, un_jour)
265      IF (pfreq_opp<0) THEN      IF (pfreq_opp<0) THEN
266         CALL ioget_calendar(un_an)         CALL ioget_calendar_real(un_an)
267         test_fopp = pfreq_opp*(-1.)*un_an/12.*un_jour         test_fopp = pfreq_opp*(-1.)*un_an/12.*un_jour
268      ELSE      ELSE
269         test_fopp = pfreq_opp         test_fopp = pfreq_opp
270      END IF      END IF
271      IF (pfreq_wrt<0) THEN      IF (pfreq_wrt<0) THEN
272         CALL ioget_calendar(un_an)         CALL ioget_calendar_real(un_an)
273         test_fwrt = pfreq_wrt*(-1.)*un_an/12.*un_jour         test_fwrt = pfreq_wrt*(-1.)*un_an/12.*un_jour
274      ELSE      ELSE
275         test_fwrt = pfreq_wrt         test_fwrt = pfreq_wrt

Legend:
Removed from v.67  
changed lines
  Added in v.178

  ViewVC Help
Powered by ViewVC 1.1.21