Buchempfehlung
MySQL kurz & gut
MySQL kurz & gut
Das preiswerte Taschen- buch stellt MySQL-rele- vante Inhalte systematisch und knapp dar, sodass es sich optimal zum Nach- schlagen beim Pro- grammieren eignet. [Mehr Infos...]
FreeBASIC-Chat
Es sind Benutzer im FreeBASIC-Chat online.
(Stand:  )
FreeBASIC bei Twitter
Twitter FreeBASIC-Nachrichten jetzt auch über Twitter erhalten. Follow us!

fb:porticula NoPaste

Info
Info / Hilfe
Liste
Übersicht / Liste
Neu
Datei hochladen
Suche
Quellcode suchen
Download
Dateidownload

Multiput.bi

Uploader:MitgliedOneCypher
Datum/Zeit:13.10.2009 11:10:46
Hinweis: Dieser Quelltext ist Bestandteil des Projekts GuiPtr, zu dem es auf FreeBASIC-Portal.de eine Projektseite gibt.

#INCLUDE once "fbgfx.bi"

'Ich danke den Urhebern von Rotozoom und Multiput! Diese Routinen stammen nicht aus meiner Feder und ich beanspruche keine eigenen Kopierrechte auf diese Quelltexte in dieser Datei!
'Thanks to the authors of Rotozoom and Multiput! These routines were not made by me and I do NOT claim a copyright on my own of any code in this file!
function ScaleImage (FromImg as any ptr, ToImg as any ptr) as any ptr
    dim as integer w1, h1, w2, h2
    dim as double xf, yf
    dim c as uinteger
    imageinfo FromImg, w1,h1
    imageinfo ToImg, w2,h2
    xf = w2 / w1
    yf = h2 / h1
    if xf <> 1 or yf <> 1 then
        for x as integer = 0 to w2 -1
            for y as integer = 0 to h2 -1
                c = point (x / xf,y / yf, FromImg)
                pset ToImg,(x,y),c
            next
        next
        return ToImg
    else
        'put ToImg,(0,0),FromImg
        return FromImg
    end if
end function

const pi = 3.1415926, pi_180 = pi / 180

type sse_t field = 1
    s(0 to 3) as single
end type

type mmx_t field = 1
    i(0 to 1) as integer
end type


sub rotozoom_alpha2( byref dst as FB.IMAGE ptr = 0, byref src as const FB.IMAGE ptr, byval positx as integer, byval posity as integer, byref angle as integer, byref zoomx as single, byref zoomy as single = 0, byval transcol as uinteger = &h00ff00ff, byval alphalvl as integer = 255, byref offsetx as integer = 0, byref offsety as integer = 0 )

    'Rotozoom for 32-bit FB.Image by Dr_D(Dave Stanley), yetifoot(Simon Nash) and Mysoft(Gregori Macario Harbs)
    'No warranty implied... use at your own risk ;)

    dim as sse_t sse0, sse1, sse2, sse3, sse4, sse5
    dim as integer nx = any, ny = any
    dim as single tcdzx = any, tcdzy = any, tsdzx = any, tsdzy = any
    dim as integer sw2 = any, sh2 = any, dw = any, dh = any
    dim as single tc = any, ts = any
    dim as uinteger ptr dstptr = any, srcptr = any
    dim as integer startx = any, endx = any, starty = any, endy = any
    dim as integer x(3), y(3)
    dim as integer xa = any, xb = any, ya = any, yb = any
    dim as integer dstpitch = any
    dim as integer srcpitch = any, srcwidth = any, srcheight = any
    Dim As Ulongint mask1 = &H00FF00FF00FF00FFULL'&H000000FF00FF00FFULL mask change copies src alpha
    dim as integer x_draw_len = any, y_draw_len = any
    dim as short alphalevel(3) = {alphalvl,alphalvl,alphalvl,alphalvl}

    if alphalvl <0 then
        alphalvl = 0
    elseif alphalvl>255 then
        alphalvl = 255
    end if

    if zoomx = 0 then exit sub
    if zoomy = 0 then zoomy = zoomx
    If src = 0 Then Exit Sub

    if dst = 0 then
        dstptr = screenptr
        screeninfo dw,dh,,,dstpitch
    else
        dstptr = cast( uinteger ptr, dst + 1 )
        dw = dst->width
        dh = dst->height
        dstpitch = dst->pitch
    end if

    srcptr = cast( uinteger ptr, src + 1 )

    sw2 = src->width\2
    sh2 = src->height\2
    srcpitch = src->pitch
    srcwidth = src->width
    srcheight = src->height

    tc = cos( angle * pi_180 )
    ts = sin( angle * pi_180 )
    tcdzx = tc/zoomx
    tcdzy = tc/zoomy
    tsdzx = ts/zoomx
    tsdzy = ts/zoomy

    xa = sw2 * tc * zoomx + sh2  * ts * zoomx
    ya = sh2 * tc * zoomy - sw2  * ts * zoomy

    xb = sh2 * ts * zoomx - sw2  * tc * zoomx
    yb = sw2 * ts * zoomy + sh2  * tc * zoomy

    Dim As Integer centerx = -(offsetx*(tc*zoomx) + offsety*(ts*zoomx)) + offsetx
    Dim As Integer centery = -(offsety*(tc*zoomy) - offsetx*(ts*zoomy)) + offsety

    x(0) = sw2-xa
    x(1) = sw2+xa
    x(2) = sw2-xb
    x(3) = sw2+xb
    y(0) = sh2-ya
    y(1) = sh2+ya
    y(2) = sh2-yb
    y(3) = sh2+yb

    for i as integer = 0 to 3
        for j as integer = i to 3
            if x(i)>=x(j) then
                swap x(i), x(j)
            end if
        next
    next
    startx = x(0)
    endx = x(3)

    for i as integer = 0 to 3
        for j as integer = i to 3
            if y(i)>=y(j) then
                swap y(i), y(j)
            end if
        next
    next
    starty = y(0)
    endy = y(3)

    positx-=sw2
    posity-=sh2
    positx+=centerx
    posity+=centery
    if posity+starty<0 then starty = -posity
    if positx+startx<0 then startx = -positx
    if posity+endy<0 then endy = -posity
    if positx+endx<0 then endx = -positx

    if positx+startx>(dw-1) then startx = (dw-1)-positx
    if posity+starty>(dh-1) then starty = (dh-1)-posity
    if positx+endx>(dw-1) then endx = (dw-1)-positx
    if posity+endy>(dh-1) then endy = (dh-1)-posity
    if startx = endx or starty = endy then exit sub

    ny = starty - sh2
    nx = startx - sw2

    dstptr += dstpitch * (starty + posity) \ 4

    x_draw_len = (endx - startx)' + 1
    y_draw_len = (endy - starty)' + 1

    sse1.s(0) = tcdzx
    sse1.s(1) = tsdzx

    sse2.s(0) = -(ny * tsdzy)
    sse2.s(1) = (ny * tcdzy)

    sse3.s(0) = -tsdzy
    sse3.s(1) = tcdzy

    sse4.s(0) = (nx * tcdzx) + sw2
    sse4.s(1) = (nx * tsdzx) + sh2

    if x_draw_len = 0 then exit sub
    if y_draw_len = 0 then exit sub

    cptr( any ptr, dstptr ) += (startx + positx) * 4

    dim as any ptr ptr row_table = callocate( srcheight * sizeof( any ptr ) )
    dim as any ptr p = srcptr

    for i as integer = 0 to srcheight - 1
        row_table[i] = p
        p += srcpitch
    next i

    asm
        .balign 4

        movups xmm1, [sse1]
        movups xmm2, [sse2]
        movups xmm3, [sse3]
        movups xmm4, [sse4]

        .balign 4
        y_inner4:

        ' _mx = nxtc + sw2
        ' _my = nxts + sh2
        movaps xmm0, xmm4

        ' _dstptr = cptr( any ptr, dstptr )
        mov edi, dword ptr [dstptr]

        ' _x_draw_len = x_draw_len
        mov ecx, dword ptr [x_draw_len]

        ' _mx += -nyts
        ' _my += nytc
        addps xmm0, xmm2

        .balign 4
        x_inner4:

        ' get _mx and _my out of sse reg
        cvtps2pi mm0, xmm0

        ' mx = mmx0.i(0)
        movd esi, mm0

        ' shift mm0 so my is ready
        psrlq mm0, 32

        ' if (mx >= srcwidth) or (mx < 0) then goto no_draw3
        cmp esi, dword ptr [srcwidth]
        jae no_draw4

        ' my = mmx0.i(1)
        movd edx, mm0

        ' if (my >= srcheight) or (my < 0) then goto no_draw3
        cmp edx, dword ptr [srcheight]
        jae no_draw4

        ' _srcptr = srcbyteptr + (my * srcpitch) + (mx shl 2)
        shl esi, 2
        mov eax, dword ptr [row_table]
        add esi, dword ptr [eax+edx*4]

        '_srccol = *cptr( uinteger ptr, _srcptr )
        mov eax, dword ptr [esi]

'        ' if (_srccol and &HFF000000) = 0 then goto no_draw3
'        test eax, &HFF000000
'        jz no_draw4

        ' if _srccol = transcol then goto no_draw3
        cmp eax, dword ptr [transcol]
        je no_draw4

        ' blend

        ' load src pixel and dst pixel mmx, with unpacking
        punpcklbw mm0, dword ptr [esi]
        punpcklbw mm1, dword ptr [edi]

        ' shift them to the right place
        psrlw mm0, 8                ' mm0 = 00sa00sr00sg00sb
        psrlw mm1, 8                ' mm1 = 00da00dr00dg00db

        ' Prepare alpha

        'changed by mysoft
        movq mm2, [alphalevel]      ' mm2 = 00sa00xx00xx00xx
        'punpckhwd mm2, mm2          ' mm2 = 00sa00sa00xx00xx
        'punpckhdq mm2, mm2          ' mm2 = 00sa00sa00sa00sa


        ' Perform blend
        psubw mm0, mm1              ' (sX - dX)
        pmullw mm0, mm2             ' (sX - dX) * sa
        psrlq mm0, 8                ' mm0 = 00aa00rr00gg00bb
        paddw mm0, mm1              ' ((sX - dX) * sa) + dX
        pand mm0, qword ptr [mask1] ' mask off alpha and high parts

        ' repack to 32 bit
        packuswb mm0, mm0

        ' store in destination
        movd dword ptr [edi], mm0

        .balign 4
        no_draw4:

        ' _mx += tcdzx
        ' _my += tsdzx
        addps xmm0, xmm1

        ' _dstptr += 4
        add edi, 4

        ' _x_draw_len -= 1
        sub ecx, 1

        jnz x_inner4

        x_end4:

        ' nyts += tsdzy
        ' nytc += tcdzy
        addps xmm2, xmm3

        ' cptr( any ptr, dstptr ) += dstpitch
        mov eax, dword ptr [dstpitch]
        add dword ptr [dstptr], eax

        ' y_draw_len -= 1
        sub dword ptr [y_draw_len], 1

        jnz y_inner4

        y_end4:

        emms
    end asm

    deallocate( row_table )

end sub

Sub MultiPut(Byval lpTarget As Any Ptr= 0, _
             Byval xMidPos  As Integer= 0, _
             Byval yMidPos  As Integer= 0, _
             Byval lpSource As Any Ptr   , _
             Byval xScale   As Single = 1, _
             Byval yScale   As Single = 1, _
             Byval Rotate   As Single = 0, _
             Byval Mirror   As Integer = 0, _
             Byval Flipp   As Integer = 0, _
             Byval Trans    As Integer= 0, _
             Byval alphavalue As Integer = 255, _
             Byval Custom As Function(Byval Src As Uinteger, Byval Dest As Uinteger, Byval Param As Any Ptr = 0) As Uinteger = 0, _
             Byval Param As Any Ptr = 0)

  If (screenptr=0) Or (lpSource=0) Then Exit Sub

  If xScale < 0.001 Then xScale=0.001
  If yScale < 0.001 Then yScale=0.001

  Dim As Integer MustLock,MustRotate

   'variables for the alpha blending
     Dim As Uinteger srb = Any
     Dim As Uinteger drb = Any
     Dim As Uinteger  rb = Any
     Dim As Uinteger sr = Any, sg = Any, sb = Any, sa = Any, sa2 = Any
     Dim As Uinteger dr = Any, dg = Any, db = Any, da = Any, da2 = Any
     Dim As Uinteger  r = Any,  g = Any,  b = Any,  a = Any

  If lpTarget= 0 Then MustLock  =1
  If Rotate  <>0 Then MustRotate=1

  Dim As Integer  TargetWidth,TargetHeight,TargetBytes,TargetPitch
  If MustLock Then
    screeninfo    _
    TargetWidth , _
    TargetHeight, _
    TargetBytes ,,_
    TargetPitch
    TargetBytes Shr=3

    lpTarget=screenptr
  Else
    TargetBytes  = cptr(Uinteger Ptr,lpTarget)[1]
    TargetWidth  = cptr(Uinteger Ptr,lpTarget)[2]
    TargetHeight = cptr(Uinteger Ptr,lpTarget)[3]
    TargetPitch  = cptr(Uinteger Ptr,lpTarget)[4]
    lpTarget    += 32
  End If
  If (TargetWidth<4) Or (TargetHeight<4) Then Exit Sub

  Dim As Integer   SourceWidth,SourceHeight,SourceBytes,SourcePitch
  If cptr(Integer Ptr,lpSource)[0] = 7 Then
    SourceBytes  = cptr(Uinteger Ptr,lpSource)[1]
    SourceWidth  = cptr(Uinteger Ptr,lpSource)[2]
    SourceHeight = cptr(Uinteger Ptr,lpSource)[3]
    SourcePitch  = cptr(Uinteger Ptr,lpSource)[4]
    lpSource    += 32
  Else
    SourceBytes  = cptr(Ushort Ptr,lpSource)[0] And 7
    SourceWidth  = cptr(Ushort Ptr,lpSource)[0] Shr 3
    SourceHeight = cptr(Ushort Ptr,lpSource)[1]
    SourcePitch  = SourceWidth * SourceBytes
    lpSource    += 4
  End If
#if 0
  ? TargetWidth & "x" & TargetHeight & "x" & TargetBytes,TargetPitch
  ? SourceWidth & "x" & SourceHeight & "x" & SourceBytes,SourcePitch
  ? MustLock,Trans
  Sleep:End
#endif

  If (SourceWidth<2) Or (SourceHeight<2) Then Exit Sub
  If (TargetBytes<>SourceBytes) Then Exit Sub

#define xs 0 'screen
#define ys 1
#define xt 2 'texture
#define yt 3
  Dim As Single Points(3,3)
  points(0,xs)=-SourceWidth/2 * xScale
  points(1,xs)= SourceWidth/2 * xScale
  points(2,xs)= points(1,xs)
  points(3,xs)= points(0,xs)

  points(0,ys)=-SourceHeight/2 * yScale
  points(1,ys)= points(0,ys)
  points(2,ys)= SourceHeight/2 * yScale
  points(3,ys)= points(2,ys)

  points(1,xt)= SourceWidth-1
  points(2,xt)= points(1,xt)
  points(2,yt)= SourceHeight-1
  points(3,yt)= points(2,yt)

If Mirror Then Swap points(0,xt),points(1,xt) :Swap points(2,xt),points(3,xt)
If Flipp Then Swap points(0,yt),points(3,yt) :Swap points(2,yt),points(1,yt)
'if Mirror then swap points(1,xt),points(2,xt)
'if Flipp then swap points(2,yt),points(3,yt)


  Dim As Uinteger i
  Dim As Single x,y
  If MustRotate Then
    #ifndef UseRad
    Rotate*=Atn(1)/45 'degree 2 rad
    #endif
    While Rotate< 0       :rotate+=8*Atn(1):Wend
    While Rotate>=8*Atn(1):rotate-=8*Atn(1):Wend
    For i=0 To 3
      x=points(i,xs)*Cos(Rotate) - points(i,ys)*Sin(Rotate)
      y=points(i,xs)*Sin(Rotate) + points(i,ys)*Cos(Rotate)
      points(i,xs)=x:points(i,ys)=y
    Next
  End If

  Dim As Integer yStart,yEnd,xStart,xEnd
  yStart=100000:yEnd=-yStart:xStart=yStart:xEnd=yEnd

#define LI 0   'LeftIndex
#define RI 1   'RightIndex
#define  IND 0 'Index
#define NIND 1 'NextIndex
  Dim As Integer CNS(1,1) 'Counters

  For i=0 To 3
    points(i,xs)=Int(points(i,xs)+xMidPos)
    points(i,ys)=Int(points(i,ys)+yMidPos)
    If points(i,ys)<yStart Then yStart=points(i,ys):CNS(LI,IND)=i
    If points(i,ys)>yEnd   Then yEnd  =points(i,ys)
    If points(i,xs)<xStart Then xStart=points(i,xs)
    If points(i,xs)>xEnd   Then xEnd  =points(i,xs)
  Next
  If yStart =yEnd         Then Exit Sub
  If yStart>=TargetHeight Then Exit Sub
  If yEnd   <0            Then Exit Sub
  If xStart = xEnd        Then Exit Sub
  If xStart>=TargetWidth  Then Exit Sub
  If xEnd   <0            Then Exit Sub

  Dim As Ubyte    Ptr t1,s1
  Dim As Ushort   Ptr t2,s2
  Dim As Uinteger     t2c, s2c
  Dim As Uinteger Ptr t4,s4


#define ADD 0
#define CMP 1
#define SET 2
  Dim As Integer ACS(1,2) 'add compare and set
  ACS(LI,ADD)=-1:ACS(LI,CMP)=-1:ACS(LI,SET)=3
  ACS(RI,ADD)= 1:ACS(RI,CMP)= 4:ACS(RI,SET)=0


#define EX  0
#define EU  1
#define EV  2
#define EXS 3
#define EUS 4
#define EVS 5
  Dim As Single E(2,6),S(6),Length,uSlope,vSlope
  Dim As Integer U,UV,UA,UN,V,VV,VA,VN

  ' share the same highest point
  CNS(RI,IND)=CNS(LI,IND)
  If MustLock Then screenlock
  ' loop from Top to Bottom
  While yStart<yEnd
    'Scan Left and Right sides together
    For i=LI To RI
      ' bad to read but fast and short ;-)
      If yStart=points(CNS(i,IND),ys) Then
        CNS(i,NIND)=CNS(i,IND)+ACS(i,Add)
        If CNS(i,NIND)=ACS(i,CMP) Then CNS(i,NIND)=ACS(i,SET)
        While points(CNS(i,IND),ys) = points(CNS(i,NIND),ys)
          CNS(i, IND)=CNS(i,NIND)
          CNS(i,NIND)=CNS(i, IND)+ACS(i,Add)
          If CNS(i,NIND)=ACS(i,CMP) Then CNS(i,NIND)=ACS(i,SET)
        Wend
        E(i,EX) = points(CNS(i, IND),xs)
        E(i,EU) = points(CNS(i, IND),xt)
        E(i,EV) = points(CNS(i, IND),yt)
        Length  = points(CNS(i,NIND),ys)
        Length -= points(CNS(i, IND),ys)
        If Length <> 0.0 Then
          E(i,EXS) = points(CNS(i, NIND),xs)-E(i,EX):E(i,EXS)/=Length
          E(i,EUS) = points(CNS(i, NIND),xt)-E(i,EU):E(i,EUS)/=Length
          E(i,EVS) = points(CNS(i, NIND),yt)-E(i,EV):E(i,EVS)/=Length
        End If
        CNS(i,IND)=CNS(i,NIND)
      End If
    Next

    If (yStart<0)                              Then Goto SkipScanLine
    xStart=E(LI,EX)+0.5:If xStart>=TargetWidth Then Goto SkipScanLine
    xEnd  =E(RI,EX)-0.5:If xEnd  < 0           Then Goto SkipScanLine
    If (xStart=xEnd)                           Then Goto SkipScanLine
    'if xEnd  <xStart                           then goto SkipScanLine
    Length=xEnd-xStart
    uSlope=E(RI,EU)-E(LI,EU):uSlope/=Length
    vSlope=E(RI,EV)-E(LI,EV):vSlope/=Length
    If xstart<0 Then
      Length=Abs(xStart)
      U=Int(E(LI,EU)+uSlope*Length)
      V=Int(E(LI,EV)+vSlope*Length)
      xStart = 0
    Else
      U=Int(E(LI,EU)):V=Int(E(LI,EV))
    End If
    If xEnd>=TargetWidth Then xEnd=TargetWidth-1
    UV=Int(uSlope):UA=(uSlope-UV)*100000:UN=0
    VV=Int(vSlope):VA=(vSlope-VV)*100000:VN=0
    xEnd-=xStart
    Select Case TargetBytes
      Case 1
        t1=cptr(Ubyte Ptr,lpTarget)
        t1+=yStart*TargetPitch+xStart:xStart=0
        If Custom Then
          While xStart<xEnd
            s1=lpSource+V*SourcePitch+U
            *t1=Custom(*s1,*t1,Param)
            U+=UV:UN+=UA:If UN>=100000 Then U+=1:UN-=100000
            V+=VV:VN+=VA:If VN>=100000 Then V+=1:VN-=100000
            If u<0 Then u=0
            If v<0 Then v=0
            xStart+=1:t1+=1
          Wend
        Elseif Trans=0 Then
          While xStart<xEnd
            s1=lpSource+V*SourcePitch+U
            *t1=*s1
            U+=UV:UN+=UA:If UN>=100000 Then U+=1:UN-=100000
            V+=VV:VN+=VA:If VN>=100000 Then V+=1:VN-=100000
            If u<0 Then u=0
            If v<0 Then v=0
            xStart+=1:t1+=1
          Wend
        Else
          While xStart<xEnd
            s1=lpSource+V*SourcePitch+U
            If *s1 Then *t1=*s1
            U+=UV:UN+=UA:If UN>=100000 Then U+=1:UN-=100000
            V+=VV:VN+=VA:If VN>=100000 Then V+=1:VN-=100000
            If u<0 Then u=0
            If v<0 Then v=0
            xStart+=1:t1+=1
          Wend
        End If
      Case 2
        t2=cptr(Short Ptr,lpTarget)
        t2+=yStart*(TargetPitch Shr 1)+xStart:xStart=0
        If Custom Then
          While xStart<xEnd
            s2=cptr(Short Ptr,lpSource)+V*(SourcePitch Shr 1)+U
            s2c=*s2
            t2c=*t2
            s2c=(s2c And &H001F) Shl 3 Or (s2c Shr 2 And &H000007) Or _
                (s2c And &H07E0) Shl 5 Or (s2c Shr 1 And &H000300) Or _
                (s2c And &HF800) Shl 8 Or (s2c Shl 3 And &H070000) Or &HFF000000
            t2c=(t2c And &H001F) Shl 3 Or (s2c Shr 2 And &H000007) Or _
                (t2c And &H07E0) Shl 5 Or (s2c Shr 1 And &H000300) Or _
                (t2c And &HF800) Shl 8 Or (s2c Shl 3 And &H070000) Or &HFF000000
            t2c=Custom(s2c,t2c,Param)
            *t2=(t2c Shr 3 And &H001F) Or _
                (t2c Shr 5 And &H07E0) Or _
                (t2c Shr 8 And &HF800)
            U+=UV:UN+=UA:If UN>=100000 Then U+=1:UN-=100000
            V+=VV:VN+=VA:If VN>=100000 Then V+=1:VN-=100000
            If u<0 Then u=0
            If v<0 Then v=0
            xStart+=1:t2+=1
          Wend
        Elseif Trans=0 Then
          While xStart<xEnd
            s2=cptr(Short Ptr,lpSource)+V*(SourcePitch Shr 1)+U
            *t2=*s2
            U+=UV:UN+=UA:If UN>=100000 Then U+=1:UN-=100000
            V+=VV:VN+=VA:If VN>=100000 Then V+=1:VN-=100000
            If u<0 Then u=0
            If v<0 Then v=0
            xStart+=1:t2+=1
          Wend
        Else
          While xStart<xEnd
            s2=cptr(Short Ptr,lpSource)+V*(SourcePitch Shr 1)+U
            If *s2<>&HF81F Then *t2=*s2
            U+=UV:UN+=UA:If UN>=100000 Then U+=1:UN-=100000
            V+=VV:VN+=VA:If VN>=100000 Then V+=1:VN-=100000
            If u<0 Then u=0
            If v<0 Then v=0
            xStart+=1:t2+=1
          Wend
         End If
      Case 4
        t4=cptr(Integer Ptr,lpTarget)+yStart*(TargetPitch Shr 2)+xStart:xStart=0
        If Custom Then
          While xStart<xEnd
            s4=cptr(Integer Ptr,lpSource)+V*(SourcePitch Shr 2)+U
            '***** start alpha blending
       'this set of if...elseif...end if conditions applies alpha blending
       'these 43 lines can be replaced with '*t4 = *s4' to remove blending
       If alphavalue = 0 Then
         'no change needed *t4 = *t4
       Elseif alphavalue = 255 Then
         *t4 = *s4
       Elseif *t4 Shr 24 = 0 Then
         *t4 = *s4
       Elseif *t4 Shr 24 = 255 Then
         srb = *s4 And &h00ff00ff
         sg  = *s4 Xor srb
         sa  = alphavalue

         drb = *t4 And &h00ff00ff
         dg  = *t4 Xor drb
         da  = 256 - sa

         rb = (drb * da + srb * sa) And &hff00ff00
         g  = (dg  * da + sg  * sa) And &h00ff0000

         *t4 = (rb Or g) Shr 8 Or &hff000000
       Else
         sr = (*s4 Shr 16) And 255
         sg = (*s4 Shr  8) And 255
         sb = (*s4       ) And 255
         sa = (alphavalue)

         dr = (*t4 Shr 16) And 255
         dg = (*t4 Shr  8) And 255
         db = (*t4       ) And 255
         da = (*t4 Shr 24)

         sa2 = sa Shl 8
         da2 = da Shl 8 - da * sa
         a = (sa2 + da2)

         r = (dr * da2 + sr * sa2) \ a
         g = (dg * da2 + sg * sa2) \ a
         b = (db * da2 + sb * sa2) \ a
         *t4 = Rgba(r, g, b, a Shr 8)
       End If
            U+=UV:UN+=UA:If UN>=100000 Then U+=1:UN-=100000
            V+=VV:VN+=VA:If VN>=100000 Then V+=1:VN-=100000
            If u<0 Then u=0
            If v<0 Then v=0
            xStart+=1:t4+=1
          Wend
        Elseif Trans=0 Then
          While xStart<xEnd
            s4=cptr(Integer Ptr,lpSource)+V*(SourcePitch Shr 2)+U
            *t4=*s4
            U+=UV:UN+=UA:If UN>=100000 Then U+=1:UN-=100000
            V+=VV:VN+=VA:If VN>=100000 Then V+=1:VN-=100000
            If u<0 Then u=0
            If v<0 Then v=0
            xStart+=1:t4+=1
          Wend
        Else
          While xStart<xEnd
            's4=cptr(Integer Ptr,lpSource):s4+=V*(SourcePitch shr 2):s4+=U
            s4=cptr(Integer Ptr,lpSource)+V*(SourcePitch Shr 2)+U
            If (*s4 And &HFFFFFF)<>&HFF00FF Then
                '***** start alpha blending
         'this set of if...elseif...end if conditions applies alpha blending
         'these 43 lines can be replaced with '*t4 = *s4' to remove blending
         If alphavalue = 0 Then
           'no change needed *t4 = *t4
         Elseif alphavalue = 255 Then
           *t4 = *s4
         Elseif *t4 Shr 24 = 0 Then
           *t4 = *s4
         Elseif *t4 Shr 24 = 255 Then
           srb = *s4 And &h00ff00ff
           sg  = *s4 Xor srb
           sa  = alphavalue

           drb = *t4 And &h00ff00ff
           dg  = *t4 Xor drb
           da  = 256 - sa

           rb = (drb * da + srb * sa) And &hff00ff00
           g  = (dg  * da + sg  * sa) And &h00ff0000

           *t4 = (rb Or g) Shr 8 Or &hff000000
         Else
           sr = (*s4 Shr 16) And 255
           sg = (*s4 Shr  8) And 255
           sb = (*s4       ) And 255
           sa = (alphavalue)

           dr = (*t4 Shr 16) And 255
           dg = (*t4 Shr  8) And 255
           db = (*t4       ) And 255
           da = (*t4 Shr 24)

           sa2 = sa Shl 8
           da2 = da Shl 8 - da * sa
           a = (sa2 + da2)

           r = (dr * da2 + sr * sa2) \ a
           g = (dg * da2 + sg * sa2) \ a
           b = (db * da2 + sb * sa2) \ a
           *t4 = Rgba(r, g, b, a Shr 8)
         End If
         '***** end alpha blending
                End If
            U+=UV:UN+=UA:If UN>=100000 Then U+=1:UN-=100000
            V+=VV:VN+=VA:If VN>=100000 Then V+=1:VN-=100000
            If u<0 Then u=0
            If v<0 Then v=0
            xStart+=1:t4+=1
          Wend
        End If
    End Select

SkipScanLine:
    E(LI,EX)+=E(LI,EXS):E(LI,EU)+=E(LI,EUS):E(LI,EV)+=E(LI,EVS)
    E(RI,EX)+=E(RI,EXS):E(RI,EU)+=E(RI,EUS):E(RI,EV)+=E(RI,EVS)
    yStart+=1:If yStart=TargetHeight Then yStart=yEnd 'exit loop
  Wend
If MustLock Then screenunlock
End Sub


Dim Shared As Ushort PRemULDIV(16*4)

Sub ResamplePut(TGT As Any Ptr=0,CENX As Short,CENY As Short, SRC As Any Ptr,SIZX As Short,SIZY As Short,MYALPHA As Integer=-256)

  Static As Any Ptr IMGB,PTA,PTB,PTBB
  Static As Integer TX,TY,OBX,TDX
  Static As Integer BX,BY,USY,SSA,SSB
  Static As Integer RESSKPCNT,RESYSKP
  Static As Double DTMP

  ' ***** Check parameters to see if they are ok ********
  If SRC = 0 Then Exit Sub
  TX = cptr(fb.image Ptr, SRC)->width
  TY = cptr(fb.image Ptr, SRC)->height
  If TX<1 Or TY<1 Or SIZX<1 Or SIZY<1 Then Exit Sub
  If TX > SIZX Then BX=TX Else BX=SIZX
  If TY > SIZY Then BY=TY Else BY=SIZY
  If (BX*BY) > OBX Then
    BX *= 1.5: BY *= 1.5
    OBX = BX*BY
    If IMGB Then Imagedestroy(IMGB)
    IMGB = ImageCreate(BX,BY,0)
    If (cast(Uinteger,IMGB) Mod 16) Then
      asm
        mov ESI,[IMGB]
        mov EDI,ESI
        And EDI,(Not 15)
        add EDI,16
        mov [IMGB],EDI
        mov ecx, sizeof(fb.image)
        rep movsb
      End asm
    End If
  End If
  If TGT = screenptr Then TGT=0

  ' ***** pointer data / header ******
  PTA = (SRC+sizeof(fb.image))
  PTB = (IMGB+sizeof(fb.image))
  cptr(fb.image Ptr, IMGB)->width = SIZX
  cptr(fb.image Ptr, IMGB)->height = SIZY
  cptr(fb.image Ptr, IMGB)->pitch = SIZX*4

  ' ***** check if special pointer is needed ****
  If SIZY >= TY Then
    PTBB=PTB+((SIZY-TY)*cptr(fb.image Ptr, IMGB)->pitch)
    asm
      mov ESI,[PTBB]
      mov EDI,ESI
      And EDI,(Not 15)
      add EDI,16
      mov [PTBB],EDI
    End asm
  Else
    PTBB=PTB
  End If

  ' ==================================================================================
  ' ********************************* reduced width **********************************
  ' ==================================================================================
  If SIZX < TX Then
    DTMP=(TX/SIZX):RESSKPCNT=4
    While DTMP > 16
      DTMP /= 2
      RESSKPCNT Shl= 1
    Wend
    TDX = DTMP*65536

    asm
      ' ************************************************************
      ' ************************* HORIZONTAL ***********************
      ' ************************************************************
      mov esi,[PTA]                  ' Load ESI with the pointer of source
      mov edi,[PTBB]                 ' Load EDI with the pointer of the destiny
      mov eax,[TDX]                  ' EDX will temporary hold the "fixed point" number
      movd MM1,[SIZX]                ' MM1 is receiving the WIDTH of the destiny image
      mov edx,[TY]                   ' MM2 is receiving the HEIGHT of the source image
      mov ebx,[RESSKPCNT]            ' Skip Pixels Value
      Shl edx,16                     ' Adjusting for use high bits
      push ebp                       ' saving base pointer
      movd MM0,esp                   ' saving stack pointer in one MMX register
      mov ebp,eax                    ' EBP is receiving a fixed point number from EDX
      mov esp,-1                     ' ESP starts with -1
      pxor MM7,MM7                   ' Clear MM7 that will be used as zero
      '------------------------------------------------------------------------------
      _NEXTLINE_:            ' Here start the next line of the image
      movd eax,MM1                   ' Getting WIDTH from mmx register
      mov dx,ax                      ' Setting WIDTH in DX
      '------------------------------------------------------------------------------
      .align 16
      _NEXTGROUP_:           ' Here Start the next group from one average
      add esp,ebp                    ' Adding a new pixel group counter
      Xor ecx,ecx                    ' Clearing Pixel Counter
      '------------------------------------------------------------------------------
      cmp esp,65536                  ' Verify For optimization (no division)
      jb _ISONEPIXELA_               ' Go optimize
      pxor MM4,MM4                   ' Clear MM4 that will be used as SUM holder
      cmp esp,65536*2                ' Verify For optimization (no division)
      jb _ISTWOPIXELA_               ' Go optimize
      cmp esp,65536*4                ' Verify For optimization (no division)
      jb _ISFOURPIXELA_               ' Go optimize
      .align 16
      _NEXTPIXEL_:           ' Here it will get a new pixel
      mov eax, [esi]                 ' Read next Pixel
      cmp eax, 0xFFFF00FF            ' Is Transparent?
      jne SKPTT                      ' no? ignore
      mov eax,0x00808080             ' yes? gray with alpha 0
      SKPTT:                 ' Skip point for trans pixel
      inc ecx                        ' Increment Pixel Counter
      add esi,ebx                    ' point source to the next pixel
      movd MM5,eax                   ' Load Components in MMX register
      punpcklbw MM5,MM7              ' Convert from 4 bytes to 4 words
      paddw MM4,MM5                  ' Add those 4 bytes to the sum register
      Sub esp,65536                  ' subtract one pixel (fix pt) from calc holder
      jns _NEXTPIXEL_                ' go get next pixel until ESP becomes less than 0
      '------------------------------------------------------------------------------
      movq MM5,[PRemULDIV+ECX*8-8]   ' Get Fixed Point Pixel Divider
      psrlw MM4,3                    ' 5 bits only (0-31)
      pmullw MM4,MM5                 ' Divide Sum by pixel count (aka ECX)
      psrlw MM4,4                    ' From 4 Fixed to 4 short
      packuswb MM4,MM4               ' Convert from 4 shorts to 4 bytes
      movd [edi],MM4                 ' Save Average Pixel
      add edi,4                      ' point to the next buffer
      dec dx                         ' Decrease WIDTH counter
      jnz _NEXTGROUP_                ' Go get next pixel =D
      '------------------------------------------------------------------------------
      Sub edx,65536                  ' Decrease line counter
      jnz _NEXTLINE_                 ' Go do the next line
      jmp _HORENDA_                  ' Finished
      '------------------------------------------------------------------------------
      _ISONEPIXELA_:          ' Here is the optimization point (no division)
      mov eax, [esi]                 ' Read next Pixel
      Sub esp,65536                  ' subtract one pixel (fix pt) from calc holder
      cmp eax, 0xFFFF00FF            ' Is Transparent?
      jne SKPTTAOA                   ' no? ignore
      mov eax,0x00808080             ' yes? gray with alpha 0
      SKPTTAOA:               ' Skip point for trans pixel
      inc ecx                        ' Increment Pixel Counter
      add esi,ebx                    ' point source to the next pixel
      stosd                          ' Store pixel and increment
      dec dx                         ' Decrease WIDTH counter
      jnz _NEXTGROUP_                ' Go get next pixel =D
      Sub edx,65536                  ' Decrease line counter
      jnz _NEXTLINE_                 ' Go do the next line
      jmp _HORENDA_                  ' Finished
      '------------------------------------------------------------------------------
      _ISTWOPIXELA_:         ' This is optimization (half)
      mov eax, [esi]                 ' Read next Pixel
      cmp eax, 0xFFFF00FF            ' Is Transparent?
      jne SKPTTOB                    ' no? ignore
      mov eax,0x00808080             ' yes? gray with alpha 0
      SKPTTOB:               ' Skip point for trans pixel
      movd MM5,eax                   ' Load Components in MMX register
      punpcklbw MM5,MM7              ' Convert from 4 bytes to 4 words
      add esi,ebx                    ' point source to the next pixel
      paddw MM4,MM5                  ' Add those 4 bytes to the sum register
      mov eax, [esi]                 ' Read next Pixel
      cmp eax, 0xFFFF00FF            ' Is Transparent?
      jne SKPTTOC                    ' no? ignore
      mov eax,0x00808080             ' yes? gray with alpha 0
      SKPTTOC:               ' Skip point for trans pixel
      movd MM5,eax                   ' Load Components in MMX register
      punpcklbw MM5,MM7              ' Convert from 4 bytes to 4 words
      add esi,ebx                    ' point source to the next pixel
      paddw MM4,MM5                  ' Add those 4 bytes to the sum register
      Sub esp,65536*2                ' subtract one pixel (fix pt) from calc holder
      psrlw MM4,1                    ' Divide Sum by 2
      packuswb MM4,MM4               ' Convert from 4 shorts to 4 bytes
      movd [edi],MM4                 ' Save Average Pixel
      add edi,4                      ' point to the next buffer
      dec dx                         ' Decrease WIDTH counter
      jnz _NEXTGROUP_                ' Go get next pixel =D
      Sub edx,65536                  ' Decrease line counter
      jnz _NEXTLINE_                 ' Go do the next line
      jmp _HORENDA_                  ' Finished
      '------------------------------------------------------------------------------
      _ISFOURPIXELA_:         ' This is optimization (half)
      mov eax, [esi]                 ' Read next Pixel
      cmp eax, 0xFFFF00FF            ' Is Transparent?
      jne SKPTTOF                    ' no? ignore
      mov eax,0x00808080             ' yes? gray with alpha 0
      SKPTTOF:               ' Skip point for trans pixel
      movd MM5,eax                   ' Load Components in MMX register
      punpcklbw MM5,MM7              ' Convert from 4 bytes to 4 words
      add esi,ebx                    ' point source to the next pixel
      paddw MM4,MM5                  ' Add those 4 bytes to the sum register
      mov eax, [esi]                 ' Read next Pixel
      cmp eax, 0xFFFF00FF            ' Is Transparent?
      jne SKPTTOG                    ' no? ignore
      mov eax,0x00808080             ' yes? gray with alpha 0
      SKPTTOG:               ' Skip point for trans pixel
      movd MM5,eax                   ' Load Components in MMX register
      punpcklbw MM5,MM7              ' Convert from 4 bytes to 4 words
      add esi,ebx                    ' point source to the next pixel
      paddw MM4,MM5                  ' Add those 4 bytes to the sum register
      mov eax, [esi]                 ' Read next Pixel
      cmp eax, 0xFFFF00FF            ' Is Transparent?
      jne SKPTTOD                    ' no? ignore
      mov eax,0x00808080             ' yes? gray with alpha 0
      SKPTTOD:               ' Skip point for trans pixel
      movd MM5,eax                   ' Load Components in MMX register
      punpcklbw MM5,MM7              ' Convert from 4 bytes to 4 words
      add esi,ebx                    ' point source to the next pixel
      paddw MM4,MM5                  ' Add those 4 bytes to the sum register
      mov eax, [esi]                 ' Read next Pixel
      cmp eax, 0xFFFF00FF            ' Is Transparent?
      jne SKPTTOE                    ' no? ignore
      mov eax,0x00808080             ' yes? gray with alpha 0
      SKPTTOE:               ' Skip point for trans pixel
      movd MM5,eax                   ' Load Components in MMX register
      punpcklbw MM5,MM7              ' Convert from 4 bytes to 4 words
      add esi,ebx                    ' point source to the next pixel
      paddw MM4,MM5                  ' Add those 4 bytes to the sum register
      Sub esp,65536*4                ' subtract one pixel (fix pt) from calc holder
      psrlw MM4,2                    ' Divide Sum by 2
      packuswb MM4,MM4               ' Convert from 4 shorts to 4 bytes
      movd [edi],MM4                 ' Save Average Pixel
      add edi,4                      ' point to the next buffer
      dec dx                         ' Decrease WIDTH counter
      jnz _NEXTGROUP_                ' Go get next pixel =D
      Sub edx,65536                  ' Decrease line counter
      jnz _NEXTLINE_                 ' Go do the next line
      '------------------------------------------------------------------------------
      _HORENDA_:             ' Finish of horizontal resize
      movd esp,MM0                   ' restoring stack pointer
      pop ebp                        ' restoin base pointer
      emms                           ' Clear MMX state
    End asm
  Elseif SIZX >= TX Then

    ' ==================================================================================
    ' ******************************* increased width **********************************
    ' ==================================================================================

    DTMP=(TX/SIZX)
    TDX = DTMP*65536
    RESYSKP = cptr(fb.image Ptr, SRC)->pitch

    ' ************************************************************
    ' ******************* HORIZONTAL WHEN BIGGER *****************
    ' ************************************************************
    asm
      mov esi,[PTA]                  ' Load ESI with the pointer of source
      mov edi,[PTBB]                 ' Load EDI with the pointer of the destiny
      mov edx,[TDX]                  ' fixed point
      mov ecx,[TY]                   ' HEIGHT of the source
      mov ebx,[SIZX]                 ' WIDTH of the destiny
      mov eax,[RESYSKP]              ' PITCH of the source
      push ebp                       ' Saves Base Pointer
      mov ebp,edx                    ' fixed point
      movd MM0,esp                   ' Saves Stack Pointer
      mov esp,eax                    ' ESP = source PITCH
      Shl ecx,16                     ' Use ECX high bits
      ' ----------------------------------------------------------
      _NEXTLINEC_:           ' Here start the next line
      mov cx,bx                      ' Restore Line Length
      Xor edx,edx                    ' Clear Fixed Point Counter
      ' ----------------------------------------------------------
      _NEXTPIXELC_:          ' Here start next pixel
      mov eax,edx                    ' Get Counter
      Shr eax,16                     ' Fixed Point to Short
      mov eax,[esi+eax*4]            ' Read Pixel
      cmp eax, 0xFFFF00FF            ' Is Transparent?
      jne HBSKPTTOC                  ' no? ignore
      mov eax,0x00808080             ' yes? gray with alpha 0
      HBSKPTTOC:             ' Skip point for trans pixel
      add edx,ebp                    ' increase fixed point counter
      stosd                          ' Save Pixel and point to next
      dec cx                         ' Decrease pixel counter
      jnz _NEXTPIXELC_               ' Go get next pixel (if any)
      ' ----------------------------------------------------------
      add esi,esp                    ' Adjust pointer for next line
      Sub ecx,65536                  ' Decrease line counter (high bits)
      jnz _NEXTLINEC_                ' Go get next line (if any)
      ' ----------------------------------------------------------
      movd esp,MM0                   ' Restore Stack Pointer
      pop ebp                        ' Base Pointer from stack
      emms                           ' Clear MMX state
    End asm


  End If

  ' ==================================================================================
  ' ******************************* reduced height  **********************************
  ' ==================================================================================

  If SIZY < TY Then

    DTMP=(TY/SIZY)
    RESSKPCNT=1
    While DTMP > 16
      DTMP /= 2
      RESSKPCNT Shl= 1
    Wend
    TDX = DTMP*65536
    RESSKPCNT *= cptr(fb.image Ptr, IMGB)->pitch
    RESYSKP = cptr(fb.image Ptr, IMGB)->pitch

    asm
      ' ESI = Pointer of the source image
      ' EDI = Pointer of the destiny image
      ' EBP = Fixed Point Number of Pixels each group
      ' EAX = sum of byte intensity
      ' ECX = pixel counter (divisor)
      ' EBX = width/height of the destiny image
      ' ESP = controller of pixel/average
      ' EDX = temporary byte/dword converter & reminder

      ' ************************************************************
      ' ************************* VERTICAL *************************
      ' ************************************************************
      mov esi,[PTB]                  ' Load ESI with the pointer of source
      mov edi,[PTB]                  ' Load EDI with the pointer of the destiny
      mov ecx,[TDX]                  ' EDX will temporary hold the "fixed point" number
      movd MM1,[SIZY]                ' MM1 is receiving the HEIGHT of the destiny image
      movd MM2,[SSA]
      movd MM3,[SSB]
      mov edx,[SIZX]                 ' EDX is receiving the WIDTH of the destiny image
      mov eax,[RESYSKP]              ' destiny pitch
      mov ebx,[RESSKPCNT]            ' skip pixels(lines) pitch
      Shl edx,16                     ' Using high bits
      push ebp                       ' saving base pointer
      movd MM0,esp                   ' saving stack pointer in one MMX register
      mov ebp,ecx                    ' EBP is receiving a fixed point number from EDX
      mov esp,-1                     ' ESP starts with -1
      pxor MM7,MM7                   ' Clear MMX register
      ' ----------------------------------------------------
      _NEXTLINEB_:           ' Here start the next line of the image
      mov ecx,edx
      movd edx,MM1                   ' Getting HEIGHT from mmx register
      Or edx,ecx
      movd MM2,esi                   ' Saving Source Pointer
      movd MM3,edi                   ' Saving Destiny Pointer
      ' ----------------------------------------------------
      .align 16
      _NEXTGROUPB_:          ' Here Start the next group from one average
      add esp,ebp                    ' Adding a new pixel group counter
      cmp esp,65536                  ' Verify For optimization (no division)
      jb _VISONEPIXELA_              ' Go optimize
      pxor MM4,MM4                   ' Clear MM4 that will be used as SUM holder
      cmp esp,65536*2                ' Verify For optimization (no division)
      jb _VISTWOPIXELA_              ' Go optimize
      cmp esp,65536*4                ' Verify For optimization (no division)
      jb _VISFOURPIXELA_             ' Go optimize
      Xor ecx,ecx                    ' Clearing ECX for be used as SUM holder
      ' ----------------------------------------------------
      .align 16
      _NEXTPIXELB_:          ' Here it will get a new pixel
      inc ecx                        ' Increment Pixel Counter
      movd MM5,[esi]                 ' Load Components in MMX register
      punpcklbw MM5,MM7              ' Convert from 4 bytes to 4 words
      add esi,ebx                    ' point source to the next pixel
      paddw MM4,MM5                  ' Add those 4 bytes to the sum register
      Sub esp,65536                  ' subtract one pixel (fix pt) from calc holder
      jns _NEXTPIXELB_               ' go get next pixel until ESP becomes less than 0
      '------------------------------------------------------------------------------
      movq MM5,[PRemULDIV+ECX*8-8]   ' Get Fixed Point Pixel Divider
      psrlw MM4,3                    ' 5 bits only (0-31)
      pmullw MM4,MM5                 ' Divide Sum by pixel count (aka ECX)
      psrlw MM4,4                    ' From 4 Fixed to 4 short
      packuswb MM4,MM4               ' Convert from 4 shorts to 4 bytes
      movd [edi],MM4                 ' Save Average Pixel
      add edi,eax                    ' point to the next buffer
      dec dx                         ' Decrease WIDTH counter
      jnz _NEXTGROUPB_               ' Go get next pixel =D
      '------------------------------------------------------------------------------
      movd esi,MM2                   ' Restoring Source Pointer
      movd edi,MM3                   ' Restoring Destiny Pointer
      add esi,4
      add edi,4
      Sub edx,65536
      jnz _NEXTLINEB_                ' Go do the next line
      jmp _ENDVERTA_
      '------------------------------------------------------------------------------
      _VISONEPIXELA_:
      mov ecx,[esi]
      mov [edi],ecx
      add esi,ebx                    ' point source to the next pixel
      add edi,eax                    ' point to the next buffer
      Sub esp,65536                  ' subtract one pixel (fix pt) from calc holder
      dec dx                         ' Decrease WIDTH counter
      jnz _NEXTGROUPB_               ' Go get next pixel =D
      movd esi,MM2                   ' Restoring Source Pointer
      movd edi,MM3                   ' Restoring Destiny Pointer
      add esi,4
      add edi,4
      Sub edx,65536
      jnz _NEXTLINEB_                ' Go do the next line
      jmp _ENDVERTA_
      '------------------------------------------------------------------------------
      _VISTWOPIXELA_:
      movd MM5,[esi]                 ' Load Components in MMX register
      punpcklbw MM5,MM7              ' Convert from 4 bytes to 4 words
      add esi,ebx                    ' point source to the next pixel
      paddw MM4,MM5                  ' Add those 4 bytes to the sum register
      movd MM5,[esi]                 ' Load Components in MMX register
      punpcklbw MM5,MM7              ' Convert from 4 bytes to 4 words
      add esi,ebx                    ' point source to the next pixel
      paddw MM4,MM5                  ' Add those 4 bytes to the sum register
      psrlw MM4,1                    ' Divide Sum by 2
      packuswb MM4,MM4               ' Convert from 4 shorts to 4 bytes
      movd [edi],MM4
      add edi,eax                    ' point to the next buffer
      Sub esp,65536*2                ' subtract one pixel (fix pt) from calc holder
      dec dx                         ' Decrease WIDTH counter
      jnz _NEXTGROUPB_               ' Go get next pixel =D
      movd esi,MM2                   ' Restoring Source Pointer
      movd edi,MM3                   ' Restoring Destiny Pointer
      add esi,4
      add edi,4
      Sub edx,65536
      jnz _NEXTLINEB_                ' Go do the next line
      jmp _ENDVERTA_
      '----------------------------------------------------------------------------
      _VISFOURPIXELA_:
      movd MM5,[esi]                 ' Load Components in MMX register
      punpcklbw MM5,MM7              ' Convert from 4 bytes to 4 words
      add esi,ebx                    ' point source to the next pixel
      paddw MM4,MM5                  ' Add those 4 bytes to the sum register
      movd MM5,[esi]                 ' Load Components in MMX register
      punpcklbw MM5,MM7              ' Convert from 4 bytes to 4 words
      add esi,ebx                    ' point source to the next pixel
      paddw MM4,MM5                  ' Add those 4 bytes to the sum register
      movd MM5,[esi]                 ' Load Components in MMX register
      punpcklbw MM5,MM7              ' Convert from 4 bytes to 4 words
      add esi,ebx                    ' point source to the next pixel
      paddw MM4,MM5                  ' Add those 4 bytes to the sum register
      movd MM5,[esi]                 ' Load Components in MMX register
      punpcklbw MM5,MM7              ' Convert from 4 bytes to 4 words
      add esi,ebx                    ' point source to the next pixel
      paddw MM4,MM5                  ' Add those 4 bytes to the sum register
      psrlw MM4,2                    ' Divide Sum by 2
      packuswb MM4,MM4               ' Convert from 4 shorts to 4 bytes
      movd [edi],MM4
      add edi,eax                    ' point to the next buffer
      Sub esp,65536*4                ' subtract one pixel (fix pt) from calc holder
      dec dx                         ' Decrease WIDTH counter
      jnz _NEXTGROUPB_               ' Go get next pixel =D
      movd esi,MM2                   ' Restoring Source Pointer
      movd edi,MM3                   ' Restoring Destiny Pointer
      add esi,4
      add edi,4
      Sub edx,65536
      jnz _NEXTLINEB_                ' Go do the next line
      _ENDVERTA_:
      movd esp,MM0                   ' restoring stack pointer
      pop ebp                        ' restoin base pointer
      emms
    End asm

  Elseif SIZY >= TY Then

    ' ==================================================================================
    ' ******************************* increased height **********************************
    ' ==================================================================================
    DTMP=(TY/SIZY)
    TDX = DTMP*65536
    RESYSKP = cptr(fb.image Ptr, IMGB)->pitch

    ' ************************************************************
    ' ******************** VERTICAL WHEN BIGGER ******************
    ' ************************************************************
    asm
      mov esi,[PTBB]                ' Load ESI with the pointer of source
      mov edi,[PTB]                 ' Load EDI with the pointer of the destiny
      mov edx,[TDX]                 ' fixed point
      mov ebx,[TY]                  ' WIDTH of the destiny
      mov eax,[RESYSKP]             ' PITCH of the source
      push ebp                      ' saving base pointer
      mov ebp,edx                   ' fixed point
      movd MM0,esp                  ' saving stack pointer
      mov esp,eax                   ' ESP = source/destiny pitch
      mov edx,-1                    ' fixed point counter start with -1
      ' ----------------------------------------------------------
      _VNEXTGROUPC_:         ' here start the next line from source
      add edx,65536                 ' one line in fixed point
      ' ---------------------------------------------------------
      _VNEXTLINEC_:          ' here start the next line into destiny
      mov ecx,esp                   ' get pitch
      Shr ecx,2                     ' transform into pixels
      rep movsd                     ' copy a line
      Sub esi,esp                   ' point to the start of the line again
      Sub edx,ebp                   ' decrease decimal fixed point
      jns _VNEXTLINEC_              ' go draw next line
      ' ---------------------------------------------------------
      add esi,esp                   ' point to the next source line
      dec bx                        ' decrease source lines count
      jnz _VNEXTGROUPC_             ' got draw next group of lines
      ' ----------------------------------------------------------
      movd esp,MM0                  ' restoring stack pointer
      pop ebp                       ' restore base pointer from stack
      emms                          ' clear MMX status
    End asm

  End If

  If MYALPHA <> -256 Then
    ' *** plotting result in target (alpha) ***
    TDX = Cint(SIZX)*SIZY
    asm
      mov esi,[PTB]
      mov ecx,[TDX]
      _TRANSNEXTPIXEL_:
      cmp Byte Ptr [esi+3], 8
      ja _IGTRANS_
      mov dword Ptr [esi],0xFFFF00FF
      _IGTRANS_:
      add esi,4
      dec ecx
      jnz _TRANSNEXTPIXEL_
    End asm
    Put TGT,(CENX-(SIZX Shr 1),CENY-(SIZY Shr 1)),IMGB,alpha,MYALPHA
  Else
    ' *** plotting result in target ***
    Put TGT,(CENX-(SIZX Shr 1),CENY-(SIZY Shr 1)),IMGB,alpha
  End If

End Sub