|
| 1 | +SUBROUTINE YAC2Elmer( Model,Solver,dt,TransientSimulation ) |
| 2 | + USE DefUtils |
| 3 | + USE SolverUtils |
| 4 | + USE elmer_coupling |
| 5 | + USE elmer_icon_coupling |
| 6 | + |
| 7 | + IMPLICIT NONE |
| 8 | + |
| 9 | + TYPE(Model_t) :: Model |
| 10 | + TYPE(Solver_t) :: Solver |
| 11 | + REAL(KIND=dp) :: dt |
| 12 | + LOGICAL :: TransientSimulation |
| 13 | + |
| 14 | + |
| 15 | + TYPE(ValueList_t), POINTER :: SolverParams |
| 16 | + TYPE(Mesh_t), POINTER :: ThisMesh |
| 17 | + CHARACTER(LEN=MAX_NAME_LEN):: SolverName='YAC2Elmer' |
| 18 | + CHARACTER(LEN=1024) :: config_file, grid_dir, model_tstep |
| 19 | + INTEGER :: num_parts, elmer_mesh_partitions, comm_rank, comm_size, ierror |
| 20 | + INTEGER :: I, t, ierr |
| 21 | + INTEGER, POINTER :: cltPerm(:), prPerm(:) |
| 22 | + LOGICAL :: Parallel, FirstTime=.TRUE. |
| 23 | + TYPE(Mesh_t),POINTER :: Mesh |
| 24 | + TYPE(Variable_t), POINTER :: cltVar, prVar |
| 25 | + |
| 26 | + SAVE elmer_mesh_partitions, grid_dir, cltPerm, prPerm |
| 27 | + |
| 28 | + Mesh => Solver % Mesh |
| 29 | + write(model_tstep, *) int(dt * 8760) |
| 30 | + WRITE(Message,*) 'ELMER timestep size in hours:', TRIM(model_tstep) |
| 31 | + CALL INFO(SolverName,Message,Level=3) |
| 32 | + |
| 33 | + !!!!!!!!!! DO WE HAVE TO INITIALIZE WITH EVERY CALL ? !!!!!!!!!!!!!! |
| 34 | + IF (FirstTime) THEN |
| 35 | + |
| 36 | + SolverParams => GetSolverParams() |
| 37 | + |
| 38 | + ! get mesh |
| 39 | + ThisMesh => GetMesh(Solver) |
| 40 | + |
| 41 | + ! check if this is a parallel run |
| 42 | + IF ((ParEnv % PEs <= 1) .AND. ( .NOT. ThisMesh % SingleMesh )) THEN |
| 43 | + CALL FATAL(SolverName,'Only parallel runs can use this solver') |
| 44 | + ELSE |
| 45 | + grid_dir= TRIM(ThisMesh % Name) |
| 46 | + elmer_mesh_partitions = ParEnv % PEs |
| 47 | + !PRINT *, TRIM(grid_dir), elmer_mesh_partitions |
| 48 | + WRITE(Message,*) 'Running on ', TRIM(grid_dir),' with ',ParEnv % PEs ,' partitions' |
| 49 | + CALL INFO(SolverName,Message,Level=3) |
| 50 | + END IF |
| 51 | + |
| 52 | + !CALL coupling_setup(TRIM(grid_dir), elmer_mesh_partitions, "1") |
| 53 | + CALL coupling_setup(TRIM(grid_dir), elmer_mesh_partitions, TRIM(model_tstep)) |
| 54 | + |
| 55 | + |
| 56 | + ! setting up Elmer-side variables for receiving YAC variables |
| 57 | + ! this coul dbe replaced by an automatic picking of the names and the DOFs |
| 58 | + ! from the coupling-deifnitions |
| 59 | + ! nodal variable |
| 60 | + |
| 61 | + ALLOCATE(cltPerm(Mesh % NumberOfNodes),prPerm(GetNOFActive(Solver))) |
| 62 | + DO i=1,Mesh % NumberOfNodes |
| 63 | + cltPerm(i) = i |
| 64 | + END DO |
| 65 | + DO t=1,GetNOFActive(Solver) |
| 66 | + prPerm(t) = t |
| 67 | + END DO |
| 68 | + |
| 69 | + CALL DefaultVariableAdd('tas', dofs=1, Perm = cltPerm) |
| 70 | + |
| 71 | + ! element wise (cell) variable |
| 72 | + CALL DefaultVariableAdd('pr_snow', dofs=1, VariableType = Variable_on_elements, Perm = prPerm) |
| 73 | + |
| 74 | + |
| 75 | + |
| 76 | + FirstTime = .FALSE. |
| 77 | + |
| 78 | + |
| 79 | + WRITE(Message,*) "Coupling setup with ",TRIM(grid_dir)," on ",& |
| 80 | + elmer_mesh_partitions, " partitions for YAC coupling done" |
| 81 | + CALL INFO(SolverName,Message,Level=1) |
| 82 | + END IF |
| 83 | +!!!!!!!!!! DO WE HAVE TO INITIALIZE WITH EVERY CALL ? !!!!!!!!!!!!!! |
| 84 | + |
| 85 | + WRITE(Message,*) 'BEFORE ELMER ICON INTERFACE' |
| 86 | + CALL INFO(SolverName,Message,Level=3) |
| 87 | + ! couple with ICON |
| 88 | + CALL elmer_icon_interface(ParEnv % MyPE) |
| 89 | + WRITE(Message,*) 'AFTER ELMER ICON INTERFACE' |
| 90 | + CALL INFO(SolverName,Message,Level=3) |
| 91 | + |
| 92 | + |
| 93 | + cltVar => VariableGet( Mesh % Variables, 'tas' ) |
| 94 | + prVar => VariableGet( Mesh % Variables, 'pr_snow' ) |
| 95 | + WRITE(Message,*) 'AFTER GETTING VARIABLES' |
| 96 | + CALL INFO(SolverName,Message,Level=3) |
| 97 | + IF ((.NOT.ASSOCIATED(cltVar)) .OR. (.NOT.ASSOCIATED(prVar))) THEN |
| 98 | + CALL FATAL(SolverName,'Elmer variables not associated') |
| 99 | + END IF |
| 100 | + |
| 101 | + WRITE(Message,*) 'BEFORE WRITING VALUES' |
| 102 | + CALL INFO(SolverName,Message,Level=3) |
| 103 | + ! write over values for nodes |
| 104 | + DO i=1, Mesh % NumberOfNodes |
| 105 | + !IF (ParEnv % MyPE == 0) PRINT *,i, clt_field(i,1) |
| 106 | + cltVar % Values(cltVar % Perm(i)) = clt_field(i,1) |
| 107 | + !prVar % Values(prVar % Perm(i)) = pr_field(i,1) |
| 108 | + END DO |
| 109 | + WRITE(Message,*) 'BEFORE WRITING SECOND VALUES' |
| 110 | + CALL INFO(SolverName,Message,Level=3) |
| 111 | + ! write over values for elements |
| 112 | + DO t=1, GetNOFActive(Solver) |
| 113 | + prVar % Values(prVar % Perm(t)) = pr_field(t,1) |
| 114 | + END DO |
| 115 | + !CALL INFO(SolverName, "Test output start", Level=1) |
| 116 | + !PRINT *, "Size of clt_field", SIZE(clt_field, 1),"First entry:", clt_field(1,1) |
| 117 | + !CALL INFO(SolverName, "Test output start", Level=1) |
| 118 | + !CALL MPI_BARRIER( ELMER_COMM_WORLD, ierr ) |
| 119 | + CALL INFO(SolverName,'Coupling step done', Level=1) |
| 120 | + |
| 121 | +END SUBROUTINE YAC2Elmer |
| 122 | + |
0 commit comments