source: trunk/LMDZ.COMMON/libf/dyn3dpar/relaxetat0.F @ 1243

Last change on this file since 1243 was 1024, checked in by aslmd, 11 years ago

LMDZ.COMMON. Added the posssibility for 3D runs without dynamics (precompiling flag NODYN). Added simple nudging (zonal wind for Saturn, but easy to extend). updated arch files for gnome with -auto. LMDZ.UNIVERSAL. Updated READMEs and latest def files (NB: saturn_tropostrato_128x96x64 and saturn_tropostrato_256x192x64 still experimental).

File size: 1.7 KB
Line 
1      SUBROUTINE relaxetat0(fichnom)
2
3      use netcdf, only: nf90_get_var
4      use comuforc_h
5      use ioipsl_getincom
6
7      IMPLICIT NONE
8
9!=======================================================================
10! Author: A. Spiga
11! Purpose: Read a simple relaxation field
12!=======================================================================
13
14#include "dimensions.h"
15#include "paramet.h"
16#include "netcdf.inc"
17#include "iniprint.h"
18
19! INPUTS
20      CHARACTER*(*) fichnom
21
22! VARIABLES
23      REAL ucov(iip1, jjp1,llm)
24      INTEGER ierr, nid, nvarid
25      INTEGER i,j,l,ij
26
27      !! OPEN NETCDF FILE
28      ierr = NF_OPEN (fichnom, NF_NOWRITE,nid)
29      IF (ierr.NE.NF_NOERR) THEN
30        write(lunout,*)'relaxetat0: Pb d''ouverture du fichier'
31        write(lunout,*)' ierr = ', ierr
32        CALL ABORT
33      ENDIF
34
35      !! ALLOCATE RELAXATION FIELD
36      IF (.NOT.ALLOCATED(uforc)) ALLOCATE(uforc(ip1jmp1,llm))
37
38      !! READ RELAXATION FIELD
39      ierr = NF_INQ_VARID (nid, "ucov", nvarid)
40      IF (ierr .NE. NF_NOERR) THEN
41         write(lunout,*)"dynetat0: Le champ <ucov> est absent"
42         CALL abort
43      ENDIF
44      ierr = nf90_get_var(nid, nvarid, ucov)
45      IF (ierr .NE. NF_NOERR) THEN
46         write(lunout,*)"dynetat0: Lecture echouee pour <ucov>"
47         CALL abort
48      ENDIF
49
50      !! TRANSFER TO SHARED VARIABLE IN comuforc_h MODULE
51      !! TBD --> check the relaxation field's dimensions are OK!
52      do l=1,llm
53        do j=1,jjp1
54           do i=1,iip1
55              ij=(j-1)*iip1+i
56              uforc(ij,l)=ucov(i,j,l)
57           enddo
58        enddo
59      enddo
60
61      !! READ THE RELAXATION RATE IN SETTINGS
62      facwind = 1000.
63      CALL getin('facwind',facwind)
64
65      !! END
66      ierr = NF_CLOSE(nid)
67      RETURN
68      END
Note: See TracBrowser for help on using the repository browser.