Understanding SHAPE and MOLD

I am new to this group but I have programmed in Fortran since 1977. The new Fortran has been a great help in creating the fairly large software for thermodynamic calculation but recently I have come across problem with a very simple use of allocation. I am sorry I do not know how to format the code nicely below.

Program allosp
implicit none
integer i
type species
character(len=:) , allocatable :: name
integer nel
character(len=:), dimension(:), allocatable :: element
double precision, dimension(:), allocatable :: stoic
double precision charge
end type species
! type(species), dimension(:), allocatable :: const
type(species), dimension(10), target :: const
type(species), pointer :: sp
!
! allocate(const(10))
sp=>const(1)
sp%name=‘H2O’
sp%nel=2
allocate(sp%element(2))
allocate(sp%stoic(1:2))
end Program allosp

Compiling this gives
Error: Allocate-object at (1) with a deferred type parameter requires either a type-spec or SOURCE tag or a MOLD tag

Initially I thought that it was a problem to allocate something inside an allocatable object but that is not the case.

During the last 15 years or so using the new Fortran I have never had this kind of error and I have used allocate many times. In my old code I find statements as:

  allocate(ceq%complist(icomp)%endmember(nsl))

where ceq is a very complex object with many allocatable TYPE objects for all the data needed to describe the equilibrium state of a material. Maybe I had some trick 15 years ago that I forgotten now.

Or is it something new? But my old code still compiles correctly.
Any hint welcome

Bosse

Deferred type parameters appear in your program for components NAME and ELEMENT. For NAME, the LEN type parameter for CHARACTER is specified by the r.h.s. ‘H2O’, to be 3. The

similarly requires a specification for the length type parameter, which can be done with a type-spec

allocate(CHARACTER(LEN=3) :: sp%element(2))

,MOLD

allocate(sp%element(2),MOLD='H2O')

or SOURCE specifier

allocate(sp%element(2),SOURCE='H2O')

Welcome to the forum.
When you declared the component

character(len=:), dimension(:), allocatable :: element

You stated that it has both a deferred length and a deferred shape.
But when doing the allocation

allocate(sp%element(2))

You’re only providing a shape (i.e., the size). You need to do something like

allocate(character(255) :: sp%element(2))

Btw, to properly format code in posts, you can either use markdown or the </> icon from the toolbar. For markdown, it should be something like this:

    ```fortran
    code goes here
    ```

Thanks for the answers, I am not used to allocatable characters, I do not think they existed when I started writing in the new Fortran standard around 2010.
However, recently I got used to just define characters as allocatable and when they are assigned a text they are automatically allocated. But I understand combining dimension and len= makes it a bit complicated but I find this MOLD very strange.
I think I have picked up somewhere that in a character array all elements must have the same length.

Deferred-length characters were introduced in Fortran 2003. They’re proper strings, but the len parameter belongs to the variable and not to the elements, so deferred-length character arrays have that limitation.

The reallocate-on-assignment feature applies to any allocatable variable (not only to deferred-length characters)… and the allocate attribute can be used on scalars as well.
As for MOLD=, it copies type parameters during allocation (e.g., length and dimension), but not content.
SOURCE= copies the whole thing, but there might be issues with partially allocated variables —you get the same effect with reallocate-on-assignment, with the added benefit that partial allocation is not an issue.

You can only have one of MOLD/SOURCE= specifiers. SOURCE=expr will use the value of expr to define the object that is being allocated. MOLD=expr will not use the value of expr (which indeed can be undefined) and will not define any values for the object being allocated. It is likely to be faster. The expr in that case is only used for its type, type parameters and attributes.