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.
Changeset 1998 for branches/DEV_R1821_Rivers/NEMO/OPA_SRC/SBC/sbcrnf.F90 – NEMO

Ignore:
Timestamp:
2010-07-08T17:12:21+02:00 (14 years ago)
Author:
acc
Message:

ticket #465_Rivers tidied code and added namelist changes in preparation for mid-year merge

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/DEV_R1821_Rivers/NEMO/OPA_SRC/SBC/sbcrnf.F90

    r1938 r1998  
    3838   REAL(wp)          , PUBLIC ::   rn_hrnf      = 0.e0    !: runoffs, depth over which enhanced vertical mixing is used 
    3939   REAL(wp)          , PUBLIC ::   rn_avt_rnf   = 0.e0    !: runoffs, value of the additional vertical mixing coef. [m2/s] 
    40    LOGICAL           , PUBLIC ::   ln_rnf_att   = .false.  !: river runoffs attributes (temp, sal & depth) are specified in a file  
     40   LOGICAL           , PUBLIC ::   ln_rnf_att   = .false. !: river runoffs attributes (temp, sal & depth) are specified in a file  
    4141   REAL(wp)          , PUBLIC ::   rn_rfact     = 1.e0    !: multiplicative factor for runoff 
    4242 
     
    4545   REAL(wp), PUBLIC, DIMENSION(jpk)     ::   rnfmsk_z    !: river mouth mask (vert.) 
    4646 
    47    TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_rnf   ! structure of input SST (file information, fields read) 
    48  
    49    TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_sal_rnf    !: structure of input salinity (file information, fields read)   
    50    TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_tmp_rnf    !: structure of input tmeperature (file information, fields read)   
     47   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_rnf        !: structure of input river runoff (file information, fields read) 
     48 
     49   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_sal_rnf    !: structure of input river runoff salinity (file information, fields read)   
     50   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_tmp_rnf    !: structure of input river runoff temperature (file information, fields read)   
    5151  
    52 !   REAL,    PUBLIC, DIMENSION(jpi,jpj) ::  rnf             !: mass flux of river runoff (in kg/m2/s)   
    5352   REAL,    PUBLIC, DIMENSION(jpi,jpj) ::  rnf_dep         !: depth of runoff in m   
    5453   INTEGER, PUBLIC, DIMENSION(jpi,jpj) ::  rnf_mod_dep     !: depth of runoff in model levels   
     
    8988      !                                    
    9089      IF( kt == nit000 ) THEN   
    91          IF( .NOT. ln_rnf_emp ) THEN 
    92             ALLOCATE( sf_rnf(1), STAT=ierror ) 
    93             IF( ierror > 0 ) THEN 
    94                CALL ctl_stop( 'sbc_rnf: unable to allocate sf_rnf structure' )   ;   RETURN 
    95             ENDIF 
    96             ALLOCATE( sf_rnf(1)%fnow(jpi,jpj) ) 
    97             ALLOCATE( sf_rnf(1)%fdta(jpi,jpj,2) ) 
    98   
    99             ALLOCATE( sf_sal_rnf(1), STAT=ierror )   
    100             IF( ierror > 0 ) THEN   
    101                CALL ctl_stop( 'sbc_sal_rnf: unable to allocate sf_sal_rnf structure' )   ;   RETURN   
    102             ENDIF   
    103             ALLOCATE( sf_sal_rnf(1)%fnow(jpi,jpj) )   
    104             ALLOCATE( sf_sal_rnf(1)%fdta(jpi,jpj,2) )   
    105     
    106             ALLOCATE( sf_tmp_rnf(1), STAT=ierror )   
    107             IF( ierror > 0 ) THEN   
    108                 CALL ctl_stop( 'sbc_tmp_rnf: unable to allocate sf_tmp_rnf structure' )   ;   RETURN   
    109             ENDIF   
    110             ALLOCATE( sf_tmp_rnf(1)%fnow(jpi,jpj) )   
    111             ALLOCATE( sf_tmp_rnf(1)%fdta(jpi,jpj,2) )   
    112          ENDIF   
    113          CALL sbc_rnf_init( sf_rnf, sf_tmp_rnf, sf_sal_rnf )   
     90         CALL sbc_rnf_init                      ! Read namelist and allocate structures 
    11491      ENDIF 
    11592 
     
    146123               rnf_tmp(:,:) = -999   
    147124            ENDIF   
    148             CALL iom_put( "runoffs", sf_rnf(1)%fnow )         ! runoffs 
     125            CALL iom_put( "runoffs", rnf )         ! runoffs 
    149126         ENDIF 
    150127         ! 
     
    154131 
    155132 
    156    SUBROUTINE sbc_rnf_init( sf_rnf, sf_tmp_rnf, sf_sal_rnf )   
     133   SUBROUTINE sbc_rnf_init 
    157134      !!---------------------------------------------------------------------- 
    158135      !!                  ***  ROUTINE sbc_rnf_init  *** 
     
    164141      !! ** Action  : - read parameters 
    165142      !!---------------------------------------------------------------------- 
    166       TYPE(FLD), INTENT(inout), DIMENSION(:) :: sf_rnf, sf_tmp_rnf, sf_sal_rnf   ! input data   
    167143      CHARACTER(len=32) ::   rn_dep_file   ! runoff file name   
    168144      !!  
     
    207183         IF(lwp) WRITE(numout,*) 
    208184         IF(lwp) WRITE(numout,*) '          runoffs directly provided in the precipitations' 
    209          IF ( ln_rnf_att ) CALL ctl_warn( 'runoffs already included in precipitations & so runoff attributes not included' )  
     185         IF ( ln_rnf_att ) THEN 
     186           CALL ctl_warn( 'runoffs already included in precipitations & so runoff attributes will not be used' )  
     187           ln_rnf_att = .FALSE. 
     188         ENDIF 
    210189         ! 
    211190      ELSE                                      ! runoffs read in a file : set sf_rnf structure  
    212191         ! 
    213          ! sf_rnf already allocated in main routine 
     192         ! Allocate sf_rnf structure and (if required) sf_sal_rnf and sf_tmp_rnf structures 
     193         ALLOCATE( sf_rnf(1), STAT=ierror ) 
     194         IF( ierror > 0 ) THEN 
     195            CALL ctl_stop( 'sbc_rnf: unable to allocate sf_rnf structure' )   ;   RETURN 
     196         ENDIF 
     197         ALLOCATE( sf_rnf(1)%fnow(jpi,jpj) ) 
     198         ALLOCATE( sf_rnf(1)%fdta(jpi,jpj,2) ) 
     199 
     200         IF( ln_rnf_att ) THEN 
     201            ALLOCATE( sf_sal_rnf(1), STAT=ierror ) 
     202            IF( ierror > 0 ) THEN 
     203               CALL ctl_stop( 'sbc_sal_rnf: unable to allocate sf_sal_rnf structure' )   ;   RETURN 
     204            ENDIF 
     205            ALLOCATE( sf_sal_rnf(1)%fnow(jpi,jpj) ) 
     206            ALLOCATE( sf_sal_rnf(1)%fdta(jpi,jpj,2) ) 
     207 
     208            ALLOCATE( sf_tmp_rnf(1), STAT=ierror ) 
     209            IF( ierror > 0 ) THEN 
     210                CALL ctl_stop( 'sbc_tmp_rnf: unable to allocate sf_tmp_rnf structure' )   ;   RETURN 
     211            ENDIF 
     212            ALLOCATE( sf_tmp_rnf(1)%fnow(jpi,jpj) ) 
     213            ALLOCATE( sf_tmp_rnf(1)%fdta(jpi,jpj,2) ) 
     214         ENDIF 
    214215         ! fill sf_rnf with sn_rnf and control print 
    215216         CALL fld_fill( sf_rnf, (/ sn_rnf /), cn_dir, 'sbc_rnf_init', 'read runoffs data', 'namsbc_rnf' ) 
Note: See TracChangeset for help on using the changeset viewer.