torrent-10000.1.1: BitTorrent file parser and generater

Safe HaskellNone
LanguageHaskell98

Data.Torrent

Description

Synopsis

Documentation

data Torrent Source #

Instances

Data Torrent Source # 

Methods

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

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

toConstr :: Torrent -> Constr #

dataTypeOf :: Torrent -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Torrent Source # 
Show Torrent Source # 
Binary Torrent Source # 

Methods

put :: Torrent -> Put #

get :: Get Torrent #

putList :: [Torrent] -> Put #

data TorrentInfo Source #

Instances

Data TorrentInfo Source # 

Methods

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

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

toConstr :: TorrentInfo -> Constr #

dataTypeOf :: TorrentInfo -> DataType #

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

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

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

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

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

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

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

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

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

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

Read TorrentInfo Source # 
Show TorrentInfo Source # 

data TorrentFile Source #

Constructors

TorrentFile 

Instances

Data TorrentFile Source # 

Methods

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

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

toConstr :: TorrentFile -> Constr #

dataTypeOf :: TorrentFile -> DataType #

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

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

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

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

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

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

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

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

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

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

Read TorrentFile Source # 
Show TorrentFile Source # 

torrentSize :: Torrent -> Integer Source #

Size of the files in the torrent.

showTorrent :: Torrent -> ByteString Source #

generates a torrent file

Due to lexographical ordering requirements of BEncoded data, this should generate the same ByteString that readTorrent read to generate the Torrent. However, torrent files may contain extensions and nonstandard fields that prevent that from holding for all torrent files.