Ignore:
Timestamp:
07/15/19 12:29:31 (5 years ago)
Author:
adurocher
Message:

trunk : GPU implementation with OpenACC ( merge from glcp.idris.fr )

File:
1 edited

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/trunk/src/diagnostics/check_conserve.f90

    r902 r953  
    11MODULE check_conserve_mod 
    22  USE icosa  
     3  USE abort_mod 
    34  IMPLICIT NONE  
    45 
     
    2829    USE getin_mod 
    2930    USE omp_para, ONLY : is_master 
     31    USE abort_mod 
    3032    CHARACTER(LEN=255) :: check_type_str 
    3133    CALL allocate_field(f_pk,field_t,type_real,llm) 
     
    4749       STOP 
    4850    END SELECT 
     51 
     52    IF (check_type /= check_basic) THEN 
     53       CALL abort_acc("check_conservation /= 'basic'") 
     54    END IF 
    4955  END SUBROUTINE init_check_conserve 
    5056 
     
    179185     
    180186    IF(check_type == check_detailed) THEN 
    181  
     187       CALL abort_acc("!check_detailed") 
    182188       CALL transfert_request(f_ue,req_e1_vect) 
    183189       CALL pression(f_ps,f_p) 
Note: See TracChangeset for help on using the changeset viewer.