-----
Generative Pre-trained Transformer 3
You are Gus the Destroyer, a knight living in the kingdom of Larion. You have a steel longsword and a wooden shield. You are on a quest to defeat the evil dragon of Larion. You've heard he lives up at the north of the kingdom. You set on the path to defeat him and walk into a dark forest. As you enter the forest you see a pale man. He is dressed in a white sleeveless shirt, brown pants, and boots. His head is completely hair and his face is expressionless. You draw your sword as the man stares at you.
> You ask where the dragon is.
"Where is the dragon?" you ask.
"What?" the man asks as he begins to look a little more alert.
"I asked where the dragon is, I want to kill him."
> You search the man.
You check the man for weapons but he is completely unarmed.
"Bah, you are new. Dragons are hard to kill, easier if you aren't a moron like you." The man sputters at you.
> You head into the forest.
You set off towards the north of the forest. You walk slowly to the point where you are a good hour away from the pale man. A flock of small birds fly through the air and land on a nearby branch.
> You look at birds.
You look down at the flock of birds. They are small birds and are chirping merrily away. They are in pretty bad shape.




F,
and minimize Loss(F(input), expected)


| \[ tanh(x) = \frac{e^{x} - e^{-x}}{e^{x} + e^{-x}} \] | |
| \[ logistic(x) = \frac{1}{1 + e^{-x}} \] | |
| \[ relu(x) = max(0, x) \] |
| Identity | ![]() |
|
| Edge Detection | ![]() |
|
| Gaussian Blur | ![]() |
SGEMM
DGEMM
CGEMM
ZGEMM
SUBROUTINE saxpy(N,SA,SX,INCX,SY,INCY)
REAL SA
INTEGER INCX,INCY,N
REAL SX(*),SY(*)
INTEGER I,IX,IY,M,MP1
INTRINSIC mod
IF (n.LE.0) RETURN
IF (sa.EQ.0.0) RETURN
IF (incx.EQ.1 .AND. incy.EQ.1) THEN
m = mod(n,4)
IF (m.NE.0) THEN
DO i = 1,m
sy(i) = sy(i) + sa*sx(i)
END DO
END IF
IF (n.LT.4) RETURN
mp1 = m + 1
DO i = mp1,n,4
sy(i) = sy(i) + sa*sx(i)
sy(i+1) = sy(i+1) + sa*sx(i+1)
sy(i+2) = sy(i+2) + sa*sx(i+2)
sy(i+3) = sy(i+3) + sa*sx(i+3)
END DO
ELSE
ix = 1
iy = 1
IF (incx.LT.0) ix = (-n+1)*incx + 1
IF (incy.LT.0) iy = (-n+1)*incy + 1
DO i = 1,n
sy(iy) = sy(iy) + sa*sx(ix)
ix = ix + incx
iy = iy + incy
END DO
END IF
RETURN
END
http://www.netlib.org/lapack/explore-html/d8/daf/saxpy_8f_source.html
1 sfloats constant sfloat
1 dfloats constant dfloat
variable incx sfloat incx !
variable incy sfloat incy !
: sf, ( r -- ) here sf! sfloat allot ;
: df, ( r -- ) here df! dfloat allot ;
: sxsy+ ( sx sy -- sx' sy' ) incy @ + swap incx @ + swap ;
: saxpy ( sx sy n f: sa -- )
0 ?do over
sf@ fover f* dup sf@ f+ dup sf! sxsy+
loop 2drop fdrop ;
: sswap ( sx sy n -- )
0 ?do dup sf@ over sf@ dup sf! over sf! sxsy+ loop 2drop ;
: sscal ( sx n f: sa -- )
0 ?do dup sf@ fover f* dup sf! incx @ + loop drop fdrop ;
: scopy ( sx sy n -- )
0 ?do over sf@ dup sf! sxsy+ loop 2drop ;
: sdsdot ( sx sy n f: sb -- f: prod )
0 ?do over sf@ dup sf@ f* f+ sxsy+ loop 2drop ;
: sdot ( sx sy n -- f: prod ) 0e sdsdot ;
: dsdot ( sx sy n -- f: prod ) 0e sdsdot ;
: snrm2 ( sx n -- f: norm )
0e 0 ?do dup sf@ fdup f* f+ incx @ + loop drop fsqrt ;
: sasum ( sx n -- f: abssum )
0e 0 ?do dup sf@ fabs f+ incx @ + loop drop ;
: isamax ( sx n -- index )
over sf@ fabs 0 -rot 0 ?do
dup sf@ fabs fover f> if fdrop dup sf@ fabs nip i swap then
incx @ +
loop drop fdrop ;
fvariable cos
fvariable sin
: srotg ( f: a b -- f: c s )
fdup f0= if fdrop fdrop 1e 0e exit then
fover fover fdup f* fswap fdup f* f+ fsqrt 1/f ( a b 1/h )
frot fdup f0<= if fswap fnegate fswap then ( b ~1/h a )
fover f* frot frot f* ;
: srot ( sx sy n -- )
0 ?do over sf@ cos sf@ f* dup sf@ sin sf@ f* f+
dup sf@ cos sf@ f* over sf@ sin sf@ f* f-
dup sf! over sf! incy @ + swap incx @ + swap loop 2drop ;
void cblas_saxpy(const int N, const float alpha,
const float *X, const int incX,
float *Y, const int incY);
: sfcell/ ( n -- n ) 2/ 2/ ;
c-function cblas_dsdot cblas_dsdot n a n a n -- r
: dsdot ( sx sy n -- f: prod )
-rot >r incx @ sfcell/ r> incy @ sfcell/ cblas_dsdot ;
c-function cblas_saxpy cblas_saxpy n r a n a n -- void
: saxpy ( sx sy n f: sa -- )
-rot >r incx @ sfcell/ r> incy @ sfcell/ cblas_saxpy ;
1000000 constant test-size
1 sfloats incx ! 1 sfloats incy !
test-size sfloats allocate throw constant foo
foo test-size sfloats 33 fill
test-size sfloats allocate throw constant bar
bar test-size sfloats 33 fill
: benchmark
1000 0 do
123e foo bar test-size saxpy
loop
;
benchmark
10000 constant test-size
1 sfloats incx ! 1 sfloats incy !
test-size test-size * sfloats allocate throw constant mat
mat test-size test-size * sfloats 33 fill
test-size sfloats allocate throw constant vec
vec test-size sfloats 33 fill
test-size sfloats allocate throw constant vec2
vec2 test-size sfloats 33 fill
test-size sfloats lda !
: benchmark
10 0 do
9e 1e mat vec vec2 test-size test-size sgemv
loop
;
benchmark
1000 constant test-size
1 sfloats incx ! 1 sfloats incy !
#NoTrans transa !
#NoTrans transb !
test-size test-size * sfloats allocate throw constant mat1
mat1 test-size test-size * sfloats 33 fill
test-size sfloats lda !
test-size test-size * sfloats allocate throw constant mat2
mat2 test-size test-size * sfloats 33 fill
test-size sfloats ldb !
test-size test-size * sfloats allocate throw constant mat3
mat3 test-size test-size * sfloats 33 fill
test-size sfloats ldc !
: benchmark
9e 1e mat1 mat2 mat3 test-size test-size test-size sgemm
;
benchmark
: im2col { src b w h c dst fw fh }
w h * c * sfloats { sb }
h c * sfloats { sw }
c sfloats { sh }
c fh * sfloats { shc }
src dst
b 0 do
over swap
w fw - 1+ 0 do
over swap
h fh - 1+ 0 do
over swap
fw 0 do
2dup shc cmove
shc + swap sw + swap
loop
nip
swap sh + swap
loop
nip
swap sw + swap
loop
nip
swap sb + swap
loop
2drop
;
: im2col-size { b w h c fw fh } b w fw - 1+ * h fh - 1+ * c * ;
: im2col' { src b w h c dst fw fh }
dst b w h c fw fh im2col-size 0 fill
sfloat incx ! sfloat incy !
w h * c * sfloats { sb }
h c * sfloats { sw }
c sfloats { sh }
c fh * { shc# }
shc# sfloats { shc }
dst src
b 0 do
over swap
w fw - 1+ 0 do
over swap
h fh - 1+ 0 do
over swap
fw 0 do
2dup swap shc# 1e saxpy
shc + swap sw + swap
loop
nip
swap sh + swap
loop
nip
swap sw + swap
loop
nip
swap sb + swap
loop
2drop
;
Big Endian
$00 - Magic # (byte)
$00 - Magic # (byte)
type - $08=uint8 $09=int8 $0B=int16 (byte)
$0C=int32 $0D=float32 $0E=float64
rank - Number of dimensions (byte)
dim 1 - Size in dimension 1 (int32)
.... ....
dim N - Size in dimension N (int32)
data - Raw data
: u8tof32 ( a a n -- )
0 do
over c@ s>f dup sf!
1 sfloats + swap 1+ swap
loop 2drop ;
\c void u8tof32(const uint8_t *src, float *dst, size_t n) {
\c for (;n;--n) {
\c *dst++ = *src++;
\c }
\c }
c-function u8tof32 u8tof32 a a n -- void