{-# LANGUAGE CPP #-} {- Copyright (c) 2005-2006 Lemmih Permission to use, copy, modify, and distribute this software for any purpose with or without fee is hereby granted, provided that the above copyright notice and this permission notice appear in all copies. THE SOFTWARE IS PROVIDED "AS IS" AND THE AUTHOR DISCLAIMS ALL WARRANTIES WITH REGARD TO THIS SOFTWARE INCLUDING ALL IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY SPECIAL, DIRECT, INDIRECT, OR CONSEQUENTIAL DAMAGES OR ANY DAMAGES WHATSOEVER RESULTING FROM LOSS OF USE, DATA OR PROFITS, WHETHER IN AN ACTION OF CONTRACT, NEGLIGENCE OR OTHER TORTIOUS ACTION, ARISING OUT OF OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE. -} ----------------------------------------------------------------------------- -- C O N J U R E -- -- How small a Bittorrent implementation can you actually do? -- -- The current Bittorrent implementation is about 10.000 lines. Let us -- beat that by lengths. ----------------------------------------------------------------------------- module Main (main,run) where import Conjure.Torrent import Conjure.Network.Client import Conjure.FileSystem.Interface as Interface import Conjure.Logic.PeerManager import Conjure.Network.Server import Conjure.UI.Http import Conjure.OptionParser import Conjure.Utils.Logger import Conjure.Debug import Control.Concurrent import Control.Concurrent.STM import System.Environment (getArgs) import Control.Monad (when) import Control.Exception (finally) #ifndef mingw32_HOST_OS import System.Posix #endif import qualified Data.Map as Map -- import Data.Map (Map) -- FIXME: Logger options and log mask should be configurable. main = do putStrLn "Conjure!" #ifndef mingw32_HOST_OS installHandler sigPIPE Ignore Nothing #endif openlog [PError] "conjure" initSTMLogger (args, files) <- (getArgs >>= getOpts) when (not $ null files) (run $ head files) closelog return () -- FIXME: This is only a temporary function. -- We only need a single connPeer list, server, wantedDownload, wantedUploads and torrentMap -- for all torrents. run torrentPath = do mbTorrent <- readTorrentFile torrentPath case mbTorrent of Left err -> putStrLn err Right torrent -> do connectedPeers <- atomically $ newTVar [] seedingPeers <- atomically $ newTVar [] torrentMap <- atomically $ newTVar (Map.empty) nSecs <- atomically $ newTVar 10 -- Options: Max peers, max downloads, max uploads, min optimistic opts <- atomically $ newTVar (50, 20, 10, 2) forkIO (runMainChoker nSecs connectedPeers opts) forkIO (httpServer connectedPeers torrentMap uiPort) tid <- forkIO $ runServer connectedPeers torrentMap port backend <- Interface.defaultOpen torrent runClient port connectedPeers torrentMap torrent backend atomically retry `finally` do putStrLn "Shutting down." killThread tid shutdownAll torrentMap putStrLn "Done." where port = 3000 uiPort = 3080