hasktorch-indef-0.0.1.0: Core Hasktorch abstractions wrapping FFI bindings

Copyright(c) Sam Stites 2017
LicenseBSD3
Maintainersam@stites.io
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Torch.Indef.Static.Tensor.Random.THC

Description

 
Synopsis

Documentation

random :: Dimensions d => IO (Tensor d) Source #

Static call to random

clampedRandom :: Dimensions d => Integer -> Integer -> IO (Tensor d) Source #

Static call to clampedRandom

cappedRandom :: Dimensions d => Integer -> IO (Tensor d) Source #

Static call to cappedRandom

bernoulli :: Dimensions d => HsAccReal -> IO (Tensor d) Source #

Static call to bernoulli

bernoulli_DoubleTensor :: Dimensions d => Tensor d -> IO (Tensor d) Source #

Static call to bernoulli_DoubleTensor

geometric :: Dimensions d => HsAccReal -> IO (Tensor d) Source #

Static call to geometric

uniform :: Dimensions d => Ord2Tuple HsAccReal -> IO (Tensor d) Source #

Static call to uniform

normal :: Dimensions d => HsAccReal -> Positive HsAccReal -> IO (Tensor d) Source #

Static call to normal

normal_means :: Dimensions d => Tensor d -> Positive HsAccReal -> IO (Tensor d) Source #

Static call to normal_means

normal_stddevs :: Dimensions d => HsAccReal -> Tensor d -> IO (Tensor d) Source #

Static call to normal_stddevs

normal_means_stddevs :: Dimensions d => Tensor d -> Tensor d -> IO (Tensor d) Source #

Static call to normal_means_stddevs

logNormal :: Dimensions d => HsAccReal -> Positive HsAccReal -> IO (Tensor d) Source #

Static call to logNormal

exponential :: Dimensions d => HsAccReal -> IO (Tensor d) Source #

Static call to exponential

cauchy :: Dimensions d => HsAccReal -> HsAccReal -> IO (Tensor d) Source #

Static call to cauchy

rand :: Dimensions d => LongStorage -> IO (Tensor d) Source #

Static call to rand

randn :: Dimensions d => LongStorage -> IO (Tensor d) Source #

Static call to randn

_multinomial :: LongTensor d1 -> Tensor d2 -> Int -> Int -> IO () Source #

Static call to _multinomial

data OpenUnit x #

Datatype to represent the open unit interval: 0 < x < 1. Any OpenUnit inhabitant must satisfy being in the interval.

FIXME: replace with numhask.

Instances
Eq x => Eq (OpenUnit x) 
Instance details

Defined in Torch.Types.Numeric

Methods

(==) :: OpenUnit x -> OpenUnit x -> Bool #

(/=) :: OpenUnit x -> OpenUnit x -> Bool #

Ord x => Ord (OpenUnit x) 
Instance details

Defined in Torch.Types.Numeric

Methods

compare :: OpenUnit x -> OpenUnit x -> Ordering #

(<) :: OpenUnit x -> OpenUnit x -> Bool #

(<=) :: OpenUnit x -> OpenUnit x -> Bool #

(>) :: OpenUnit x -> OpenUnit x -> Bool #

(>=) :: OpenUnit x -> OpenUnit x -> Bool #

max :: OpenUnit x -> OpenUnit x -> OpenUnit x #

min :: OpenUnit x -> OpenUnit x -> OpenUnit x #

Show x => Show (OpenUnit x) 
Instance details

Defined in Torch.Types.Numeric

Methods

showsPrec :: Int -> OpenUnit x -> ShowS #

show :: OpenUnit x -> String #

showList :: [OpenUnit x] -> ShowS #

openUnit :: (Ord x, Num x) => x -> Maybe (OpenUnit x) #

smart constructor to place a number in the open unit interval.

openUnitValue :: OpenUnit x -> x #

Get a value from the open unit interval.

data ClosedUnit x #

Datatype to represent the closed unit interval: 0 =< x =< 1. Any ClosedUnit inhabitant must satisfy being in the interval.

FIXME: replace with numhask.

Instances
Eq x => Eq (ClosedUnit x) 
Instance details

Defined in Torch.Types.Numeric

Methods

(==) :: ClosedUnit x -> ClosedUnit x -> Bool #

(/=) :: ClosedUnit x -> ClosedUnit x -> Bool #

Ord x => Ord (ClosedUnit x) 
Instance details

Defined in Torch.Types.Numeric

Show x => Show (ClosedUnit x) 
Instance details

Defined in Torch.Types.Numeric

closedUnit :: (Ord x, Num x) => x -> Maybe (ClosedUnit x) #

smart constructor to place a number in the closed unit interval.

closedUnitValue :: ClosedUnit x -> x #

Get a value from the closed unit interval.

data Positive x #

Datatype to represent a generic positive number: 0 =< x.

FIXME: replace with numhask.

Instances
Eq x => Eq (Positive x) 
Instance details

Defined in Torch.Types.Numeric

Methods

(==) :: Positive x -> Positive x -> Bool #

(/=) :: Positive x -> Positive x -> Bool #

Ord x => Ord (Positive x) 
Instance details

Defined in Torch.Types.Numeric

Methods

compare :: Positive x -> Positive x -> Ordering #

(<) :: Positive x -> Positive x -> Bool #

(<=) :: Positive x -> Positive x -> Bool #

(>) :: Positive x -> Positive x -> Bool #

(>=) :: Positive x -> Positive x -> Bool #

max :: Positive x -> Positive x -> Positive x #

min :: Positive x -> Positive x -> Positive x #

Show x => Show (Positive x) 
Instance details

Defined in Torch.Types.Numeric

Methods

showsPrec :: Int -> Positive x -> ShowS #

show :: Positive x -> String #

showList :: [Positive x] -> ShowS #

positive :: (Ord x, Num x) => x -> Maybe (Positive x) #

smart constructor to place a number in a positive bound.

positiveValue :: Positive x -> x #

Get a value from the positive bound.

data Ord2Tuple x #

Datatype to represent an ordered pair of numbers, (a, b), where a <= b.

FIXME: replace with numhask.

Instances
Eq x => Eq (Ord2Tuple x) 
Instance details

Defined in Torch.Types.Numeric

Methods

(==) :: Ord2Tuple x -> Ord2Tuple x -> Bool #

(/=) :: Ord2Tuple x -> Ord2Tuple x -> Bool #

Show x => Show (Ord2Tuple x) 
Instance details

Defined in Torch.Types.Numeric

ord2Tuple :: (Ord x, Num x) => (x, x) -> Maybe (Ord2Tuple x) #

smart constructor to place two values in an ordered tuple.

ord2TupleValue :: Ord2Tuple x -> (x, x) #

Get the values of an ordered tuple.