{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedLists #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE UndecidableSuperClasses #-}
{-# LANGUAGE NoStarIsType #-}
{-# OPTIONS_GHC -fconstraint-solver-iterations=0 #-}
{-# OPTIONS_GHC -fplugin GHC.TypeLits.Extra.Solver #-}
{-# OPTIONS_GHC -fplugin GHC.TypeLits.KnownNat.Solver #-}
{-# OPTIONS_GHC -fplugin GHC.TypeLits.Normalise #-}
module Torch.Typed.NN.Recurrent.Cell.GRU where
import Data.List
( foldl',
scanl',
)
import GHC.Generics
import GHC.TypeLits
import qualified Torch.DType as D
import qualified Torch.Device as D
import qualified Torch.NN as A
import Torch.Typed.Factories
import Torch.Typed.Functional hiding (linear)
import Torch.Typed.NN.Dropout
import Torch.Typed.Parameter
import Torch.Typed.Tensor
data
GRUCellSpec
(inputDim :: Nat)
(hiddenDim :: Nat)
(dtype :: D.DType)
(device :: (D.DeviceType, Nat))
=
GRUCellSpec
deriving (Int -> GRUCellSpec inputDim hiddenDim dtype device -> ShowS
[GRUCellSpec inputDim hiddenDim dtype device] -> ShowS
GRUCellSpec inputDim hiddenDim dtype device -> String
(Int -> GRUCellSpec inputDim hiddenDim dtype device -> ShowS)
-> (GRUCellSpec inputDim hiddenDim dtype device -> String)
-> ([GRUCellSpec inputDim hiddenDim dtype device] -> ShowS)
-> Show (GRUCellSpec inputDim hiddenDim dtype device)
forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
Int -> GRUCellSpec inputDim hiddenDim dtype device -> ShowS
forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
[GRUCellSpec inputDim hiddenDim dtype device] -> ShowS
forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
GRUCellSpec inputDim hiddenDim dtype device -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
Int -> GRUCellSpec inputDim hiddenDim dtype device -> ShowS
showsPrec :: Int -> GRUCellSpec inputDim hiddenDim dtype device -> ShowS
$cshow :: forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
GRUCellSpec inputDim hiddenDim dtype device -> String
show :: GRUCellSpec inputDim hiddenDim dtype device -> String
$cshowList :: forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
[GRUCellSpec inputDim hiddenDim dtype device] -> ShowS
showList :: [GRUCellSpec inputDim hiddenDim dtype device] -> ShowS
Show, GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device -> Bool
(GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device -> Bool)
-> (GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device -> Bool)
-> Eq (GRUCellSpec inputDim hiddenDim dtype device)
forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device -> Bool
== :: GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device -> Bool
$c/= :: forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device -> Bool
/= :: GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device -> Bool
Eq, Eq (GRUCellSpec inputDim hiddenDim dtype device)
Eq (GRUCellSpec inputDim hiddenDim dtype device) =>
(GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device -> Ordering)
-> (GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device -> Bool)
-> (GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device -> Bool)
-> (GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device -> Bool)
-> (GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device -> Bool)
-> (GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device)
-> (GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device)
-> Ord (GRUCellSpec inputDim hiddenDim dtype device)
GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device -> Bool
GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device -> Ordering
GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device
forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
Eq (GRUCellSpec inputDim hiddenDim dtype device)
forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device -> Bool
forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device -> Ordering
forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device -> Ordering
compare :: GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device -> Ordering
$c< :: forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device -> Bool
< :: GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device -> Bool
$c<= :: forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device -> Bool
<= :: GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device -> Bool
$c> :: forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device -> Bool
> :: GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device -> Bool
$c>= :: forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device -> Bool
>= :: GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device -> Bool
$cmax :: forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device
max :: GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device
$cmin :: forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device
min :: GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device
Ord, (forall x.
GRUCellSpec inputDim hiddenDim dtype device
-> Rep (GRUCellSpec inputDim hiddenDim dtype device) x)
-> (forall x.
Rep (GRUCellSpec inputDim hiddenDim dtype device) x
-> GRUCellSpec inputDim hiddenDim dtype device)
-> Generic (GRUCellSpec inputDim hiddenDim dtype device)
forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)) x.
Rep (GRUCellSpec inputDim hiddenDim dtype device) x
-> GRUCellSpec inputDim hiddenDim dtype device
forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)) x.
GRUCellSpec inputDim hiddenDim dtype device
-> Rep (GRUCellSpec inputDim hiddenDim dtype device) x
forall x.
Rep (GRUCellSpec inputDim hiddenDim dtype device) x
-> GRUCellSpec inputDim hiddenDim dtype device
forall x.
GRUCellSpec inputDim hiddenDim dtype device
-> Rep (GRUCellSpec inputDim hiddenDim dtype device) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)) x.
GRUCellSpec inputDim hiddenDim dtype device
-> Rep (GRUCellSpec inputDim hiddenDim dtype device) x
from :: forall x.
GRUCellSpec inputDim hiddenDim dtype device
-> Rep (GRUCellSpec inputDim hiddenDim dtype device) x
$cto :: forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)) x.
Rep (GRUCellSpec inputDim hiddenDim dtype device) x
-> GRUCellSpec inputDim hiddenDim dtype device
to :: forall x.
Rep (GRUCellSpec inputDim hiddenDim dtype device) x
-> GRUCellSpec inputDim hiddenDim dtype device
Generic, Int -> GRUCellSpec inputDim hiddenDim dtype device
GRUCellSpec inputDim hiddenDim dtype device -> Int
GRUCellSpec inputDim hiddenDim dtype device
-> [GRUCellSpec inputDim hiddenDim dtype device]
GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device
GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device
-> [GRUCellSpec inputDim hiddenDim dtype device]
GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device
-> [GRUCellSpec inputDim hiddenDim dtype device]
(GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device)
-> (GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device)
-> (Int -> GRUCellSpec inputDim hiddenDim dtype device)
-> (GRUCellSpec inputDim hiddenDim dtype device -> Int)
-> (GRUCellSpec inputDim hiddenDim dtype device
-> [GRUCellSpec inputDim hiddenDim dtype device])
-> (GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device
-> [GRUCellSpec inputDim hiddenDim dtype device])
-> (GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device
-> [GRUCellSpec inputDim hiddenDim dtype device])
-> (GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device
-> [GRUCellSpec inputDim hiddenDim dtype device])
-> Enum (GRUCellSpec inputDim hiddenDim dtype device)
forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
Int -> GRUCellSpec inputDim hiddenDim dtype device
forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
GRUCellSpec inputDim hiddenDim dtype device -> Int
forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
GRUCellSpec inputDim hiddenDim dtype device
-> [GRUCellSpec inputDim hiddenDim dtype device]
forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device
forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device
-> [GRUCellSpec inputDim hiddenDim dtype device]
forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device
-> [GRUCellSpec inputDim hiddenDim dtype device]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device
succ :: GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device
$cpred :: forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device
pred :: GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device
$ctoEnum :: forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
Int -> GRUCellSpec inputDim hiddenDim dtype device
toEnum :: Int -> GRUCellSpec inputDim hiddenDim dtype device
$cfromEnum :: forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
GRUCellSpec inputDim hiddenDim dtype device -> Int
fromEnum :: GRUCellSpec inputDim hiddenDim dtype device -> Int
$cenumFrom :: forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
GRUCellSpec inputDim hiddenDim dtype device
-> [GRUCellSpec inputDim hiddenDim dtype device]
enumFrom :: GRUCellSpec inputDim hiddenDim dtype device
-> [GRUCellSpec inputDim hiddenDim dtype device]
$cenumFromThen :: forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device
-> [GRUCellSpec inputDim hiddenDim dtype device]
enumFromThen :: GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device
-> [GRUCellSpec inputDim hiddenDim dtype device]
$cenumFromTo :: forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device
-> [GRUCellSpec inputDim hiddenDim dtype device]
enumFromTo :: GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device
-> [GRUCellSpec inputDim hiddenDim dtype device]
$cenumFromThenTo :: forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device
-> [GRUCellSpec inputDim hiddenDim dtype device]
enumFromThenTo :: GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device
-> [GRUCellSpec inputDim hiddenDim dtype device]
Enum, GRUCellSpec inputDim hiddenDim dtype device
GRUCellSpec inputDim hiddenDim dtype device
-> GRUCellSpec inputDim hiddenDim dtype device
-> Bounded (GRUCellSpec inputDim hiddenDim dtype device)
forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
GRUCellSpec inputDim hiddenDim dtype device
forall a. a -> a -> Bounded a
$cminBound :: forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
GRUCellSpec inputDim hiddenDim dtype device
minBound :: GRUCellSpec inputDim hiddenDim dtype device
$cmaxBound :: forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
GRUCellSpec inputDim hiddenDim dtype device
maxBound :: GRUCellSpec inputDim hiddenDim dtype device
Bounded)
data
GRUCell
(inputDim :: Nat)
(hiddenDim :: Nat)
(dtype :: D.DType)
(device :: (D.DeviceType, Nat)) = GRUCell
{
forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
GRUCell inputDim hiddenDim dtype device
-> Parameter device dtype '[3 * hiddenDim, inputDim]
gruCell_w_ih :: Parameter device dtype '[3 * hiddenDim, inputDim],
forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
GRUCell inputDim hiddenDim dtype device
-> Parameter device dtype '[3 * hiddenDim, hiddenDim]
gruCell_w_hh :: Parameter device dtype '[3 * hiddenDim, hiddenDim],
forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
GRUCell inputDim hiddenDim dtype device
-> Parameter device dtype '[3 * hiddenDim]
gruCell_b_ih :: Parameter device dtype '[3 * hiddenDim],
forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
GRUCell inputDim hiddenDim dtype device
-> Parameter device dtype '[3 * hiddenDim]
gruCell_b_hh :: Parameter device dtype '[3 * hiddenDim]
}
deriving (Int -> GRUCell inputDim hiddenDim dtype device -> ShowS
[GRUCell inputDim hiddenDim dtype device] -> ShowS
GRUCell inputDim hiddenDim dtype device -> String
(Int -> GRUCell inputDim hiddenDim dtype device -> ShowS)
-> (GRUCell inputDim hiddenDim dtype device -> String)
-> ([GRUCell inputDim hiddenDim dtype device] -> ShowS)
-> Show (GRUCell inputDim hiddenDim dtype device)
forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
Int -> GRUCell inputDim hiddenDim dtype device -> ShowS
forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
[GRUCell inputDim hiddenDim dtype device] -> ShowS
forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
GRUCell inputDim hiddenDim dtype device -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
Int -> GRUCell inputDim hiddenDim dtype device -> ShowS
showsPrec :: Int -> GRUCell inputDim hiddenDim dtype device -> ShowS
$cshow :: forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
GRUCell inputDim hiddenDim dtype device -> String
show :: GRUCell inputDim hiddenDim dtype device -> String
$cshowList :: forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
[GRUCell inputDim hiddenDim dtype device] -> ShowS
showList :: [GRUCell inputDim hiddenDim dtype device] -> ShowS
Show, (forall x.
GRUCell inputDim hiddenDim dtype device
-> Rep (GRUCell inputDim hiddenDim dtype device) x)
-> (forall x.
Rep (GRUCell inputDim hiddenDim dtype device) x
-> GRUCell inputDim hiddenDim dtype device)
-> Generic (GRUCell inputDim hiddenDim dtype device)
forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)) x.
Rep (GRUCell inputDim hiddenDim dtype device) x
-> GRUCell inputDim hiddenDim dtype device
forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)) x.
GRUCell inputDim hiddenDim dtype device
-> Rep (GRUCell inputDim hiddenDim dtype device) x
forall x.
Rep (GRUCell inputDim hiddenDim dtype device) x
-> GRUCell inputDim hiddenDim dtype device
forall x.
GRUCell inputDim hiddenDim dtype device
-> Rep (GRUCell inputDim hiddenDim dtype device) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)) x.
GRUCell inputDim hiddenDim dtype device
-> Rep (GRUCell inputDim hiddenDim dtype device) x
from :: forall x.
GRUCell inputDim hiddenDim dtype device
-> Rep (GRUCell inputDim hiddenDim dtype device) x
$cto :: forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)) x.
Rep (GRUCell inputDim hiddenDim dtype device) x
-> GRUCell inputDim hiddenDim dtype device
to :: forall x.
Rep (GRUCell inputDim hiddenDim dtype device) x
-> GRUCell inputDim hiddenDim dtype device
Generic, GRUCell inputDim hiddenDim dtype device
-> HList (Parameters (GRUCell inputDim hiddenDim dtype device))
GRUCell inputDim hiddenDim dtype device
-> HList (Parameters (GRUCell inputDim hiddenDim dtype device))
-> GRUCell inputDim hiddenDim dtype device
(GRUCell inputDim hiddenDim dtype device
-> HList (Parameters (GRUCell inputDim hiddenDim dtype device)))
-> (GRUCell inputDim hiddenDim dtype device
-> HList (Parameters (GRUCell inputDim hiddenDim dtype device))
-> GRUCell inputDim hiddenDim dtype device)
-> Parameterized (GRUCell inputDim hiddenDim dtype device)
forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
GRUCell inputDim hiddenDim dtype device
-> HList (Parameters (GRUCell inputDim hiddenDim dtype device))
forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
GRUCell inputDim hiddenDim dtype device
-> HList (Parameters (GRUCell inputDim hiddenDim dtype device))
-> GRUCell inputDim hiddenDim dtype device
forall f.
(f -> HList (Parameters f))
-> (f -> HList (Parameters f) -> f) -> Parameterized f
$cflattenParameters :: forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
GRUCell inputDim hiddenDim dtype device
-> HList (Parameters (GRUCell inputDim hiddenDim dtype device))
flattenParameters :: GRUCell inputDim hiddenDim dtype device
-> HList (Parameters (GRUCell inputDim hiddenDim dtype device))
$creplaceParameters :: forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
GRUCell inputDim hiddenDim dtype device
-> HList (Parameters (GRUCell inputDim hiddenDim dtype device))
-> GRUCell inputDim hiddenDim dtype device
replaceParameters :: GRUCell inputDim hiddenDim dtype device
-> HList (Parameters (GRUCell inputDim hiddenDim dtype device))
-> GRUCell inputDim hiddenDim dtype device
Parameterized)
instance
( KnownDevice device,
KnownDType dtype,
KnownNat inputDim,
KnownNat hiddenDim,
RandDTypeIsValid device dtype
) =>
A.Randomizable
(GRUCellSpec inputDim hiddenDim dtype device)
(GRUCell inputDim hiddenDim dtype device)
where
sample :: GRUCellSpec inputDim hiddenDim dtype device
-> IO (GRUCell inputDim hiddenDim dtype device)
sample GRUCellSpec inputDim hiddenDim dtype device
GRUCellSpec =
Parameter device dtype '[3 * hiddenDim, inputDim]
-> Parameter device dtype '[3 * hiddenDim, hiddenDim]
-> Parameter device dtype '[3 * hiddenDim]
-> Parameter device dtype '[3 * hiddenDim]
-> GRUCell inputDim hiddenDim dtype device
forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
Parameter device dtype '[3 * hiddenDim, inputDim]
-> Parameter device dtype '[3 * hiddenDim, hiddenDim]
-> Parameter device dtype '[3 * hiddenDim]
-> Parameter device dtype '[3 * hiddenDim]
-> GRUCell inputDim hiddenDim dtype device
GRUCell
(Parameter device dtype '[3 * hiddenDim, inputDim]
-> Parameter device dtype '[3 * hiddenDim, hiddenDim]
-> Parameter device dtype '[3 * hiddenDim]
-> Parameter device dtype '[3 * hiddenDim]
-> GRUCell inputDim hiddenDim dtype device)
-> IO (Parameter device dtype '[3 * hiddenDim, inputDim])
-> IO
(Parameter device dtype '[3 * hiddenDim, hiddenDim]
-> Parameter device dtype '[3 * hiddenDim]
-> Parameter device dtype '[3 * hiddenDim]
-> GRUCell inputDim hiddenDim dtype device)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (Tensor device dtype '[3 * hiddenDim, inputDim]
-> IO (Parameter device dtype '[3 * hiddenDim, inputDim])
forall (shape :: [Nat]) (dtype :: DType)
(device :: (DeviceType, Nat)).
Tensor device dtype shape -> IO (Parameter device dtype shape)
makeIndependent (Tensor device dtype '[3 * hiddenDim, inputDim]
-> IO (Parameter device dtype '[3 * hiddenDim, inputDim]))
-> IO (Tensor device dtype '[3 * hiddenDim, inputDim])
-> IO (Parameter device dtype '[3 * hiddenDim, inputDim])
forall (m :: Type -> Type) a b. Monad m => (a -> m b) -> m a -> m b
=<< IO (Tensor device dtype '[3 * hiddenDim, inputDim])
forall (shape :: [Nat]) (dtype :: DType)
(device :: (DeviceType, Nat)).
(TensorOptions shape dtype device,
RandDTypeIsValid device dtype) =>
IO (Tensor device dtype shape)
randn)
IO
(Parameter device dtype '[3 * hiddenDim, hiddenDim]
-> Parameter device dtype '[3 * hiddenDim]
-> Parameter device dtype '[3 * hiddenDim]
-> GRUCell inputDim hiddenDim dtype device)
-> IO (Parameter device dtype '[3 * hiddenDim, hiddenDim])
-> IO
(Parameter device dtype '[3 * hiddenDim]
-> Parameter device dtype '[3 * hiddenDim]
-> GRUCell inputDim hiddenDim dtype device)
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> (Tensor device dtype '[3 * hiddenDim, hiddenDim]
-> IO (Parameter device dtype '[3 * hiddenDim, hiddenDim])
forall (shape :: [Nat]) (dtype :: DType)
(device :: (DeviceType, Nat)).
Tensor device dtype shape -> IO (Parameter device dtype shape)
makeIndependent (Tensor device dtype '[3 * hiddenDim, hiddenDim]
-> IO (Parameter device dtype '[3 * hiddenDim, hiddenDim]))
-> IO (Tensor device dtype '[3 * hiddenDim, hiddenDim])
-> IO (Parameter device dtype '[3 * hiddenDim, hiddenDim])
forall (m :: Type -> Type) a b. Monad m => (a -> m b) -> m a -> m b
=<< IO (Tensor device dtype '[3 * hiddenDim, hiddenDim])
forall (shape :: [Nat]) (dtype :: DType)
(device :: (DeviceType, Nat)).
(TensorOptions shape dtype device,
RandDTypeIsValid device dtype) =>
IO (Tensor device dtype shape)
randn)
IO
(Parameter device dtype '[3 * hiddenDim]
-> Parameter device dtype '[3 * hiddenDim]
-> GRUCell inputDim hiddenDim dtype device)
-> IO (Parameter device dtype '[3 * hiddenDim])
-> IO
(Parameter device dtype '[3 * hiddenDim]
-> GRUCell inputDim hiddenDim dtype device)
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> (Tensor device dtype '[3 * hiddenDim]
-> IO (Parameter device dtype '[3 * hiddenDim])
forall (shape :: [Nat]) (dtype :: DType)
(device :: (DeviceType, Nat)).
Tensor device dtype shape -> IO (Parameter device dtype shape)
makeIndependent (Tensor device dtype '[3 * hiddenDim]
-> IO (Parameter device dtype '[3 * hiddenDim]))
-> IO (Tensor device dtype '[3 * hiddenDim])
-> IO (Parameter device dtype '[3 * hiddenDim])
forall (m :: Type -> Type) a b. Monad m => (a -> m b) -> m a -> m b
=<< IO (Tensor device dtype '[3 * hiddenDim])
forall (shape :: [Nat]) (dtype :: DType)
(device :: (DeviceType, Nat)).
(TensorOptions shape dtype device,
RandDTypeIsValid device dtype) =>
IO (Tensor device dtype shape)
randn)
IO
(Parameter device dtype '[3 * hiddenDim]
-> GRUCell inputDim hiddenDim dtype device)
-> IO (Parameter device dtype '[3 * hiddenDim])
-> IO (GRUCell inputDim hiddenDim dtype device)
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> (Tensor device dtype '[3 * hiddenDim]
-> IO (Parameter device dtype '[3 * hiddenDim])
forall (shape :: [Nat]) (dtype :: DType)
(device :: (DeviceType, Nat)).
Tensor device dtype shape -> IO (Parameter device dtype shape)
makeIndependent (Tensor device dtype '[3 * hiddenDim]
-> IO (Parameter device dtype '[3 * hiddenDim]))
-> IO (Tensor device dtype '[3 * hiddenDim])
-> IO (Parameter device dtype '[3 * hiddenDim])
forall (m :: Type -> Type) a b. Monad m => (a -> m b) -> m a -> m b
=<< IO (Tensor device dtype '[3 * hiddenDim])
forall (shape :: [Nat]) (dtype :: DType)
(device :: (DeviceType, Nat)).
(TensorOptions shape dtype device,
RandDTypeIsValid device dtype) =>
IO (Tensor device dtype shape)
randn)
gruCellForward ::
forall inputDim hiddenDim batchSize dtype device.
( KnownDType dtype,
KnownNat inputDim,
KnownNat hiddenDim,
KnownNat batchSize
) =>
GRUCell inputDim hiddenDim dtype device ->
Tensor device dtype '[batchSize, hiddenDim] ->
Tensor device dtype '[batchSize, inputDim] ->
Tensor device dtype '[batchSize, hiddenDim]
gruCellForward :: forall (inputDim :: Nat) (hiddenDim :: Nat) (batchSize :: Nat)
(dtype :: DType) (device :: (DeviceType, Nat)).
(KnownDType dtype, KnownNat inputDim, KnownNat hiddenDim,
KnownNat batchSize) =>
GRUCell inputDim hiddenDim dtype device
-> Tensor device dtype '[batchSize, hiddenDim]
-> Tensor device dtype '[batchSize, inputDim]
-> Tensor device dtype '[batchSize, hiddenDim]
gruCellForward GRUCell {Parameter device dtype '[3 * hiddenDim, inputDim]
Parameter device dtype '[3 * hiddenDim, hiddenDim]
Parameter device dtype '[3 * hiddenDim]
gruCell_w_ih :: forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
GRUCell inputDim hiddenDim dtype device
-> Parameter device dtype '[3 * hiddenDim, inputDim]
gruCell_w_hh :: forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
GRUCell inputDim hiddenDim dtype device
-> Parameter device dtype '[3 * hiddenDim, hiddenDim]
gruCell_b_ih :: forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
GRUCell inputDim hiddenDim dtype device
-> Parameter device dtype '[3 * hiddenDim]
gruCell_b_hh :: forall (inputDim :: Nat) (hiddenDim :: Nat) (dtype :: DType)
(device :: (DeviceType, Nat)).
GRUCell inputDim hiddenDim dtype device
-> Parameter device dtype '[3 * hiddenDim]
gruCell_w_ih :: Parameter device dtype '[3 * hiddenDim, inputDim]
gruCell_w_hh :: Parameter device dtype '[3 * hiddenDim, hiddenDim]
gruCell_b_ih :: Parameter device dtype '[3 * hiddenDim]
gruCell_b_hh :: Parameter device dtype '[3 * hiddenDim]
..} =
Tensor device dtype '[3 * hiddenDim, inputDim]
-> Tensor device dtype '[3 * hiddenDim, hiddenDim]
-> Tensor device dtype '[3 * hiddenDim]
-> Tensor device dtype '[3 * hiddenDim]
-> Tensor device dtype '[batchSize, hiddenDim]
-> Tensor device dtype '[batchSize, inputDim]
-> Tensor device dtype '[batchSize, hiddenDim]
forall (inputSize :: Nat) (hiddenSize :: Nat) (batchSize :: Nat)
(dtype :: DType) (device :: (DeviceType, Nat)).
Tensor device dtype '[3 * hiddenSize, inputSize]
-> Tensor device dtype '[3 * hiddenSize, hiddenSize]
-> Tensor device dtype '[3 * hiddenSize]
-> Tensor device dtype '[3 * hiddenSize]
-> Tensor device dtype '[batchSize, hiddenSize]
-> Tensor device dtype '[batchSize, inputSize]
-> Tensor device dtype '[batchSize, hiddenSize]
gruCell
(Parameter device dtype '[3 * hiddenDim, inputDim]
-> Tensor device dtype '[3 * hiddenDim, inputDim]
forall (shape :: [Nat]) (dtype :: DType)
(device :: (DeviceType, Nat)).
Parameter device dtype shape -> Tensor device dtype shape
toDependent Parameter device dtype '[3 * hiddenDim, inputDim]
gruCell_w_ih)
(Parameter device dtype '[3 * hiddenDim, hiddenDim]
-> Tensor device dtype '[3 * hiddenDim, hiddenDim]
forall (shape :: [Nat]) (dtype :: DType)
(device :: (DeviceType, Nat)).
Parameter device dtype shape -> Tensor device dtype shape
toDependent Parameter device dtype '[3 * hiddenDim, hiddenDim]
gruCell_w_hh)
(Parameter device dtype '[3 * hiddenDim]
-> Tensor device dtype '[3 * hiddenDim]
forall (shape :: [Nat]) (dtype :: DType)
(device :: (DeviceType, Nat)).
Parameter device dtype shape -> Tensor device dtype shape
toDependent Parameter device dtype '[3 * hiddenDim]
gruCell_b_ih)
(Parameter device dtype '[3 * hiddenDim]
-> Tensor device dtype '[3 * hiddenDim]
forall (shape :: [Nat]) (dtype :: DType)
(device :: (DeviceType, Nat)).
Parameter device dtype shape -> Tensor device dtype shape
toDependent Parameter device dtype '[3 * hiddenDim]
gruCell_b_hh)
gruFold ::
forall inputDim hiddenDim batchSize dtype device.
( KnownDType dtype,
KnownNat inputDim,
KnownNat hiddenDim,
KnownNat batchSize
) =>
GRUCell inputDim hiddenDim dtype device ->
Tensor device dtype '[batchSize, hiddenDim] ->
[Tensor device dtype '[batchSize, inputDim]] ->
Tensor device dtype '[batchSize, hiddenDim]
gruFold :: forall (inputDim :: Nat) (hiddenDim :: Nat) (batchSize :: Nat)
(dtype :: DType) (device :: (DeviceType, Nat)).
(KnownDType dtype, KnownNat inputDim, KnownNat hiddenDim,
KnownNat batchSize) =>
GRUCell inputDim hiddenDim dtype device
-> Tensor device dtype '[batchSize, hiddenDim]
-> [Tensor device dtype '[batchSize, inputDim]]
-> Tensor device dtype '[batchSize, hiddenDim]
gruFold GRUCell inputDim hiddenDim dtype device
cell = (Tensor device dtype '[batchSize, hiddenDim]
-> Tensor device dtype '[batchSize, inputDim]
-> Tensor device dtype '[batchSize, hiddenDim])
-> Tensor device dtype '[batchSize, hiddenDim]
-> [Tensor device dtype '[batchSize, inputDim]]
-> Tensor device dtype '[batchSize, hiddenDim]
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: Type -> Type) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (GRUCell inputDim hiddenDim dtype device
-> Tensor device dtype '[batchSize, hiddenDim]
-> Tensor device dtype '[batchSize, inputDim]
-> Tensor device dtype '[batchSize, hiddenDim]
forall (inputDim :: Nat) (hiddenDim :: Nat) (batchSize :: Nat)
(dtype :: DType) (device :: (DeviceType, Nat)).
(KnownDType dtype, KnownNat inputDim, KnownNat hiddenDim,
KnownNat batchSize) =>
GRUCell inputDim hiddenDim dtype device
-> Tensor device dtype '[batchSize, hiddenDim]
-> Tensor device dtype '[batchSize, inputDim]
-> Tensor device dtype '[batchSize, hiddenDim]
gruCellForward GRUCell inputDim hiddenDim dtype device
cell)
gruCellScan ::
forall inputDim hiddenDim batchSize dtype device.
( KnownDType dtype,
KnownNat inputDim,
KnownNat hiddenDim,
KnownNat batchSize
) =>
GRUCell inputDim hiddenDim dtype device ->
Tensor device dtype '[batchSize, hiddenDim] ->
[Tensor device dtype '[batchSize, inputDim]] ->
[Tensor device dtype '[batchSize, hiddenDim]]
gruCellScan :: forall (inputDim :: Nat) (hiddenDim :: Nat) (batchSize :: Nat)
(dtype :: DType) (device :: (DeviceType, Nat)).
(KnownDType dtype, KnownNat inputDim, KnownNat hiddenDim,
KnownNat batchSize) =>
GRUCell inputDim hiddenDim dtype device
-> Tensor device dtype '[batchSize, hiddenDim]
-> [Tensor device dtype '[batchSize, inputDim]]
-> [Tensor device dtype '[batchSize, hiddenDim]]
gruCellScan GRUCell inputDim hiddenDim dtype device
cell = (Tensor device dtype '[batchSize, hiddenDim]
-> Tensor device dtype '[batchSize, inputDim]
-> Tensor device dtype '[batchSize, hiddenDim])
-> Tensor device dtype '[batchSize, hiddenDim]
-> [Tensor device dtype '[batchSize, inputDim]]
-> [Tensor device dtype '[batchSize, hiddenDim]]
forall b a. (b -> a -> b) -> b -> [a] -> [b]
scanl' (GRUCell inputDim hiddenDim dtype device
-> Tensor device dtype '[batchSize, hiddenDim]
-> Tensor device dtype '[batchSize, inputDim]
-> Tensor device dtype '[batchSize, hiddenDim]
forall (inputDim :: Nat) (hiddenDim :: Nat) (batchSize :: Nat)
(dtype :: DType) (device :: (DeviceType, Nat)).
(KnownDType dtype, KnownNat inputDim, KnownNat hiddenDim,
KnownNat batchSize) =>
GRUCell inputDim hiddenDim dtype device
-> Tensor device dtype '[batchSize, hiddenDim]
-> Tensor device dtype '[batchSize, inputDim]
-> Tensor device dtype '[batchSize, hiddenDim]
gruCellForward GRUCell inputDim hiddenDim dtype device
cell)