Create an object at a given address

From Rosetta Code
Task
Create an object at a given address
You are encouraged to solve this task according to the task description, using any language you may know.

Basic Data Operation
This is a basic data operation. It represents a fundamental action on a basic data type.

You may see other such operations in the Basic Data Operations category, or:

Integer Operations
Arithmetic | Comparison

Boolean Operations
Bitwise | Logical

String Operations
Concatenation | Interpolation | Comparison | Matching

Memory Operations
Pointers & references | Addresses


In systems programing it is sometimes required to place language objects at specific memory locations, like I/O registers, hardware interrupt vectors etc.


Task

Show how language objects can be allocated at a specific machine addresses.

Since most OSes prohibit access to the physical memory if it is not mapped by the application, as an example, rather than a physical address, take the address of some existing object (using suitable address operations if necessary).


For example:

  •   create an integer object
  •   print the machine address of the object
  •   take the address of the object and create another integer object at this address
  •   print the value of this object to verify that it is same as one of the origin
  •   change the value of the origin and verify it again



6502 Assembly

In 6502 Assembly memory is represented by either an 8-bit or a 16-bit address (i.e. $0000 - $FFFF). 8-bit address are reserved for the memory from $00 to $FF - known as zero page; access to this memory takes one less byte in the opcode and one less cycle to execute.

Data can be stored, one byte at a time, through the store instructions, for example to store data at $1900:

        sta $1900
        stx $1901
        sty $1902

Storage can be indexed through the use of the X or Y registers:

        ldx #54
.loop   sta $1900,X
        dex
        bne loop

It can also be stored via indirect indexed addressing (i.e. memory points to an address), using the Y register:

        lda #0
        sta $70
        lda #$20
        sta $71
        ldy #0
        sta ($70),Y

Finally, it can be stored via indexed indirect addressing (i.e. read the address of memory from the table stored at the parameter), using the X register:

        lda #0
        sta $70
        lda #$20
        sta $71
        ldx #0
        sta ($70,X)

It should be noted that on the 6502 processor hardware is normally memory mapped, so this is often used for manipulating hardware.

68000 Assembly

First, an integer object will be created at address $100000:

MOVE.L #$12345678,$100000

Finding the address of a given object isn't actually possible in the same way it would be on C, since anything loaded from an address is just a numeric copy and is not actually related in any way to the "object." The closest way is to label a memory address and load that label as a numeric constant.

myVariable equ $100000
MOVE.L #myVariable,D0
JSR printLong           ;some unimplemented printing routine.

Creating a new object at that location is as simple as storing a new value there.

MOVE.L #$FFFFFFFF,myVariable

8086 Assembly

This example uses UASM to assemble MS-DOS compatible code.

.model small                             ;specify memory model to use
.stack 1024                              ;set up stack

.data                                    ;data segment

UserRam BYTE 256 DUP (0)                 ;allocate 256 bytes of user RAM, initialized to zero.

tempByte equ UserRam                     ;define a few labels for clarity
tempWord equ UserRam+2
tempLong_LoWord equ UserRam+4
tempLong_HiWord equ UserRam+6          

.code                                    ;code segment

mov ax, @data
mov ds, ax                  

mov ax, @code
mov es, ax                               ;load segment registers with the appropriate segments.

; now there is no need to use "mov ax, seg UserRam" since we've already loaded the data segment into DS


;store an integer value into memory

mov ax, 1000h                            ;load the value 0x1000 into AX
mov word ptr [ds:tempLong_LoWord],ax     ;store 0x1000 into tempLong_LoWord
mov ax, 0040h                            ;the 8086 is 16-bit so we have to load the pieces separately.
mov word ptr [ds:tempLong_HiWord],ax     ;store 0x0040 into tempLong_HiWord

;get the address of a variable
mov ax, tempLong_LoWord                  ;without "word ptr" and brackets, the assembler interprets a label as a constant.

Action!

DEFINE FIRST="12345"
DEFINE SECOND="54321"
DEFINE PTR="CARD"

PROC Main()
  PTR base,copy=base

  PrintF("Address of base variable: %H%E",@base)
  PrintF("Address of copy variable: %H%E",@copy)
  PutE()

  PrintF("Assign %U value to base variable%E",FIRST)
  base=FIRST
  PrintF("Value of base variable: %U%E",base)
  PrintF("Value of copy variable: %U%E",copy)
  PutE()

  PrintF("Assign %U value to base variable%E",SECOND)
  base=SECOND
  PrintF("Value of base variable: %U%E",base)
  PrintF("Value of copy variable: %U%E",copy)
RETURN
Output:

Screenshot from Atari 8-bit computer

Address of base variable: $268C
Address of copy variable: $268C

Assign 12345 value to base variable
Value of base variable: 12345
Value of copy variable: 12345

Assign 54321 value to base variable
Value of base variable: 54321
Value of copy variable: 54321

Ada

In Ada object address can be specified using the address representation clause RM 13.3:

type IO_Port is mod 2**8; -- One byte
Device_Port : type IO_Port;
for Device_Port'Address use 16#FFFF_F000#;

In the example above the address is specified constant. It is also possible to specify address dynamically as the following solution of the task does:

with Ada.Text_IO;              use Ada.Text_IO;
with System.Storage_Elements;  use System.Storage_Elements;

procedure Test_Address is
   X : Integer := 123;
   Y : Integer;
   for Y'Address use X'Address;
begin
   Put_Line ("At address:" & Integer_Address'Image (To_Integer (Y'Address)));
   Put_Line (Integer'Image (Y));
   X := 456;
   Put_Line (Integer'Image (Y));
end Test_Address;

Sample output:

At address: 38207236
 123
 456

Aikido

Aikido doesn't support getting the address of a variable. However, in the spirit of this task, it does support raw memory access using peek and poke. These can be used on both an integer representing an address (64 bit) or a value obtained from calling malloc.

var portaddr = 0x80
var v = peek (portaddr, 1)   // 1 byte
v |= 0x40
poke (portaddr, v, 1) // 1 byte back again

var addr = malloc (16)
poke (addr, 1234, 4)
poke (addr+4, 0, 2)
poke (addr+6, 12, 2)

Applesoft BASIC

 0  DEF  FN P(A) =  PEEK (A) +  PEEK (A + 1) * 256
 100 :
 110  REM CREATE AN INTEGER OBJECT
 120 :
 130 I$ =  CHR$ (42)
 140  POKE 236, PEEK (131)
 150  POKE 237, PEEK (132)
 160  PRINT "HERE IS AN INTEGER    : " ASC (I$)
 200 :
 210  REM PRINT THE MACHINE ADDRESS OF THE OBJECT
 220 :
 230  PRINT "ITS ADDRESS IS        : " FN P( FN P(236) + 1)
 300 :
 310  REM TAKE THE ADDRESS OF THE OBJECT AND CREATE ANOTHER INTEGER OBJECT AT THIS ADDRESS
 320 :
 330 O$ =  CHR$ (0)
 340  POKE 250, PEEK (131)
 350  POKE 251, PEEK (132)
 360  POKE  FN P(250) + 1, PEEK ( FN P(236) + 1)
 370  POKE  FN P(250) + 2, PEEK ( FN P(236) + 2)
 400 :
 410  REM PRINT THE VALUE OF THIS OBJECT TO VERIFY THAT IT IS SAME AS ONE OF THE ORIGIN 
 420 :
 430  PRINT "COMPARE OTHER INTEGER : " ASC (O$)
 500 :
 510  REM CHANGE THE VALUE OF THE ORIGIN AND VERIFY IT AGAIN
 520 :
 530  POKE  FN P( FN P(236) + 1),69
 540  PRINT "NEW INTEGER VALUE     : " ASC (I$)
 550  PRINT "COMPARE OTHER INTEGER : " ASC (O$)
Output:
HERE IS AN INTEGER    : 42
ITS ADDRESS IS        : 38399
COMPARE OTHER INTEGER : 42
NEW INTEGER VALUE     : 69
COMPARE OTHER INTEGER : 69

ARM Assembly

Translation of: 68000 Assembly

First, an integer object will be created at address $100000:

mov r0,#0x00100000
ldr r1,testData
str r1,[r0]   ;store 0x12345678 at address $100000
bx lr         ;return from subroutine

testData:
     .long 0x12345678    ;VASM uses .long for 32 bit and .word for 16 bit values, unlike most ARM assemblers.

Finding the address of a given object isn't actually possible in the same way it would be on C, since anything loaded from an address is just a numeric copy and is not actually related in any way to the "object." The closest way is to label a memory address and load that label as a numeric constant.

.equ myVariable,0x00100000
mov r0,#myVariable
bl printLong        ;unimplemented printing routine

Creating a new object at that location is as simple as storing a new value there.

mov r0,#0x00100000
mov r1,#0
mvn r1,r1     ;flip the bits of r1
str r1,[r0]   ;store 0xFFFFFFFF at address $100000
bx lr         ;return from subroutine

AutoHotkey

In AutoHotkey indeed no language objects can be created at a specified address. But it's very well possible to read and write memory addresses directly. All standard number types are allowed.

; Create a variable with 4 bytes size and show it's machine address.
VarSetCapacity(var, 4, 0)
pAddress := &var
MsgBox Machine address: %pAddress%

; pAddress contains the memory address.
; Write a number and read it back.
NumPut(123456, pAddress+0, 0, "UInt")                               
MsgBox % "Contents of *pAddress: " . NumGet(pAddress+0, 0, "UInt")

BBC BASIC

      REM Create an integer object:
      anInteger% = 12345678
      PRINT "Original value =", anInteger%
      
      REM Print the machine address of the object:
      address% = ^anInteger%
      PRINT "Hexadecimal address =   ";~address%
      
      REM Take the address of the object and create
      REM another integer object at this address:
      !address% = 87654321
      
      REM Print the value of this object to verify
      REM that it is same as one of the origin:
      PRINT "New value =", anInteger%
      
      REM Change the value and verify it again:
      anInteger% = 55555555
      PRINT "Final value =", !address%

Output:

Original value =      12345678
Hexadecimal address =   B51955
New value =           87654321
Final value =         55555555

C

#include <stdio.h>

int main()
{
  int intspace;
  int *address;

  address = &intspace; // address = 0x100;
  *address = 65535;
  printf("%p: %08x (=%08x)\n", address, *address, intspace);
  // likely we must be worried about endianness, e.g.
  *((char*)address) = 0x00;
  *((char*)address+1) = 0x00;
  *((char*)address+2) = 0xff;
  *((char*)address+3) = 0xff; // if sizeof(int) == 4!
  // which maybe is not the best way of writing 32 bit values...
  printf("%p: %08x (=%08x)\n", address, *address, intspace);
  return 0;
}
0xbfc5675c: 0000ffff (=0000ffff)
0xbfc5675c: ffff0000 (=ffff0000)

A more typical embedded way of doing this is below. Note that the OS will probably not allow this due to memory protections. Embedded systems often do not have memory managers.

#include <stdint.h>
#include <stddef.h>

// This is a port variable located at address 0x100
#define PORT_A (*(volatile uint32_t*)0x100)

int main()
{
  uint32_t dat;
  size_t addr;

  PORT_A ^= 0x01;   // Toggle bit 0 of PORT_A
  dat = PORT_A;     // Read PORT_A
  addr = &PORT_A;   // addr = 0x100

  return 0;
}

C++

C++ supports this natively through placement new. This allows construction of complex object types in arbitrary memory locations.

#include <string>
#include <iostream>

int main()
{
    // Allocate enough memory to hold an instance of std::string
    char* data = new char[sizeof(std::string)];

    // use placement new to construct a std::string in the memory we allocated previously
    std::string* stringPtr = new (data) std::string("ABCD");

    std::cout << *stringPtr << " 0x" << stringPtr << std::endl;

    // use placement new to construct a new string object in the same memory location
    // remember to manually call destructor
    stringPtr->~basic_string();
    stringPtr = new (data) std::string("123456");

    std::cout << *stringPtr << " 0x" << stringPtr << std::endl;

    // clean up
    stringPtr->~basic_string();
    delete[] data;
}

Sample output:

ABCD 0x00204040
123456 0x00204040

COBOL

Works with: COBOL 2002
IDENTIFICATION DIVISION.
PROGRAM-ID. object-address-test.
DATA DIVISION.
LOCAL-STORAGE SECTION.
77  int-space PICTURE IS 9(5) VALUE IS 12345.
77  addr      PICTURE IS 9(5) BASED VALUE IS ZERO.
77  point       USAGE IS POINTER.
PROCEDURE DIVISION.
    DISPLAY "Value of integer object   : " int-space
    SET point TO ADDRESS OF int-space
    DISPLAY "Machine address of object : " point
    SET ADDRESS OF addr TO point
    DISPLAY "Value of referent object  : " addr
    MOVE 65535 TO int-space
    DISPLAY "New value of original     : " addr
    DISPLAY "New value of reference    : " int-space
    GOBACK.
END PROGRAM object-address-test.

Output:

Value of integer object   : 12345
Machine address of object : 0x0000563e11e77fd0
Value of referent object  : 12345
New value of original     : 65535
New value of reference    : 65535

Commodore BASIC

The PEEK and POKE commands allow the Commodore BASIC user to perform limited 6502 Assembly operations.

10 POKE 50000,(3) REM EQUIVALENT OF LDA #$03 STA 50000
20 PEEK(50000) REM READ THE VALUE AT MEMORY ADDRESS 50000

D

A better presentation.

import std.stdio ;

void main() {
    int[] arr ;
    foreach(i; [0,1,2,3])
        arr ~= i*(1 << 24) + 0x417e7e7e ;

    struct X {
        char[16] msg ;
    }

    X* xPtr ;
    int* iPtr ;
    float* fPtr ;

    int adrSpace = cast(int) arr.ptr ;
    // get address of an existing object arr

    xPtr = cast(X*) adrSpace ;
    // xPtr now point to arr, as a struct X
    writefln("arr(as X)'s msg = '%s' (len %d) @ 0x%08x",
        xPtr.msg, xPtr.msg.length, xPtr) ;

    iPtr = cast(int*) (adrSpace + 1 * 4 /*bytes*/) ;
    fPtr = cast(float*) iPtr ;
    // pointers now point to arr[1]
    writefln("arr[1] = 0x%8x (%9.4f) @ 0x%08X", *iPtr, *fPtr, iPtr) ;
    iPtr = cast(int*) (adrSpace + 3 * 4 /*bytes*/) ;
    fPtr = cast(float*) iPtr ;
    // pointers now point to arr[3]
    writefln("arr[3] = 0x%8x (%9.4f) @ 0x%08X", *iPtr, *fPtr, iPtr) ;
    *fPtr = 0.5f ; // change value
    writefln("arr[3] = 0x%8x (%9.4f) @ 0x%08X", *iPtr, *fPtr, iPtr) ;
}

output:

arr(as X)'s msg = '~~~A~~~B~~~C~~~D' (len 16) @ 0x401C2F80
arr[1] = 0x427e7e7e (  63.6235) @ 0x401C2F84
arr[3] = 0x447e7e7e (1017.9764) @ 0x401C2F8C
arr[3] = 0x3f000000 (   0.5000) @ 0x401C2F8C

Delphi

program Create_an_object_at_a_given_address;

{$APPTYPE CONSOLE}

var
  origem: Integer;
  copy: Integer absolute origem;   // This is old the trick

begin
  writeln('The "origem" adress is: ', cardinal(@origem));
  writeln('The "copy" adress is: ', cardinal(@copy));
  writeln;

  origem := 10;
  writeln('Assign 10 to "origem" ');
  writeln('The value of "origem" é ', origem);
  writeln('The value of "copy" é ', copy);
  writeln;

  copy := 2;
  writeln('Assign 2 to "copy" ');

  writeln('The value of "origem" é ', origem);
  writeln('The value of "copy" é ', copy);

  Readln;

end.
Output:
The "origem" adress is: 4261256
The "copy" adress is: 4261256

Assign 10 to "origem"
The value of "origem" é 10
The value of "copy" é 10

Assign 2 to "copy"
The value of "origem" é 2
The value of "copy" é 2

Forth

As an untyped language, specific machine addresses are very easy to represent in Forth. This is usually most useful for embedded targets.

$3f8 constant LPT1:

LPT1: c@ .
$3f LPT1: c!

Some architectures may require special fetch and store operators to access ports. For example, Open Firmware defines l@ and l! for safe 32-bit port writes.

FreeBASIC

' FB 1.05.0

Type Person
  As String name
  As Integer age
  Declare Constructor(name As String, age As Integer)
End Type

Constructor Person(name As String, age As Integer)
  This.name = name
  This.age = age
End Constructor

Dim ap As Any Ptr = CAllocate(SizeOf(Person)) ' allocate memory to store a Person object

'create a Person object at the address of the memory we've just allocated

Dim p As Person Ptr = New(ap) Person("Teresa", 60)

'check addresses are same
Print ap, p

'check data is not corrupt
Print p -> name, p -> age

'call implicit destructor
p -> Destructor

'free memory
Deallocate(ap)

Print
Print "Press any key to quit"
Sleep
Output:
4790800       4790800
Teresa         60

FutureBasic

include "NSLog.incl"


local fn DoIt
  NSLog( @"Dimension in integer \"x\", but do not assign it a value.\n" )
  long x
  // Note that the @ (at sign) prefixing x is a pointer to its machine address
  NSLog( @"The machine address of x is: %p", @x )
  NSLog( @"While x is unassigned, the machine address will contain a garbage value: %ld\n", x )
  
  // Assign x a value of 1234
  x = 1234
  NSLog( @"When x is assigned a value of %ld, that value will be stored in the machine address: %p", x, @x )
  NSLog( @"The machine address now contains the value: %ld\n", x )
  
  // Reassign x a value of 5678
  x = 5678
  NSLog( @"Wnen x is reassigned the new value %ld, that value will be stored in the existing machine address: %p", x, @x )
  NSLog( @"The machine address now contains the value: %ld\n", x )
end fn

fn DoIt

HandleEvents
Output:
Dimension in integer "x", but do not assign it a value.

The machine address of x is: 0x7ffee279bb58
While x is unassigned, the machine address will contain a garbage value: 1099524915200

When x is assigned a value of 1234, that value will be stored in the machine address: 0x7ffee279bb58
The machine address now contains the value: 1234

Wnen x is reassigned the new value 5678, that value will be stored in the existing machine address: 0x7ffee279bb58
The machine address now contains the value: 5678


Go

Go has several ways to access arbitrary memory locations using the built-in unsafe package. If the desired memory contains an array, since Go doesn't have pointer arithmetic, then a slice should be used instead of a pointer. The following solution demonstrates both a pointer and a slice.

package main

import(
	"fmt"
	"unsafe"
	"reflect"
)

func pointer() {
	fmt.Printf("Pointer:\n")

	// Create a *int and store the address of 'i' in it. To create a pointer to
	// an arbitrary memory location, use something like the following:
	//    p := (*int)(unsafe.Pointer(uintptr(0x100)))
	// And replace '0x100' with the desired address.
	var i int
	p := &i

	fmt.Printf("Before:\n\t%v: %v, %v\n", p, *p, i)

	*p = 3

	fmt.Printf("After:\n\t%v: %v, %v\n", p, *p, i)
}

func slice() {
	fmt.Printf("Slice:\n")

	var a [10]byte

	// reflect.SliceHeader is a runtime representation of the internal workings
	// of a slice. To make it point to a specific address, use something like
	// the following:
	//    h.Data = uintptr(0x100)
	// And replace '0x100' with the desired address.
	var h reflect.SliceHeader
	h.Data = uintptr(unsafe.Pointer(&a)) // The address of the first element of the underlying array.
	h.Len = len(a)
	h.Cap = len(a)

	// Create an actual slice from the SliceHeader.
	s := *(*[]byte)(unsafe.Pointer(&h))

	fmt.Printf("Before:\n\ts: %v\n\ta: %v\n", s, a)

	// Copy a string into the slice. This fills the underlying array, which in
	// this case has been manually set to 'a'.
	copy(s, "A string.")

	fmt.Printf("After:\n\ts: %v\n\ta: %v\n", s, a)
}

func main() {
	pointer()
	fmt.Println()

	slice()
}

Output:

Pointer:
Before:
        0xf840026018: 0, 0
After:
        0xf840026018: 3, 3

Slice:
Before:
        s: [0 0 0 0 0 0 0 0 0 0]
        a: [0 0 0 0 0 0 0 0 0 0]
After:
        s: [65 32 115 116 114 105 110 103 46 0]
        a: [65 32 115 116 114 105 110 103 46 0]

J

For this task, it's probably best to use the C implementation via a shared library (which requires changing the C function name from main to something else).

Julia

Julia has pointer access functions for interface with C code. Because the address of a Julia integer variable within the VM may change when it is re-assigned a new value, an array of a single integer is used below.

function unsafepointers()
    intspace = [42]
    address = pointer_from_objref(intspace)
    println("The address of intspace is $address")
    anotherint = unsafe_pointer_to_objref(address)
    println("intspace is $(intspace[1]), memory at $address, reference value $(anotherint[1])")
    intspace[1] = 123456
    println("Now, intspace is $(intspace[1]), memory at $address, reference value $(anotherint[1])")
    anotherint[1] = 7890
    println("Now, intspace is $(intspace[1]), memory at $(pointer_from_objref(anotherint)), reference value $(anotherint[1])")
end

unsafepointers()
Output:

The address of intspace is Ptr{Void} @0x0000000007271030 intspace is 42, memory at Ptr{Void} @0x0000000007271030, reference value 42 Now, intspace is 123456, memory at Ptr{Void} @0x0000000007271030, reference value 123456 Now, intspace is 7890, memory at Ptr{Void} @0x0000000007271030, reference value 7890

Kotlin

Works with: Ubuntu version 14.04
// Kotlin/Native Technology Preview

import kotlinx.cinterop.*

fun main(args: Array<String>) {
    val intVar = nativeHeap.alloc<IntVar>().apply { value = 42 }
    with(intVar) { println("Value is $value, address is $rawPtr") }
    intVar.value = 52  // create new value at this address
    with(intVar) { println("Value is $value, address is $rawPtr") }
    nativeHeap.free(intVar)
}
Output:

Sample output:

Value is 42, address is 26431776
Value is 52, address is 26431776

Lua

Lua has addresses by tables:

local a = {10}
local b = a

print ("address a:"..tostring(a), "value a:"..a[1])
print ("address b:"..tostring(b), "value b:"..b[1])

b[1] = 42

print ("address a:"..tostring(a), "value a:"..a[1])
print ("address b:"..tostring(b), "value b:"..b[1])
Output:

Sample output:

address a:table: 007c8d48	value a:10
address b:table: 007c8d48	value b:10
address a:table: 007c8d48	value a:42
address b:table: 007c8d48	value b:42

M2000 Interpreter

In M2000 we can create two kind of buffers, one for data, and one for code. Buffer for code is immutable at execution time. We can execute code by using an offset. Buffer for data is always mutable, but can't execute code.

There is no assembler x86 for M2000 yet, so we have to write code using a reference book and some subs for help

Memory addresses are nit the physical address, it's from virtual space.

Module CheckIt {
      structure  alfa {
            val as long
      }
      Buffer Clear Beta as alfa*2
      Print Beta(0)  ' return address
      Return Beta, 0!val:=500 ' unsigned integer 32 bit
      Print Eval(Beta, 0!val)=500
      Return Beta, 0!val:=0xFFFFFFFF
      Print Eval(Beta, 0!val)=4294967295
      Buffer Code ExecMem as byte*1024
      Offset=0
      EmbLong(0xb8, 5000) ' mov eax,5100
      EmbByteLong(0x3,0x5, Beta(0)) ' add eax, [Beta(0)] 
      EmbLong(0xa3, Beta(1)) ' mov [Beta(1)], eax
      EmbByte(0x31, 0xC0) ' xor eax, eax       
      Ret() ' Return
      Execute Code ExecMem, 0
      Print eval(Beta, 1!val)=4999
      Sub Ret()
            Return ExecMem, Offset:=0xC3
            Offset++
      End Sub
      Sub EmbByte()
            Return ExecMem, Offset:=Number, Offset+1:=Number
            Offset+=2
      End Sub
      Sub EmbLong()
            Return ExecMem, Offset:=Number, Offset+1:=Number as Long
            Offset+=5
      End Sub
      Sub EmbByteLong()
            Return ExecMem, Offset:=Number, Offset+1:=Number, Offset+2:=Number as Long
            Offset+=6
      End Sub
}
Checkit

Nim

type
  MyObject = object
    x: int
    y: float

var
  mem = alloc(sizeof(MyObject))
  objPtr = cast[ptr MyObject](mem)
echo "object at ", cast[int](mem), ": ", objPtr[]

objPtr[] = MyObject(x: 42, y: 3.1415)
echo "object at ", cast[int](mem), ": ", objPtr[]

Output:

object at 139966605271112: (x: 0, y: 0.0)
object at 139966605271112: (x: 42, y: 3.1415)

This works for global variables too:

var x: int = 3
var p: ptr int

p = cast[ptr int](addr(x))

echo "Before ", x
p[] = 5
echo "After: ", x

Output:

Before 3
After: 5

Pascal

Like in Ada you can assigne different variables at the same adress of an already declared variable. Nice to get the bytes out of an Int64.

program test;
type
  t8Byte =  array[0..7] of byte;
var
  I : integer;
  A : integer absolute I;
  K : t8Byte;
  L : Int64 absolute K;
begin
  I := 0;
  A := 255; writeln(I);
  I := 4711;writeln(A);

  For i in t8Byte do
  Begin
    K[i]:=i;
    write(i:3,' ');
  end;
  writeln(#8#32);
  writeln(L);
end.
{OUT}
255
4711
  0  1  2  3  4  5  6  7 
506097522914230528

Perl

The is basically a simplified version of the solution to the Address of a variable task, so for more detail please consult that entry.

# 20210218 Perl programming solution

use strict;
use warnings;

# create an integer object

print "Here is an integer             : ", my $target = 42, "\n";

# print the machine address of the object

print "And its reference is           : ", my $targetref = \$target, "\n";

# take the address of the object and create another integer object at this address

print "Now assigns a new value to it  : ", $$targetref = 69, "\n";

#  print the value of this object to verify that it is same as one of the origin

print "Then compare with the referent : ", $target, "\n";
Output:
Here is an integer             : 42
And its reference is           : SCALAR(0x1e25328)
Now assigns a new value to it  : 69
Then compare with the referent : 69

Phix

Phix does not support creation of a "language object" at a specific address, but you can peek and poke bytes, words, dwords and qwords to any address, as long as doing so does not trigger a hardware exception. You could also use inline assembly, if that helps any.

poke(0x80,or_bits(peek(0x80),0x40))
#ilASM{ mov al,[0x80]
        or al,0x40
        mov [0x80],al}

PicoLisp

: (setq IntSpace 12345)          # Integer
-> 12345

: (setq Address (adr 'IntSpace)) # Encoded machine address
-> -2969166782547

: (set (adr Address) 65535)      # Set this address to a new value
-> 65535

: IntSpace                       # Show the new value
-> 65535

PureBasic

; Allocate a 1Mb memory area work within to avoid conflicts,
; this address could be any number but it may then fail on some systems.
*a=AllocateMemory(1024*1024)

; Write a int wit value "31415" at address +312,
; using pointer '*a' with a displacement.
PokeI(*a+312, 31415)

; Write a float with value Pi at address +316,
; by creating a new pointer '*b' for this address
*b=*a+316
PokeF(*b, #PI)

;Now test it
For i=0 To 1024000 Step 4
  n=PeekI(*a+i)
  If n
    Debug "Int at +"+Str(i)+"  = "+Str(n)
    Debug "Float at +"+Str(i)+"= "+StrF(PeekF(*a+i))
  EndIf
Next

Racket

#lang racket
(require ffi/unsafe)

(define x #"Foo")
;; Get the address of the `x' object
(printf "The address of `x' is: ~s\n" (cast x _scheme _long))
(define address (cast x _bytes _long))
(printf "The address of the bytestring it holds: ~s\n" address)
(define y (cast address _long _bytes))
(printf "Converting this back to a bytestring: ~s\n" y)
(bytes-set! y 0 71)
(printf "Changed the converted bytestring: ~s\n" y)
(printf "The original one is now: ~s\n" x)
;; But (bytes-set! x 0 71) will throw an error since `x' is immutable,
;; showing that we've really modifed the memory directly in a way that
;; the runtime doesn't like.

;; Also, the above can fail at any moment if a GC happens, since
;; Racket's GC moves objects.  So a proper way to do this is not to
;; start from an existing object, but allocate one outside of the GC's
;; reach, using raw malloc():
(define buf (malloc 4 'raw))
(make-sized-byte-string buf 4)
;; or start with a given address of something like a memory-mapped IO
;; object

Raku

(formerly Perl 6) Raku has fairly comprehensive facilities for accessing allocating and accessing memory and also declaring C-style structs, via the NativeCall interface, as this example demonstrates.

use NativeCall;
use NativeCall::Types;

# bind to basic libc memory management
sub malloc(size_t) returns Pointer[uint8] is native {*};
sub memset(Pointer, uint32, size_t) is native {*};
sub free(Pointer[uint8]) is native {*};

my Pointer[uint8] $base-p = malloc(100);
memset($base-p, 0, 100);

# define object as a C struct that contains a short and an int
class SampleObject is repr('CStruct') {
    has uint16 $.foo is rw;
    has uint8  $.bar is rw;
}

# for arguments sake our object is at byte offset 64 in the
# allocated memory

my $offset-p =  $base-p.clone.add(64);
my $object-p := nativecast(Pointer[SampleObject], $offset-p);
note "creating object at address {+$object-p}";

my $struct := $object-p.deref;

$struct.foo = 41;
$struct.bar = 99;

# check we can update
$struct.foo++; # 42

# Check that we're actually updating the memory
use Test;

# look at the bytes directly to verify we've written to memory. Don't be too exact, as
# the positions may vary on different platforms depending on endianess and field alignment.

my $rec-size = nativesizeof(SampleObject);
my uint8 @bytes-written = (0 ..^ $rec-size).map(-> $i {$base-p[64 + $i]}).grep: * > 0;

# first field 'foo' (amount is small enough to fit in one byte)
is @bytes-written[0], 42, 'object first field';

# second field 'bar'
is @bytes-written[1], 99, 'object second field';

# verify that changing the origin changes the object values
memset($base-p, 1, 100); # set every byte to 1

is $struct.foo, 256 + 1, 'short updated at origin';
is $struct.bar, 1, 'byte updated at origin';

# tidy up
free($base-p);
done-testing;
Output:
creating object at address 94299589110352
ok 1 - object first field
ok 2 - object second field
ok 3 - short updated at origin
ok 4 - byte updated at origin
1..4

Rust

In a real program, most if not all of the contents of main would all be in one `unsafe` block, however in this one each unsafe operation gets its own block to emphasize exactly which actions Rust considers unsafe.

use std::{mem,ptr};

fn main() {
    let mut data: i32;

    // Rust does not allow us to use uninitialized memory but the STL provides an `unsafe`
    // function to override this protection.
    unsafe {data = mem::uninitialized()}

    // Construct a raw pointer (perfectly safe)
    let address = &mut data as *mut _;

    unsafe {ptr::write(address, 5)}
    println!("{0:p}: {0}", &data);

    unsafe {ptr::write(address, 6)}
    println!("{0:p}: {0}", &data);

}


S-BASIC

S-BASIC fully supports "based" variables that can be positioned at run-time.

var first, addr = integer
based second = integer

first = 12345
location var addr = first
base second at addr

print "Value of first variable   ="; first
print "Address of first variable = "; hex$(addr)
print "Value of second variable  ="; second

end
Output:
Value of first variable   = 12345
Address of first variable = 0CEE
Value of second variable  = 12345

Scala

As a high-level, type safe Functional Programming language this sort of (low-level) assembler tasks are in the danger zone and therefore not allowed. One of the reasons; a variable at a physical memory address has also a type. A memory location could contain e.g. an integer but for the same ease it could also a character object. This must by guarded by the programming language in order to shield the programmer from errors.

Direct physical memory address is considered harmful. It divides the languages which supports and the other that prohibits this bad practice. Its adorns languages which are you preventing from this evil.

It is rather unprofessional to deliver this kind of error-prone software. And we are wondering why this tasks is made.

Tcl

As noted in the Address Operations task, it is highly unusual to work with low-level addresses in Tcl. However it is possible to use Tcl's C API (specifically Tcl_LinkVar) to couple Tcl variables to a particular address:

Library: critcl
package require critcl

# A command to 'make an integer object' and couple it to a Tcl variable
critcl::cproc linkvar {Tcl_Interp* interp char* var1} int {
    int *intPtr = (int *) ckalloc(sizeof(int));

    *intPtr = 0;
    Tcl_LinkVar(interp, var1, (void *) intPtr, TCL_LINK_INT);
    return (int) intPtr;
}

# A command to couple another Tcl variable to an 'integer object'; UNSAFE!
critcl::cproc linkagain(Tcl_Interp* interp int addr char* var2} void {
    int *intPtr = (int *) addr;

    Tcl_LinkVar(interp, var2, (void *) intPtr, TCL_LINK_INT);
}

# Conventionally, programs that use critcl structure in packages
# This is used to prevent recompilation, especially on systems like Windows
package provide machAddrDemo 1

Demonstrating:

package require machAddrDemo
set addr [linkvar foo]
puts "var 'foo' at $addr with value $foo"
linkagain $addr bar
puts "var 'bar' at $addr with value $bar"
incr foo
puts "incremented 'foo' so 'bar' is $bar"

Example output (your mileage may vary when it comes to addresses):

var 'foo' at 19363848 with value 0
var 'bar' at 19363848 with value 0
incremented 'foo' so 'bar' is 1

Wren

Library: Wren-fmt

Wren is a high-level scripting language which doesn't support pointers and has no way of obtaining the machine address of variables.

This is still true even when Wren is embedded in a program written in a low-level language such as C because the embedding API has been designed so as not to expose raw pointers to memory managed by Wren to the host.

Perhaps the closest we can get to the spirit of this task is to create a new foreign class, Integer, memory for which is allocated from a C host and the machine address is therefore available. We can then use this class to wrap Wren integers (though, strictly speaking, Wren doesn't have integers - they're just a special case of the Num class), get and set their values and take their address.

Note that it is not possible to specify the address at which the embedding API function wrenSetSlotNewForeign allocates new objects and any attempt to allocate a new object at the same address as an old one by juggling with pointers will almost certainly lead to a seg fault. So all we can sensibly do is to change the value of the current object.

/* Create_an_object_at_a_given_address.wren */

import "./fmt" for Fmt

foreign class Integer {
    construct new(i) {}

    foreign value

    foreign value=(i)

    foreign address
}

var i = Integer.new(42)
Fmt.print("Integer object with value of:    $d allocated at address $#x.", i.value, i.address)
i.value = 42
Fmt.print("Integer object value reset to:   $d but still at address $#x.", i.value, i.address)
i.value = 43
Fmt.print("Integer object value changed to: $d but still at address $#x.", i.value, i.address)


We now embed this in the following C program, compile and run it.

/* gcc Create_an_object_at_a_given_address.c -o Create_an_object_at_a_given_address -lwren -lm */

#include <stdio.h>
#include <stdlib.h>
#include <string.h>
#include "wren.h"

/* C <=> Wren interface functions */

void C_integerAllocate(WrenVM* vm) {
    long *pi = (long *)wrenSetSlotNewForeign(vm, 0, 0, sizeof(long));
    long i = (long)wrenGetSlotDouble(vm, 1);
    *pi = i;
}

void C_value(WrenVM* vm) {
    long i = *(long *)wrenGetSlotForeign(vm, 0);
    wrenSetSlotDouble(vm, 0, (double)i);
}

void C_setValue(WrenVM* vm) {
    long *pi = (long *)wrenGetSlotForeign(vm, 0);
    long i = (long)wrenGetSlotDouble(vm, 1);
    *pi = i;
}

void C_address(WrenVM* vm) {
    long *pi = (long *)wrenGetSlotForeign(vm, 0);
    wrenSetSlotDouble(vm, 0, (double)(unsigned long long)pi);
}

WrenForeignClassMethods bindForeignClass(WrenVM* vm, const char* module, const char* className) {
    WrenForeignClassMethods methods;
    methods.allocate = NULL;
    methods.finalize = NULL;
    if (strcmp(module, "main") == 0) {
        if (strcmp(className, "Integer") == 0) {
            methods.allocate = C_integerAllocate;
        }
    }
    return methods;
}

WrenForeignMethodFn bindForeignMethod(
    WrenVM* vm,
    const char* module,
    const char* className,
    bool isStatic,
    const char* signature) {
    if (strcmp(module, "main") == 0) {
        if (strcmp(className, "Integer") == 0) {
            if (!isStatic && strcmp(signature, "value") == 0)     return C_value;
            if (!isStatic && strcmp(signature, "value=(_)") == 0) return C_setValue;
            if (!isStatic && strcmp(signature, "address") == 0)   return C_address;
        } 
    }
    return NULL;
}

static void writeFn(WrenVM* vm, const char* text) {
    printf("%s", text);
}

void errorFn(WrenVM* vm, WrenErrorType errorType, const char* module, const int line, const char* msg) {
    switch (errorType) {
        case WREN_ERROR_COMPILE:
            printf("[%s line %d] [Error] %s\n", module, line, msg);
            break;
        case WREN_ERROR_STACK_TRACE:
            printf("[%s line %d] in %s\n", module, line, msg);
            break;
        case WREN_ERROR_RUNTIME:
            printf("[Runtime Error] %s\n", msg);
            break;
    }
}

char *readFile(const char *fileName) {
    FILE *f = fopen(fileName, "r");
    fseek(f, 0, SEEK_END);
    long fsize = ftell(f);
    rewind(f);
    char *script = malloc(fsize + 1);
    fread(script, 1, fsize, f);
    fclose(f);
    script[fsize] = 0;
    return script;
}

static void loadModuleComplete(WrenVM* vm, const char* module, WrenLoadModuleResult result) {
    if( result.source) free((void*)result.source);
}

WrenLoadModuleResult loadModule(WrenVM* vm, const char* name) {
    WrenLoadModuleResult result = {0};
    if (strcmp(name, "random") != 0 && strcmp(name, "meta") != 0) {
        result.onComplete = loadModuleComplete;
        char fullName[strlen(name) + 6];
        strcpy(fullName, name);
        strcat(fullName, ".wren");
        result.source = readFile(fullName);
    }
    return result;
}

int main(int argc, char **argv) {
    WrenConfiguration config;
    wrenInitConfiguration(&config);
    config.writeFn = &writeFn;
    config.errorFn = &errorFn;
    config.bindForeignClassFn = &bindForeignClass;
    config.bindForeignMethodFn = &bindForeignMethod;
    config.loadModuleFn = &loadModule;
    WrenVM* vm = wrenNewVM(&config);
    const char* module = "main";
    const char* fileName = "Create_an_object_at_a_given_address.wren";
    char *script = readFile(fileName);
    WrenInterpretResult result = wrenInterpret(vm, module, script);
    switch (result) {
        case WREN_RESULT_COMPILE_ERROR:
            printf("Compile Error!\n");
            break;
        case WREN_RESULT_RUNTIME_ERROR:
            printf("Runtime Error!\n");
            break;
        case WREN_RESULT_SUCCESS:
            break;
    }
    wrenFreeVM(vm);
    free(script);
    return 0;
}
Output:

Sample output:

Integer object with value of:    42 allocated at address 0x55a56e0f2dd8.
Integer object value reset to:   42 but still at address 0x55a56e0f2dd8.
Integer object value changed to: 43 but still at address 0x55a56e0f2dd8.

Z80 Assembly

When writing assembly yourself, you'll know any object's memory location in advance. This code creates the 16-bit integer object 0xFFFF at memory address 0xC000:

LD HL,&FFFF
LD (&C000),HL

Loading a value into a register from memory only loads a copy; the original value at that memory location isn't altered, nor is the memory location of that value. Assume this code is executed immediately after the above example:

LD HL,(&C000)    ;load &FFFF into HL
INC HL           ;HL now equals &0000
LD BC,(&C000)    ;load &FFFF into BC.

In order to change a value at a memory location, it either needs to be loaded into a register and stored back after altering that register in some way, or by using certain indirect addressing modes, like so:

LD HL,&C000   ;get the address of our variable.
INC (hl)      ;increment the low byte.
LD HL,(&C000) ;load &FF00 into HL.

If you're not familiar with the Z80's syntax, this can be a bit confusing. The brackets are like the dereference operator in C, and not having brackets is like the unary & operator in C. The Z80's ability to do 16-bit operations is limited; it can load from two consecutive memory locations into a 16-bit register pair, however when using (hl) as an operand it is only operating on the lower 8 bits. When learning Z80 Assembly, it is very helpful to view a hex editor while learning the instruction set.