MODULE guided_mod CHARACTER(LEN=255),SAVE :: guided_type !$OMP THREADPRIVATE(guided_type) CONTAINS SUBROUTINE init_guided USE icosa USE guided_ncar_mod, ONLY : init_guided_ncar => init_guided IMPLICIT NONE guided_type='none' CALL getin("guided_type",guided_type) SELECT CASE(TRIM(guided_type)) CASE ('none') CASE ('dcmip1') CALL init_guided_ncar CASE DEFAULT PRINT*,"Bad selector for varaible guided_type >",TRIM(guided_type),"> option are , " STOP END SELECT END SUBROUTINE init_guided SUBROUTINE guided(tt, f_ps, f_theta_rhodz, f_u, f_q) USE icosa USE guided_ncar_mod, ONLY : guided_ncar => guided IMPLICIT NONE REAL(rstd), INTENT(IN):: tt TYPE(t_field),POINTER :: f_ps(:) TYPE(t_field),POINTER :: f_theta_rhodz(:) TYPE(t_field),POINTER :: f_u(:) TYPE(t_field),POINTER :: f_q(:) SELECT CASE(TRIM(guided_type)) CASE ('none') CASE ('dcmip1') CALL guided_ncar(tt, f_ps, f_theta_rhodz, f_u, f_q) CASE DEFAULT PRINT*,"Bad selector for varaible guided_type >",TRIM(guided_type),"> option are , " STOP END SELECT END SUBROUTINE guided END MODULE guided_mod