|
- module MudSystemMain
- implicit none
- public
- contains
-
- subroutine MudSystem_Setup()
- use CSimulationVariables
- use MudSystem
- implicit none
- call SetupMudSystem()
- call OnSimulationStop%Add(MudSystem_Stop)
- call OnMudSystemStart%Add(MudSystem_Start)
- call OnMudSystemStep%Add(MudSystem_Step)
- call OnMudSystemMain%Add(MudSystemMainBody)
- end subroutine
-
- subroutine MudSystem_Stop
- implicit none
- !print* , 'MudSystem_Stop'
- CALL DEALLOCATE_ARRAYS_MudSystem()
- end subroutine MudSystem_Stop
-
- subroutine MudSystem_Start
- implicit none
- !print* , 'MudSystem_Start'
- CALL MudSystem_StartUp()
- end subroutine MudSystem_Start
-
- subroutine MudSystem_Step
- use MudSystem
- use CManifolds
- implicit none
- !print* , 'MudSystem_Step'
- !CALL main
- if(IsTraverse) then
- call LineupAndPath()
- IsTraverse = .false.
- endif
- call main()
- end subroutine MudSystem_Step
-
- subroutine MudSystemMainBody
- USE CSimulationVariables
- use MudSystem
- implicit none
-
- ! INTEGER :: MudDuration
- ! integer,dimension(8) :: MudStartTime , MudEndTime
- !
- !CALL MudSystem_StartUp()
- ! loop1: DO
- !
- ! CALL DATE_AND_TIME(values=MudStartTime)
- ! !WRITE (*,*) '***MudSys_timeCounter', MudSys_timeCounter
- !
- !
- ! CALL main
- !
- ! CALL DATE_AND_TIME(values=MudEndTime)
- !
- ! MudDuration = 3600000 * (MudEndTime(5) - MudStartTime(5)) + 60000 * (MudEndTime(6) - MudStartTime(6)) + 1000 * (MudEndTime(7) - MudStartTime(7)) + (MudEndTime(8) - MudStartTime(8))
- !
- ! if (MudDuration < 100) then
- ! ELSE
- ! WRITE (*,*) 'Mud System run duration exceeded 100 ms and =', MudDuration
- ! end if
- !
- ! IF (IsStopped==.true.) THEN
- ! EXIT loop1
- ! ENDIF
- !
- ! !CALL DATE_AND_TIME(values=FlowEndTime)
- ! !WRITE (*,*) 'FlowEndTime=' , FlowEndTime
- !
- ! !FlowDuration = FlowEndTime(8) - FlowStartTime(8)
- !
- ! !WRITE (*,*) 'FlowDuration Mud system=' , FlowDuration
- !
- ! ENDDO loop1
- !
- ! CALL DEALLOCATE_ARRAYS_MudSystem()
-
- end subroutine MudSystemMainBody
-
- end module MudSystemMain
|