ROMS
Loading...
Searching...
No Matches
inp_decode_mod::load_l Interface Reference

Public Member Functions

integer function load_0d_l (ninp, vinp, nout, vout)
 
integer function load_1d_l (ninp, vinp, nout, vout)
 
integer function load_2d_l (ninp, vinp, iout, jout, vout)
 
integer function load_3d_l (ninp, vinp, iout, jout, kout, vout)
 

Detailed Description

Definition at line 64 of file inp_decode.F.

Member Function/Subroutine Documentation

◆ load_0d_l()

integer function inp_decode_mod::load_l::load_0d_l ( integer, intent(in) ninp,
character (len=*), dimension(:), intent(in) vinp,
integer, intent(in) nout,
logical, intent(out) vout )

Definition at line 717 of file inp_decode.F.

718!
719!***********************************************************************
720! !
721! It loads input values into a requested model scalar logical !
722! variable. !
723! !
724! On Input: !
725! !
726! Ninp Number of input elements to process in Vinp (integer) !
727! Vinp Input values (character 1D array) !
728! Nout Size of output logical variable dimension (not used) !
729! !
730! On Output: !
731! !
732! Vout Output scalar logical variable !
733! Nval Number of output values processed !
734! !
735!***********************************************************************
736!
737! Imported variable declarations.
738!
739 integer, intent(in) :: Ninp, Nout
740 character (len=*), intent(in) :: Vinp(:)
741!
742 logical, intent(out) :: Vout
743!
744! Local variable declarations.
745!
746 integer :: ic
747 integer :: Nval
748!
749!-----------------------------------------------------------------------
750! Load scalar logical variable with input value.
751!-----------------------------------------------------------------------
752!
753 ic=1
754 IF ((vinp(ic)(1:1).eq.'T').or. &
755 & (vinp(ic)(1:1).eq.'t')) THEN
756 vout=.true.
757 ELSE
758 vout=.false.
759 END IF
760 nval=ic
761!
762 RETURN

◆ load_1d_l()

integer function inp_decode_mod::load_l::load_1d_l ( integer, intent(in) ninp,
character (len=*), dimension(:), intent(in) vinp,
integer, intent(in) nout,
logical, dimension(:), intent(out) vout )

Definition at line 765 of file inp_decode.F.

766!
767!***********************************************************************
768! !
769! It loads input values into a requested model 1D logical array. !
770! !
771! On Input: !
772! !
773! Ninp Number of input elements to process in Vinp (integer) !
774! Vinp Input values (character 1D array) !
775! Nout Size of output logical variable dimension !
776! !
777! On Output: !
778! !
779! Vout Output 1D logical variable !
780! Nval Number of output values processed !
781! !
782!***********************************************************************
783!
784! Imported variable declarations.
785!
786 integer, intent(in) :: Ninp, Nout
787 character (len=*), intent(in) :: Vinp(:)
788!
789 logical, intent(out) :: Vout(:)
790!
791! Local variable declarations.
792!
793 logical :: LastValue
794
795 integer :: Nstr, i, ic
796 integer :: Nval
797!
798!-----------------------------------------------------------------------
799! Load logical variable with input values.
800!-----------------------------------------------------------------------
801!
802! If not all values are provided for variable, assume the last value
803! for the rest of the array.
804!
805 ic=0
806 lastvalue=.false.
807 IF (ninp.le.nout) THEN
808 DO i=1,ninp
809 ic=ic+1
810 IF ((vinp(i)(1:1).eq.'T').or. &
811 & (vinp(i)(1:1).eq.'t')) THEN
812 vout(i)=.true.
813 ELSE
814 vout(i)=.false.
815 END IF
816 lastvalue=vout(i)
817 END DO
818 IF (nout.gt.ninp) THEN
819 nstr=ninp+1
820 DO i=nstr,nout
821 ic=ic+1
822 vout(i)=lastvalue
823 END DO
824 END IF
825 ELSE
826 DO i=1,nout
827 ic=ic+1
828 IF ((vinp(i)(1:1).eq.'T').or. &
829 & (vinp(i)(1:1).eq.'t')) THEN
830 vout(i)=.true.
831 ELSE
832 vout(i)=.false.
833 END IF
834 END DO
835 END IF
836 nval=ic
837!
838 RETURN

References mod_param::nstr.

◆ load_2d_l()

integer function inp_decode_mod::load_l::load_2d_l ( integer, intent(in) ninp,
character (len=*), dimension(:), intent(in) vinp,
integer, intent(in) iout,
integer, intent(in) jout,
logical, dimension(:,:), intent(out) vout )

Definition at line 841 of file inp_decode.F.

842!
843!***********************************************************************
844! !
845! It loads input values into a requested model 2D logical array. !
846! !
847! On Input: !
848! !
849! Ninp Number of input elements to process in Vinp (integer) !
850! Vinp Input values (character 1D array) !
851! Iout Size of output logical variable first I-dimension !
852! Jout Size of output logical variable second J-dimension !
853! !
854! On Output: !
855! !
856! Vout Output 2D logical variable !
857! Nval Number of output values processed !
858! !
859!***********************************************************************
860!
861! Imported variable declarations.
862!
863 integer, intent(in) :: Ninp, Iout, Jout
864 character (len=*), intent(in) :: Vinp(:)
865!
866 logical, intent(out) :: Vout(:,:)
867!
868! Local variable declarations.
869!
870 logical :: LastValue
871!
872 logical, dimension(Iout*Jout) :: Vwrk
873!
874 integer :: Nstr, i, ic
875 integer :: Nout, Nval
876!
877!-----------------------------------------------------------------------
878! Load 2D logical variable with input values.
879!-----------------------------------------------------------------------
880!
881! If not all values are provided for variable, assume the last value
882! for the rest of the array.
883!
884 ic=0
885 nout=iout*jout
886 lastvalue=.false.
887 IF (ninp.le.nout) THEN
888 DO i=1,ninp
889 ic=ic+1
890 IF ((vinp(i)(1:1).eq.'T').or. &
891 & (vinp(i)(1:1).eq.'t')) THEN
892 vwrk(i)=.true.
893 ELSE
894 vwrk(i)=.false.
895 END IF
896 lastvalue=vwrk(i)
897 END DO
898 IF (nout.gt.ninp) THEN
899 nstr=ninp+1
900 DO i=nstr,nout
901 ic=ic+1
902 vwrk(i)=lastvalue
903 END DO
904 END IF
905 ELSE
906 DO i=1,nout
907 ic=ic+1
908 IF ((vinp(i)(1:1).eq.'T').or. &
909 & (vinp(i)(1:1).eq.'t')) THEN
910 vwrk(i)=.true.
911 ELSE
912 vwrk(i)=.false.
913 END IF
914 END DO
915 END IF
916 vout=reshape(vwrk,(/iout,jout/))
917 nval=ic
918!
919 RETURN

References mod_param::nstr.

◆ load_3d_l()

integer function inp_decode_mod::load_l::load_3d_l ( integer, intent(in) ninp,
character (len=*), dimension(:), intent(in) vinp,
integer, intent(in) iout,
integer, intent(in) jout,
integer, intent(in) kout,
logical, dimension(:,:,:), intent(out) vout )

Definition at line 922 of file inp_decode.F.

924!
925!***********************************************************************
926! !
927! It loads input values into a requested model 3D logical array. !
928! !
929! On Input: !
930! !
931! Ninp Number of input elements to process in Vinp (integer) !
932! Vinp Input values (character 1D array) !
933! Iout Size of output logical variable first I-dimension !
934! Jout Size of output logical variable second J-dimension !
935! Kout Size of output logical variable third K-dimension !
936! !
937! On Output: !
938! !
939! Vout Output 3D logical variable !
940! Nval Number of output values processed !
941! !
942!***********************************************************************
943!
944! Imported variable declarations.
945!
946 integer, intent(in) :: Ninp, Iout, Jout, Kout
947 character (len=*), intent(in) :: Vinp(:)
948!
949 logical, intent(out) :: Vout(:,:,:)
950!
951! Local variable declarations.
952!
953 logical :: LastValue
954!
955 logical, dimension(Iout*Jout*Kout) :: Vwrk
956!
957 integer :: Nstr, i, ic
958 integer :: Nout, Nval
959!
960!-----------------------------------------------------------------------
961! Load 3D logical variable with input values.
962!-----------------------------------------------------------------------
963!
964! If not all values are provided for variable, assume the last value
965! for the rest of the array.
966!
967 ic=0
968 nout=iout*jout*kout
969 lastvalue=.false.
970 IF (ninp.le.nout) THEN
971 DO i=1,ninp
972 ic=ic+1
973 IF ((vinp(i)(1:1).eq.'T').or. &
974 & (vinp(i)(1:1).eq.'t')) THEN
975 vwrk(i)=.true.
976 ELSE
977 vwrk(i)=.false.
978 END IF
979 lastvalue=vwrk(i)
980 END DO
981 IF (nout.gt.ninp) THEN
982 nstr=ninp+1
983 DO i=nstr,nout
984 ic=ic+1
985 vwrk(i)=lastvalue
986 END DO
987 END IF
988 ELSE
989 DO i=1,nout
990 ic=ic+1
991 IF ((vinp(i)(1:1).eq.'T').or. &
992 & (vinp(i)(1:1).eq.'t')) THEN
993 vwrk(i)=.true.
994 ELSE
995 vwrk(i)=.false.
996 END IF
997 END DO
998 END IF
999 vout=reshape(vwrk,(/iout,jout,kout/))
1000 nval=ic
1001!
1002 RETURN

References mod_param::nstr.


The documentation for this interface was generated from the following file: