|
| 1 | +module cosp2_test |
| 2 | + |
| 3 | + use physcons, ONLY: grav => con_g |
| 4 | + use GFS_typedefs, ONLY: GFS_control_type, GFS_diag_type, & |
| 5 | + GFS_statein_type, GFS_stateout_type, GFS_sfcprop_type, & |
| 6 | + GFS_radtend_type, GFS_init_type |
| 7 | + |
| 8 | + implicit none |
| 9 | + |
| 10 | + public :: cosp2_offline |
| 11 | + |
| 12 | +contains |
| 13 | + |
| 14 | + !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% |
| 15 | + ! SUBROUTINE cosp2_offline |
| 16 | + !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% |
| 17 | + subroutine cosp2_offline (Model, Statein, Stateout, Sfcprop, Radtend, Diag, Init_parm) |
| 18 | + |
| 19 | + implicit none |
| 20 | + |
| 21 | + type(GFS_init_type), intent(in) :: Init_parm |
| 22 | + type (GFS_control_type), intent (in) :: Model |
| 23 | + type (GFS_statein_type), intent (in) :: Statein(:) |
| 24 | + type (GFS_stateout_type), intent (in) :: Stateout(:) |
| 25 | + type (GFS_sfcprop_type), intent (in) :: Sfcprop(:) |
| 26 | + type (GFS_radtend_type), intent (in) :: Radtend(:) |
| 27 | + |
| 28 | + type (GFS_diag_type), intent (inout) :: Diag(:) |
| 29 | + |
| 30 | + integer :: nb, Nlevels, nblks |
| 31 | + |
| 32 | + nblks = size(Init_parm%blksz) |
| 33 | + |
| 34 | + Nlevels = Model%levs |
| 35 | + |
| 36 | + do nb = 1, nblks |
| 37 | + |
| 38 | + Diag(nb)%cosp%p = Statein(nb)%prsl |
| 39 | + Diag(nb)%cosp%ph = Statein(nb)%prsi(:,1:Nlevels) |
| 40 | + Diag(nb)%cosp%zlev = Statein(nb)%phil / grav |
| 41 | + Diag(nb)%cosp%zlev_half = Statein(nb)%phii(:,1:Nlevels) / grav |
| 42 | + Diag(nb)%cosp%T = Stateout(nb)%gt0 |
| 43 | + Diag(nb)%cosp%sh = Stateout(nb)%gq0(:,:,1) |
| 44 | + Diag(nb)%cosp%tca = Stateout(nb)%gq0(:,:,Model%ntclamt) |
| 45 | + Diag(nb)%cosp%cca = 0 |
| 46 | + Diag(nb)%cosp%mr_lsliq = Stateout(nb)%gq0(:,:,Model%ntcw) |
| 47 | + Diag(nb)%cosp%mr_lsice = Stateout(nb)%gq0(:,:,Model%ntiw) |
| 48 | + Diag(nb)%cosp%mr_ccliq = 0.0 |
| 49 | + Diag(nb)%cosp%mr_ccice = 0.0 |
| 50 | + Diag(nb)%cosp%fl_lsrain = Diag(nb)%pfr / 86400. |
| 51 | + Diag(nb)%cosp%fl_lssnow = Diag(nb)%pfs / 86400. |
| 52 | + Diag(nb)%cosp%fl_lsgrpl = Diag(nb)%pfg / 86400. |
| 53 | + Diag(nb)%cosp%fl_ccrain = 0.0 |
| 54 | + Diag(nb)%cosp%fl_ccsnow = 0.0 |
| 55 | + Diag(nb)%cosp%Reff_LSCLIQ = Diag(nb)%reff(:,:,1) * 1.e-6 |
| 56 | + Diag(nb)%cosp%Reff_LSCICE = Diag(nb)%reff(:,:,2) * 1.e-6 |
| 57 | + Diag(nb)%cosp%Reff_LSRAIN = Diag(nb)%reff(:,:,3) * 1.e-6 |
| 58 | + Diag(nb)%cosp%Reff_LSSNOW = Diag(nb)%reff(:,:,4) * 1.e-6 |
| 59 | + Diag(nb)%cosp%Reff_LSGRPL = Diag(nb)%reff(:,:,5) * 1.e-6 |
| 60 | + Diag(nb)%cosp%dtau_s = Diag(nb)%ctau(:,:,1) |
| 61 | + Diag(nb)%cosp%dtau_c = 0.0 |
| 62 | + Diag(nb)%cosp%dem_s = Diag(nb)%ctau(:,:,2) |
| 63 | + Diag(nb)%cosp%dem_c = 0.0 |
| 64 | + Diag(nb)%cosp%skt = Sfcprop(nb)%tsfc |
| 65 | + Diag(nb)%cosp%landmask = 1-abs(Sfcprop(nb)%slmsk-1) |
| 66 | + Diag(nb)%cosp%mr_ozone = Stateout(nb)%gq0(:,:,Model%ntoz) |
| 67 | + Diag(nb)%cosp%u_wind = Stateout(nb)%gu0 |
| 68 | + Diag(nb)%cosp%v_wind = Stateout(nb)%gv0 |
| 69 | + Diag(nb)%cosp%sunlit = ceiling(Radtend(nb)%coszen) |
| 70 | + Diag(nb)%cosp%surfelev = Sfcprop(nb)%oro |
| 71 | + |
| 72 | + enddo |
| 73 | + |
| 74 | + end subroutine cosp2_offline |
| 75 | + |
| 76 | + end module cosp2_test |
| 77 | + |
0 commit comments