OpenCores
URL https://opencores.org/ocsvn/openrisc/openrisc/trunk

Subversion Repositories openrisc

[/] [openrisc/] [trunk/] [gnu-dev/] [or1k-gcc/] [gcc/] [testsuite/] [gfortran.dg/] [intrinsic_unpack_2.f90] - Rev 858

Go to most recent revision | Compare with Previous | Blame | View Log

! { dg-do run }
! { dg-require-effective-target fortran_large_real }
! Program to test the UNPACK intrinsic for large real type
program intrinsic_unpack
   implicit none
   integer,parameter :: k = selected_real_kind (precision (0.0_8) + 1)

   real(kind=k), dimension(3,3) :: ark, brk
   complex(kind=k), dimension(3,3) :: ack, bck

   logical, dimension(3, 3) :: mask
   character(len=500) line1, line2
   integer i

   mask = reshape ((/.false.,.true.,.false.,.true.,.false.,.false.,&
                    &.false.,.false.,.true./), (/3, 3/));

   ark = reshape ((/1._k, 0._k, 0._k, 0._k, 1._k, 0._k, 0._k, 0._k, 1._k/), &
         (/3, 3/));
   brk = unpack ((/2._k, 3._k, 4._k/), mask, ark)
   if (any (brk .ne. reshape ((/1._k, 2._k, 0._k, 3._k, 1._k, 0._k, &
                               0._k, 0._k, 4._k/), (/3, 3/)))) &
      call abort
   write (line1,'(9F9.5)') brk
   write (line2,'(9F9.5)') unpack((/2._k, 3._k, 4._k/), mask, ark)
   if (line1 .ne. line2) call abort
   brk = -1._k
   brk = unpack ((/2._k, 3._k, 4._k/), mask, 0._k)
   if (any (brk .ne. reshape ((/0._k, 2._k, 0._k, 3._k, 0._k, 0._k, &
      0._k, 0._k, 4._k/), (/3, 3/)))) &
      call abort

   ack = reshape ((/1._k, 0._k, 0._k, 0._k, 1._k, 0._k, 0._k, 0._k, 1._k/), &
        (/3, 3/));
   bck = unpack ((/(2._k, 0._k), (3._k, 0._k), (4._k,   0._k)/), mask, ack)
   if (any (real(bck) .ne. reshape ((/1._k, 2._k, 0._k, 3._k, 1._k, 0._k, &
        0._k, 0._k, 4._k/), (/3, 3/)))) &
        call abort
   write (line1,'(18F9.5)') bck
   write (line2,'(18F9.5)') unpack((/(2._k, 0._k), (3._k, 0._k), (4._k,0._k)/), &
        mask, ack)
   if (line1 .ne. line2) call abort

end program

Go to most recent revision | Compare with Previous | Blame | View Log

powered by: WebSVN 2.1.0

© copyright 1999-2024 OpenCores.org, equivalent to Oliscience, all rights reserved. OpenCores®, registered trademark.