C $Header: /u/gcmpack/MITgcm/pkg/ecco/ecco_cost_init_fixed.F,v 1.23 2010/09/07 16:13:00 gforget Exp $
C $Name:  $

#include "PACKAGES_CONFIG.h"
#include "AD_CONFIG.h"
#include "COST_CPPOPTIONS.h"

      subroutine ECCO_COST_INIT_FIXED( mythid )

c     ==================================================================
c     SUBROUTINE ecco_cost_init_fixed
c     ==================================================================
c
c     o Set contributions to the cost function and the cost function
c       itself to zero. The cost function and the individual contribu-
c       tions are defined in the header file "ecco_cost.h".
c
c     started: Christian Eckert eckert@mit.edu 30-Jun-1999
c
c     changed: Christian Eckert eckert@mit.edu 25-Feb-2000
c
c              - Restructured the code in order to create a package
c                for the MITgcmUV.
c
c     changed: Ralf Giering 18-Jan-2001
c
c              - move namelist reading to cost_readparms.F
c
c     ==================================================================
c     SUBROUTINE ecco_cost_init_fixed
c     ==================================================================

      implicit none

c     == global variables ==

#include "EEPARAMS.h"
#include "SIZE.h"
#include "GRID.h"
#include "PARAMS.h"

#ifdef ALLOW_CAL
#include "cal.h"
#endif
#include "ecco_cost.h"

c     == routine arguments ==

      integer mythid

c     == local variables ==

      integer tempDate1(4)
      integer tempDate2(4)
      integer gwunit
      integer ilo,ihi
      integer irec,k
      logical exst
      _RL     dummy
      _RL     missingObsFlag
      PARAMETER ( missingObsFlag = 1. _d 23 )
      character*(max_len_mbuf) msgbuf

c     == external functions ==

      integer  cal_IntYears
      external 
      integer  cal_IntMonths
      external 
      integer  cal_IntDays
      external 
      integer  ifnblnk
      external 
      integer  ilnblnk
      external 

c     == end of interface ==

#ifdef ALLOW_CAL

c--   The number of monthly and daily averages generated by the
c--   current model integration.
      nyearsrec = cal_IntYears( mythid )
      nmonsrec = cal_IntMonths( mythid )
      ndaysrec = cal_IntDays( mythid )

      _BEGIN_MASTER( myThid )

c--     Get the complete dates of the ...
c--     ... TMI data.
        if ( tmidatfile .ne. ' ' )
     &   call CAL_FULLDATE( tmistartdate1,   tmistartdate2,
     &                      tmistartdate,    mythid )
c--     ... SST data.
        if ( sstdatfile .ne. ' ' )
     &   call CAL_FULLDATE( sststartdate1,   sststartdate2,
     &                      sststartdate,    mythid )
c--     ... SSS data.
        if ( sssdatfile .ne. ' ' )
     &   call CAL_FULLDATE( sssstartdate1,   sssstartdate2,
     &                      sssstartdate,    mythid )
c--     ... BP data.
        if ( bpdatfile .ne. ' ' )
     &   call CAL_FULLDATE( bpstartdate1,   bpstartdate2,
     &                      bpstartdate,    mythid )
c--     ... T/P data.
        if ( topexfile .ne. ' ' )
     &  call CAL_FULLDATE( topexstartdate1, topexstartdate2,
     &                     topexstartdate,  mythid )
c--     ... ERS data.
        if ( ersfile .ne. ' ' )
     &   call CAL_FULLDATE( ersstartdate1,   ersstartdate2,
     &                      ersstartdate,    mythid )
c--     ... GFO data.
        if ( gfofile .ne. ' ' )
     &   call CAL_FULLDATE( gfostartdate1,   gfostartdate2,
     &                      gfostartdate,    mythid )
c--     ... SCAT data.
        if ( scatxdatfile .ne. ' ' )
     &   call CAL_FULLDATE( scatstartdate1,   scatstartdate2,
     &                      scatxstartdate,    mythid )
        if ( scatydatfile .ne. ' ' )
     &   call CAL_FULLDATE( scatstartdate1,   scatstartdate2,
     &                      scatystartdate,    mythid )
c--     ... ARGO data.
        if ( argotfile .ne. ' ' )
     &  call CAL_FULLDATE( argotstartdate1,   argotstartdate2,
     &                     argotstartdate,    mythid )
         if ( argosfile .ne. ' ' )
     &  call CAL_FULLDATE( argosstartdate1,   argotstartdate2,
     &                     argosstartdate,    mythid )

#ifdef ALLOW_GENCOST_CONTRIBUTION
      do k = 1, NGENCOST
         if ( gencost_avgperiod(k) .EQ. 'day' .OR.
     &        gencost_avgperiod(k) .EQ. 'DAY' ) then
            gencost_nrec(k)   = ndaysrec
            gencost_period(k) = 86400.
         else if ( gencost_avgperiod(k) .EQ. 'month' .OR.
     &        gencost_avgperiod(k) .EQ. 'MONTH' ) then
            gencost_nrec(k)   =nmonsrec
            gencost_period(k) = 0.
         else if ( gencost_avgperiod(k) .EQ. 'year' .OR.
     &        gencost_avgperiod(k) .EQ. 'YEAR' ) then
            STOP
     &       'COST_GENCOST_ALL: yearly data not yet implemented'
#ifndef ALLOW_GENCOST_FREEFORM         
         else
            STOP 
     &       'COST_GENCOST_ALL: gencost_avgperiod wrongly specified'
#endif   
         endif
      enddo
#endif /* ALLOW_GENCOST_CONTRIBUTION */

      _END_MASTER( mythid )

#endif /* ALLOW_CAL */

      call ECCO_CHECK( myThid )

c--   Get the weights that are to be used for the individual cost
c--   function contributions.
      call ECCO_COST_WEIGHTS( mythid )

c--   Initialise adjoint of monthly mean files calculated
c--   in cost_averagesfields (and their ad...).
cph(
cph   The following init. shoud not be applied if in the middle
cph   of a divided adjoint run
cph)
#ifndef ALLOW_TANGENTLINEAR_RUN
cph!!! and I think it needs to be seen by TAF
cph!!! for repeated TLM runs
cph!!!
      inquire( file='costfinal', exist=exst )
      if ( .NOT. exst) then
         call ECCO_COST_INIT_BARFILES( mythid )
      endif
#endif

#ifdef ALLOW_TRANSPORT_COST_CONTRIBUTION
      do irec = 1, ndaysrec
       wtransp(irec)   = 0. _d 0
       transpobs(irec) = 0. _d 0
      enddo

      if ( costTranspDataFile .NE. ' ' ) then
      _BEGIN_MASTER(myThid)
      ilo = ifnblnk(costTranspDataFile)
      ihi = ilnblnk(costTranspDataFile)
      CALL OPEN_COPY_DATA_FILE(
     I                          costTranspDataFile(ilo:ihi),
     I                          'ECCO_COST_INIT_FIXED',
     O                          gwunit,
     I                          myThid )
      do irec = 1, ndaysrec
c-- read daily transport time series
c-- 1st: transport in m/s
c-- 2nd: date in YYYYMMDD
c-- 3rd: uncertainty in m/s
         read(gwunit,*) transpobs(irec), dummy, wtransp(irec)
c-- convert std.dev. to weight
         if ( wtransp(irec) .NE. 0. )
     &        wtransp(irec) =1.0/(wtransp(irec)*wtransp(irec))
c-- set weight to zero for missing values
         if ( transpobs(irec) .EQ. missingObsFlag )
     &        wtransp(irec) = 0. _d 0
      enddo
      _END_MASTER(myThid)
      _BARRIER
      endif
#endif /* ALLOW_TRANSPORT_COST_CONTRIBUTION */

#ifdef ALLOW_SSH_COST_CONTRIBUTION

c--   Read flags for picking SSH time averages
      do irec = 1, ndaysrec
       tpTimeMask(irec)  = 1. _d 0
       ersTimeMask(irec) = 1. _d 0
       gfoTimeMask(irec) = 1. _d 0
      enddo
c
      _BEGIN_MASTER(myThid)
c
#ifdef ALLOW_SSH_TPANOM_COST_CONTRIBUTION
      if ( tpTimeMaskFile .NE. ' ' ) then
       ilo = ifnblnk(tpTimeMaskFile)
       ihi = ilnblnk(tpTimeMaskFile)
       CALL OPEN_COPY_DATA_FILE(
     I                          tpTimeMaskFile(ilo:ihi),
     I                          'cost_ssh tp',
     O                          gwunit,
     I                          myThid )
       do irec = 1, ndaysrec
        read(gwunit,*) tpTimeMask(irec)
       enddo
      endif
#endif
c
#ifdef ALLOW_SSH_ERSANOM_COST_CONTRIBUTION
      if ( ersTimeMaskFile .NE. ' ' ) then
       ilo = ifnblnk(ersTimeMaskFile)
       ihi = ilnblnk(ersTimeMaskFile)
       CALL OPEN_COPY_DATA_FILE(
     I                          ersTimeMaskFile(ilo:ihi),
     I                          'cost_ssh ers',
     O                          gwunit,
     I                          myThid )
       do irec = 1, ndaysrec
        read(gwunit,*) ersTimeMask(irec)
       enddo
      endif
#endif
c
#ifdef ALLOW_SSH_GFOANOM_COST_CONTRIBUTION
      if ( gfoTimeMaskFile .NE. ' ' ) then
       ilo = ifnblnk(gfoTimeMaskFile)
       ihi = ilnblnk(gfoTimeMaskFile)
       CALL OPEN_COPY_DATA_FILE(
     I                          gfoTimeMaskFile(ilo:ihi),
     I                          'cost_ssh gfo',
     O                          gwunit,
     I                          myThid )
       do irec = 1, ndaysrec
        read(gwunit,*) gfoTimeMask(irec)
       enddo
      endif
#endif
c
       do irec = 1, ndaysrec
        if ( 
     &   ( tpTimeMask(irec).NE.0. .AND. tpTimeMask(irec).NE.1. ) .OR.
     &   ( ersTimeMask(irec).NE.0. .AND. ersTimeMask(irec).NE.1. ) .OR.
     &   ( ersTimeMask(irec).NE.0. .AND. ersTimeMask(irec).NE.1. ) )
     &  then
           WRITE(msgBuf,'(2A,I10)')
     &        'ecco_cost_init_fixed: (SSH)TimeMask not 0. or 1. ',
     &        'for irec (=day) ', irec
           CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
     &          SQUEEZE_RIGHT , myThid )
           CALL PRINT_ERROR( msgBuf , myThid )
           STOP 'ABNORMAL END: S/R ECCO_COST_INIT_FIXED'
        endif
       enddo
c
      _END_MASTER(myThid)
      _BARRIER
#endif

c--   Summarize the cost function setup.
      _BEGIN_MASTER( mythid )
      call ECCO_COST_SUMMARY( mythid )
      _END_MASTER( mythid )

      _BARRIER

      end