diff --git a/fortls/intrinsic.procedures.markdown.json b/fortls/intrinsic.procedures.markdown.json index 3e0adcc1..b2ca4ad5 100644 --- a/fortls/intrinsic.procedures.markdown.json +++ b/fortls/intrinsic.procedures.markdown.json @@ -147,7 +147,7 @@ "NOT": "## not\n\n### **Name**\n\n**not** - \\[BIT:LOGICAL\\] Logical negation; flips all bits in an integer\n\n### **Synopsis**\n```fortran\n result = not(i)\n```\n```fortran\n elemental integer(kind=KIND) function not(i)\n\n integer(kind=KIND), intent(in) :: i\n```\n### **Characteristics**\n\n- **i** may be an _integer_ of any valid kind\n- The returned _integer_ is of the same kind as the argument **i**.\n\n### **Description**\n\n **not** returns the bitwise Boolean inverse of **i**. This is also\n known as the \"Bitwise complement\" or \"Logical negation\" of the value.\n\n If an input bit is a one, that position is a zero on output. Conversely\n any input bit that is zero is a one on output.\n\n### **Options**\n\n- **i**\n : The value to flip the bits of.\n\n### **Result**\n\n The result has the value obtained by complementing **i** bit-by-bit\n according to the following truth table:\n\n > I | NOT(I)\n > ----#----------\n > 1 | 0\n > 0 | 1\n\n That is, every input bit is flipped.\n\n### **Examples**\n\nSample program\n\n```fortran\nprogram demo_not\nimplicit none\ninteger :: i\n ! basics\n i=-13741\n print *,'the input value',i,'represented in bits is'\n write(*,'(1x,b32.32,1x,i0)') i, i\n i=not(i)\n print *,'on output it is',i\n write(*,'(1x,b32.32,1x,i0)') i, i\n print *, \" on a two's complement machine flip the bits and add 1\"\n print *, \" to get the value with the sign changed, for example.\"\n print *, 1234, not(1234)+1\n print *, -1234, not(-1234)+1\n print *, \" of course 'x=-x' works just fine and more generally.\"\nend program demo_not\n```\nResults:\n```text\n the input value -13741 represented in bits is\n 11111111111111111100101001010011 -13741\n on output it is 13740\n 00000000000000000011010110101100 13740\n on a two's complement machine flip the bits and add 1\n to get the value with the sign changed, for example.\n 1234 -1234\n -1234 1234\n of course 'x=-x' works just fine and more generally.\n```\n### **Standard**\n\nFortran 95\n\n### **See Also**\n\n[**iand**(3)](#iand),\n[**ior**(3)](#ior),\n[**ieor**(3)](#ieor),\n[**ibits**(3)](#ibits),\n[**ibset**(3)](#ibset),\n\n[**ibclr**(3)](#ibclr)\n\n _fortran-lang intrinsic descriptions (license: MIT) \\@urbanjost_\n", "NULL": "## null\n\n### **Name**\n\n**null** - \\[TRANSFORMATIONAL\\] Function that returns a disassociated pointer\n\n### **Synopsis**\n```fortran\n ptr => null( [mold] )\n```\n```fortran\n function null(mold)\n\n type(TYPE(kind=**)),pointer,optional :: mold\n```\n### **Characteristics**\n\n- **mold** is a pointer of any association status and of any type.\n- The result is a disassociated pointer or an unallocated allocatable entity.\n\n### **Description**\n\n **null** returns a disassociated pointer.\n\n If **mold** is present, a disassociated pointer of the same type is\n returned, otherwise the type is determined by context.\n\n In _Fortran 95_, **mold** is optional. Please note that _Fortran 2003_\n includes cases where it is required.\n\n### **Options**\n\n- **mold**\n : a pointer of any association status and of any\n type.\n\n### **Result**\n\n A disassociated pointer or an unallocated allocatable entity.\n\n### **Examples**\n\nSample program:\n\n```fortran\n!program demo_null\nmodule showit\nimplicit none\nprivate\ncharacter(len=*),parameter :: g='(*(g0,1x))'\npublic gen\n! a generic interface that only differs in the\n! type of the pointer the second argument is\ninterface gen\n module procedure s1\n module procedure s2\nend interface\n\ncontains\n\nsubroutine s1 (j, pi)\n integer j\n integer, pointer :: pi\n if(associated(pi))then\n write(*,g)'Two integers in S1:,',j,'and',pi\n else\n write(*,g)'One integer in S1:,',j\n endif\nend subroutine s1\n\nsubroutine s2 (k, pr)\n integer k\n real, pointer :: pr\n if(associated(pr))then\n write(*,g)'integer and real in S2:,',k,'and',pr\n else\n write(*,g)'One integer in S2:,',k\n endif\nend subroutine s2\n\nend module showit\n\nprogram demo_null\nuse showit, only : gen\n\nreal,target :: x = 200.0\ninteger,target :: i = 100\n\nreal, pointer :: real_ptr\ninteger, pointer :: integer_ptr\n\n! so how do we call S1() or S2() with a disassociated pointer?\n\n! the answer is the null() function with a mold value\n\n! since s1() and s2() both have a first integer\n! argument the NULL() pointer must be associated\n! to a real or integer type via the mold option\n! so the following can distinguish whether s1(1)\n! or s2() is called, even though the pointers are\n! not associated or defined\n\ncall gen (1, null (real_ptr) ) ! invokes s2\ncall gen (2, null (integer_ptr) ) ! invokes s1\nreal_ptr => x\ninteger_ptr => i\ncall gen (3, real_ptr ) ! invokes s2\ncall gen (4, integer_ptr ) ! invokes s1\n\nend program demo_null\n```\nResults:\n```text\n One integer in S2:, 1\n One integer in S1:, 2\n integer and real in S2:, 3 and 200.000000\n Two integers in S1:, 4 and 100\n```\n### **Standard**\n\nFortran 95\n\n### **See Also**\n\n[**associated**(3)](#associated)\n\n _fortran-lang intrinsic descriptions (license: MIT) \\@urbanjost_\n", "NUM_IMAGES": "## num_images\n\n### **Name**\n\n**num_images** - \\[COLLECTIVE\\] Number of images\n\n### **Synopsis**\n```fortran\n result = num_images([team|team_number])\n```\n```fortran\n integer function num_images (team)\n\n type(TEAM_TYPE),intent(in),optional :: team\n integer(kind=KIND),intent(in),optional :: team_number\n```\n### **Characteristics**\n\n - use of **team** and **team_number** is mutually exclusive\n - **team** is a scalar of type **TEAM_TYPE** from the intrinsic module ISO_FORTRAN_ENV.\n - **team_number** is an _integer_ scalar.\n - the result is a default _integer_ scalar.\n\n### **Description**\n\n**num_images** Returns the number of images.\n\n### **Options**\n\n- **team**\n : shall be a scalar of type TEAM_TYPE from the intrinsic module\n ISO_FORTRAN_ENV, with a value that identifies the current or an\n ancestor team.\n\n- **team_number**\n : identifies the initial team or a team whose parent is the same as\n that of the current team.\n\n### **Result**\n\n The number of images in the specified team, or in the current team if\n no team is specified.\n\n### **Examples**\n\nSample program:\n```fortran\nprogram demo_num_images\nimplicit none\ninteger :: value[*]\nreal :: p[*]\ninteger :: i\n\n value = this_image()\n sync all\n if (this_image() == 1) then\n do i = 1, num_images()\n write(*,'(2(a,i0))') 'value[', i, '] is ', value[i]\n end do\n endif\n\n ! The following code uses image 1 to read data and\n ! broadcast it to other images.\n if (this_image()==1) then\n p=1234.5678\n do i = 2, num_images()\n p[i] = p\n end do\n end if\n sync all\n\nend program demo_num_images\n```\n### **Standard**\n\nFortran 2008 . With DISTANCE or FAILED argument, TS 18508\n\n### **See Also**\n\n[**this_image**(3)](#this_image),\n[**image_index**(3)](#this_index)\n\n _fortran-lang intrinsic descriptions (license: MIT) \\@urbanjost_\n", - "OUT_OF_RANGE": "## out_of_range\n\n### **Name**\n\n**out_of_range** - \\[TYPE:NUMERIC\\] Whether a value cannot be converted safely.\n\n### **Synopsis**\n```fortran\n result = out_of_range (x, mold [, round])\n```\n```fortran\n elemental logical function(x, mold, round)\n\n TYPE,kind=KIND),intent(in) :: x\n TYPE,kind=KIND),intent(in) :: mold\n logical,intent(in),optional :: round\n```\n### **Characteristics**\n\n - **x** is of type _integer_ or _real_.\n - **mold** is an _integer_ or _real_ scalar.\n - **round** is a _logical_ scalar.\n - the result is a default _logical_.\n\n### **Description**\n\n **out_of_range** determines whether a value **x** can be converted\n safely to a _real_ or _integer_ variable the same type and kind\n as **mold**.\n\n For example, if **int8** is the kind value for an 8-bit binary integer\n type, **out_of_range(-128.5, 0_int8)** will have the value false and\n **out_of_range(-128.5, 0_int8, .true.)** will have the value _.true._\n because the value will be truncated when converted to an _integer_\n and -128 is a representable value on a two's complement machine in\n eight bits even though +128 is not.\n\n### **Options**\n - **x**\n : a scalar to be tested for whether\n it can be stored in a variable of the type and kind of **mold**\n\n - **mold**\n and kind are queried to determine the characteristics of what\n needs to be fit into.\n\n - **round**\n : flag whether to round the value of **xx** before validating it as\n an integer value like **mold**.\n\n **round** can only be present if **x** is of type\n _real_ and **mold** is of type _integer_.\n\n### **Result**\n\nFrom the standard:\n\n Case (i): If **mold** is of type integer, and **round** is absent or\n present with the value false, the result is true\n if and only if the value of X is an IEEE infinity or\n NaN, or if the integer with largest magnitude that lies\n between zero and X inclusive is not representable by\n objects with the type and kind of **mold**.\n\n Case (ii): If **mold** is of type integer, and **round** is present with\n the value true, the result is true if and only\n if the value of X is an IEEE infinity or NaN, or\n if the integer nearest X, or the integer of greater\n magnitude if two integers are equally near to X, is not\n representable by objects with the type and kind of **mold**.\n\n Case (iii): Otherwise, the result is true if and only if the value\n of X is an IEEE infinity or NaN that is not\n supported by objects of the type and kind of **mold**,\n or if X is a finite number and the result of rounding\n the value of X (according to the IEEE rounding mode if\n appropriate) to the extended model for the kind of **mold**\n has magnitude larger than that of the largest finite\n number with the same sign as X that is representable\n by objects with the type and kind of **mold**.\n\n NOTE\n\n **mold** is required to be a scalar because the only information\n taken from it is its type and kind. Allowing an array **mold** would\n require that it be conformable with **x**. **round** is scalar because\n allowing an array rounding mode would have severe performance\n difficulties on many processors.\n\n### **Examples**\n\nSample program:\n\n```fortran\nprogram demo_out_of_range\nuse, intrinsic :: iso_fortran_env, only : int8, int16, int32, int64\nuse, intrinsic :: iso_fortran_env, only : real32, real64, real128\nimplicit none\ninteger :: i\ninteger(kind=int8) :: i8, j8\n\n ! compilers are not required to produce an error on out of range.\n ! here storing the default integers into 1-byte integers\n ! incorrectly can have unexpected results\n do i=127,130\n i8=i\n j8=-i\n ! OUT_OF_RANGE(3f) can let you check if the value will fit\n write(*,*)i8,j8,' might have expected',i,-i, &\n & out_of_range( i,i8), &\n & out_of_range(-i,i8)\n enddo\n write(*,*) 'RANGE IS ',-1-huge(0_int8),'TO',huge(0_int8)\n ! the real -128.5 is truncated to -128 and is in range\n write(*,*) out_of_range ( -128.5, 0_int8) ! false\n\n ! the real -128.5 is rounded to -129 and is not in range\n write(*,*) out_of_range ( -128.5, 0_int8, .true.) ! true\n\nend program demo_out_of_range\n```\nResults:\n```text\n > 127 -127 might have expected 127 -127 F F\n > -128 -128 might have expected 128 -128 T F\n > -127 127 might have expected 129 -129 T T\n > -126 126 might have expected 130 -130 T T\n > RANGE IS -128 TO 127\n > F\n > T\n```\n### **Standard**\n\n FORTRAN 2018\n\n### **See also**\n\n- [**aimag**(3)](#aimag) - Imaginary part of complex number\n- [**cmplx**(3)](#cmplx) - Convert values to a complex type\n- [**dble**(3)](#dble) - Double conversion function\n- [**int**(3)](#int) - Truncate towards zero and convert to integer\n- [**nint**(3)](#nint) - Nearest whole number\n- [**real**(3)](#real) - Convert to real type\n\n _fortran-lang intrinsic descriptions (license: MIT) \\@urbanjost_\n", + "OUT_OF_RANGE": "## out_of_range\n\n### **Name**\n\n**out_of_range** - \\[TYPE:NUMERIC\\] Whether a numeric value can be\nconverted safely to another type\n\n### **Synopsis**\n```fortran\n result = out_of_range (x, mold [, round])\n```\n```fortran\n elemental logical function(x, mold, round)\n\n TYPE,kind=KIND),intent(in) :: x\n TYPE,kind=KIND),intent(in) :: mold\n logical,intent(in),optional :: round\n```\n### **Characteristics**\n\n - **x** is of type _integer_ or _real_.\n - **mold** is an _integer_ or _real_ scalar.\n - **round** is a _logical_ scalar.\n - the result is a default _logical_.\n\n### **Description**\n\n **out_of_range** determines whether a value **x** can be converted\n safely to a _real_ or _integer_ variable the same type and kind\n as **mold**.\n\n For example, if **int8** is the __kind__ name for an 8-bit binary integer type,\n then for\n```fortran\n logical :: L1, L2\n L1=out_of_range(-128.5, 0_int8)\n L2=out_of_range(-128.5, 0_int8,.true.)\n end\n```\n L1 likely will have the value __.false.__ because the value will\n be truncated to -128.0, which is a representable integer number on a two's\n complement machine.\n\n L2 will be __.true.__ because it will be rounded to -129.0, which is not\n likely to be a representable eight-bit integer.\n\n### **Options**\n - **x**\n : a scalar to be tested for whether it can be stored in a variable\n of the type and kind of **mold**\n\n - **mold**\n : the type and kind of the variable (but not the value) is used to\n identify the characteristics of the variable type to fit **x** into.\n\n - **round**\n : flag whether to round the value of **x** before validating it as\n a value like **mold**.\n\n **round** can only be present if **x** is of type\n _real_ and **mold** is of type _integer_.\n\n### **Result**\n\nFrom the standard:\n\n Case (i): If **mold** is of type integer, and **round** is absent or\n present with the value false, the result is true\n if and only if the value of X is an IEEE infinity or\n NaN, or if the integer with largest magnitude that lies\n between zero and X inclusive is not representable by\n objects with the type and kind of **mold**.\n\n Case (ii): If **mold** is of type integer, and **round** is present with\n the value true, the result is true if and only\n if the value of X is an IEEE infinity or NaN, or\n if the integer nearest X, or the integer of greater\n magnitude if two integers are equally near to X, is not\n representable by objects with the type and kind of **mold**.\n\n Case (iii): Otherwise, the result is true if and only if the value\n of X is an IEEE infinity or NaN that is not\n supported by objects of the type and kind of **mold**,\n or if X is a finite number and the result of rounding\n the value of X (according to the IEEE rounding mode if\n appropriate) to the extended model for the kind of **mold**\n has magnitude larger than that of the largest finite\n number with the same sign as X that is representable\n by objects with the type and kind of **mold**.\n\n NOTE\n\n **mold** is required to be a scalar because the only information\n taken from it is its type and kind. Allowing an array **mold** would\n require that it be conformable with **x**. **round** is scalar because\n allowing an array rounding mode would have severe performance\n difficulties on many processors.\n\n### **Examples**\n\nSample program:\n\n```fortran\nprogram demo_out_of_range\nuse, intrinsic :: iso_fortran_env, only : int8, int16, int32, int64\nuse, intrinsic :: iso_fortran_env, only : real32, real64, real128\nimplicit none\ninteger :: i\ninteger(kind=int8) :: i8, j8\n\n ! compilers are not required to produce an error on out of range.\n ! here storing the default integers into 1-byte integers\n ! incorrectly can have unexpected results\n do i=127,130\n i8=i\n j8=-i\n ! OUT_OF_RANGE(3f) can let you check if the value will fit\n write(*,*)i8,j8,' might have expected',i,-i, &\n & out_of_range( i,i8), &\n & out_of_range(-i,i8)\n enddo\n write(*,*) 'RANGE IS ',-1-huge(0_int8),'TO',huge(0_int8)\n ! the real -128.5 is truncated to -128 and is in range\n write(*,*) out_of_range ( -128.5, 0_int8) ! false\n\n ! the real -128.5 is rounded to -129 and is not in range\n write(*,*) out_of_range ( -128.5, 0_int8, .true.) ! true\n\nend program demo_out_of_range\n```\nResults:\n```text\n > 127 -127 might have expected 127 -127 F F\n > -128 -128 might have expected 128 -128 T F\n > -127 127 might have expected 129 -129 T T\n > -126 126 might have expected 130 -130 T T\n > RANGE IS -128 TO 127\n > F\n > T\n```\n### **Standard**\n\n FORTRAN 2018\n\n### **See also**\n\n- [**aimag**(3)](#aimag) - Imaginary part of complex number\n- [**cmplx**(3)](#cmplx) - Convert values to a complex type\n- [**dble**(3)](#dble) - Double conversion function\n- [**int**(3)](#int) - Truncate towards zero and convert to integer\n- [**nint**(3)](#nint) - Nearest whole number\n- [**real**(3)](#real) - Convert to real type\n\n _fortran-lang intrinsic descriptions (license: MIT) \\@urbanjost_\n", "PACK": "## pack\n\n### **Name**\n\n**pack** - \\[ARRAY:CONSTRUCTION\\] Pack an array into an array of rank one\n\n### **Synopsis**\n```fortran\n result = pack( array, mask [,vector] )\n```\n```fortran\n TYPE(kind=KIND) function pack(array,mask,vector)\n\n TYPE(kind=KIND),option(in) :: array(..)\n logical :: mask(..)\n TYPE(kind=KIND),option(in),optional :: vector(*)\n```\n### **Characteristics**\n\n - **array** is an array of any type\n - **mask** a _logical_ scalar as well as an array conformable with **array**.\n - **vector** is of the same kind and type as **array** and of rank one\n - the returned value is of the same kind and type as **array**\n\n### **Description**\n\n **pack** stores the elements of **array** in an array of rank one.\n\n The beginning of the resulting array is made up of elements whose\n **mask** equals _.true._. Afterwards, remaining positions are filled with elements\n taken from **vector**\n\n### **Options**\n\n- **array**\n : The data from this array is used to fill the resulting vector\n\n- **mask**\n : the _logical_ mask must be the same size as **array** or,\n alternatively, it may be a _logical_ scalar.\n\n- **vector**\n : an array of the same type as **array** and of rank\n one. If present, the number of elements in **vector** shall be equal to\n or greater than the number of true elements in **mask**. If **mask** is\n scalar, the number of elements in **vector** shall be equal to or\n greater than the number of elements in **array**.\n\n**vector** shall have at least as many elements as there are in **array**.\n\n### **Result**\n\nThe result is an array of rank one and the same type as that of **array**.\nIf **vector** is present, the result size is that of **vector**, the number of\n_.true._ values in **mask** otherwise.\n\nIf **mask** is scalar with the value _.true._, in which case the result\nsize is the size of **array**.\n\n### **Examples**\n\nSample program:\n\n```fortran\nprogram demo_pack\nimplicit none\ninteger, allocatable :: m(:)\ncharacter(len=10) :: c(4)\n\n ! gathering nonzero elements from an array:\n m = [ 1, 0, 0, 0, 5, 0 ]\n write(*, fmt=\"(*(i0, ' '))\") pack(m, m /= 0)\n\n ! Gathering nonzero elements from an array and appending elements\n ! from VECTOR till the size of the mask array (or array size if the\n ! mask is scalar):\n m = [ 1, 0, 0, 2 ]\n write(*, fmt=\"(*(i0, ' '))\") pack(m, m /= 0, [ 0, 0, 3, 4 ])\n write(*, fmt=\"(*(i0, ' '))\") pack(m, m /= 0 )\n\n ! select strings whose second character is \"a\"\n c = [ character(len=10) :: 'ape', 'bat', 'cat', 'dog']\n write(*, fmt=\"(*(g0, ' '))\") pack(c, c(:)(2:2) == 'a' )\n\nend program demo_pack\n```\nResults:\n```text\n > 1 5\n > 1 2 3 4\n > 1 2\n > bat cat\n```\n### **Standard**\n\nFortran 95\n\n### **See Also**\n\n[**merge**(3)](#merge),\n[**spread**(3)](#spread),\n[**unpack**(3)](#unpack)\n\n _fortran-lang intrinsic descriptions (license: MIT) \\@urbanjost_\n", "PARITY": "## parity\n\n### **Name**\n\n**parity** - \\[ARRAY:REDUCTION\\] Array reduction by .NEQV. operation\n\n### **Synopsis**\n```fortran\n result = parity( mask [,dim] )\n```\n```fortran\n logical(kind=KIND) function parity(mask, dim)\n\n type(logical(kind=KIND)),intent(in) :: mask(..)\n type(integer(kind=**)),intent(in),optional :: dim\n```\n### **Characteristics**\n\n - **mask** is a _logical_ array\n - **dim** is an integer scalar\n - the result is of type _logical_ with the same kind type parameter as **mask**.\n It is a scalar if **dim** does not appear; otherwise it is the rank and shape\n of **mask** with the dimension specified by **dim** removed.\n - a kind designated as ** may be any supported kind for the type\n\n### **Description**\n\n**parity** calculates the parity array (i.e. the reduction using .neqv.) of\n**mask** along dimension **dim** if **dim** is present and not 1. Otherwise, it\nreturns the parity of the entire **mask** array as a scalar.\n\n### **Options**\n\n - **mask**\n : Shall be an array of type _logical_.\n\n - **dim**\n : (Optional) shall be a scalar of type _integer_ with a value in the\n range from _1 to n_, where _n_ equals the rank of **mask**.\n\n### **Result**\n\n The result is of the same type as **mask**.\n\n If **dim** is absent, a scalar with the parity of all elements in **mask**\n is returned: _.true._ if an odd number of elements are _.true._\n and _.false._ otherwise.\n\n If MASK has rank one, PARITY (MASK, DIM) is equal to PARITY (MASK). Otherwise, the\n result is an array of parity values with dimension **dim** dropped.\n\n### **Examples**\n\nSample program:\n```fortran\nprogram demo_parity\nimplicit none\nlogical, parameter :: T=.true., F=.false.\nlogical :: x(3,4)\n ! basics\n print *, parity([T,F])\n print *, parity([T,F,F])\n print *, parity([T,F,F,T])\n print *, parity([T,F,F,T,T])\n x(1,:)=[T,T,T,T]\n x(2,:)=[T,T,T,T]\n x(3,:)=[T,T,T,T]\n print *, parity(x)\n print *, parity(x,dim=1)\n print *, parity(x,dim=2)\nend program demo_parity\n```\nResults:\n```text\n > T\n > T\n > F\n > T\n > F\n > T T T T\n > F F F\n```\n### **Standard**\n\nFortran 2008\n\n### **See also**\n\n - [**all**(3)](#all) - Determines if all the values are true\n - [**any**(3)](#any) - Determines if any of the values in the logical array are _.true._\n - [**count**(3)](#count) - Count true values in an array\n - [**sum**(3)](#sum) - Sum the elements of an array\n - [**maxval**(3)](#maxval) - Determines the maximum value in an array or row\n - [**minval**(3)](#minval) - Minimum value of an array\n - [**product**(3)](#product) - Product of array elements\n - [**reduce**(3)](#reduce) - General array reduction\n\n _fortran-lang intrinsic descriptions (license: MIT) \\@urbanjost_\n", "POPCNT": "## popcnt\n\n### **Name**\n\n**popcnt** - \\[BIT:COUNT\\] Number of bits set\n\n### **Synopsis**\n```fortran\n result = popcnt(i)\n```\n```fortran\n elemental integer function popcnt(i)\n\n integer(kind=KIND), intent(in) :: i\n```\n### **Characteristics**\n\n- **i** may be an _integer_ of any kind.\n- The return value is an _integer_ of the default integer kind.\n\n### **Description**\n\n **popcnt** returns the number of bits set to one in the binary\n representation of an _integer_.\n\n### **Options**\n\n- **i**\n : value to count set bits in\n\n### **Result**\n\nThe number of bits set to one in **i**.\n\n### **Examples**\n\nSample program:\n\n```fortran\nprogram demo_popcnt\nuse, intrinsic :: iso_fortran_env, only : integer_kinds, &\n & int8, int16, int32, int64\nimplicit none\ncharacter(len=*),parameter :: pretty='(b64,1x,i0)'\n ! basic usage\n print pretty, 127, popcnt(127)\n print pretty, int(b\"01010\"), popcnt(int(b\"01010\"))\n\n ! any kind of an integer can be used\n print pretty, huge(0_int8), popcnt(huge(0_int8))\n print pretty, huge(0_int16), popcnt(huge(0_int16))\n print pretty, huge(0_int32), popcnt(huge(0_int32))\n print pretty, huge(0_int64), popcnt(huge(0_int64))\nend program demo_popcnt\n```\nResults:\n\nNote that on most machines the first bit is the sign bit, and a zero is\nused for positive values; but that this is system-dependent. These are\ntypical values, where the huge(3f) function has set all but the first\nbit to 1.\n```text\n > 1111111 7\n > 1010 2\n > 1111111 7\n > 111111111111111 15\n > 1111111111111111111111111111111 31\n > 111111111111111111111111111111111111111111111111111111111111111 63\n```\n### **Standard**\n\nFortran 2008\n\n### **See Also**\n\nThere are many procedures that operator or query values at the bit level:\n\n[**poppar**(3)](#poppar),\n[**leadz**(3)](#leadz),\n[**trailz**(3)](#trailz)\n[**atomic_and**(3)](#atomic_and),\n[**atomic_fetch_and**(3)](#atomic_fetch_and),\n[**atomic_fetch_or**(3)](#atomic_fetch_or),\n[**atomic_fetch_xor**(3)](#atomic_fetch_xor),\n[**atomic_or**(3)](#atomic_or),\n[**atomic_xor**(3)](#atomic_xor),\n[**bge**(3)](#bge),\n[**bgt**(3)](#bgt),\n[**bit_size**(3)](#bit_size),\n[**ble**(3)](#ble),\n[**blt**(3)](#blt),\n[**btest**(3)](#btest),\n[**dshiftl**(3)](#dshiftl),\n[**dshiftr**(3)](#dshiftr),\n[**iall**(3)](#iall),\n[**iand**(3)](#iand),\n[**iany**(3)](#iany),\n[**ibclr**(3)](#ibclr),\n[**ibits**(3)](#ibits),\n[**ibset**(3)](#ibset),\n[**ieor**(3)](#ieor),\n[**ior**(3)](#ior),\n[**iparity**(3)](#iparity),\n[**ishftc**(3)](#ishftc),\n[**ishft**(3)](#ishft),\n[**maskl**(3)](#maskl),\n[**maskr**(3)](#maskr),\n[**merge_bits**(3)](#merge_bits),\n[**mvbits**(3)](#mvbits),\n[**not**(3)](#not),\n[**shifta**(3)](#shifta),\n[**shiftl**(3)](#shiftl),\n[**shiftr**(3)](#shiftr),\n[**storage_size**(3)](#storage_size)\n\n _fortran-lang intrinsic descriptions (license: MIT) \\@urbanjost_\n",