Skip to content

Commit

Permalink
DAA.TF.Lite: Improve haddocks
Browse files Browse the repository at this point in the history
  • Loading branch information
tomsmeding committed Sep 5, 2023
1 parent 9ec930b commit 6a582ee
Show file tree
Hide file tree
Showing 5 changed files with 77 additions and 12 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -18,10 +18,24 @@

module Data.Array.Accelerate.TensorFlow.Lite (

Smart.Acc, Sugar.Arrays, Afunction, AfunctionR,
Model, RepresentativeData, Shapes, Args(..),
encodeModel, decodeModel,

-- * Representative sample data
--
-- | A TPU model is quantised, meaning that floating-point numbers in the
-- source model are actually lowered to 8-bit integer arithmetic, under some
-- affine transformation (i.e. the int8 ranges between a minimum and a maximum
-- float value, with equal spacing in between).
--
-- To calibrate this quantisation, the compilation process needs representative
-- sample input data, together with the shape of the output of the model.

RepresentativeData, Args(..), Shapes,

-- * Compiling a model
--
-- | The first step of running a TPU program is compiling the model to a
-- 'Model'. This can be done using 'compile' or 'compileWith'.

Model,
compile,
compileWith,
ConverterPy,
Expand All @@ -30,10 +44,34 @@ module Data.Array.Accelerate.TensorFlow.Lite (
ConverterSettings(..),
defaultConverterSettings,

-- * Executing a compiled model
--
-- | After a model has been compiled, it can be executed on the TPU hardware.

execute,
withDeviceContext,

argMin, argMax
-- * Special cases
--
-- | These functions are additional Accelerate primitives with a special
-- implementation in TensorFlow. They have a fallback implementation (using
-- 'Data.Array.Accelerate.foreignAcc') that is implemented in standard
-- Accelerate, and hence work also on other backends (via the fallback
-- implementation).

argMin, argMax,

-- * Model serialisation
--
-- | These functions implement a bespoke model serialisation format (i.e. not
-- a TensorFlow-specific format). They can be used if you want to create a
-- model once, then re-calibrate and re-run it multiple times in various
-- invocations of your program.
--
encodeModel, decodeModel,

-- * Re-exports from Accelerate
Smart.Acc, Sugar.Arrays, Afunction, AfunctionR,

) where

Expand Down Expand Up @@ -83,6 +121,10 @@ import Prelude as
-- | A representative data set for a given tensor computation. This
-- typically consists of a subset of the data that was used for training.
--
-- The type @f@ is the type of the function as usually passed to @runN@, and
-- as passed to 'Data.Array.Accelerate.TensorFlow.Lite.compile' with the TPU
-- backend.
--
type RepresentativeData f = [Args f]


Expand All @@ -101,6 +143,8 @@ type RepresentativeData f = [Args f]
-- > m :: Model (a -> b -> c)
-- > m = compile f args
--
-- Note that e.g. @'AfunctionR' ('Data.Array.Accelerate.Acc' a -> 'Data.Array.Accelerate.Acc' b -> 'Data.Array.Accelerate.Acc' c) = a -> b -> c@.
--
-- The compiled model can then be evaluated using 'execute' or serialised
-- using 'encodeModel'.
--
Expand Down Expand Up @@ -148,7 +192,7 @@ compileWith' converter acc args = do
-- > result :: Vector Word8
-- > result = execute m xs ys
--
-- **Note about contexts**:
-- __Note about contexts__:
-- If a TPU device context has not yet been acquired using 'withDeviceContext',
-- 'execute' will open a new device context just for this evaluation and close
-- it when the computation is finished. Opening a new device context is very
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -50,9 +50,11 @@ import Paths_accelerate_tensorflow_lite
-- | The representation of a running converter.py process.
--
-- Every distinct 'ConverterPy' represents a distinct process. Access to these
-- processes is NOT thread-safe! See 'runConverterJob' for details.
-- processes is NOT thread-safe! You can use separate 'ConverterPy' objects
-- simultaneously just fine, but do run multiple jobs concurrently on a single
-- 'ConverterPy'.
data ConverterPy = ConverterPy ConverterSettings (IORef (Maybe CPImpl))
-- This is an IORef so that we can mutate the contents in-place. Nothing
-- This is an IORef so that we can mutate the contents in-place. 'Nothing'
-- indicates that no process has been started yet; presumably the last job
-- failed, and we want to wait until a new job happens to start a new
-- converter. Just indiates a running process.
Expand All @@ -63,10 +65,20 @@ data CPImpl = CPImpl
Handle -- ^ tflite output stream
(IORef LB.ByteString) -- ^ stderr

-- | Some settings for the converter process.
data ConverterSettings = ConverterSettings
{ csVerbose :: Bool }
{ csVerbose :: Bool
-- ^ Indicates whether to always show stdout/stderr output from the
-- conversion process (TensorFlow Lite). If @True@, stdout and stderr are
-- inherited from the Haskell process, meaning that informational as well
-- as error output (typically) end up in the terminal. If @False@, output
-- is captured and only printed if an error occurred. Note that the
-- @False@ option is sometimes unreliable: sometimes there is more output
-- than we can reliably print if an error occurs.
}
deriving (Show)

-- | Default settings for the converter. This sets verbose = false.
defaultConverterSettings :: ConverterSettings
defaultConverterSettings = ConverterSettings False

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -47,8 +47,10 @@ infixr 0 :->
-- ('Data.Array.Accelerate.Acc') arrays. For the output type @c@ we only
-- need the extents ('Shapes') of each of the output arrays. For example:
--
-- > Shapes (Array DIM1 Float) = DIM1
-- > Shapes (Array DIM1 Int8, Array DIM2 Float) = (DIM1, DIM2)
-- @
-- 'Shapes' ('Array' 'Data.Array.Accelerate.DIM1' Float) = 'Data.Array.Accelerate.DIM1'
-- 'Shapes' ('Array' 'Data.Array.Accelerate.DIM1' Int8, 'Array' 'Data.Array.Accelerate.DIM2' Float) = ('Data.Array.Accelerate.DIM1', 'Data.Array.Accelerate.DIM2')
-- @
--
data Args f where
(:->) :: Arrays a => a -> Args b -> Args (a -> b)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -26,6 +26,13 @@ import qualified Data.Array.Accelerate.TensorFlow.Lite.Representation.Shapes as


class Arrays a => HasShapes a where
-- | The shapes of the arrays in this type. The definition is as follows:
--
-- > Shapes (Array sh e) = sh
-- > Shapes () = ()
-- > Shapes (a, b) = (Shapes a, Shapes b)
-- > Shapes (a, b, c) = (Shapes a, Shapes b, Shapes c)
-- > -- etc.
type Shapes a :: Type
shapesR :: R.ShapesR (ArraysR a)
fromShapes :: Shapes a -> R.Shapes (ArraysR a)
Expand Down
2 changes: 1 addition & 1 deletion accelerate-tensorflow-lite/src/System/Process/Extra.hs
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,7 @@ import GHC.IO.Exception ( IOErrorTyp
-- Handle lock, because when we clean up the process we try to close that
-- handle, which could otherwise deadlock.
--
-- Stolen from the 'process' package.
-- Stolen from the @process@ package.
--
withForkWait :: IO () -> (IO () -> IO a) -> IO a
withForkWait async body = do
Expand Down

0 comments on commit 6a582ee

Please sign in to comment.