Changeset 2235 in lmdz_wrf
- Timestamp:
- Nov 16, 2018, 10:27:45 PM (6 years ago)
- Location:
- trunk/tools
- Files:
-
- 3 edited
Legend:
- Unmodified
- Added
- Removed
-
trunk/tools/module_generic.f90
r1683 r2235 13 13 ! Nvalues_2DArrayI: Number of different values of a 2D integer array 14 14 ! mat2DPosition: Function to provide the i, j indices of a given value inside a 2D matrix 15 ! numberTimes: Function to provide the number of times that a given set of characters happen within a string 15 16 ! RangeI: Function to provide a range of d1 values from 'iniv' to 'endv', of integer values in a vector 16 17 ! RangeR: Function to provide a range of d1 values from 'iniv' to 'endv', of real values in a vector … … 225 226 226 227 END FUNCTION Index2DArrayR_K 228 229 INTEGER FUNCTION numberTimes(String, charv) 230 ! Function to provide the number of times that a given set of characters happen within a string 231 232 IMPLICIT NONE 233 234 CHARACTER(LEN=*), INTENT(IN) :: String, charv 235 236 ! Local 237 INTEGER :: i, Lstring, Lcharv 238 239 numberTimes = 0 240 241 Lstring = LEN_TRIM(String) 242 Lcharv = LEN_TRIM(charv) 243 244 DO i=1,Lstring - Lcharv 245 IF (String(i:i+Lcharv-1) == TRIM(charv)) numberTimes = numberTimes + 1 246 END DO 247 248 END FUNCTION numberTimes 249 227 250 228 251 FUNCTION RangeI(d1, iniv, endv) -
trunk/tools/module_scientific.f90
r2210 r2235 24 24 ! paths_border: Subroutine to search the paths of a border field. 25 25 ! path_properties: Subroutine to determine the properties of a path 26 ! percentiles_R_K*D: Subroutine to compute the percentiles of a *D R_K array along given set of axis 26 27 ! polygon_properties: Subroutine to determine the properties of a polygon (as .TRUE. matrix) 27 28 ! polygons: Subroutine to search the polygons of a border field. FORTRAN based. 1st = 1! … … 3682 3683 END SUBROUTINE runmean_F1D 3683 3684 3685 SUBROUTINE percentiles_R_K2D(values, axisS, Npercen, d1, d2, percentiles) 3686 ! Subroutine to compute the percentiles of a 2D R_K array along given set of axis 3687 3688 IMPLICIT NONE 3689 3690 INTEGER, INTENT(in) :: d1, d2, Npercen 3691 REAL(r_k), DIMENSION(d1,d2), INTENT(in) :: values 3692 CHARACTER(LEN=*), INTENT(in) :: axisS 3693 REAL(r_k), DIMENSION(d1, d2, Npercen), INTENT(out) :: percentiles 3694 3695 ! Local 3696 INTEGER :: i 3697 INTEGER :: Lstring, LaxisS, iichar 3698 CHARACTER(LEN=1000) :: splitaxis 3699 INTEGER, DIMENSION(1) :: axis1 3700 CHARACTER(LEN=200), DIMENSION(2) :: axis2S 3701 INTEGER, DIMENSION(2) :: axis2 3702 CHARACTER(LEN=1) :: Naxs 3703 3704 !!!!!!! Variables 3705 ! d1,d2: length of the 2D dimensions 3706 ! values: values to use to compute the percentiles 3707 ! axisS: ':' separated list of axis to use to compute the percentiles ('all' for all axes) 3708 ! Npercen: number of percentiles 3709 ! percentiles: percentiles of the daata 3710 3711 fname = 'percentiles_R_K2D' 3712 3713 LaxisS = LEN_TRIM(axisS) 3714 iichar = numberTimes(axisS(1:LaxisS), ':') 3715 3716 splitaxis = '' 3717 splitaxis(1:LaxisS) = axisS(1:LaxisS) 3718 percentiles = 0. 3719 3720 IF (iichar == 0) THEN 3721 READ(axisS,'(I1)')axis1(1) 3722 ELSE IF (iichar == 1) THEN 3723 CALL split(splitaxis, ':', 2, axis2S) 3724 ELSE 3725 WRITE(Naxs,'(A1)')iichar 3726 msg = "' rank 2 values can not compute percentiles using " // Naxs // "' number of axis !!" 3727 CALL ErrMsg(msg, fname, -1) 3728 END IF 3729 3730 IF (TRIM(axisS) == 'all') iichar = 2 3731 3732 IF (iichar == 0) THEN 3733 ! Might be a better way, but today I can't think it !! 3734 IF (axis1(1) == 1) THEN 3735 DO i=1, d2 3736 CALL quantilesR_K(d1, values(:,i), Npercen, percentiles(1,i,:)) 3737 END DO 3738 ELSE IF (axis1(1) == 2) THEN 3739 DO i=1, d1 3740 CALL quantilesR_K(d2, values(i,:), Npercen, percentiles(i,1,:)) 3741 END DO 3742 ELSE 3743 WRITE(Naxs,'(A1)')axis1(1) 3744 msg = "' rank 2 values can not compute percentiles using axis " // Naxs // "' !!" 3745 CALL ErrMsg(msg, fname, -1) 3746 END IF 3747 ELSE 3748 CALL quantilesR_K(d1*d2, RESHAPE(values, (/d1*d2/)), Npercen, percentiles(1,1,:)) 3749 END IF 3750 3751 END SUBROUTINE percentiles_R_K2D 3752 3753 SUBROUTINE percentiles_R_K3D(values, axisS, Npercen, d1, d2, d3, percentiles) 3754 ! Subroutine to compute the percentiles of a 3D R_K array along given set of axis 3755 3756 IMPLICIT NONE 3757 3758 INTEGER, INTENT(in) :: d1, d2, d3, Npercen 3759 REAL(r_k), DIMENSION(d1,d2,d3), INTENT(in) :: values 3760 CHARACTER(LEN=*), INTENT(in) :: axisS 3761 REAL(r_k), DIMENSION(d1, d2, d3, Npercen), INTENT(out) :: percentiles 3762 3763 ! Local 3764 INTEGER :: i, j 3765 INTEGER :: Lstring, LaxisS, iichar 3766 CHARACTER(LEN=1000) :: splitaxis 3767 INTEGER, DIMENSION(1) :: axis1 3768 CHARACTER(LEN=200), DIMENSION(2) :: axis2S 3769 INTEGER, DIMENSION(2) :: axis2 3770 CHARACTER(LEN=200), DIMENSION(3) :: axis3S 3771 INTEGER, DIMENSION(3) :: axis3 3772 CHARACTER(LEN=1) :: Naxs1, Naxs2 3773 3774 !!!!!!! Variables 3775 ! d1,d2: length of the 2D dimensions 3776 ! values: values to use to compute the percentiles 3777 ! axisS: ':' separated list of axis to use to compute the percentiles ('all' for all axes) 3778 ! Npercen: number of percentiles 3779 ! percentiles: percentiles of the daata 3780 3781 fname = 'percentiles_R_K3D' 3782 3783 LaxisS = LEN_TRIM(axisS) 3784 iichar = numberTimes(axisS(1:LaxisS), ':') 3785 3786 splitaxis = '' 3787 splitaxis(1:LaxisS) = axisS(1:LaxisS) 3788 3789 percentiles = 0. 3790 3791 IF (iichar == 0) THEN 3792 READ(axisS,'(I1)')axis1(1) 3793 ELSE IF (iichar == 1) THEN 3794 CALL split(splitaxis, ':', 2, axis2S) 3795 DO i=1,2 3796 READ(axis2S(i), '(I1)')axis2(i) 3797 END DO 3798 ELSE IF (iichar == 2) THEN 3799 CALL split(splitaxis, ':', 3, axis3S) 3800 ELSE 3801 READ(Naxs1,'(A1)')iichar 3802 msg = "' rank 3 values can not compute percentiles using " // Naxs1 // "' number of axis !!" 3803 CALL ErrMsg(msg, fname, -1) 3804 END IF 3805 3806 IF (TRIM(axisS) == 'all') iichar = 3 3807 3808 IF (iichar == 0) THEN 3809 ! Might be a better way, but today I can't think it !! 3810 IF (axis1(1) == 1) THEN 3811 DO i=1, d2 3812 DO j=1, d3 3813 CALL quantilesR_K(d1, values(:,i,j), Npercen, percentiles(1,i,j,:)) 3814 END DO 3815 END DO 3816 ELSE IF (axis1(1) == 2) THEN 3817 DO i=1, d1 3818 DO j=1, d3 3819 CALL quantilesR_K(d2, values(i,:,j), Npercen, percentiles(i,1,j,:)) 3820 END DO 3821 END DO 3822 ELSE IF (axis1(1) == 3) THEN 3823 DO i=1, d1 3824 DO j=1, d2 3825 CALL quantilesR_K(d3, values(i,j,:), Npercen, percentiles(i,j,1,:)) 3826 END DO 3827 END DO 3828 ELSE 3829 WRITE(Naxs1,'(A1)')axis1(1) 3830 msg = "' rank 3 values can not compute percentiles using axis " // Naxs1 // "' !!" 3831 CALL ErrMsg(msg, fname, -1) 3832 END IF 3833 ELSE IF (iichar == 1) THEN 3834 ! Might be a better way, but today I can't think it !! 3835 IF (axis2(1) == 1 .AND. axis2(2) == 2) THEN 3836 DO i=1, d3 3837 CALL quantilesR_K(d1*d2, RESHAPE(values(:,:,i), (/d1*d2/)), Npercen, percentiles(1,1,i,:)) 3838 END DO 3839 ELSE IF (axis2(1) == 1 .AND. axis2(2) == 3) THEN 3840 DO i=1, d2 3841 CALL quantilesR_K(d1*d3, RESHAPE(values(:,i,:), (/d1*d3/)), Npercen, percentiles(1,i,1,:)) 3842 END DO 3843 ELSE IF (axis2(1) == 2 .AND. axis2(2) == 3) THEN 3844 DO i=1, d1 3845 CALL quantilesR_K(d2*d3, RESHAPE(values(i,:,:), (/d2*d3/)), Npercen, percentiles(i,1,1,:)) 3846 END DO 3847 ELSE 3848 WRITE(Naxs1,'(A1)')axis2(1) 3849 WRITE(Naxs2,'(A1)')axis2(2) 3850 msg="' rank 3 values can not compute percentiles using axis "//Naxs1// ', ' // Naxs2 // "' !!" 3851 CALL ErrMsg(msg, fname, -1) 3852 END IF 3853 ELSE 3854 CALL quantilesR_K(d1*d2*d3, RESHAPE(values, (/d1*d2*d3/)), Npercen, percentiles(1,1,1,:)) 3855 END IF 3856 3857 END SUBROUTINE percentiles_R_K3D 3858 3859 SUBROUTINE percentiles_R_K4D(values, axisS, Npercen, d1, d2, d3, d4, percentiles) 3860 ! Subroutine to compute the percentiles of a 4D R_K array along given set of axis 3861 3862 IMPLICIT NONE 3863 3864 INTEGER, INTENT(in) :: d1, d2, d3, d4, Npercen 3865 REAL(r_k), DIMENSION(d1,d2,d3,d4), INTENT(in) :: values 3866 CHARACTER(LEN=*), INTENT(in) :: axisS 3867 REAL(r_k), DIMENSION(d1,d2,d3,d4,Npercen), INTENT(out) :: percentiles 3868 3869 ! Local 3870 INTEGER :: i, j, k 3871 INTEGER :: Lstring, LaxisS, iichar 3872 CHARACTER(LEN=1000) :: splitaxis 3873 INTEGER, DIMENSION(1) :: axis1 3874 CHARACTER(LEN=200), DIMENSION(2) :: axis2S 3875 INTEGER, DIMENSION(2) :: axis2 3876 CHARACTER(LEN=200), DIMENSION(3) :: axis3S 3877 INTEGER, DIMENSION(3) :: axis3 3878 CHARACTER(LEN=200), DIMENSION(4) :: axis4S 3879 CHARACTER(LEN=1) :: Naxs1, Naxs2, Naxs3 3880 3881 !!!!!!! Variables 3882 ! d1,d2: length of the 2D dimensions 3883 ! values: values to use to compute the percentiles 3884 ! axisS: ':' separated list of axis to use to compute the percentiles ('all' for all axes) 3885 ! Npercen: number of percentiles 3886 ! percentiles: percentiles of the daata 3887 3888 fname = 'percentiles_R_K3D' 3889 3890 LaxisS = LEN_TRIM(axisS) 3891 iichar = numberTimes(axisS(1:LaxisS), ':') 3892 3893 splitaxis = '' 3894 splitaxis(1:LaxisS) = axisS(1:LaxisS) 3895 3896 percentiles = 0. 3897 3898 PRINT *,'iichar:', iichar, axisS(1:LaxisS) 3899 3900 IF (iichar == 0) THEN 3901 READ(axisS,'(I1)')axis1(1) 3902 ELSE IF (iichar == 1) THEN 3903 CALL split(splitaxis, ':', 2, axis2S) 3904 DO i=1,2 3905 READ(axis2S(i), '(I1)')axis2(i) 3906 END DO 3907 ELSE IF (iichar == 2) THEN 3908 CALL split(splitaxis, ':', 3, axis3S) 3909 DO i=1,3 3910 READ(axis3S(i), '(I1)')axis3(i) 3911 END DO 3912 ELSE IF (iichar == 3) THEN 3913 CALL split(splitaxis, ':', 4, axis4S) 3914 ELSE 3915 READ(Naxs1,'(A1)')iichar 3916 msg = "' rank 4 values can not compute percentiles using " // Naxs1 // "' number of axis !!" 3917 CALL ErrMsg(msg, fname, -1) 3918 END IF 3919 3920 IF (TRIM(axisS) == 'all') iichar = 4 3921 3922 IF (iichar == 0) THEN 3923 ! Might be a better way, but today I can't think it !! 3924 IF (axis1(1) == 1) THEN 3925 DO i=1, d2 3926 DO j=1, d3 3927 DO k=1, d4 3928 CALL quantilesR_K(d1, values(:,i,j,k), Npercen, percentiles(1,i,j,k,:)) 3929 END DO 3930 END DO 3931 END DO 3932 ELSE IF (axis1(1) == 2) THEN 3933 DO i=1, d1 3934 DO j=1, d3 3935 DO k=1, d4 3936 CALL quantilesR_K(d2, values(i,:,j,k), Npercen, percentiles(i,1,j,k,:)) 3937 END DO 3938 END DO 3939 END DO 3940 ELSE IF (axis1(1) == 3) THEN 3941 DO i=1, d1 3942 DO j=1, d2 3943 DO k=1, d4 3944 CALL quantilesR_K(d3, values(i,j,:,k), Npercen, percentiles(i,j,1,k,:)) 3945 END DO 3946 END DO 3947 END DO 3948 ELSE IF (axis1(1) == 4) THEN 3949 DO i=1, d1 3950 DO j=1, d2 3951 DO k=1, d3 3952 CALL quantilesR_K(d4, values(i,j,k,:), Npercen, percentiles(i,j,k,1,:)) 3953 END DO 3954 END DO 3955 END DO 3956 ELSE 3957 WRITE(Naxs1,'(A1)')axis1(1) 3958 msg = "' rank 3 values can not compute percentiles using axis " // Naxs1 // "' !!" 3959 CALL ErrMsg(msg, fname, -1) 3960 END IF 3961 ELSE IF (iichar == 1) THEN 3962 ! Might be a better way, but today I can't think it !! 3963 IF (axis2(1) == 1 .AND. axis2(2) == 2) THEN 3964 DO i=1, d3 3965 DO j=1, d4 3966 CALL quantilesR_K(d1*d2, RESHAPE(values(:,:,i,j), (/d1*d2/)), Npercen, & 3967 percentiles(1,1,i,j,:)) 3968 END DO 3969 END DO 3970 ELSE IF (axis2(1) == 1 .AND. axis2(2) == 3) THEN 3971 DO i=1, d2 3972 DO j=1, d4 3973 CALL quantilesR_K(d1*d3, RESHAPE(values(:,i,:,j), (/d1*d3/)), Npercen, & 3974 percentiles(1,i,1,j,:)) 3975 END DO 3976 END DO 3977 ELSE IF (axis2(1) == 1 .AND. axis2(2) == 4) THEN 3978 DO i=1, d2 3979 DO j=1, d3 3980 CALL quantilesR_K(d1*d4, RESHAPE(values(:,i,j,:), (/d1*d4/)), Npercen, & 3981 percentiles(1,i,j,1,:)) 3982 END DO 3983 END DO 3984 ELSE IF (axis2(1) == 2 .AND. axis2(2) == 3) THEN 3985 DO i=1, d1 3986 DO j=1, d4 3987 CALL quantilesR_K(d2*d3, RESHAPE(values(i,:,:,j), (/d2*d3/)), Npercen, & 3988 percentiles(i,1,1,j,:)) 3989 END DO 3990 END DO 3991 ELSE IF (axis2(1) == 2 .AND. axis2(2) == 4) THEN 3992 DO i=1, d1 3993 DO j=1, d3 3994 CALL quantilesR_K(d2*d4, RESHAPE(values(i,:,j,:), (/d2*d4/)), Npercen, & 3995 percentiles(i,1,j,1,:)) 3996 END DO 3997 END DO 3998 ELSE IF (axis2(1) == 3 .AND. axis2(2) == 4) THEN 3999 DO i=1, d1 4000 DO j=1, d2 4001 CALL quantilesR_K(d3*d4, RESHAPE(values(i,j,:,:), (/d3*d4/)), Npercen, & 4002 percentiles(i,j,1,1,:)) 4003 END DO 4004 END DO 4005 ELSE 4006 WRITE(Naxs1,'(A1)')axis2(1) 4007 WRITE(Naxs2,'(A1)')axis2(2) 4008 msg="' rank 4 values can not compute percentiles using axis "//Naxs1// ', ' // Naxs2 // "' !!" 4009 CALL ErrMsg(msg, fname, -1) 4010 END IF 4011 ELSE IF (iichar == 2) THEN 4012 IF (axis2(1) == 1 .AND. axis2(2) == 2 .AND. axis3(3) == 3) THEN 4013 DO i=1, d4 4014 CALL quantilesR_K(d1*d2*d3, RESHAPE(values(:,:,:,i), (/d1*d2*d3/)), Npercen, & 4015 percentiles(1,1,1,i,:)) 4016 END DO 4017 ELSE IF (axis2(1) == 1 .AND. axis2(2) == 2 .AND. axis3(3) == 4) THEN 4018 DO i=1, d3 4019 CALL quantilesR_K(d1*d2*d4, RESHAPE(values(:,:,i,:), (/d1*d2*d4/)), Npercen, & 4020 percentiles(1,1,i,1,:)) 4021 END DO 4022 ELSE IF (axis2(1) == 1 .AND. axis2(2) == 3 .AND. axis3(3) == 4) THEN 4023 DO i=1, d2 4024 CALL quantilesR_K(d1*d3*d4, RESHAPE(values(:,i,:,:), (/d1*d3*d4/)), Npercen, & 4025 percentiles(1,i,1,1,:)) 4026 END DO 4027 ELSE IF (axis2(1) == 2 .AND. axis2(2) == 3 .AND. axis3(3) == 4) THEN 4028 DO i=1, d1 4029 CALL quantilesR_K(d2*d3*d4, RESHAPE(values(i,:,:,:), (/d2*d3*d4/)), Npercen, & 4030 percentiles(i,1,1,1,:)) 4031 END DO 4032 ELSE 4033 WRITE(Naxs1,'(A1)')axis3(1) 4034 WRITE(Naxs2,'(A1)')axis3(2) 4035 WRITE(Naxs3,'(A1)')axis3(2) 4036 msg="' rank 4 values can not compute percentiles using axis "// Naxs1 // ', ' // Naxs2 // & 4037 ', ' // Naxs3 //"' !!" 4038 CALL ErrMsg(msg, fname, -1) 4039 END IF 4040 ELSE 4041 CALL quantilesR_K(d1*d2*d3*d4, RESHAPE(values, (/d1*d2*d3*d4/)), Npercen, percentiles(1,1,1,1,:)) 4042 END IF 4043 4044 END SUBROUTINE percentiles_R_K4D 4045 3684 4046 END MODULE module_scientific -
trunk/tools/nc_var_tools.py
r2225 r2235 17 17 import subprocess as sub 18 18 import module_ForDef as fdef 19 import module_ForSci as fsci 19 20 20 21 ####### Contents: … … 25431 25432 timestatsv.append(amount) 25432 25433 statn = timest.split('@')[iamount+1] 25434 if not gen.searchInlist(Lstatn.keys(), statn): 25435 print errormsg 25436 print ' ' + fname + ": statistics '" + statn + "' not ready !!" 25437 print ' available ones:', Lstatn.keys() 25438 quit(-1) 25439 25433 25440 timestatsv.append(statn) 25434 if statn == 'percentiles': 25441 if statn == 'percentiles': 25442 if len(timest.split('@')) != iamount+3: 25443 print errormsg 25444 print ' ' + fname + ': no number of percentiles provided!!' 25445 print ' provided values:', timest 25446 quit(-1) 25435 25447 Npercen = int(timest.split('@')[iamount+2]) 25436 25448 timestatsv.append(Npercen) … … 25464 25476 amount = timestatv[iamount] 25465 25477 25466 timeslice, Ntimeslice = gen.time_slices(timevc, timeu, timec, period, amount) 25478 time_desc = gen.temporal_desc(timevc, timeu, timec) 25479 timeslice, Ntimeslice= gen.time_slices(timevc, timeu, timec, period, amount, \ 25480 time_desc) 25467 25481 statslices[iTst] = [Ntimeslice, timeslice] 25468 25482 … … 25600 25614 newvarn = varn+str(amount)+periodn+statn 25601 25615 25602 newvarv = onewnc.createVariable(newvarn, 'f', tuple(dimntstat), \ 25603 fill_value=gen.fillValueR) 25616 if statn != 'percentiles': 25617 newvarv = onewnc.createVariable(newvarn, 'f', tuple(dimntstat), \ 25618 fill_value=gen.fillValueF) 25619 else: 25620 if not gen.searchInlist(onewnc.dimensions, 'percentile'): 25621 print ' ' + fname + ": adding '" + statn + "' dimension !!" 25622 newdim = onewnc.createDimension('percentile', Npercen+1) 25623 25624 newvar= onewnc.createVariable('percentile','f', ('percentile')) 25625 newvar[:] = np.arange(0.,100.+100./Npercen,100./Npercen) 25626 basicvardef(newvar, 'percentile', 'Percentile', '%') 25627 25628 dimntstat = ['percentile'] + dimntstat 25629 newvarv = onewnc.createVariable(newvarn, 'f', tuple(dimntstat), \ 25630 fill_value=gen.fillValueF) 25631 25604 25632 varunits = get_varunits(ovar) 25605 25633 if statn == 'std': varunits = '(' + varunits + ')**2)' … … 25624 25652 newvarN[islc] = timeslcv[1]-timeslcv[0]+1 25625 25653 25626 timeslc = [] 25627 shapetimeslc = [] 25628 tstatslc = [] 25629 for dn in vardims: 25630 if dn == timedimn: 25631 timeslc.append(slice(timeslcv[0],timeslcv[1],timeslcv[2])) 25632 shapetimeslc.append(timeslcv[1]-timeslcv[0]+1) 25633 tstatslc.append(islc) 25634 else: 25635 Ldim = len(onc.dimensions[dn]) 25636 timeslc.append(slice(0,Ldim)) 25637 shapetimeslc.append(Ldim) 25638 tstatslc.append(slice(0,Ldim)) 25639 25640 tvals = ovar[tuple(timeslc)] 25654 if periodn[0:3] != 'agg': 25655 timeslc = [] 25656 shapetimeslc = [] 25657 tstatslc = [] 25658 for dn in vardims: 25659 if dn == timedimn: 25660 timeslc.append(slice(timeslcv[0],timeslcv[1],timeslcv[2])) 25661 shapetimeslc.append(timeslcv[1]-timeslcv[0]+1) 25662 tstatslc.append(islc) 25663 else: 25664 Ldim = len(onc.dimensions[dn]) 25665 timeslc.append(slice(0,Ldim)) 25666 shapetimeslc.append(Ldim) 25667 tstatslc.append(slice(0,Ldim)) 25668 tvals = ovar[tuple(timeslc)] 25669 else: 25670 newshape = list(vals.shape) 25671 aggslc = tslc[islc] 25672 NNtslc = len(aggslc) 25673 newshape[itdim] = NNtslc 25674 tvals = np.zeros(tuple(newshape), dtype=vals.dtype) 25675 origshape = list(vals.shape) 25676 iishape = list(vals.shape) 25677 for iislc in range(NNtslc): 25678 origshape[itdim] = aggslc[iislc] 25679 iishape[itdim] = iislc 25680 tvals[tuple(iishape)] = vals[tuple(origshape)] 25681 25641 25682 if statn == 'min': 25642 25683 newvarv[tuple(tstatslc)] = np.min(tvals, axis=itdim) … … 25649 25690 elif statn == 'std': 25650 25691 newvarv[tuple(tstatslc)] = np.std(tvals, axis=itdim) 25692 elif statn == 'percentiles': 25693 axesS = str(len(tvals.shape)-itdim) 25694 if tvals.shape[itdim] < Npercen: 25695 tstatslc = [slice(0,Npercen+1)] + tstatslc 25696 print warnmsg 25697 print ' ' + fname + ': Not enough temporal data:', \ 25698 tvals.shape[itdim], ' to copmute:',Npercen, 'percentiles !!' 25699 dimspercen = [Npercen+1] 25700 for i in range(len(tvals.shape)): 25701 if i != itdim: 25702 dimspercen.append(tvals.shape[i]) 25703 percens = np.ones(tuple(dimspercen), dtype=np.float)*gen.fillValueF 25704 newvarv[tuple(tstatslc)] = percens[:] 25705 else: 25706 tvalst = tvals.transpose() 25707 if len(tvals.shape) == 4: 25708 percenst = fsci.module_scientific.percentiles_r_k4d(tvalst, \ 25709 axesS, npercen=Npercen+1, d1=tvals.shape[3], \ 25710 d2=tvals.shape[2], d3=tvals.shape[1], d4=tvals.shape[0]) 25711 elif len(tvals.shape) == 3: 25712 percenst = fsci.module_scientific.percentiles_r_k3d(tvalst, \ 25713 axesS, npercen=Npercen+1, d1=tvals.shape[2], \ 25714 d2=tvals.shape[1], d3=tvals.shape[0]) 25715 elif len(tvals.shape) == 2: 25716 percenst = fsci.module_scientific.percentiles_r_k2d(tvalst, \ 25717 axesS, npercen=Npercen+1, d1=tvals.shape[1], \ 25718 d2=tvals.shape[0]) 25719 elif len(tvals.shape) == 1: 25720 quants = Quantiles(tvals, Npercen) 25721 percenst = quants.quantilesv 25722 else: 25723 print errormsg 25724 print ' ' +fname+ ': rank of temporal data:', tvals.shape, \ 25725 'not ready !!' 25726 quit(-1) 25727 percens = percenst.transpose() 25728 25729 shapev = list(percens.shape) 25730 for idd in range(len(shapev)): 25731 if idd != itdim+1: 25732 shapev[idd] = slice(0,shapev[idd]) 25733 else: 25734 shapev[itdim+1] = 0 25735 25736 tstatslc = [slice(0,Npercen+1)] + tstatslc 25737 newvarv[tuple(tstatslc)] = percens[tuple(shapev)] 25651 25738 else: 25652 25739 print errormsg
Note: See TracChangeset
for help on using the changeset viewer.