regcomp Subroutine

public subroutine regcomp(this, pattern, flags, nmatch, status)

NAME

 regcomp(3f) - [M_regex] Compile a regular expression into a regex object

SYNOPSIS

subroutine regcomp(this,pattern,flags,status)

  type(regex_type), intent(out)          :: this
  character(len=*), intent(in)           :: pattern
  character(len=*), intent(in), optional :: flags
  integer, intent(out), optional         :: nmatch
  integer, intent(out), optional         :: status

DESCRIPTION

  The regcomp() function compiles an RE written as a string into an
  internal form for use by regexec().

OPTIONS

  THIS     new regex object
  PATTERN  regex pattern string
  FLAGS    flag characters:
             x=  extended regex (REG_EXTENDED). Default is obsolete
                 ("basic") REs.
             m=  multi-line (REG_NEWLINE).
                 Compile for newline-sensitive matching. By default,
                 newline is a completely ordinary character with no
                 special meaning in either REs or strings. With this
                 flag, '[^' bracket expressions and . never match
                 newline, a '^' anchor matches the null string after
                 any newline in the string in addition to its normal
                 function, and the '$' anchor matches the null string
                 before any newline in the string in addition to its
                 normal function.
             i=  case-insensitive (REG_ICASE)
             n=  no MATCH required (REG_NOSUB)
                 Compile for matching that need only report success
                 or failure, not what was matched.
  NMATCH   number of subexpressions in regular expression
  STATUS   If absent, errors are fatal

EXAMPLE

Sample program

program demo_regcomp
use M_regex, only: regex_type, regcomp, regexec, regfree
use M_regex, only: regmatch
implicit none
type(regex_type)             :: regex
integer                      :: matches(2,1)
character(len=:),allocatable :: input_line
character(len=:),allocatable :: output_line
character(len=:),allocatable :: expression
logical                      :: match
integer                      :: ipass
integer                      :: istart
   expression= "[-0-9.*/+]+"                              ! define extended regular expression
   input_line= "30*0 250*1 5 AND 6 7:and some text8 999"  ! define an input line to search for the expression
   call regcomp(regex,expression,'x')                     ! compile the regex
   ipass=1                                                ! initialize pass counter
   INFINITE: do                     ! find match, then look again in remainder of line till all matches found
      match=regexec(regex,input_line,matches)        ! look for a match in (remaining) string
      if(.not.match)exit INFINITE                    ! if no match found exit
      output_line=regmatch(1,input_line,matches)     ! use bounds in MATCHES to select the matching substring
      write(*,'(8x,*(a))') 'match="',output_line,'"' ! show match
      istart=matches(2,1)+1                          ! find beginning of remainder of string
      if(istart.gt.len(input_line))exit INFINITE     ! reached end of string
      input_line=input_line(istart:)                 ! reduce string by any previous match
      ipass=ipass+1                                  ! increment count of passes made
   enddo INFINITE                                    ! free memory used for compiled regular expression
   call regfree(regex)
end program demo_regcomp

Expected output

match="30*0"
match="250*1"
match="5"
match="6"
match="7"
match="8"
match="999"

SEE ALSO

  This routine calls an implementation of IEEE Std 1003.2 ( POSIX.2 ) regular expressions ( RE's); see re_format(7).

Arguments

Type IntentOptional Attributes Name
type(regex_type), intent(out) :: this
character(len=*), intent(in) :: pattern
character(len=*), intent(in), optional :: flags
integer, intent(out), optional :: nmatch
integer, intent(out), optional :: status

Source Code

subroutine regcomp(this,pattern,flags,nmatch,status)

! ident_1="@(#) M_exec regcomp(3f) compile regular expression"

type(regex_type), intent(out)            :: this
character(len=*), intent(in)             :: pattern
character(len=*), intent(in), optional   :: flags
integer, intent(out), optional           :: nmatch
integer, intent(out), optional           :: status
character(len=10,kind=C_char)            :: flags_
integer(C_int)                           :: nmatch_
integer(C_int)                           :: status_
character(kind=c_char,len=1),allocatable :: char_temp1(:)
character(kind=c_char,len=1),allocatable :: char_temp2(:)

   interface
     subroutine C_regcomp(preg,pattern,flags,nmatch,status) bind(C,name="C_regcomp")
       import
       type(C_ptr), intent(in), value           :: preg
       character(len=1,kind=C_char), intent(in) :: pattern(*)
       character(len=1,kind=C_char), intent(in) :: flags(*)
       integer(C_int), intent(inout)            :: nmatch
       integer(C_int), intent(inout)            :: status
     end subroutine C_regcomp

     subroutine C_regalloc(preg_return) bind(C,name="C_regalloc")
       import
       type(C_ptr), intent(out)                 :: preg_return
     end subroutine C_regalloc
   end interface

   flags_=' '
   if (present(flags)) flags_=flags
   this%preg = C_NULL_ptr
   call C_regalloc(this%preg)
   char_temp1 = s2c( trim(pattern) )
   char_temp2 = s2c( trim(flags) )
   call C_regcomp(this%preg, char_temp1, char_temp2, nmatch_, status_)
   if (present(nmatch)) then
     nmatch=nmatch_
   endif
   if (present(status)) then
     status=status_
   elseif (status_/=0) then
     stop 'Regex runtime error: regcomp failed.'
   endif
end subroutine regcomp