tensorflow-haskell/tensorflow-ops/tests/BuildTest.hs

178 lines
5.7 KiB
Haskell
Raw Normal View History

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.
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE OverloadedLists #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Main where
import Control.Monad.IO.Class (liftIO)
import Lens.Family2 ((^.), (.~))
2016-10-24 21:26:42 +02:00
import Data.List (sort)
import Proto.Tensorflow.Core.Framework.Graph_Fields
2016-10-24 21:26:42 +02:00
( node )
import Proto.Tensorflow.Core.Framework.NodeDef
( NodeDef )
import Proto.Tensorflow.Core.Framework.NodeDef_Fields
( device
2016-10-24 21:26:42 +02:00
, name
, op )
import TensorFlow.Build
( Build
, BuildT
, asGraphDef
, evalBuildT
, flushNodeBuffer
, withDevice
, withNameScope
, opName
2016-10-24 21:26:42 +02:00
)
Support fetching storable vectors + use them in benchmark (#50) In addition, you can now fetch TensorData directly. This might be useful in scenarios where you feed the result of a computation back in, like RNN. Before: benchmarking feedFetch/4 byte time 83.31 μs (81.88 μs .. 84.75 μs) 0.997 R² (0.994 R² .. 0.998 R²) mean 87.32 μs (86.06 μs .. 88.83 μs) std dev 4.580 μs (3.698 μs .. 5.567 μs) variance introduced by outliers: 55% (severely inflated) benchmarking feedFetch/4 KiB time 114.9 μs (111.5 μs .. 118.2 μs) 0.996 R² (0.994 R² .. 0.998 R²) mean 117.3 μs (116.2 μs .. 118.6 μs) std dev 3.877 μs (3.058 μs .. 5.565 μs) variance introduced by outliers: 31% (moderately inflated) benchmarking feedFetch/4 MiB time 109.0 ms (107.9 ms .. 110.7 ms) 1.000 R² (0.999 R² .. 1.000 R²) mean 108.6 ms (108.2 ms .. 109.2 ms) std dev 740.2 μs (353.2 μs .. 1.186 ms) After: benchmarking feedFetch/4 byte time 82.92 μs (80.55 μs .. 85.24 μs) 0.996 R² (0.993 R² .. 0.998 R²) mean 83.58 μs (82.34 μs .. 84.89 μs) std dev 4.327 μs (3.664 μs .. 5.375 μs) variance introduced by outliers: 54% (severely inflated) benchmarking feedFetch/4 KiB time 85.69 μs (83.81 μs .. 87.30 μs) 0.997 R² (0.996 R² .. 0.999 R²) mean 86.99 μs (86.11 μs .. 88.15 μs) std dev 3.608 μs (2.854 μs .. 5.273 μs) variance introduced by outliers: 43% (moderately inflated) benchmarking feedFetch/4 MiB time 1.582 ms (1.509 ms .. 1.677 ms) 0.970 R² (0.936 R² .. 0.993 R²) mean 1.645 ms (1.554 ms .. 1.981 ms) std dev 490.6 μs (138.9 μs .. 1.067 ms) variance introduced by outliers: 97% (severely inflated)
2016-12-15 03:53:06 +01:00
import TensorFlow.Types (unScalar)
2016-10-24 21:26:42 +02:00
import TensorFlow.Ops
( add
, assign
, constant
, initializedVariable
, variable
, variable'
2016-10-24 21:26:42 +02:00
)
import TensorFlow.Output (Device(..))
import TensorFlow.Tensor
( colocateWith
, render
, Tensor
, Value
, Ref
)
2016-10-24 21:26:42 +02:00
import TensorFlow.Session
( run
2016-10-24 21:26:42 +02:00
, runSession
, run_
)
import Test.Framework (defaultMain, Test)
2016-10-24 21:26:42 +02:00
import Test.Framework.Providers.HUnit (testCase)
import Test.HUnit ((@=?))
import qualified Data.Vector as V
-- | Test 'opName' behavior.
testOpName :: Test
testOpName = testCase "testOpName" $ do
let graph = variable' (opName .~ "foo") [] :: Build (Tensor Ref Float)
2016-10-24 21:26:42 +02:00
nodeDef :: NodeDef
nodeDef = head $ asGraphDef graph ^. node
"Variable" @=? (nodeDef ^. op)
2016-10-24 21:26:42 +02:00
"foo" @=? (nodeDef ^. name)
-- | Test that "run" will render and extend any pure ops that haven't already
-- been rendered.
testPureRender :: Test
2016-10-24 21:26:42 +02:00
testPureRender = testCase "testPureRender" $ runSession $ do
result <- run $ 2 `add` 2
liftIO $ 4 @=? (unScalar result :: Float)
-- | Test that "run" assigns any previously accumulated initializers.
testInitializedVariable :: Test
2016-10-24 21:26:42 +02:00
testInitializedVariable =
testCase "testInitializedVariable" $ runSession $ do
(formula, reset) <- do
2016-10-24 21:26:42 +02:00
v <- initializedVariable 42
r <- assign v 24
return (1 `add` v, r)
result <- run formula
liftIO $ 43 @=? (unScalar result :: Float)
run_ reset -- Updates v to a different value
rerunResult <- run formula
liftIO $ 25 @=? (unScalar rerunResult :: Float)
testInitializedVariableShape :: Test
2016-10-24 21:26:42 +02:00
testInitializedVariableShape =
testCase "testInitializedVariableShape" $ runSession $ do
vector <- initializedVariable (constant [1] [42 :: Float])
2016-10-24 21:26:42 +02:00
result <- run vector
liftIO $ [42] @=? (result :: V.Vector Float)
-- | Test nameScoped behavior.
testNameScoped :: Test
2016-10-24 21:26:42 +02:00
testNameScoped = testCase "testNameScoped" $ do
let graph = withNameScope "foo" $ variable [] :: Build (Tensor Ref Float)
nodeDef :: NodeDef
[nodeDef] = asGraphDef graph ^. node
"foo/Variable_0" @=? (nodeDef ^. name) -- TODO: Check prefix.
"Variable" @=? (nodeDef ^. op)
-- | Test combined opName and nameScoped behavior.
testNamedAndScoped :: Test
2016-10-24 21:26:42 +02:00
testNamedAndScoped = testCase "testNamedAndScoped" $ do
let graph :: Build (Tensor Ref Float)
graph = withNameScope "foo1" (variable' (opName .~ "bar1") [])
2016-10-24 21:26:42 +02:00
nodeDef :: NodeDef
nodeDef = head $ asGraphDef graph ^. node
"Variable" @=? (nodeDef ^. op)
2016-10-24 21:26:42 +02:00
"foo1/bar1" @=? (nodeDef ^. name)
-- | Flush the node buffer and sort the nodes by name (for more stable tests).
flushed :: Ord a => (NodeDef -> a) -> BuildT IO [a]
flushed field = sort . map field <$> flushNodeBuffer
2016-10-24 21:26:42 +02:00
-- | Test the interaction of rendering, CSE and scoping.
testRenderDedup :: Test
2016-10-24 21:26:42 +02:00
testRenderDedup = testCase "testRenderDedup" $ evalBuildT $ do
renderNodes
2016-10-24 21:26:42 +02:00
names <- flushed (^. name)
liftIO $ ["Const_1", "Variable_0", "Variable_2"] @=? names
-- Render the nodes in a different scope, which should cause them
-- to be distinct from the previous ones.
withNameScope "foo" renderNodes
2016-10-24 21:26:42 +02:00
scopedNames <- flushed (^. name)
liftIO $ ["foo/Const_4", "foo/Variable_3", "foo/Variable_5"] @=? scopedNames
where
renderNodes = do
-- A stateful op and a pure op.
_ :: Tensor Ref Float <- variable []
_ :: Tensor Value Float <- render 3
-- Another stateful op, and a pure op which should be
-- deduped with the previous one.
_ :: Tensor Ref Float <- variable []
_ :: Tensor Value Float <- render 3
return ()
-- | Test the interaction of rendering, CSE and scoping.
testDeviceColocation :: Test
2016-10-24 21:26:42 +02:00
testDeviceColocation = testCase "testDeviceColocation" $ evalBuildT $ do
renderNodes
2016-10-24 21:26:42 +02:00
devices <- flushed (\x -> (x ^. name, x ^. device))
liftIO $ [ ("Add_2","dev0")
, ("Const_1","dev0")
, ("Variable_0","dev0")] @=? devices
where
renderNodes = do
-- A stateful op and a pure op.
var :: Tensor Ref Float <- withDevice (Just $ Device "dev0") $ variable []
-- Uses render to cause the expression be added to the graph.
_ <- colocateWith var $ render $ 3 `add` var
return ()
main :: IO ()
main = defaultMain
[ testInitializedVariable
, testInitializedVariableShape
, testDeviceColocation
, testOpName
, testNameScoped
, testNamedAndScoped
, testPureRender
, testRenderDedup
]