Well, originally I was thinking a function-based approach might look like the following, but
after pondering the rest of the discussion I have started to reconsider (everything!) 
I was going to do some comparison timings on function versus subroutine and the other methods
discussed here; and it got me curious about what the real instructions generated are; had not really thought out or tested the endian issues (It has been a while, but there are more than two types)
but I was just playing and the discussion raised questions on this approach. Your original point
about how these issues would actually be thrashed out more under other circumstances certainly is hitting home after seeing the thrashing here just discussing it all. It worked on my platform
and I admit to doing a little “golf coding” here as well, but it is a complete program (probable bugs and all) so …
program append
use,intrinsic::iso_fortran_env,only:int8,int16,int32,int64, real64
implicit none
character(len=*),parameter :: g='(*(g0,1x))'
integer(kind=int64) :: clicks(2), count64, count_rate64
integer(kind=int64),allocatable :: result(:)
integer(kind=int32),allocatable :: ia(:), ib(:), i32(:)
integer :: i,isz
real(kind=real64) :: time_read
doubleprecision ::t0
call system_clock(count64, count_rate64 )
print g,'COUNT RATE FOR INT64:',count_rate64
ia= [int(b'01010101010101010101010101010101'), &
int(b'10101010101010101010101010101010'), &
int(b'00000000000000000000000000000001'), &
int(b'11111111111111111111111111111111'), &
int(b'10000000000000000000000000000000')]
ib = [int(b'11111111111111111111111111111111'), &
int(b'00100100100100100100100100100100'), &
int(b'10000000000000000000000000000000'), &
int(b'11111111111111111111111111111111'), &
int(b'00000000000000000000000000000001')]
write(*,g)'concatentate'
call system_clock(clicks(1))
result= concat(ia,ib)
call system_clock(clicks(2))
write(*,'(2(b32.32),/,b64.64)')(ia(i),ib(i),result(i),i=1,size(ia))
call timeit()
write(*,g)'bifurcate'
call system_clock(clicks(1))
i32=[( bifurcate(result(i)),i=1,size(result) )]
call system_clock(clicks(2))
write(*,'(2(b32.32),/,b64.64)')(i32(i*2-1:i*2),result(i),i=1,size(result))
call timeit()
isz=size(i32)
write(*,g)'compare odd elments of i32 to ia', all(i32(1:isz:2).eq.ia)
write(*,g)'compare even elments of i32 to ib',all(i32(2:isz:2).eq.ib)
contains
subroutine timeit()
write(*,g)'clicks:',clicks(2)-clicks(1)
time_read=(clicks(2)-clicks(1))/real(count_rate64,real64)
write(*,'(a,g0,1x,a)') 'time : ', time_read, ' seconds'
end subroutine timeit
elemental integer(kind=int64) function concat(ia,ib)
integer(kind=int32),intent(in) :: ia, ib
logical, parameter :: IS_BIG_ENDIAN = iachar( c=transfer(source=1,mold="a") ) == 0
integer,parameter :: LSHIFT=merge(0,32,IS_BIG_ENDIAN)
integer,parameter :: RSHIFT=merge(32,0,IS_BIG_ENDIAN)
concat = dshiftl( shiftr(int(ia,kind=int64),RSHIFT), shiftl(int(ib,kind=int64), LSHIFT),32)
end function concat
function bifurcate(i64)
integer(kind=int64),intent(in) :: i64
integer(kind=int32) :: bifurcate(2)
logical, parameter :: IS_BIG_ENDIAN = iachar( c=transfer(source=1,mold="a") ) == 0
integer,parameter :: LSHIFT=merge(32,0,IS_BIG_ENDIAN)
integer,parameter :: RSHIFT=merge(0,32,IS_BIG_ENDIAN)
bifurcate = int([ ibits(i64,RSHIFT,32), ibits(i64, LSHIFT,32)],kind=int32)
end function bifurcate
end program append
results from gfortran and ifort on my laptop …
$ fpm run --profile release --compiler ifort
fpm: Entering directory '/home/urbanjs/venus/V600/github/fun/bits2'
Project is up to date
COUNT RATE FOR INT64: 1000000
concatentate
0101010101010101010101010101010111111111111111111111111111111111
0101010101010101010101010101010111111111111111111111111111111111
1010101010101010101010101010101000100100100100100100100100100100
1010101010101010101010101010101000100100100100100100100100100100
0000000000000000000000000000000110000000000000000000000000000000
0000000000000000000000000000000110000000000000000000000000000000
1111111111111111111111111111111111111111111111111111111111111111
1111111111111111111111111111111111111111111111111111111111111111
1000000000000000000000000000000000000000000000000000000000000001
1000000000000000000000000000000000000000000000000000000000000001
clicks: 1
time : .1000000000000000E-05 seconds
bifurcate
0101010101010101010101010101010111111111111111111111111111111111
0101010101010101010101010101010111111111111111111111111111111111
1010101010101010101010101010101000100100100100100100100100100100
1010101010101010101010101010101000100100100100100100100100100100
0000000000000000000000000000000110000000000000000000000000000000
0000000000000000000000000000000110000000000000000000000000000000
1111111111111111111111111111111111111111111111111111111111111111
1111111111111111111111111111111111111111111111111111111111111111
1000000000000000000000000000000000000000000000000000000000000001
1000000000000000000000000000000000000000000000000000000000000001
clicks: 6
time : .6000000000000000E-05 seconds
compare odd elments of i32 to ia T
compare even elments of i32 to ib T
fpm: Leaving directory '/home/urbanjs/venus/V600/github/fun/bits2'
urbanjs@mercury:~/github/fun/bits2/app$ fpm run --profile release --compiler gfortran
fpm: Entering directory '/home/urbanjs/venus/V600/github/fun/bits2'
Project is up to date
COUNT RATE FOR INT64: 1000000000
concatentate
0101010101010101010101010101010111111111111111111111111111111111
0101010101010101010101010101010111111111111111111111111111111111
1010101010101010101010101010101000100100100100100100100100100100
1010101010101010101010101010101000100100100100100100100100100100
0000000000000000000000000000000110000000000000000000000000000000
0000000000000000000000000000000110000000000000000000000000000000
1111111111111111111111111111111111111111111111111111111111111111
1111111111111111111111111111111111111111111111111111111111111111
1000000000000000000000000000000000000000000000000000000000000001
1000000000000000000000000000000000000000000000000000000000000001
clicks: 851
time : 0.85099999999999998E-6 seconds
bifurcate
0101010101010101010101010101010111111111111111111111111111111111
0101010101010101010101010101010111111111111111111111111111111111
1010101010101010101010101010101000100100100100100100100100100100
1010101010101010101010101010101000100100100100100100100100100100
0000000000000000000000000000000110000000000000000000000000000000
0000000000000000000000000000000110000000000000000000000000000000
1111111111111111111111111111111111111111111111111111111111111111
1111111111111111111111111111111111111111111111111111111111111111
1000000000000000000000000000000000000000000000000000000000000001
1000000000000000000000000000000000000000000000000000000000000001
clicks: 7005
time : 0.70049999999999998E-5 seconds
compare odd elments of i32 to ia T
compare even elments of i32 to ib T
An interesting footnote is how something very similar is handled with complex values and their components. A complex value is two real values, but you can define and extract the components individually, and refer to them as a%re and a%im; which might be an interesting model to emulate.