source: trunk/LMDZ.MARS/libf/phymars/eofdump_mod.F90 @ 1524

Last change on this file since 1524 was 1524, checked in by emillour, 9 years ago

All GCMS:
More updates to enforce dynamics/physics separation:

get rid of references to "temps_mod" from physics packages;
make a "time_phylmdz_mod.F90" module to store that
information and fill it via "iniphysiq".

EM

File size: 4.1 KB
Line 
1module eofdump_mod
2! this module controls the production of data for EOFs
3implicit none
4! Dump profiles for EOFs every ieofs physics timesteps,
5! starting at first call;
6integer :: ieofs
7! Dump profiles every eofskip points in each direction
8! on the model grid.
9integer, parameter :: eofskip = 4
10! Units for writing EOF header and data:
11integer, parameter :: uehead = 82, uedata = 83
12
13contains
14
15      subroutine eofdump(ngrid,nlayer,u,v,t,rho,ps)
16
17      implicit none
18!
19!     Dumps profiles for calculation of variability EOFs
20!     Modified to include rho, FF 09/2004
21!     Corrected small bug in sampling rate/count, EM 11/2007
22!
23#include "dimensions.h"
24!
25
26      integer,intent(in) :: ngrid ! total number of physics grid points
27      integer,intent(in) :: nlayer ! number of atmospheric layers
28      real,intent(in) :: u(ngrid,nlayer)
29      real,intent(in) :: v(ngrid,nlayer)
30      real,intent(in) :: t(ngrid,nlayer)
31      real,intent(in) :: rho(ngrid,nlayer)
32      real,intent(in) :: ps(ngrid)
33      integer,save :: count=0
34      integer i,j,l, ig
35
36      LOGICAL,SAVE :: firstcall=.true.
37
38!-------------------------------------------------------
39!     Initialization at first call:
40!     ~~~~~~~~~~~~~~~~~~~~~~~~~~~~
41      IF (firstcall) THEN
42        write(*,*) 'CALL ineofdump'
43        CALL ineofdump(ngrid,nlayer)
44        firstcall=.false.
45      END IF
46
47!-------------------------------------------------------
48!     Dumps every ieofs physics timesteps
49!
50!      write(*,*)'eofdump:count=',count,' ps(1)=',ps(1)
51!      if ((ieofs.gt.0).and.(mod(count,ieofs).eq.0)) then
52      if (mod(count+1,ieofs).eq.0) then
53!        write(*,*)'eofdump: dump --> ps(1)=',ps(1)
54        do i=1,iim,eofskip
55          do j=1+eofskip/2,jjm+1,eofskip
56            ig = 1+ (j-2)*iim +i
57#ifdef NC_DOUBLE
58            write(uedata) (real(u(ig,l)),l=1,nlayer)
59            write(uedata) (real(v(ig,l)),l=1,nlayer)
60            write(uedata) (real(t(ig,l)),l=1,nlayer)
61            write(uedata) (real(rho(ig,l)),l=1,nlayer)
62            write(uedata) real(ps(ig))
63#else
64            write(uedata) (u(ig,l),l=1,nlayer)
65            write(uedata) (v(ig,l),l=1,nlayer)
66            write(uedata) (t(ig,l),l=1,nlayer)
67            write(uedata) (rho(ig,l),l=1,nlayer)
68            write(uedata) ps(ig)
69#endif
70          enddo
71        enddo
72      endif
73      count=count+1
74 
75      end subroutine eofdump
76
77
78      subroutine ineofdump(ngrid,nlayer)
79
80      use comgeomfi_h, only: long, lati
81      use comcstfi_h, only: pi
82      use time_phylmdz_mod, only: daysec, dtphys
83      USE comvert_mod, ONLY: aps,bps
84      implicit none
85!
86!     Initialise dumping of profiles for EOF calculations
87!
88#include "dimensions.h"
89
90      integer,intent(in) :: ngrid ! total number of physics grid points
91      integer,intent(in) :: nlayer ! number of atmospheric layers
92      integer ig,i,j,l   
93      logical,save :: firstcall=.true.
94      integer,save :: npgrid
95
96
97      if (firstcall) then
98         npgrid=ngrid+2*(iim-1)
99         firstcall=.false.
100      endif
101
102!
103!     Set frequency for dumping at once per day
104!
105      ieofs=nint(daysec/dtphys)
106      if (abs(float(ieofs)-daysec/dtphys).gt.1.e-8*daysec) &
107         stop'In ineofdump:  1 day .ne. n physics timesteps'
108!
109!     Header
110!
111      open(uehead,file='profiles.hdr',form='formatted')
112      write(uehead,*) 0.E+0,0,0,ieofs,1,0
113      write(uehead,*) iim,npgrid/iim,npgrid,nlayer
114
115      do i=1,iim,eofskip
116        do j=1+eofskip/2,jjm+1,eofskip   
117          ig = 1+ (j-2)*iim +i
118          if(j.eq.1) stop 'Problem in ineofdump.F'
119          if(j.eq.jjm+1) stop 'Problem in ineofdump.F'
120#ifdef NC_DOUBLE
121          write(uehead,*) real(long(ig)*180./pi),real(lati(ig)*180./pi)
122#else
123          write(uehead,*) long(ig)*180./pi, lati(ig)*180./pi
124#endif
125!         write(*,*) 'eof grid j=',j,' lat= ', lati(ig)*180./pi
126        enddo
127      enddo
128
129#ifdef NC_DOUBLE
130      write(uehead,*) real(aps)
131      write(uehead,*) real(bps)
132#else
133      write(uehead,*) aps
134      write(uehead,*) bps
135#endif
136      close(uehead)
137!
138!     Main profile file
139!
140      open(uedata,file='profiles.dat',form='unformatted')
141      end subroutine ineofdump
142
143end module eofdump_mod
Note: See TracBrowser for help on using the repository browser.