source: codes/icosagcm/trunk/src/dissip/guided_mod.f90 @ 963

Last change on this file since 963 was 899, checked in by adurocher, 5 years ago

trunk : Fixed GCC warnings

Fixed iso c bindings
fixed warnings with -Wall -Wno-aliasing -Wno-unused -Wno-unused-dummy-argument -Wno-maybe-uninitialized -Wno-tabs warnings
Removed all unused variables (-Wunused-variable)
vector%dot_product is now dot_product_3d to avoid compilation warning "dot_product shadows intrinsic" with GCC

File size: 1.3 KB
Line 
1MODULE guided_mod
2
3  CHARACTER(LEN=255),SAVE :: guided_type
4!$OMP THREADPRIVATE(guided_type)
5
6CONTAINS
7
8
9  SUBROUTINE init_guided
10  USE icosa
11  USE guided_ncar_mod, ONLY : init_guided_ncar => init_guided
12  IMPLICIT NONE
13   
14    guided_type='none'
15    CALL getin("guided_type",guided_type)
16   
17    SELECT CASE(TRIM(guided_type))
18      CASE ('none')
19     
20      CASE ('dcmip1')
21        CALL init_guided_ncar
22       
23      CASE DEFAULT
24         PRINT*,"Bad selector for varaible guided_type >",TRIM(guided_type),"> option are <none>, <dcmip1>"
25         STOP
26    END SELECT
27   
28  END SUBROUTINE init_guided
29
30 
31  SUBROUTINE guided(tt, f_ps, f_theta_rhodz, f_u, f_q)
32  USE icosa
33  USE guided_ncar_mod, ONLY : guided_ncar => guided
34  IMPLICIT NONE
35    REAL(rstd), INTENT(IN):: tt
36    TYPE(t_field),POINTER :: f_ps(:)
37    TYPE(t_field),POINTER :: f_theta_rhodz(:)
38    TYPE(t_field),POINTER :: f_u(:) 
39    TYPE(t_field),POINTER :: f_q(:) 
40
41    SELECT CASE(TRIM(guided_type))
42      CASE ('none')
43      CASE ('dcmip1')
44        CALL guided_ncar(tt, f_ps, f_theta_rhodz, f_u, f_q)
45      CASE DEFAULT
46         PRINT*,"Bad selector for varaible guided_type >",TRIM(guided_type),"> option are <none>, <dcmip1>"
47         STOP
48    END SELECT
49 
50  END SUBROUTINE guided
51 
52END MODULE guided_mod
53 
Note: See TracBrowser for help on using the repository browser.