“As so often, I find that talks that I’m giving are basically explaining what Conal Elliot and Ed Kmett have done several years ago.”
neuralNet wL bL ... w1 b1 =
layer wL bL
. ...
. layer w1 b1
layer weightMatrix biasVector =
fmap activationFunction
. vectorAddition biasVector
. matrixVectorProduct weightMatrix
”[…] layers (die im modernen maschinellen Lernen als zustandsbehaftete Funktionen mit impliziten Parametern verstanden werden sollten) werden typischerweise als Python-Klassen dargestellt, deren Konstruktoren ihre Parameter erzeugen und initialisieren […]”
Übersetzt aus:
- Finde Parameter, für die das NN auf gegebenem Trainingsdatensatz möglichst gute Ergebnisse liefert
- Güte durch skalarwertige Fehlerfunktion beurteilt
$⇒$ Löse Optimierungsproblem:$\textrm{argmin}ω ∈ Ω (\textrm{loss} ˆ \textrm{neuralNet} (ω; \textrm{data}))$
$wn+1 = w_n - α ⋅ \frac {∂ f}{∂ w}$
- Funktionskomposition ist assoziativ, erlaubt Auswertung in beliebiger Reihenfolge
- Aufwand “vorwärts” abhängig von Eingangsdimension (hier: Anzahl der Parameter; heute bis $1011$)
- Aufwand “rückwärts” abhängig von Ausgangsdimension (hier: 1)
$Dnn(v) = Dl_L(lL-1(…)) ˆ … ˆ Dl_1(v)$
Um
Deep Learning Bibliotheken sind im Wesentlichen Werkzeuge zur Generierung und Verwaltung von Berechnungsgraphen.
class SimpleNN:
def __init__(self, dimIn dimOut):
self.dims = [dimIn, dimIn, dimIn, dimOut, dimOut]
self.weights = []
self.biases = []
for i in range(4):
self.weights.append(
tf.Variable(tf.random.normal(shape=(self.dims[i+1],self.dims[i])))
)
self.biases.append(
tf.Variable(tf.random.normal(shape=(self.dims[i+1],1)))
)
def __call__(self, x):
inputs = tf.convert_to_tensor([x], dtype=tf.float32)
out = tf.matmul(self.weights[0],
inputs, transpose_b=True) + self.biases[0]
out = tf.tanh(out)
out = tf.matmul(self.weights[1], out) + self.biases[1]
out = tf.nn.relu(out)
out = tf.matmul(self.weights[2], out) + self.biases[2]
out = tf.tanh(out)
return tf.matmul(self.weights[3], out) + self.biases[3]
simpleNN ::
( KnownNat m,
KnownNat n,
Functor f,
Foldable f,
Floating num,
...
) =>
SimpleNNParameters f m n num ->
f m num ->
f n num
simpleNN =
affine
@. affTanh
@. affRelu
@. affTanh
(@.) ::
(q s -> b -> c) ->
(p s -> a -> b) ->
((q :*: p) s -> a -> c)
(g @. f) (q :*: p) = g q . f p
type p --* q = q :.: p
type Bump h = h :*: Par1
bump :: Num s => a s -> Bump a s
bump a = a :*: Par1 1
type a --+ b = Bump a --* b
type SimpleNNParameters (f :: Nat -> * -> *) m n =
( (f n --+ f n)
:*: (f m --+ f n)
:*: (f m --+ f m)
:*: (f m --+ f m)
)
(<.>) :: (Foldable a, Zip a, Additive s, Num s)
=> a s -> a s -> s
xs <.> ys = sumA (zipWith (*) xs ys)
linear :: (Foldable a, Zip a, Functor b, Additive s, Num s)
=> (a --* b) s -> (a s -> b s)
linear (Comp1 ba) a = (<.> a) <$> ba
affine :: (Foldable a, Zip a, Functor b, Additive s, Num s)
=> (a --+ b) s -> (a s -> b s)
affine m = linear m . bump
affRelu ::
( Foldable a,
Zip a,
Functor b,
Ord s,
Additive s,
Num s
) =>
(a --+ b) s -> (a s -> b s)
affRelu l = relus . affine l
- Nutzt Isomorphie zwischen Lambda-Kalkülen und kartesisch abgeschlossenen Kategorien (CCC) [*]
- Übersetzt Haskell-Core in kategorielle Sprache
- Ausdrücke in kategorieller Sprache können in beliebigen CCCs interpretiert werden
- Abstrahiert dadurch Haskells Funktionspfeil {{{inline-hs((->))}}}
magSqr :: Num a => (a, a) -> a
magSqr (a, b) = sqr a + sqr b
In Kategorie der Graphen – src_haskell[:exports code]{(a, a) `Graph` a}:
Idee: Ergänze Funktion um ihre Ableitung
Kategorie der generalisierten Ableitungen:
newtype GD k a b = D {unD :: a -> b :* (a `k` b)}
instance Category k => Category (GD k) where
...
D g . D f =
D (\ a ->
let (b, f') = f a
(c, g') = g b
in (c, g' . f')
)
Kettenregel:
instance (LinearCat k s, Additive s, Num s) => NumCat (GD k) s where
...
mulC = D (mulC &&& \ (u,v) -> scale v |||| scale u)
Produktregel:
Im Dual einer Kategorie drehen sich alle Pfeile um
In Haskell:
newtype Dual k a b = Dual (b `k` a)
instance Category k => Category (Dual k) where
...
-- flip :: (a -> b -> c) -> b -> a -> c
(.) = inAbst2 (flip (.))
instance CoproductPCat k => ProductCat (Dual k) where
...
-- exl :: (a, b) -> a; inlP :: a -> (a, b)
exl = abst inlP
type RAD = GD (Dual (-+>))
grad :: Num s => (a -> s) -> (a -> a)
grad = friemelOutGrad . toCcc @RAD
nnGrad :: parameters -> parameters
nnGrad = grad (loss . nn)
“Data.Array.Accelerate defines an embedded array language for computations for high-performance computing in Haskell. […] These computations may then be online compiled and executed on a range of architectures.”
Kategorie der Accelerate-Funktionen:
newtype AccFun a b where
AccFun :: (AccValue a -> AccValue b) -> AccFun a b
simpleNN :: (SimpleNNConstraints f m n num) => SimpleNN f m n num
simpleNN = affine @. affTanh @. affRelu @. affTanh
simpleNNGrad ::
(KnownNat m, KnownNat n) =>
(Vector m Double, Vector n Double) ->
SimpleNNParameters m n Double ->
SimpleNNParameters m n Double
simpleNNGrad = errGrad simpleNN
simpleNNGradAccFun ::
(KnownNat m, KnownNat n) =>
(Vector m Double, Vector n Double) ->
SimpleNNParameters m n Double `AccFun` SimpleNNParameters m n Double
simpleNNGradAccFun pair = toCcc (simpleNNGrad pair)