neural-0.3.0.0: Neural Networks in native Haskell

Copyright(c) Lars Brünjes, 2016
LicenseMIT
Maintainerbrunjlar@gmail.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010
Extensions
  • RankNTypes
  • ExplicitForAll

Data.Utils.Pipes

Description

This module provides various utilities for working with pipes.

Synopsis

Documentation

chunks :: Monad m => Int -> Pipe a [a] m () Source #

Collects upstream data in chunks of a specified size and then passes those chunks downstram.

>>> import qualified Pipes.Prelude as P
>>> runEffect $ each [1 .. 10 :: Int] >-> chunks 3 >-> P.mapM_ print
[1,2,3]
[4,5,6]
[7,8,9]
>>> runEffect $ each [1 .. 30000 :: Int] >-> chunks 10000 >-> P.mapM_ (print . sum)
50005000
150005000
250005000

fromFile :: (MonadSafe m, MonadIO m) => FilePath -> Producer' ByteString m () Source #

Safely produces ByteStrings from a file.

toWord8 :: Monad m => Pipe ByteString Word8 m () Source #

Converts a stream of ByteStrings into a stream of Word8s.

class (MonadCatch m, MonadMask m, MonadIO m, MonadIO (Base m)) => MonadSafe m #

MonadSafe lets you register and release finalizers that execute in a Base monad

Minimal complete definition

liftBase, register, release

Instances

MonadSafe m => MonadSafe (CatchT m) 

Associated Types

type Base (CatchT m :: * -> *) :: * -> * #

Methods

liftBase :: Base (CatchT m) r -> CatchT m r #

register :: Base (CatchT m) () -> CatchT m ReleaseKey #

release :: ReleaseKey -> CatchT m () #

(MonadIO m, MonadCatch m, MonadMask m) => MonadSafe (SafeT m) 

Associated Types

type Base (SafeT m :: * -> *) :: * -> * #

Methods

liftBase :: Base (SafeT m) r -> SafeT m r #

register :: Base (SafeT m) () -> SafeT m ReleaseKey #

release :: ReleaseKey -> SafeT m () #

MonadSafe m => MonadSafe (IdentityT * m) 

Associated Types

type Base (IdentityT * m :: * -> *) :: * -> * #

MonadSafe m => MonadSafe (StateT s m) 

Associated Types

type Base (StateT s m :: * -> *) :: * -> * #

Methods

liftBase :: Base (StateT s m) r -> StateT s m r #

register :: Base (StateT s m) () -> StateT s m ReleaseKey #

release :: ReleaseKey -> StateT s m () #

MonadSafe m => MonadSafe (StateT s m) 

Associated Types

type Base (StateT s m :: * -> *) :: * -> * #

Methods

liftBase :: Base (StateT s m) r -> StateT s m r #

register :: Base (StateT s m) () -> StateT s m ReleaseKey #

release :: ReleaseKey -> StateT s m () #

(MonadSafe m, Monoid w) => MonadSafe (WriterT w m) 

Associated Types

type Base (WriterT w m :: * -> *) :: * -> * #

Methods

liftBase :: Base (WriterT w m) r -> WriterT w m r #

register :: Base (WriterT w m) () -> WriterT w m ReleaseKey #

release :: ReleaseKey -> WriterT w m () #

(MonadSafe m, Monoid w) => MonadSafe (WriterT w m) 

Associated Types

type Base (WriterT w m :: * -> *) :: * -> * #

Methods

liftBase :: Base (WriterT w m) r -> WriterT w m r #

register :: Base (WriterT w m) () -> WriterT w m ReleaseKey #

release :: ReleaseKey -> WriterT w m () #

MonadSafe m => MonadSafe (ReaderT * i m) 

Associated Types

type Base (ReaderT * i m :: * -> *) :: * -> * #

Methods

liftBase :: Base (ReaderT * i m) r -> ReaderT * i m r #

register :: Base (ReaderT * i m) () -> ReaderT * i m ReleaseKey #

release :: ReleaseKey -> ReaderT * i m () #

(MonadSafe m, Monoid w) => MonadSafe (RWST i w s m) 

Associated Types

type Base (RWST i w s m :: * -> *) :: * -> * #

Methods

liftBase :: Base (RWST i w s m) r -> RWST i w s m r #

register :: Base (RWST i w s m) () -> RWST i w s m ReleaseKey #

release :: ReleaseKey -> RWST i w s m () #

(MonadSafe m, Monoid w) => MonadSafe (RWST i w s m) 

Associated Types

type Base (RWST i w s m :: * -> *) :: * -> * #

Methods

liftBase :: Base (RWST i w s m) r -> RWST i w s m r #

register :: Base (RWST i w s m) () -> RWST i w s m ReleaseKey #

release :: ReleaseKey -> RWST i w s m () #

MonadSafe m => MonadSafe (Proxy a' a b' b m) 

Associated Types

type Base (Proxy a' a b' b m :: * -> *) :: * -> * #

Methods

liftBase :: Base (Proxy a' a b' b m) r -> Proxy a' a b' b m r #

register :: Base (Proxy a' a b' b m) () -> Proxy a' a b' b m ReleaseKey #

release :: ReleaseKey -> Proxy a' a b' b m () #

runSafeP :: (MonadMask m, MonadIO m) => Effect (SafeT m) r -> Effect' m r #

Run SafeT in the base monad, executing all unreleased finalizers at the end of the computation

Use runSafeP to safely flush all unreleased finalizers and ensure prompt finalization without exiting the Proxy monad.

runSafeT :: (MonadMask m, MonadIO m) => SafeT m r -> m r #

Run the SafeT monad transformer, executing all unreleased finalizers at the end of the computation

data ByteString :: * #

A space-efficient representation of a Word8 vector, supporting many efficient operations.

A ByteString contains 8-bit bytes, or by using the operations from Data.ByteString.Char8 it can be interpreted as containing 8-bit characters.

Instances

Eq ByteString 
Data ByteString 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ByteString -> c ByteString #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ByteString #

toConstr :: ByteString -> Constr #

dataTypeOf :: ByteString -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ByteString) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ByteString) #

gmapT :: (forall b. Data b => b -> b) -> ByteString -> ByteString #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ByteString -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ByteString -> r #

gmapQ :: (forall d. Data d => d -> u) -> ByteString -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ByteString -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ByteString -> m ByteString #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ByteString -> m ByteString #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ByteString -> m ByteString #

Ord ByteString 
Read ByteString 
Show ByteString 
IsString ByteString 
Semigroup ByteString 
Monoid ByteString 
NFData ByteString 

Methods

rnf :: ByteString -> () #

Hashable ByteString 
Ixed ByteString 
type Index ByteString 
type IxValue ByteString 

data Word8 :: * #

8-bit unsigned integer type

Instances

Bounded Word8 
Enum Word8 
Eq Word8 

Methods

(==) :: Word8 -> Word8 -> Bool #

(/=) :: Word8 -> Word8 -> Bool #

Integral Word8 
Num Word8 
Ord Word8 

Methods

compare :: Word8 -> Word8 -> Ordering #

(<) :: Word8 -> Word8 -> Bool #

(<=) :: Word8 -> Word8 -> Bool #

(>) :: Word8 -> Word8 -> Bool #

(>=) :: Word8 -> Word8 -> Bool #

max :: Word8 -> Word8 -> Word8 #

min :: Word8 -> Word8 -> Word8 #

Read Word8 
Real Word8 

Methods

toRational :: Word8 -> Rational #

Show Word8 

Methods

showsPrec :: Int -> Word8 -> ShowS #

show :: Word8 -> String #

showList :: [Word8] -> ShowS #

Ix Word8 
Lift Word8 

Methods

lift :: Word8 -> Q Exp #

Random Word8 

Methods

randomR :: RandomGen g => (Word8, Word8) -> g -> (Word8, g) #

random :: RandomGen g => g -> (Word8, g) #

randomRs :: RandomGen g => (Word8, Word8) -> g -> [Word8] #

randoms :: RandomGen g => g -> [Word8] #

randomRIO :: (Word8, Word8) -> IO Word8 #

randomIO :: IO Word8 #

NFData Word8 

Methods

rnf :: Word8 -> () #

Mode Word8 
PrintfArg Word8 
Storable Word8 

Methods

sizeOf :: Word8 -> Int #

alignment :: Word8 -> Int #

peekElemOff :: Ptr Word8 -> Int -> IO Word8 #

pokeElemOff :: Ptr Word8 -> Int -> Word8 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Word8 #

pokeByteOff :: Ptr b -> Int -> Word8 -> IO () #

peek :: Ptr Word8 -> IO Word8 #

poke :: Ptr Word8 -> Word8 -> IO () #

Bits Word8 
FiniteBits Word8 
Hashable Word8 

Methods

hashWithSalt :: Int -> Word8 -> Int #

hash :: Word8 -> Int #

Prim Word8 
Unbox Word8 
IArray UArray Word8 

Methods

bounds :: Ix i => UArray i Word8 -> (i, i) #

numElements :: Ix i => UArray i Word8 -> Int

unsafeArray :: Ix i => (i, i) -> [(Int, Word8)] -> UArray i Word8

unsafeAt :: Ix i => UArray i Word8 -> Int -> Word8

unsafeReplace :: Ix i => UArray i Word8 -> [(Int, Word8)] -> UArray i Word8

unsafeAccum :: Ix i => (Word8 -> e' -> Word8) -> UArray i Word8 -> [(Int, e')] -> UArray i Word8

unsafeAccumArray :: Ix i => (Word8 -> e' -> Word8) -> Word8 -> (i, i) -> [(Int, e')] -> UArray i Word8

Vector Vector Word8 
MVector MVector Word8 
MArray (STUArray s) Word8 (ST s) 

Methods

getBounds :: Ix i => STUArray s i Word8 -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Word8 -> ST s Int

newArray :: Ix i => (i, i) -> Word8 -> ST s (STUArray s i Word8) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word8) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word8)

unsafeRead :: Ix i => STUArray s i Word8 -> Int -> ST s Word8

unsafeWrite :: Ix i => STUArray s i Word8 -> Int -> Word8 -> ST s ()

type Scalar Word8 
data Vector Word8 
data MVector s Word8