I know => can fix it
use modA,only:sub1
use,prefix::modB
call sub1()
call modB.sub1()
Like Python
import modB
modB.sub1
I know => can fix it
use modA,only:sub1
use,prefix::modB
call sub1()
call modB.sub1()
Like Python
import modB
modB.sub1
Hi @weixing1531 and welcome.
The namespace for modules is actually the first issue in the Fortran proposals, but as I mentioned here, it might not make it to the f202y revision.
Maybe by July weāll finally get to know why.
methed2: module subrountine bind to nopass procedure
You might try being less cryptic when posting. I feel like chatting with a bot (i.e., your posts donāt pass the Turing Test, ).
The nopass
trick only works well for procedures.
For module constants, thereās no way of stating that a derived-type public component cannot be modified from outside the module (I think there was a proposal for that, but the standard committee found it too confusing?).
And for module variables, you might need to use pointers āand pointers imply the target
attribute, which in turn might inhibit optimizations.
NoPass method
Type(TypeName)::ObjectName
ObjectName%NoPassMethod()
I need:
TypeName%NoPassMethod()
I like this - the user can choose the prefix to shorten it or avoid name clashes. I assume that
USE,NAMESPACE :: some_module
or something similar is written if the prefix were not to change?
A minor issue:
The example uses ā.ā as the separator between the module name (or alias) and the object in the module. I prefer ā.ā to ā%ā, but for type components I think that battle has been lost. Is there a problem in using ā%ā for all parent-child separators? We do that in fpt - so if you want to specify the type component āphiā in he type āpolarsā in the internal routine āto_polarsā in the module subroutine āattitudeā in the module ākinematicsā you write
kinematics%attitude%to_polars%polars%phi
So far I donāt think this has caused problems, but there may be cases we havenāt encountered.
Weāll have to do %
for sure. But Iāve been thinking about this for 6 years now, and I still like .
, and after we can compile all codes with LFortran, I want to see if there is a way to implement rules for .
to make it work.
I agree with the people who would prefer to avoid % for derived types. What would be wrong with | ?
I think |
is better than %
, but I think .
is well established by now.
I think the only significant and āobjectiveā improvement (in the sense of not simply being a matter of getting used to it) is something like .
because 1) it distracts less; parent and child are easier to immediately distinguish in parent.child
than in parent%child
, which may initially be read as one variable, 2) .
will feel more familiar to many who are used to other languages. |
would probably distract less than %
(I canāt tell cause Iām so used to the latter), but it still takes up a lot of vertical space like characters used in variable names.
RE the use of dot (.
) for type components or namespace, I always wonder whether it is possible to introduce an appropriate precedence rule at the language level (like the table in the following page), such that dots for those cases have higher precedence to avoid possible ambiguity with operators like .foo.
, for example� Naively it seems possible to me, but more considerations may be necessary for corner cases�
Other languages also āoverloadā the same symbol for different purposes, for example, semicolon (;
) is used for both multidimensional array literals and statement separators in Julia (and also Matlab?).
> a = [1 2; 3 4]
2Ć2 Matrix{Int64}:
1 2
3 4
> print("a = "); print(a)
a = [1 2; 3 4]
Though not elegant at all, a possible workaround might be to just define a module procedure named like TypeName_NoPassMethod()
, bind it to the type TypeName
as procedure, nopass :: NoPassMethod => TypeName_NoPassMethod
, and then use TypeName_NoPassMethod()
from a different module directly via implicit use
statement (assuming the routine is public), to mimic TypeName%NoPassMethod()
Clearly there are rules to make it work. ifx, ifort, gfortran, vms (still alive) and HP-UX and CVF all support or supported STRUCTURE/MAP/UNION and the separator between a record and a field in this construct is ā.ā There are already some construct-specific lexical rules in the Standard (I believe you canāt end a user-defined operator with a numeric character?).
The Standard does not allow sub-types like sub-structures. Therefore I believe that the only way to get a type component surrounded by component delimiters with the same name as an operator is to name a component with the same name as an operator without the dots. e.g.
PROGRAM t
TYPE stp ! Sub-type
INTEGER*4 i
END TYPE stp
TYPE tp ! Main type
TYPE(stp) and
END TYPE tp
TYPE(tp) vtp
vtp%and%i = 42
WRITE(*,*)vtp%and%i
END PROGRAM t ! *********************************************************
The dot-delimited operator and the type component are in the same scope. Could that become illegal?
Actually, numbers are not allowed in user-defined operators (and the intrinsic, dot-delimited symbols donāt contain numbers either).
The names for user-defined operators and variables are in different bags (i.e., namespaces) and never collide when in the same scope:
module mod1
implicit none
type x
integer :: i = 7
end type
type y
integer :: l = 4
type(x) :: op
end type
generic :: operator(.op.) => y_op_int
integer :: op = 9
contains
integer function y_op_int(lhs, rhs)
type(y), intent(in) :: lhs
integer, intent(in) :: rhs
y_op_int = lhs%l + rhs
end function
end module mod1
use mod1
implicit none
integer :: i = 9
type(y) :: a
print *, a.op.i
print *, a%op%i
end
Probably the ambiguity could be solved by assigning the highest precedence to the dot? With that, parentheses might be required when one wants to actually use the operator.
(The code above compiles properly with ifx and flang-new. But for gfortran, the generic-stmt
needs to be converted into a generic interface block)
One idea is to use a (.op.) i
to mean an operator, and a.op.i
would mean a%op%i
. However, it does break backwards compatibility. I donāt know if there is another way.
User-defined binary operators have the lowest precedence, which means that parentheses must be used when in the presence of other binary operators. So, your idea may become:
...
if ( (a (.op.) i) > (b (.op.) j) ) then
...
endif
...
Which, imho, requires too much visual parsing just to understand the conditional expression.
Would this be equivalent and easier to read?
if ( (a).op.(i) > (b).op.(j) ) then
The other part to consider is also how often you use user-defined operators. For example I never use them (but I know that others do). But derived types I sometimes use.
They are quite useful in terms of abstraction (i.e., the āForā in Fortran), e.g.:
a = 'there are '//.str. 400//' items'
print*, .hex. ptr
print*, 'hello' .in. strings_set
vres = .nabla. p - v * dt
The unary ones are nicer, since they have the highest precedence so no parentheses are required.
And IIRC even the IMSL libraries defined a bunch of them (.x.
, .xt.
, .tx.
and so on).
Whatās the benefit of a user defined operator versus a normal function for your examples of str
and hex
?