/[lmdze]/trunk/Sources/IOIPSL/histwrite.f
ViewVC logotype

Diff of /trunk/Sources/IOIPSL/histwrite.f

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

trunk/IOIPSL/histwrite.f90 revision 76 by guez, Fri Nov 15 18:45:49 2013 UTC trunk/Sources/IOIPSL/histwrite.f revision 178 by guez, Fri Mar 11 18:47:26 2016 UTC
# Line 2  MODULE histwrite_m Line 2  MODULE histwrite_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      USE errioipsl, ONLY: histerr
6      use histbeg_totreg_m, ONLY: nb_files, date0, deltat
7      USE histcom_var, ONLY: datasz_in, freq_opp, freq_wrt, fuchnbout, last_opp, &
8           last_opp_chk, last_wrt, last_wrt_chk, missing_val, nb_files_max, &
9           nb_var_max, nbopp, scal, scsize, sopps, topp
10      use histvar_seq_m, only: histvar_seq
11      use histwrite_real_m, only: histwrite_real
12      use isittime_m, only: isittime
13      USE mathop_m, ONLY: mathop
14    
15    implicit none    implicit none
16    
17      INTEGER, SAVE:: datasz_max(nb_files_max, nb_var_max) = -1
18    
19    INTERFACE histwrite    INTERFACE histwrite
20       ! The "histwrite" procedures give the data to the input-output system.       ! The "histwrite" procedures give the data to the input-output system.
21       ! They trigger the operations to be performed and the writing to       ! They trigger the operations to be performed and the writing to
# Line 31  MODULE histwrite_m Line 43  MODULE histwrite_m
43       MODULE PROCEDURE histwrite_r1d, histwrite_r2d, histwrite_r3d       MODULE PROCEDURE histwrite_r1d, histwrite_r2d, histwrite_r3d
44    END INTERFACE histwrite    END INTERFACE histwrite
45    
46    PRIVATE histwrite_r1d, histwrite_r2d, histwrite_r3d    PRIVATE
47      public histwrite
48    
49  CONTAINS  CONTAINS
50    
51    SUBROUTINE histwrite_r1d(fileid, varname, itau, pdata)    SUBROUTINE histwrite_r1d(fileid, varname, itau, pdata)
52    
     USE errioipsl, ONLY: histerr  
     use calendar, only: isittime  
     USE mathop_m, ONLY: mathop  
     USE histcom_var, ONLY: datasz_in, datasz_max, date0, deltat, &  
          freq_opp, freq_wrt, fuchnbout, last_opp, last_opp_chk, last_wrt, &  
          last_wrt_chk, missing_val, nbopp, nb_files, scal, scsize, sopps, &  
          topp  
     use histvar_seq_m, only: histvar_seq  
     use histwrite_real_m, only: histwrite_real  
   
53      INTEGER, INTENT(IN):: fileid, itau      INTEGER, INTENT(IN):: fileid, itau
54      CHARACTER(LEN=*), INTENT(IN):: varname      CHARACTER(LEN=*), INTENT(IN):: varname
55      REAL, INTENT(IN):: pdata(:)      REAL, INTENT(IN):: pdata(:)
# Line 157  CONTAINS Line 160  CONTAINS
160         nbpt_out = datasz_max(fileid, varid)         nbpt_out = datasz_max(fileid, varid)
161         CALL mathop(sopps(fileid, varid, 1), nbpt_in, pdata, missing_val, &         CALL mathop(sopps(fileid, varid, 1), nbpt_in, pdata, missing_val, &
162              nbindex, nindex, scal(fileid, varid, 1), nbpt_out, buff_tmp)              nbindex, nindex, scal(fileid, varid, 1), nbpt_out, buff_tmp)
163         CALL histwrite_real(fileid, varid, itau, nbpt_out, buff_tmp, nbindex, &         CALL histwrite_real(datasz_max, fileid, varid, itau, nbpt_out, &
164              nindex, do_oper, do_write)              buff_tmp, nbindex, nindex, do_oper, do_write)
165      ENDIF      ENDIF
166    
167      ! 6.0 Manage time steps      ! 6.0 Manage time steps
# Line 177  CONTAINS Line 180  CONTAINS
180    
181    SUBROUTINE histwrite_r2d (fileid, varname, itau, pdata)    SUBROUTINE histwrite_r2d (fileid, varname, itau, pdata)
182    
     use calendar, only: isittime  
     USE errioipsl, ONLY: histerr  
     USE mathop_m, ONLY: mathop  
     USE histcom_var, ONLY: datasz_in, datasz_max, date0, deltat, &  
          freq_opp, freq_wrt, fuchnbout, last_opp, last_opp_chk, last_wrt, &  
          last_wrt_chk, missing_val, nbopp, nb_files, scal, scsize, sopps, &  
          topp  
     use histvar_seq_m, only: histvar_seq  
     use histwrite_real_m, only: histwrite_real  
   
183      INTEGER, INTENT(IN):: fileid, itau      INTEGER, INTENT(IN):: fileid, itau
184      REAL, INTENT(IN):: pdata(:, :)      REAL, INTENT(IN):: pdata(:, :)
185      CHARACTER(LEN=*), INTENT(IN):: varname      CHARACTER(LEN=*), INTENT(IN):: varname
# Line 300  CONTAINS Line 293  CONTAINS
293         CALL mathop (sopps(fileid, varid, 1), nbpt_in, pdata, &         CALL mathop (sopps(fileid, varid, 1), nbpt_in, pdata, &
294              missing_val, nbindex, nindex, &              missing_val, nbindex, nindex, &
295              scal(fileid, varid, 1), nbpt_out, buff_tmp)              scal(fileid, varid, 1), nbpt_out, buff_tmp)
296         CALL histwrite_real (fileid, varid, itau, nbpt_out, &         CALL histwrite_real (datasz_max, fileid, varid, itau, nbpt_out, &
297              buff_tmp, nbindex, nindex, do_oper, do_write)              buff_tmp, nbindex, nindex, do_oper, do_write)
298      ENDIF      ENDIF
299    
# Line 320  CONTAINS Line 313  CONTAINS
313    
314    SUBROUTINE histwrite_r3d (fileid, varname, itau, pdata)    SUBROUTINE histwrite_r3d (fileid, varname, itau, pdata)
315    
     use calendar, only: isittime  
     USE errioipsl, ONLY: histerr  
     USE mathop_m, ONLY: mathop  
     USE histcom_var, ONLY: datasz_in, datasz_max, date0, deltat, &  
          freq_opp, freq_wrt, fuchnbout, last_opp, last_opp_chk, last_wrt, &  
          last_wrt_chk, missing_val, nbopp, nb_files, scal, scsize, sopps, &  
          topp  
     use histvar_seq_m, only: histvar_seq  
     use histwrite_real_m, only: histwrite_real  
   
316      INTEGER, INTENT(IN):: fileid, itau      INTEGER, INTENT(IN):: fileid, itau
317      REAL, DIMENSION(:, :, :), INTENT(IN):: pdata      REAL, DIMENSION(:, :, :), INTENT(IN):: pdata
318      CHARACTER(LEN=*), INTENT(IN):: varname      CHARACTER(LEN=*), INTENT(IN):: varname
# Line 447  CONTAINS Line 430  CONTAINS
430         CALL mathop (sopps(fileid, varid, 1), nbpt_in, pdata, &         CALL mathop (sopps(fileid, varid, 1), nbpt_in, pdata, &
431              missing_val, nbindex, nindex, &              missing_val, nbindex, nindex, &
432              scal(fileid, varid, 1), nbpt_out, buff_tmp)              scal(fileid, varid, 1), nbpt_out, buff_tmp)
433         CALL histwrite_real (fileid, varid, itau, nbpt_out, &         CALL histwrite_real(datasz_max, fileid, varid, itau, nbpt_out, &
434              buff_tmp, nbindex, nindex, do_oper, do_write)              buff_tmp, nbindex, nindex, do_oper, do_write)
435      ENDIF      ENDIF
436    

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

  ViewVC Help
Powered by ViewVC 1.1.21