New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
flx_forced_daily.h90 in trunk/NEMO/OPA_SRC/SBC – NEMO

source: trunk/NEMO/OPA_SRC/SBC/flx_forced_daily.h90 @ 699

Last change on this file since 699 was 699, checked in by smasson, 17 years ago

insert revision Id

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 4.6 KB
Line 
1   !!----------------------------------------------------------------------
2   !!                    ***  flx_forced_daily  ***
3   !!----------------------------------------------------------------------
4
5   !!----------------------------------------------------------------------
6   !!   flx          : define the thermohaline fluxes for the ocean
7   !!                  in forced mode using flux formulation (not bulk)
8   !!                  (read in NetCDF file)
9   !!----------------------------------------------------------------------
10   !! * Modules used     C A U T I O N  already defined in flxmod.F90
11
12   !! * Module variables
13   INTEGER ::          &
14      numflx,          &  ! logical unit for surface fluxes data
15      ndayflx             ! new day for ecmwf flx forcing
16   REAL(wp), DIMENSION(jpi,jpj,3) ::   &
17      flxdta              ! 3 consecutive daily fluxes
18   !!----------------------------------------------------------------------
19   !!   OPA 9.0 , LOCEAN-IPSL (2005)
20   !! $Id$
21   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
22   !!----------------------------------------------------------------------
23
24CONTAINS
25
26   SUBROUTINE flx( kt )
27      !!---------------------------------------------------------------------
28      !!                    ***  ROUTINE flx  ***
29      !!                   
30      !! ** Purpose :   provide the thermohaline fluxes (heat and freshwater)
31      !!      to the ocean at each time step.
32      !!
33      !! ** Method  :   READ daily flux file in NetCDF files
34      !!      the net downward radiative flux qsr      1 (watt/m2)
35      !!      the net downward heat flux      q        2 (watt/m2)
36      !!      the net upward water            emp      3 (kg/m2/s)
37      !!      (evaporation - precipitation)
38      !!
39      !! History :
40      !!        !  90-03  (O. Marti and P. Dandin)  Original code
41      !!        !  92-07  (M. Imbard)
42      !!        !  96-11  (E. Guilyardi)  Daily AGCM input files
43      !!        !  99-11  (M. Imbard)  NetCDF FORMAT with io-ipsl
44      !!        !  00-10  (J.-P. Boulanger)  adjusted for reading any
45      !!                         daily wind stress data including a climatology
46      !!        !  01-09  (A. Lazar and C. Levy)  config with no ice model
47      !!   8.5  !  03-07  (G. Madec)  F90: Free form and module
48      !!----------------------------------------------------------------------
49      !! * Modules used
50      USE iom
51      USE flx_oce
52
53      !! * arguments
54      INTEGER, INTENT( in  ) ::   kt ! ocean time step
55
56      !!---------------------------------------------------------------------
57
58
59      ! First call kt=nit000
60      ! --------------------
61
62      IF( kt == nit000 ) THEN
63         
64         ndayflx = 0   ! Initialization
65         ! open the file
66         IF(lwp) THEN
67            WRITE(numout,*) ' '
68            WRITE(numout,*) ' **** Routine flx_forced_daily.h90'
69            WRITE(numout,*) ' '
70            WRITE(numout,*) ' daily fluxes Q, Qsr, EmP'
71         ENDIF
72         CALL iom_open ( 'flx_1d.nc', numflx )
73
74      ENDIF
75
76      ! Read daily fluxes in flxdta(1,1,jm)
77      !     1. Qtot    (w/m2)
78      !     2. Qsr     (w/m2)
79      !     3. emp     (kg/m2/s)
80     
81      IF( ndayflx /= nday ) THEN
82         
83         ndayflx = nday
84                 
85         ! read Qtot
86         CALL iom_get ( numflx, jpdom_data, 'sohefldo', flxdta(:,:,1), nday_year )
87         ! read qsr
88         CALL iom_get ( numflx, jpdom_data, 'soshfldo', flxdta(:,:,2), nday_year )
89         ! read emp
90         CALL iom_get ( numflx, jpdom_data, 'sowaflup', flxdta(:,:,3), nday_year )
91
92         IF(lwp) WRITE (numout,*)'Lecture flx record :',nday
93
94         IF( nit000 == 1 ) THEN
95            IF( kt == nit000 ) THEN
96               IF(lwp) THEN
97                  WRITE(numout,*)
98                  WRITE(numout,*) ' read daily fluxes ok'
99                  WRITE(numout,*)
100                  WRITE(numout,*) ' Q * .1, day: ',ndastp
101                  CALL prihre( flxdta(:,:,1),jpi,jpj,1,jpi,20,1,jpj,10,.1,numout )
102                  WRITE(numout,*)
103                  WRITE(numout,*) ' QSR * .1, day: ',ndastp
104                  CALL prihre( flxdta(:,:,2),jpi,jpj,1,jpi,20,1,jpj,10,.1,numout )
105                  WRITE(numout,*)
106                  WRITE(numout,*) ' E-P *86400, day: ',ndastp
107                  CALL prihre( flxdta(:,:,3),jpi,jpj,1,jpi,20,1,jpj,10,86400.,numout )
108                  WRITE(numout,*) ' '
109               ENDIF
110            ENDIF
111         ENDIF
112      ENDIF
113
114      p_qt (:,:) = flxdta(:,:,1)
115      p_qsr(:,:) = flxdta(:,:,2)
116      p_emp(:,:) = flxdta(:,:,3)
117 
118      ! Closing all files
119      ! -----------------
120 
121      IF( kt == nitend ) CALL iom_close ( numflx )
122 
123   END SUBROUTINE flx
Note: See TracBrowser for help on using the repository browser.