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

Last change on this file since 1047 was 1047, checked in by emillour, 11 years ago

Mars GCM:

  • IMPORTANT CHANGE: Removed all reference/use of ngridmx (dimphys.h) in routines (necessary prerequisite to using parallel dynamics); in most cases this just means adding 'ngrid' as routine argument, and making local saved variables allocatable (and allocated at first call). In the process, had to convert many *.h files to equivalent modules: yomaer.h => yomaer_h.F90 , surfdat.h => surfdat_h.F90 , comsaison.h => comsaison_h.F90 , yomlw.h => yomlw_h.F90 , comdiurn.h => comdiurn_h.F90 , dimradmars.h => dimradmars_mod.F90 , comgeomfi.h => comgeomfi_h.F90, comsoil.h => comsoil_h.F90 , slope.h => slope_mod.F90
  • Also updated EOF routines, everything is now in eofdump_mod.F90
  • Removed unused routine lectfux.F (in dyn3d)

EM

File size: 3.5 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!#include "dimphys.h"
25!
26
27      integer,intent(in) :: ngrid ! total number of physics grid points
28      integer,intent(in) :: nlayer ! number of atmospheric layers
29      real*4 u(ngrid,nlayer)
30      real*4 v(ngrid,nlayer)
31      real*4 t(ngrid,nlayer)
32      real*4 rho(ngrid,nlayer)
33      real*4 ps(ngrid)
34      integer,save :: count=0
35      integer i,j,l, ig
36
37      LOGICAL,SAVE :: firstcall=.true.
38
39!-------------------------------------------------------
40!     Initialization at first call:
41!     ~~~~~~~~~~~~~~~~~~~~~~~~~~~~
42      IF (firstcall) THEN
43        write(*,*) 'CALL ineofdump'
44        CALL ineofdump(ngrid,nlayer)
45        firstcall=.false.
46      END IF
47
48!-------------------------------------------------------
49!     Dumps every ieofs physics timesteps
50!
51!      write(*,*)'eofdump:count=',count,' ps(1)=',ps(1)
52!      if ((ieofs.gt.0).and.(mod(count,ieofs).eq.0)) then
53      if (mod(count+1,ieofs).eq.0) then
54!        write(*,*)'eofdump: dump --> ps(1)=',ps(1)
55        do i=1,iim,eofskip
56          do j=1+eofskip/2,jjm+1,eofskip
57            ig = 1+ (j-2)*iim +i
58            write(uedata) (u(ig,l),l=1,nlayer)
59            write(uedata) (v(ig,l),l=1,nlayer)
60            write(uedata) (t(ig,l),l=1,nlayer)
61            write(uedata) (rho(ig,l),l=1,nlayer)
62            write(uedata) ps(ig)
63          enddo
64        enddo
65      endif
66      count=count+1
67 
68      end subroutine eofdump
69
70
71      subroutine ineofdump(ngrid,nlayer)
72
73      use comgeomfi_h, only: long, lati
74      implicit none
75!
76!     Initialise dumping of profiles for EOF calculations
77!
78#include "dimensions.h"
79!#include "dimphys.h"
80#include "comvert.h"
81#include "comcstfi.h"
82!#include "comgeomfi.h"
83
84      integer,intent(in) :: ngrid ! total number of physics grid points
85      integer,intent(in) :: nlayer ! number of atmospheric layers
86      integer ig,i,j,l   
87      logical,save :: firstcall=.true.
88      integer,save :: npgrid
89
90
91      if (firstcall) then
92         npgrid=ngrid+2*(iim-1)
93         firstcall=.false.
94      endif
95
96!
97!     Set frequency for dumping at once per day
98!
99      ieofs=nint(daysec/dtphys)
100      if (abs(float(ieofs)-daysec/dtphys).gt.1.e-8*daysec) &
101         stop'In ineofdump:  1 day .ne. n physics timesteps'
102!
103!     Header
104!
105      open(uehead,file='profiles.hdr',form='formatted')
106      write(uehead,*) 0.E+0,0,0,ieofs,1,0
107      write(uehead,*) iim,npgrid/iim,npgrid,nlayer
108
109      do i=1,iim,eofskip
110        do j=1+eofskip/2,jjm+1,eofskip   
111          ig = 1+ (j-2)*iim +i
112          if(j.eq.1) stop 'Problem in ineofdump.F'
113          if(j.eq.jjm+1) stop 'Problem in ineofdump.F'
114          write(uehead,*) long(ig)*180./pi, lati(ig)*180./pi
115!         write(*,*) 'eof grid j=',j,' lat= ', lati(ig)*180./pi
116        enddo
117      enddo
118
119      write(uehead,*) aps
120      write(uehead,*) bps
121      close(uehead)
122!
123!     Main profile file
124!
125      open(uedata,file='profiles.dat',form='unformatted')
126      end subroutine ineofdump
127
128end module eofdump_mod
Note: See TracBrowser for help on using the repository browser.