Ignore:
Timestamp:
07/14/19 14:40:34 (5 years ago)
Author:
dubos
Message:

devel/unstructured : towards Fortran driver for DYNAMICO-unstructured

File:
1 edited

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/devel/src/time/hevi_scheme.f90

    r732 r950  
    1111  REAL(rstd), PARAMETER, DIMENSION(3) :: zero = (/0.,0.,0./) 
    1212 
    13   PUBLIC :: set_coefs_ark23, set_coefs_ark33, hevi_scheme 
     13  PUBLIC :: set_coefs_ark23, set_coefs_ark33, set_coefs_ark11, hevi_scheme 
    1414 
    1515CONTAINS 
     
    3434  END SUBROUTINE set_coefs_ark33 
    3535     
     36  SUBROUTINE set_coefs_ark11(dt) 
     37    ! Euler scheme disguised as ARK for development purposes 
     38    REAL(rstd) :: dt 
     39    CALL set_coefs_rk(dt, (/ zero, (/1.,0.,0./), (/0.,0.,0./), (/0./0.,0./0.,0./) /) ) 
     40  END SUBROUTINE set_coefs_ark11 
     41     
    3642  SUBROUTINE set_coefs_rk(dt, ajl) 
    3743    REAL(rstd) :: dt, ajl(3,4) 
     
    4248    REAL(rstd) :: dt, ajl_slow(3,4), ajl_fast(3,4) ! fast/slow Butcher tableaus 
    4349    INTEGER :: j 
    44     DO j=1,3 
     50    DO j=1,nb_stage 
    4551       bjl(:,j) = dt*(ajl_slow(:,j+1)-ajl_slow(:,j)) 
    4652       cjl(:,j) = dt*(ajl_fast(:,j+1)-ajl_fast(:,j)) 
    4753       taujj(j) = dt*ajl_fast(j,j) 
    4854    END DO 
    49     wj=dt*ajl_slow(:,4) 
     55    wj=dt*ajl_slow(:,nb_stage+1) 
    5056  END SUBROUTINE set_coefs_hevi 
    5157 
     
    142148    INTENT(INOUT) :: y 
    143149    INTENT(IN) :: dy 
    144     INTEGER :: l 
    145     DO l=ll_begin,ll_end 
     150    INTEGER :: l, l_begin, l_end 
     151    IF(grid_type==grid_ico) THEN 
     152       l_begin = ll_begin 
     153       l_end   = l_end 
     154    ELSE ! unstructured : FIXME OpenMP 
     155       l_begin = 1 
     156       l_end   = SIZE(y,2) 
     157    END IF 
     158    DO l=l_begin,l_end 
    146159       y(:,l)=y(:,l)+w*dy(:,l) 
    147160    ENDDO 
     
    157170       IF (.NOT. assigned_domain(ind)) CYCLE 
    158171       dy=f_dy(ind); y=f_y(ind) 
    159        IF (is_omp_level_master) CALL compute_update_2D(w,y,dy) 
     172       IF (is_omp_level_master) CALL compute_update_2D(w,y,dy) ! FIXME OpenMP+unstructured 
    160173    ENDDO 
    161174  END SUBROUTINE update_2D 
Note: See TracChangeset for help on using the changeset viewer.