module TypedFlow.Learn where
import TypedFlow.Types
import TypedFlow.TF
import qualified Prelude (Float)
import Prelude (($),return,Maybe(..),(=<<))
import Text.PrettyPrint.Compact (text)
import Data.Monoid hiding (Last)
import GHC.TypeLits (KnownNat)
import Control.Monad.State (modify, gets)
categorical :: forall nCat bs. KnownNat nCat => Model '[nCat,bs] Float32 '[bs] Int32
categorical logits' y = do
logits <- assign logits'
let y_ = argmax0 logits
modelY = y_
correctPrediction <- assign (equal y_ y)
modelAccuracy <- assign (reduceMeanAll (cast @Float32 correctPrediction))
modelLoss <- assign (reduceMeanAll (sparseSoftmaxCrossEntropyWithLogits y logits))
return ModelOutput{..}
categoricalDistribution :: forall nCat bs. Model '[nCat,bs] Float32 '[nCat,bs] Float32
categoricalDistribution logits' y = do
logits <- assign logits'
let y_ = softmax0 logits
modelY = y_
correctPrediction <- assign (equal (argmax0 @'B32 logits) (argmax0 y))
modelAccuracy <- assign (reduceMeanAll (cast @Float32 correctPrediction))
modelLoss <- assign (reduceMeanAll (softmaxCrossEntropyWithLogits y logits))
return ModelOutput{..}
timedCategorical :: forall len nCat bs bits. KnownNat nCat => KnownNat bs => KnownNat len => KnownBits bits =>
Tensor '[len,bs] (Flt bits) -> Tensor '[len,nCat,bs] (Flt bits) -> Tensor '[len,bs] Int32 -> Gen (ModelOutput '[len,nCat,bs] (Flt bits))
timedCategorical targetWeights logits' y = do
logits <- assign logits'
let y_ = argmax1 logits
modelY = softmax1 logits
correctPrediction <- assign (equal y_ y)
modelAccuracy <- assign (cast @Float32 (reduceSumAll (flatten2 (cast @(Flt bits) correctPrediction ⊙ targetWeights)) ⊘ reduceSumAll targetWeights))
let crossEntropies = sparseSoftmaxCrossEntropyWithLogits y (transpose01 logits)
modelLoss <- assign (cast @Float32 (reduceMeanAll (crossEntropies ⊙ targetWeights)))
return ModelOutput{..}
data ModelOutput s t = ModelOutput {modelY :: T s t
,modelLoss :: Scalar Float32
,modelAccuracy :: Scalar Float32
}
type Model input tIn output tOut = T input tIn -> T output tOut -> Gen (ModelOutput output tOut)
binary :: forall n bs. (KnownNat bs) => Model '[n,bs] Float32 '[n,bs] Int32
binary logits y = do
sigy_ <- assign (sigmoid logits)
let y_ = cast @Int32 (round sigy_)
modelY = y_
correctPrediction <- assign (equal y_ y)
modelAccuracy <- assign (reduceMeanAll (cast @Float32 correctPrediction))
modelLoss <- assign (reduceMeanAll (sigmoidCrossEntropyWithLogits (cast @Float32 y) logits))
return ModelOutput{..}
data Options = Options {maxGradientNorm :: Maybe Prelude.Float
}
defaultOptions :: Options
defaultOptions = Options {maxGradientNorm = Nothing}
compile :: forall sx tx sy ty sy_ ty_.
(KnownShape sx, KnownTyp tx, KnownShape sy, KnownTyp ty, KnownShape sy_) =>
Options -> (Tensor sx tx -> Tensor sy ty -> Gen (ModelOutput sy_ ty_))
-> Gen ()
compile options f = compileGen options $ do
x <- placeholder "x"
f x =<< placeholder "y"
compileGen :: forall sy ty. (KnownShape sy) =>
Options -> Gen (ModelOutput sy ty) -> Gen ()
compileGen Options{..} model = knownLast @sy $ do
gen (text "import tensorflow as tf")
genFun "mkModel" [text "optimizer=tf.train.AdamOptimizer()"] $ do
peekAt "optimizer" (T (text "optimizer"))
peekAt "batch_size" (T (showDim @ (Last sy)))
trainingPhasePlaceholder <- placeholder "training_phase"
modify $ \GState{..} -> GState{genTrainingPlaceholder = trainingPhasePlaceholder,..}
ModelOutput{..} <- model
y_ <- assign modelY
peekAt "y_" y_
loss <- assign modelLoss
peekAt "loss" loss
accuracy <- assign modelAccuracy
peekAt "accuracy" accuracy
params <- getParameters
peekAt "params" (T params)
trainStep <- assign $ case maxGradientNorm of
Nothing -> T (funcall "optimizer.minimize" [fromTensor loss])
Just clip -> T (funcall "optimizer.apply_gradients" [funcall "zip" [clipByGlobalNorm clip (grad loss params),params]])
peekAt "train" trainStep
peeks <- gets genPeeks
gen (text "return " <> dict peeks)