Ignore:
Timestamp:
Feb 25, 2016 12:31:13 PM (8 years ago)
Author:
hellstea
Message:

Introduction of nested domain system

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/poismg.f90

    r1683 r1762  
    1919! Current revisions:
    2020! -----------------
    21 !
     21! Introduction of nested domain feature
    2222!
    2323! Former revisions:
     
    259259    USE control_parameters,                                                    &
    260260        ONLY:  bc_lr_cyc, bc_ns_cyc, grid_level, ibc_p_b, ibc_p_t, inflow_l,   &
    261                inflow_n, inflow_r, inflow_s, outflow_l, outflow_n, outflow_r,  &
     261               inflow_n, inflow_r, inflow_s, nest_bound_l, nest_bound_n,       &
     262               nest_bound_r, nest_bound_s, outflow_l, outflow_n, outflow_r,    &
    262263               outflow_s
    263264
     
    353354
    354355    IF ( .NOT. bc_lr_cyc )  THEN
    355        IF ( inflow_l .OR. outflow_l )  r(:,:,nxl_mg(l)-1) = r(:,:,nxl_mg(l))
    356        IF ( inflow_r .OR. outflow_r )  r(:,:,nxr_mg(l)+1) = r(:,:,nxr_mg(l))
     356       IF ( inflow_l .OR. outflow_l .OR. nest_bound_l )  THEN
     357          r(:,:,nxl_mg(l)-1) = r(:,:,nxl_mg(l))
     358       ENDIF
     359       IF ( inflow_r .OR. outflow_r .OR. nest_bound_r )  THEN
     360          r(:,:,nxr_mg(l)+1) = r(:,:,nxr_mg(l))
     361       ENDIF
    357362    ENDIF
    358363
    359364    IF ( .NOT. bc_ns_cyc )  THEN
    360        IF ( inflow_n .OR. outflow_n )  r(:,nyn_mg(l)+1,:) = r(:,nyn_mg(l),:)
    361        IF ( inflow_s .OR. outflow_s )  r(:,nys_mg(l)-1,:) = r(:,nys_mg(l),:)
     365       IF ( inflow_n .OR. outflow_n .OR. nest_bound_n )  THEN
     366          r(:,nyn_mg(l)+1,:) = r(:,nyn_mg(l),:)
     367       ENDIF
     368       IF ( inflow_s .OR. outflow_s .OR. nest_bound_s )  THEN
     369          r(:,nys_mg(l)-1,:) = r(:,nys_mg(l),:)
     370       ENDIF
    362371    ENDIF
    363372
     
    393402    USE control_parameters,                                                    &
    394403        ONLY:  bc_lr_cyc, bc_ns_cyc, grid_level, ibc_p_b, ibc_p_t, inflow_l,   &
    395                inflow_n, inflow_r, inflow_s, outflow_l, outflow_n, outflow_r,  &
     404               inflow_n, inflow_r, inflow_s, nest_bound_l, nest_bound_n,       &
     405               nest_bound_r, nest_bound_s, outflow_l, outflow_n, outflow_r,    &
    396406               outflow_s
    397407
     
    560570
    561571    IF ( .NOT. bc_lr_cyc )  THEN
    562        IF (inflow_l .OR. outflow_l)  f_mg(:,:,nxl_mg(l)-1) = f_mg(:,:,nxl_mg(l))
    563        IF (inflow_r .OR. outflow_r)  f_mg(:,:,nxr_mg(l)+1) = f_mg(:,:,nxr_mg(l))
     572       IF ( inflow_l .OR. outflow_l .OR. nest_bound_l )  THEN
     573          f_mg(:,:,nxl_mg(l)-1) = f_mg(:,:,nxl_mg(l))
     574       ENDIF
     575       IF ( inflow_r .OR. outflow_r .OR. nest_bound_r )  THEN
     576          f_mg(:,:,nxr_mg(l)+1) = f_mg(:,:,nxr_mg(l))
     577       ENDIF
    564578    ENDIF
    565579
    566580    IF ( .NOT. bc_ns_cyc )  THEN
    567        IF (inflow_n .OR. outflow_n)  f_mg(:,nyn_mg(l)+1,:) = f_mg(:,nyn_mg(l),:)
    568        IF (inflow_s .OR. outflow_s)  f_mg(:,nys_mg(l)-1,:) = f_mg(:,nys_mg(l),:)
     581       IF ( inflow_n .OR. outflow_n .OR. nest_bound_n )  THEN
     582          f_mg(:,nyn_mg(l)+1,:) = f_mg(:,nyn_mg(l),:)
     583       ENDIF
     584       IF ( inflow_s .OR. outflow_s .OR. nest_bound_s )  THEN
     585          f_mg(:,nys_mg(l)-1,:) = f_mg(:,nys_mg(l),:)
     586       ENDIF
    569587    ENDIF
    570588
     
    600618    USE control_parameters,                                                    &
    601619        ONLY:  bc_lr_cyc, bc_ns_cyc, grid_level, ibc_p_b, ibc_p_t, inflow_l,   &
    602                inflow_n, inflow_r, inflow_s, outflow_l, outflow_n, outflow_r,  &
     620               inflow_n, inflow_r, inflow_s, nest_bound_l, nest_bound_n,       &
     621               nest_bound_r, nest_bound_s, outflow_l, outflow_n, outflow_r,    &
    603622               outflow_s
    604623
     
    668687
    669688    IF ( .NOT. bc_lr_cyc )  THEN
    670        IF (inflow_l .OR. outflow_l)  temp(:,:,nxl_mg(l)-1) = temp(:,:,nxl_mg(l))
    671        IF (inflow_r .OR. outflow_r)  temp(:,:,nxr_mg(l)+1) = temp(:,:,nxr_mg(l))
     689       IF ( inflow_l .OR. outflow_l .OR. nest_bound_l )  THEN
     690          temp(:,:,nxl_mg(l)-1) = temp(:,:,nxl_mg(l))
     691       ENDIF
     692       IF ( inflow_r .OR. outflow_r .OR. nest_bound_r )  THEN
     693          temp(:,:,nxr_mg(l)+1) = temp(:,:,nxr_mg(l))
     694       ENDIF
    672695    ENDIF
    673696
    674697    IF ( .NOT. bc_ns_cyc )  THEN
    675        IF (inflow_n .OR. outflow_n)  temp(:,nyn_mg(l)+1,:) = temp(:,nyn_mg(l),:)
    676        IF (inflow_s .OR. outflow_s)  temp(:,nys_mg(l)-1,:) = temp(:,nys_mg(l),:)
     698       IF ( inflow_n .OR. outflow_n .OR. nest_bound_n )  THEN
     699          temp(:,nyn_mg(l)+1,:) = temp(:,nyn_mg(l),:)
     700       ENDIF
     701       IF ( inflow_s .OR. outflow_s .OR. nest_bound_s )  THEN
     702          temp(:,nys_mg(l)-1,:) = temp(:,nys_mg(l),:)
     703       ENDIF
    677704    ENDIF
    678705
     
    709736    USE control_parameters,                                                    &
    710737        ONLY:  bc_lr_cyc, bc_ns_cyc, grid_level, ibc_p_b, ibc_p_t, inflow_l,   &
    711                inflow_n, inflow_r, inflow_s, ngsrb, outflow_l, outflow_n,      &
     738               inflow_n, inflow_r, inflow_s, ngsrb, nest_bound_l,              &
     739               nest_bound_n, nest_bound_r, nest_bound_s, outflow_l, outflow_n, &
    712740               outflow_r, outflow_s
    713741
     
    10681096
    10691097          IF ( .NOT. bc_lr_cyc )  THEN
    1070              IF ( inflow_l .OR. outflow_l )  THEN
     1098             IF ( inflow_l .OR. outflow_l .OR. nest_bound_l )  THEN
    10711099                p_mg(:,:,nxl_mg(l)-1) = p_mg(:,:,nxl_mg(l))
    10721100             ENDIF
    1073              IF ( inflow_r .OR. outflow_r )  THEN
     1101             IF ( inflow_r .OR. outflow_r .OR. nest_bound_r )  THEN
    10741102                p_mg(:,:,nxr_mg(l)+1) = p_mg(:,:,nxr_mg(l))
    10751103             ENDIF
     
    10771105
    10781106          IF ( .NOT. bc_ns_cyc )  THEN
    1079              IF ( inflow_n .OR. outflow_n )  THEN
     1107             IF ( inflow_n .OR. outflow_n .OR. nest_bound_n )  THEN
    10801108                p_mg(:,nyn_mg(l)+1,:) = p_mg(:,nyn_mg(l),:)
    10811109             ENDIF
    1082              IF ( inflow_s .OR. outflow_s )  THEN
     1110             IF ( inflow_s .OR. outflow_s .OR. nest_bound_s )  THEN
    10831111                p_mg(:,nys_mg(l)-1,:) = p_mg(:,nys_mg(l),:)
    10841112             ENDIF
     
    12961324               gamma_mg, grid_level, grid_level_count, ibc_p_b, ibc_p_t,       &
    12971325               inflow_l, inflow_n, inflow_r, inflow_s, maximum_grid_level,     &
    1298                mg_switch_to_pe0_level, mg_switch_to_pe0, ngsrb, outflow_l,     &
    1299                outflow_n, outflow_r, outflow_s
     1326               mg_switch_to_pe0_level, mg_switch_to_pe0, nest_domain,          &
     1327               nest_bound_l, nest_bound_n, nest_bound_r, nest_bound_s, ngsrb,  &
     1328               outflow_l, outflow_n, outflow_r, outflow_s
    13001329
    13011330
     
    14461475             outflow_l = .TRUE.
    14471476             outflow_r = .FALSE.
     1477          ELSEIF ( nest_domain )  THEN
     1478             nest_bound_l = .TRUE.
     1479             nest_bound_r = .TRUE.
    14481480          ENDIF
    14491481
     
    14581490             outflow_n = .TRUE.
    14591491             outflow_s = .FALSE.
     1492          ELSEIF ( nest_domain )  THEN
     1493             nest_bound_s = .TRUE.
     1494             nest_bound_n = .TRUE.
    14601495          ENDIF
    14611496
     
    15281563             ELSEIF ( bc_lr_raddir )  THEN
    15291564                outflow_l = .TRUE.
     1565             ELSEIF ( nest_domain )  THEN
     1566                nest_bound_l = .TRUE.
    15301567             ENDIF
    15311568          ENDIF
     
    15361573             ELSEIF ( bc_lr_raddir )  THEN
    15371574                inflow_r  = .TRUE.
     1575             ELSEIF ( nest_domain )  THEN
     1576                nest_bound_r = .TRUE.
    15381577             ENDIF
    15391578          ENDIF
     
    15441583             ELSEIF ( bc_ns_raddir )  THEN
    15451584                inflow_s  = .TRUE.
     1585             ELSEIF ( nest_domain )  THEN
     1586                nest_bound_s = .TRUE.
    15461587             ENDIF
    15471588          ENDIF
     
    15521593             ELSEIF ( bc_ns_raddir )  THEN
    15531594                outflow_n = .TRUE.
     1595             ELSEIF ( nest_domain )  THEN
     1596                nest_bound_n = .TRUE.
    15541597             ENDIF
    15551598          ENDIF
Note: See TracChangeset for help on using the changeset viewer.