Custom Query (964 matches)

Filters
 
Or
 
  
 
Columns

Show under each result:


Results (460 - 462 of 964)

Ticket Owner Reporter Resolution Summary
#570 arango arango Fixed NTC parameter redeclared
Description

Renamed parameter NTC in mod_param.F to NTCLM. This parameter is used to count the number of climatology tracer type variables to process. The NTC parameter was already declared in mod_stepping.F to account for the number of tidal components to process.

This bug was introduced recently in src:ticket:569. Many thanks to Kate for bringing this to my attention.

#571 arango arango Done set_data.F and friends
Description

Added an additional and optional argument SetBC to set_2dfld.F, set_2dfldr.F, set_3dfld.F, and set_3dfldr.F to control the setting of periodic boundary conditions to a particular interpolated field. For example, in set_2dfld.F we now have:

      SUBROUTINE set_2dfld_tile (ng, tile, model, ifield,               &
     &                           LBi, UBi, LBj, UBj,                    &
     &                           Finp, Fout, update,                    &
     &                           SetBC)

...

      logical, intent(in), optional :: SetBC

...

!
!  Set switch to apply boundary conditions.
!
      IF (PRESENT(SetBC)) THEN
        LapplyBC=SetBC
      ELSE
        LapplyBC=.TRUE.
      END IF

...

!
!  Exchange boundary data.
!
      IF (update) THEN
        IF (LapplyBC.and.(EWperiodic(ng).or.NSperiodic(ng))) THEN
          IF (gtype.eq.r2dvar) THEN
            CALL exchange_r2d_tile (ng, tile,                           &
     &                              LBi, UBi, LBj, UBj,                 &
     &                              Fout)
          ELSE IF (gtype.eq.u2dvar) THEN
            CALL exchange_u2d_tile (ng, tile,                           &
     &                              LBi, UBi, LBj, UBj,                 &
     &                              Fout)
          ELSE IF (gtype.eq.v2dvar) THEN
            CALL exchange_v2d_tile (ng, tile,                           &
     &                              LBi, UBi, LBj, UBj,                 &
     &                              Fout)
          END IF
        END IF

#ifdef DISTRIBUTE
        IF (.not.LapplyBC) THEN
          CALL mp_exchange2d (ng, tile, model, 1,                       &
     &                        LBi, UBi, LBj, UBj,                       &
     &                        NghostPoints,                             &
     &                        .FALSE., .FALSE.,                         &
     &                        Fout)
        ELSE
          CALL mp_exchange2d (ng, tile, model, 1,                       &
     &                        LBi, UBi, LBj, UBj,                       &
     &                        NghostPoints,                             &
     &                        EWperiodic(ng), NSperiodic(ng),           &
     &                        Fout)
        END IF
#endif
      END IF

This will facilitate configuring toy problems that require a non-periodic forcing field, say surface air pressure (Pair). Then, in set_data.F we now have:

# if defined BULK_FLUXES || defined ECOSIM || defined ATM_PRESS
!
!-----------------------------------------------------------------------
!  Set surface air pressure (mb).
!-----------------------------------------------------------------------
!
#  ifdef ANA_PAIR
      CALL ana_pair (ng, tile, iNLM)
#  else
      SetBC=.TRUE.
!     SetBC=.FALSE.
      CALL set_2dfld_tile (ng, tile, iNLM, idPair,                      &
     &                     LBi, UBi, LBj, UBj,                          &
     &                     FORCES(ng)%PairG,                            &
     &                     FORCES(ng)%Pair,                             &
     &                     update, SetBC)
      IF (exit_flag.ne.NoError) RETURN
#  endif
# endif

The default is set to always apply periodic boundary conditions (SetBC=.TRUE.). The user may edit set_data.F or Build/set_data.f90 to avoid applying periodic boundary conditions (SetBC=.FALSE.).

Many thanks to John Wilkin for requesting this useful capability.

#572 arango arango Done Corrected CPP syntax
Description

Corrected endif C-preprocessing syntax in tl_step3d_t.F, rp_step3d_t.F, and ad_step3d_t.F. This bug was incorpoarated recently in src:ticket:570.

Batch Modify
Note: See TracBatchModify for help on using batch modify.
Note: See TracQuery for help on using queries.