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

Last change on this file since 1422 was 1422, checked in by milmd, 10 years ago

In GENERIC, MARS and COMMON models replace some include files by modules (usefull for decoupling physics with dynamics).

File size: 4.0 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
82      USE comvert_mod, ONLY: aps,bps
83      implicit none
84!
85!     Initialise dumping of profiles for EOF calculations
86!
87#include "dimensions.h"
88
89      integer,intent(in) :: ngrid ! total number of physics grid points
90      integer,intent(in) :: nlayer ! number of atmospheric layers
91      integer ig,i,j,l   
92      logical,save :: firstcall=.true.
93      integer,save :: npgrid
94
95
96      if (firstcall) then
97         npgrid=ngrid+2*(iim-1)
98         firstcall=.false.
99      endif
100
101!
102!     Set frequency for dumping at once per day
103!
104      ieofs=nint(daysec/dtphys)
105      if (abs(float(ieofs)-daysec/dtphys).gt.1.e-8*daysec) &
106         stop'In ineofdump:  1 day .ne. n physics timesteps'
107!
108!     Header
109!
110      open(uehead,file='profiles.hdr',form='formatted')
111      write(uehead,*) 0.E+0,0,0,ieofs,1,0
112      write(uehead,*) iim,npgrid/iim,npgrid,nlayer
113
114      do i=1,iim,eofskip
115        do j=1+eofskip/2,jjm+1,eofskip   
116          ig = 1+ (j-2)*iim +i
117          if(j.eq.1) stop 'Problem in ineofdump.F'
118          if(j.eq.jjm+1) stop 'Problem in ineofdump.F'
119#ifdef NC_DOUBLE
120          write(uehead,*) real(long(ig)*180./pi),real(lati(ig)*180./pi)
121#else
122          write(uehead,*) long(ig)*180./pi, lati(ig)*180./pi
123#endif
124!         write(*,*) 'eof grid j=',j,' lat= ', lati(ig)*180./pi
125        enddo
126      enddo
127
128#ifdef NC_DOUBLE
129      write(uehead,*) real(aps)
130      write(uehead,*) real(bps)
131#else
132      write(uehead,*) aps
133      write(uehead,*) bps
134#endif
135      close(uehead)
136!
137!     Main profile file
138!
139      open(uedata,file='profiles.dat',form='unformatted')
140      end subroutine ineofdump
141
142end module eofdump_mod
Note: See TracBrowser for help on using the repository browser.