2016-10-24 21:26:42 +02:00
|
|
|
-- Copyright 2016 TensorFlow authors.
|
|
|
|
--
|
|
|
|
-- Licensed under the Apache License, Version 2.0 (the "License");
|
|
|
|
-- you may not use this file except in compliance with the License.
|
|
|
|
-- You may obtain a copy of the License at
|
|
|
|
--
|
|
|
|
-- http://www.apache.org/licenses/LICENSE-2.0
|
|
|
|
--
|
|
|
|
-- Unless required by applicable law or agreed to in writing, software
|
|
|
|
-- distributed under the License is distributed on an "AS IS" BASIS,
|
|
|
|
-- WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
|
|
|
|
-- See the License for the specific language governing permissions and
|
|
|
|
-- limitations under the License.
|
|
|
|
|
2016-10-26 20:14:38 +02:00
|
|
|
{-# LANGUAGE FlexibleContexts #-}
|
2016-10-24 21:26:42 +02:00
|
|
|
{-# LANGUAGE OverloadedLists #-}
|
2017-10-19 19:41:55 +02:00
|
|
|
{-# LANGUAGE TypeApplications #-}
|
2016-10-24 21:26:42 +02:00
|
|
|
|
2017-05-26 04:19:22 +02:00
|
|
|
import Control.Monad (forM_, when)
|
2016-10-24 21:26:42 +02:00
|
|
|
import Control.Monad.IO.Class (liftIO)
|
|
|
|
import Data.Int (Int32, Int64)
|
2016-10-26 20:14:38 +02:00
|
|
|
import Data.List (genericLength)
|
2016-10-24 21:26:42 +02:00
|
|
|
import qualified Data.Text.IO as T
|
|
|
|
import qualified Data.Vector as V
|
|
|
|
|
2016-12-15 03:53:06 +01:00
|
|
|
import qualified TensorFlow.Core as TF
|
2017-05-17 22:20:51 +02:00
|
|
|
import qualified TensorFlow.Ops as TF hiding (initializedVariable, zeroInitializedVariable)
|
|
|
|
import qualified TensorFlow.Variable as TF
|
2017-05-26 04:19:22 +02:00
|
|
|
import qualified TensorFlow.Minimize as TF
|
2016-10-24 21:26:42 +02:00
|
|
|
|
|
|
|
import TensorFlow.Examples.MNIST.InputData
|
|
|
|
import TensorFlow.Examples.MNIST.Parse
|
|
|
|
|
2016-11-18 19:42:02 +01:00
|
|
|
numPixels, numLabels :: Int64
|
|
|
|
numPixels = 28*28 :: Int64
|
2016-10-24 21:26:42 +02:00
|
|
|
numLabels = 10 :: Int64
|
|
|
|
|
|
|
|
-- | Create tensor with random values where the stddev depends on the width.
|
2017-04-07 00:10:33 +02:00
|
|
|
randomParam :: Int64 -> TF.Shape -> TF.Build (TF.Tensor TF.Build Float)
|
2016-10-24 21:26:42 +02:00
|
|
|
randomParam width (TF.Shape shape) =
|
2017-04-07 00:10:33 +02:00
|
|
|
(`TF.mul` stddev) <$> TF.truncatedNormal (TF.vector shape)
|
2016-10-24 21:26:42 +02:00
|
|
|
where
|
|
|
|
stddev = TF.scalar (1 / sqrt (fromIntegral width))
|
|
|
|
|
2016-10-26 20:14:38 +02:00
|
|
|
-- Types must match due to model structure.
|
2016-10-24 21:26:42 +02:00
|
|
|
type LabelType = Int32
|
|
|
|
|
|
|
|
data Model = Model {
|
|
|
|
train :: TF.TensorData Float -- ^ images
|
|
|
|
-> TF.TensorData LabelType
|
|
|
|
-> TF.Session ()
|
|
|
|
, infer :: TF.TensorData Float -- ^ images
|
|
|
|
-> TF.Session (V.Vector LabelType) -- ^ predictions
|
2016-10-26 20:14:38 +02:00
|
|
|
, errorRate :: TF.TensorData Float -- ^ images
|
|
|
|
-> TF.TensorData LabelType
|
|
|
|
-> TF.Session Float
|
2016-10-24 21:26:42 +02:00
|
|
|
}
|
|
|
|
|
2016-10-26 20:14:38 +02:00
|
|
|
createModel :: TF.Build Model
|
|
|
|
createModel = do
|
|
|
|
-- Use -1 batch size to support variable sized batches.
|
|
|
|
let batchSize = -1
|
2016-10-24 21:26:42 +02:00
|
|
|
-- Inputs.
|
|
|
|
images <- TF.placeholder [batchSize, numPixels]
|
|
|
|
-- Hidden layer.
|
|
|
|
let numUnits = 500
|
|
|
|
hiddenWeights <-
|
|
|
|
TF.initializedVariable =<< randomParam numPixels [numPixels, numUnits]
|
|
|
|
hiddenBiases <- TF.zeroInitializedVariable [numUnits]
|
2017-05-17 22:20:51 +02:00
|
|
|
let hiddenZ = (images `TF.matMul` TF.readValue hiddenWeights)
|
|
|
|
`TF.add` TF.readValue hiddenBiases
|
2016-10-24 21:26:42 +02:00
|
|
|
let hidden = TF.relu hiddenZ
|
|
|
|
-- Logits.
|
|
|
|
logitWeights <-
|
|
|
|
TF.initializedVariable =<< randomParam numUnits [numUnits, numLabels]
|
|
|
|
logitBiases <- TF.zeroInitializedVariable [numLabels]
|
2017-05-17 22:20:51 +02:00
|
|
|
let logits = (hidden `TF.matMul` TF.readValue logitWeights)
|
|
|
|
`TF.add` TF.readValue logitBiases
|
2017-10-19 19:41:55 +02:00
|
|
|
predict <- TF.render @TF.Build @LabelType $
|
2016-10-24 21:26:42 +02:00
|
|
|
TF.argMax (TF.softmax logits) (TF.scalar (1 :: LabelType))
|
|
|
|
|
|
|
|
-- Create training action.
|
|
|
|
labels <- TF.placeholder [batchSize]
|
2016-10-26 20:14:38 +02:00
|
|
|
let labelVecs = TF.oneHot labels (fromIntegral numLabels) 1 0
|
|
|
|
loss =
|
2017-06-21 05:50:46 +02:00
|
|
|
TF.reduceMean $ fst $ TF.softmaxCrossEntropyWithLogits logits labelVecs
|
2016-10-24 21:26:42 +02:00
|
|
|
params = [hiddenWeights, hiddenBiases, logitWeights, logitBiases]
|
2017-05-26 04:19:22 +02:00
|
|
|
trainStep <- TF.minimizeWith TF.adam loss params
|
2016-10-24 21:26:42 +02:00
|
|
|
|
2016-10-26 20:14:38 +02:00
|
|
|
let correctPredictions = TF.equal predict labels
|
2017-06-21 05:50:46 +02:00
|
|
|
errorRateTensor <- TF.render $ 1 - TF.reduceMean (TF.cast correctPredictions)
|
2016-10-26 20:14:38 +02:00
|
|
|
|
2016-10-24 21:26:42 +02:00
|
|
|
return Model {
|
2016-10-26 20:14:38 +02:00
|
|
|
train = \imFeed lFeed -> TF.runWithFeeds_ [
|
|
|
|
TF.feed images imFeed
|
|
|
|
, TF.feed labels lFeed
|
|
|
|
] trainStep
|
2016-10-24 21:26:42 +02:00
|
|
|
, infer = \imFeed -> TF.runWithFeeds [TF.feed images imFeed] predict
|
2016-10-26 20:14:38 +02:00
|
|
|
, errorRate = \imFeed lFeed -> TF.unScalar <$> TF.runWithFeeds [
|
|
|
|
TF.feed images imFeed
|
|
|
|
, TF.feed labels lFeed
|
|
|
|
] errorRateTensor
|
2016-10-24 21:26:42 +02:00
|
|
|
}
|
|
|
|
|
2016-11-18 19:42:02 +01:00
|
|
|
main :: IO ()
|
2016-10-24 21:26:42 +02:00
|
|
|
main = TF.runSession $ do
|
|
|
|
-- Read training and test data.
|
|
|
|
trainingImages <- liftIO (readMNISTSamples =<< trainingImageData)
|
|
|
|
trainingLabels <- liftIO (readMNISTLabels =<< trainingLabelData)
|
|
|
|
testImages <- liftIO (readMNISTSamples =<< testImageData)
|
|
|
|
testLabels <- liftIO (readMNISTLabels =<< testLabelData)
|
|
|
|
|
|
|
|
-- Create the model.
|
2016-10-26 20:14:38 +02:00
|
|
|
model <- TF.build createModel
|
|
|
|
|
|
|
|
-- Functions for generating batches.
|
|
|
|
let encodeImageBatch xs =
|
|
|
|
TF.encodeTensorData [genericLength xs, numPixels]
|
|
|
|
(fromIntegral <$> mconcat xs)
|
|
|
|
let encodeLabelBatch xs =
|
|
|
|
TF.encodeTensorData [genericLength xs]
|
|
|
|
(fromIntegral <$> V.fromList xs)
|
|
|
|
let batchSize = 100
|
|
|
|
let selectBatch i xs = take batchSize $ drop (i * batchSize) (cycle xs)
|
2016-10-24 21:26:42 +02:00
|
|
|
|
|
|
|
-- Train.
|
|
|
|
forM_ ([0..1000] :: [Int]) $ \i -> do
|
2016-10-26 20:14:38 +02:00
|
|
|
let images = encodeImageBatch (selectBatch i trainingImages)
|
|
|
|
labels = encodeLabelBatch (selectBatch i trainingLabels)
|
|
|
|
train model images labels
|
2016-10-24 21:26:42 +02:00
|
|
|
when (i `mod` 100 == 0) $ do
|
2016-10-26 20:14:38 +02:00
|
|
|
err <- errorRate model images labels
|
|
|
|
liftIO $ putStrLn $ "training error " ++ show (err * 100)
|
2016-10-24 21:26:42 +02:00
|
|
|
liftIO $ putStrLn ""
|
|
|
|
|
|
|
|
-- Test.
|
2016-10-26 20:14:38 +02:00
|
|
|
testErr <- errorRate model (encodeImageBatch testImages)
|
|
|
|
(encodeLabelBatch testLabels)
|
|
|
|
liftIO $ putStrLn $ "test error " ++ show (testErr * 100)
|
2016-10-24 21:26:42 +02:00
|
|
|
|
|
|
|
-- Show some predictions.
|
2016-10-26 20:14:38 +02:00
|
|
|
testPreds <- infer model (encodeImageBatch testImages)
|
2016-10-24 21:26:42 +02:00
|
|
|
liftIO $ forM_ ([0..3] :: [Int]) $ \i -> do
|
|
|
|
putStrLn ""
|
|
|
|
T.putStrLn $ drawMNIST $ testImages !! i
|
|
|
|
putStrLn $ "expected " ++ show (testLabels !! i)
|
|
|
|
putStrLn $ " got " ++ show (testPreds V.! i)
|