!MODULE MOD_NORMALPDF ! ! INTEGER,PARAMETER :: DP_KIND=SELECTED_REAL_KIND(6 ,37 ) ! INTEGER :: SEED=12345 ! ! CONTAINS ! ! !###==================================================================== ! SUBROUTINE IPEST_NORMAL_MS_SAMPLE(MU,SIGMA,SEED,X) ! !###==================================================================== ! IMPLICIT NONE ! REAL(KIND=DP_KIND),INTENT(IN) :: MU,SIGMA ! REAL(KIND=DP_KIND),INTENT(OUT) :: X ! REAL(KIND=DP_KIND) :: X01 ! INTEGER,INTENT(INOUT) :: SEED ! ! CALL IPEST_NORMAL_01_SAMPLE(SEED,X01) ! ! X=MU+SIGMA*X01 ! ! END SUBROUTINE IPEST_NORMAL_MS_SAMPLE ! ! !###==================================================================== ! SUBROUTINE IPEST_NORMAL_01_SAMPLE(SEED,X) ! !###==================================================================== ! IMPLICIT NONE !!*****************************************************************************80 ! REAL(KIND=DP_KIND) :: R1,R2 !,IPEST_R8_UNIFORM_01 ! REAL(KIND=DP_KIND), PARAMETER :: R8_PI = 3.141592653589793D+00 ! INTEGER,INTENT(INOUT) :: SEED ! INTEGER,SAVE :: USED = -1 ! REAL(KIND=DP_KIND),INTENT(OUT) :: X ! REAL(KIND=DP_KIND), SAVE :: Y = 0.0D+00 ! ! IF ( USED == -1 ) THEN ! USED = 0 ! END IF ! ! IF ( MOD ( USED, 2 ) == 0 ) THEN ! ! DO ! ! R1 = IPEST_R8_UNIFORM_01 ( SEED ) ! ! IF ( R1 /= 0.0D+00 ) THEN ! EXIT ! END IF ! ! END DO ! ! R2 = IPEST_R8_UNIFORM_01 ( SEED ) ! ! X = SQRT ( - 2.0D+00 * LOG ( R1 ) ) * COS ( 2.0D+00 * R8_PI * R2 ) ! Y = SQRT ( - 2.0D+00 * LOG ( R1 ) ) * SIN ( 2.0D+00 * R8_PI * R2 ) ! ! ELSE ! ! X = Y ! ! END IF ! ! USED = USED + 1 ! ! END SUBROUTINE IPEST_NORMAL_01_SAMPLE ! ! !###==================================================================== ! REAL(KIND=DP_KIND) FUNCTION IPEST_R8_UNIFORM_01 ( SEED ) ! !###==================================================================== ! IMPLICIT NONE ! INTEGER, PARAMETER :: I4_HUGE = 2147483647 ! INTEGER,INTENT(INOUT) :: SEED ! INTEGER :: K ! ! IF ( SEED == 0 ) THEN ! WRITE ( *, '(A)' ) ' ' ! WRITE ( *, '(A)' ) 'R8_UNIFORM_01 - FATAL ERROR!' ! WRITE ( *, '(A)' ) ' INPUT VALUE OF SEED = 0.' ! STOP 1 ! END IF ! ! K = SEED / 127773 ! ! SEED = 16807 * ( SEED - K * 127773 ) - K * 2836 ! ! IF ( SEED < 0 ) THEN ! SEED = SEED + I4_HUGE ! END IF ! ! IPEST_R8_UNIFORM_01 = REAL ( SEED, KIND = 8 ) * 4.656612875D-10 ! ! END FUNCTION IPEST_R8_UNIFORM_01 ! !END MODULE MOD_NORMALPDF !## It turns out that we can combat both this problem and the problem of local minima using a modified version of gradient descent called stochastic gradient descent (SGD). With SGD, we shuffle our dataset, and then go through each sample individually, !## calculating the gradient with respect to that single point, and performing a weight update for each. This may seem like a bad idea at first because a single example may be an outlier and not necessarily give a good approximation of the actual gradient. !## But it turns out that if we do this for each sample of our dataset in some random order, the overall fluctuations of the gradient update path will average out and converge towards a good solution. Moreover, SGD helps us get out of local minima !## and saddle points by making the updates more “jerky” and erratic, which can be enough to get unstuck if we find ourselves in the bottom of a valley. !## https://playground.tensorflow.org/#activation=tanh&batchSize=10&dataset=xor®Dataset=reg-plane&learningRate=0.03®ularizationRate=0&noise=0&networkShape=5,5&seed=0.75078&showTestData=false&discretize=true&percTrainData=40&x=true&y=true&xTimesY=false&xSquared=false&ySquared=false&cosX=false&sinX=false&cosY=false&sinY=false&collectStats=false&problem=classification&initZero=false&hideText=false !## https://ml4a.github.io/ml4a/how_neural_networks_are_trained/ !## https://www.linkedin.com/pulse/forward-back-propagation-over-cnn-code-from-scratch-coy-ulloa MODULE MOD_AI_PAR ! USE MOD_NORMALPDF, ONLY : IPEST_NORMAL_MS_SAMPLE,SEED USE IMODVAR, ONLY : DP_KIND REAL(KIND=DP_KIND),PARAMETER :: ALPHA=0.001 REAL(KIND=DP_KIND),PARAMETER :: EPSILON=10E-8 REAL(KIND=DP_KIND),ALLOCATABLE,DIMENSION(:) :: FINPUT !## shifting input REAL(KIND=DP_KIND),ALLOCATABLE,DIMENSION(:) :: SINPUT !## scaling input REAL(KIND=DP_KIND),ALLOCATABLE,DIMENSION(:) :: FOUTPUT !## shifting input REAL(KIND=DP_KIND),ALLOCATABLE,DIMENSION(:) :: SOUTPUT !## scaling input INTEGER,POINTER,DIMENSION(:) :: SEQ INTEGER :: NUM_INPUTS INTEGER :: NX_INPUTS !## size of the image (nx) INTEGER :: NY_INPUTS !## size of the image (ny) INTEGER :: NUM_OUTPUTS INTEGER :: NUM_SAMPLES INTEGER :: NUM_LAYERS INTEGER :: NUM_CNNLAYERS INTEGER :: NUM_CHANNELS INTEGER :: NUM_TRAINING INTEGER :: NUM_BATCHES INTEGER :: NUM_VALIDATION INTEGER :: IDEBUG CHARACTER(LEN=256) :: FNAMEIN,FNAMEOUT REAL(KIND=DP_KIND),ALLOCATABLE,DIMENSION(:,:) :: INPUTS, V_INPUTS REAL(KIND=DP_KIND),ALLOCATABLE,DIMENSION(:,:) :: OUTPUTS,V_OUTPUTS REAL(KIND=DP_KIND),ALLOCATABLE,DIMENSION(:) :: ERROR,PERFORMANCE REAL(KIND=DP_KIND),ALLOCATABLE,DIMENSION(:,:,:,:) :: INPUTS_2D CHARACTER(LEN=10),ALLOCATABLE,DIMENSION(:) :: L_INPUTS,L_OUTPUTS !TYPE CNNLAYEROBJ ! CHARACTER(LEN=10) :: ACTIVATION ! INTEGER :: CHANNELS !## number of channels (cq. filters) ! INTEGER :: WIDTH !## width of the output from filters ! INTEGER :: HEIGHT !## height of the output from filters ! INTEGER :: KERNEL_SIZE !## size of kernel which is the filter size ! INTEGER :: FILTERS !## number of filters ! REAL(KIND=DP_KIND),DIMENSION(:,:,:),POINTER :: OUTPUT=>NULL() !## output of the filters ! REAL(KIND=DP_KIND),DIMENSION(:),POINTER :: BIASES=>NULL() !## biases ! REAL(KIND=DP_KIND),DIMENSION(:),POINTER :: TBIASES=>NULL() !## total biases ! REAL(KIND=DP_KIND),DIMENSION(:,:,:,:),POINTER :: KERNEL=>NULL() !## weight filters x channels x width x height ! REAL(KIND=DP_KIND),DIMENSION(:,:,:,:),POINTER :: TKERNEL=>NULL()!## total weight filters x channels x width x height ! REAL(KIND=DP_KIND),DIMENSION(:,:,:),POINTER :: Z=>NULL() !## kernel dot input + bias ! REAL(KIND=DP_KIND),DIMENSION(:,:,:,:),POINTER :: DW=>NULL() !## weights (kernel) gradients ! REAL(KIND=DP_KIND),DIMENSION(:),POINTER :: DB=>NULL() !## bias gradients ! REAL(KIND=DP_KIND),DIMENSION(:,:,:),POINTER :: GRADIENT=>NULL() !## gradient !END TYPE CNNLAYEROBJ !TYPE(CNNLAYEROBJ),ALLOCATABLE,DIMENSION(:) :: CNNLAYER TYPE LAYEROBJ CHARACTER(LEN=10) :: ACTIVATION REAL(KIND=DP_KIND),DIMENSION(:),POINTER :: A=>NULL() !## activation REAL(KIND=DP_KIND),DIMENSION(:),POINTER :: B=>NULL() !## biases REAL(KIND=DP_KIND),DIMENSION(:),POINTER :: Z=>NULL() !## temporary array REAL(KIND=DP_KIND),DIMENSION(:,:),POINTER :: W=>NULL() !## weights INTEGER :: NUM_NEURONS !## number of neurons per layer INTEGER :: NUM_WEIGHTS !## number of weights, for all neurons from previous layer REAL(KIND=DP_KIND),DIMENSION(:,:),POINTER :: DW=>NULL() !## adjustment of weights REAL(KIND=DP_KIND),DIMENSION(:,:),POINTER :: TW=>NULL() !## accumulated weights REAL(KIND=DP_KIND),DIMENSION(:,:),POINTER :: PW=>NULL() !## previous weights REAL(KIND=DP_KIND),DIMENSION(:,:),POINTER :: SW=>NULL() !## sum of squared weights REAL(KIND=DP_KIND),DIMENSION(:),POINTER :: DB=>NULL() !## adjustment of biases REAL(KIND=DP_KIND),DIMENSION(:),POINTER :: TB=>NULL() !## accumulated biases REAL(KIND=DP_KIND),DIMENSION(:),POINTER :: PB=>NULL() !## previous biases REAL(KIND=DP_KIND),DIMENSION(:),POINTER :: SB=>NULL() !## sum of squared biases END TYPE LAYEROBJ TYPE(LAYEROBJ),ALLOCATABLE,DIMENSION(:) :: LAYER REAL(KIND=DP_KIND) :: LEARNING_RATE,MOMENTUM INTEGER :: IU END MODULE MOD_AI_PAR