/[lmdze]/trunk/IOIPSL/Mathelp/buildop.f
ViewVC logotype

Contents of /trunk/IOIPSL/Mathelp/buildop.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 254 - (show annotations)
Mon Feb 5 10:39:38 2018 UTC (6 years, 3 months ago) by guez
File size: 2990 byte(s)
Move Sources/* to root directory.
1 module buildop_m
2
3 implicit none
4
5 contains
6
7 SUBROUTINE buildop (str, ex_topps, topp, nbops_max, &
8 & missing_val, opps, scal, nbops)
9 !- This subroutine decomposes the input string in the elementary
10 !- functions which need to be applied to the vector of data.
11 !- This vector is represented by X in the string.
12 !- This subroutine is the driver of the decomposition and gets
13 !- the time operation but then call decoop for the other operations
14 !- INPUT
15
16 !- str : String containing the operations
17 !- ex_toops : The time operations that can be expected
18 !- within the string
19
20 !- OUTPUT
21
22 USE errioipsl, ONLY : histerr
23 use decoop_m, only: decoop
24
25 CHARACTER(LEN=80) :: str
26 CHARACTER(LEN=*) :: ex_topps
27 CHARACTER(LEN=7) :: topp
28 INTEGER :: nbops_max, nbops
29 CHARACTER(LEN=7) :: opps(nbops_max)
30 REAL :: scal(nbops_max), missing_val
31
32 CHARACTER(LEN=80) :: new_str
33 INTEGER :: leng, ind_opb, ind_clb
34
35 LOGICAL :: check = .FALSE.
36 !---------------------------------------------------------------------
37 IF (check) WRITE(*, *) 'buildop : Some preliminary cleaning'
38
39 leng = LEN_TRIM(str)
40 IF ( str(1:1) == '(' .AND. str(leng:leng) == ')' ) THEN
41 str = str(2:leng-1)
42 leng = leng-2
43 ENDIF
44
45 IF (check) &
46 & WRITE(*, *) 'buildop : Starting to test the various options'
47
48 IF (leng <= 5 .AND. INDEX(ex_topps, str(1:leng)) > 0) THEN
49 IF (check) WRITE(*, *) 'buildop : Time operation only'
50 nbops = 0
51 topp = str(1:leng)
52 ELSE
53 IF (check) THEN
54 WRITE(*, *) 'buildop : Time operation and something else'
55 ENDIF
56 !--
57 ind_opb = INDEX(str(1:leng), '(')
58 IF (ind_opb > 0) THEN
59 IF (INDEX(ex_topps, str(1:ind_opb-1)) > 0) THEN
60 IF (check) THEN
61 WRITE(*, '(2a)') &
62 & ' buildop : Extract time operation from : ', str
63 ENDIF
64 topp = str(1:ind_opb-1)
65 ind_clb = INDEX(str(1:leng), ')', BACK=.TRUE.)
66 new_str = str(ind_opb+1:ind_clb-1)
67 IF (check) THEN
68 WRITE(*, '(2a, 2I3)') &
69 & ' buildop : Call decoop ', new_str, ind_opb, ind_clb
70 ENDIF
71 CALL decoop (new_str, nbops_max, missing_val, opps, scal, nbops)
72 ELSE
73 CALL histerr(3, 'buildop', &
74 & 'time opperation does not exist', str(1:ind_opb-1), ' ')
75 ENDIF
76 ELSE
77 CALL histerr(3, 'buildop', &
78 & 'some long opperation exists but wihout parenthesis', &
79 & str(1:leng), ' ')
80 ENDIF
81 ENDIF
82
83 IF (check) THEN
84 DO leng=1, nbops
85 WRITE(*, *) &
86 & 'buildop : i -- opps, scal : ', leng, opps(leng), scal(leng)
87 ENDDO
88 ENDIF
89 !---------------------
90 END SUBROUTINE buildop
91
92 end module buildop_m

  ViewVC Help
Powered by ViewVC 1.1.21