[Haskell-cafe] [tryReadAdvChan :: AdvChan a -> IO (Maybe a)] problems

Neil Davies semanticphilosopher at googlemail.com
Fri May 1 03:42:10 EDT 2009


Belka

You've described what you don't want - what do you want?

Given that the fundamental premise of a DDoS attack is to saturate  
resources
so that legitimate activity is curtailed - ultimately the only  
response has to be to
discard load, preferably not the legitimate load (and therein lies the
nub of the problem).

What are you trying to achieve here - a guarantee of progress for the  
system?
a guarantee of a fairness property? (e.g. some legitimate traffic will  
get
processed) or, given that the DDoS load can be identified given some  
initial
computation, guarantee to progress legitimate load up to some level of  
DDoS
attack?

Neil


On 1 May 2009, at 05:09, Belka wrote:

>
> Hi!
>
> I need this function with requirement of heavy reads, *possibly  
> under DDoS
> attack*.
> Was trying to write such function, but discovered some serious  
> problems of
> ** possible racings,
> ** possible starvations
> ** unbalance: readAdvChan users may get better service than ones of
> tryReadAdvChan
> These are totally unacceptible for my case of DDoS risk.
>
> Actually, am I wrong thinking, that it can't be helped - and the  
> degradation
> from cute concurency synchronization model of Chan is unavoidable?
>
> My (untested) code:
> -------------------------------------------
> -------------------------------------------
> module AdvChan ( AdvChan
>               , newAdvChan
>               , readAdvChan
>               , writeAdvChan
>               , writeList2AdvChan
>               , advChan2StrictList
>               , withResourceFromAdvChan
>               , tryReadAdvChan
>               , isEmptyAdvChan
>               ) where
>
> import Control.Concurrent.Chan
> import Control.Concurrent.MVar
>
> data AdvChan a = AdvChan {
>        acInst    :: MVar Chan a
>      , acWrite   :: a -> IO ()
>      , acIsEmpty :: IO Bool
> }
>
> newAdvChan :: IO AdvChan a
> newAdvChan = do ch    <- newChan
>                mv_ch <- newMVar ch
>                return AdvChan {
>                         acInst    = mv_ch
>                       , acWrite   = writeChan ch
>                       , acIsEmpty = isEmptyChan ch
>                       }
>
> readAdvChan :: AdvChan a -> IO a
> readAdvChan ach = modifyMVar (acInst ach)
>                             (\ ch -> do a <- readChan ch
>                                         return (ch, a)
>                             )
>
> writeAdvChan :: AdvChan a -> a -> IO ()
> writeAdvChan = acWrite
>
> writeList2AdvChan :: AdvChan a -> [a] -> IO ()
> writeList2AdvChan ach    [] = return ()
> writeList2AdvChan ach (h:t) = writeAdvChan ach h >>  
> writeList2AdvChan ach t
>
> advChan2StrictList :: AdvChan a -> IO [a]
> advChan2StrictList ach = modifyMVar (acInst ach)
>                                    (\ ch -> let readLoop = do emp <-
> isEmptyChan ch
>                                                               case  
> emp of
>                                                                    
> True  ->
> return []
>                                                                    
> False ->
> do _head <- readChan ch
>
> _rest <- readLoop
>
> return (_head : _rest)
>                                              in liftTuple (return ch,
> readLoop)
>                                    )
>
> withResourceFromAdvChan :: AdvChan a -> (\ a -> IO (a, b)) -> IO b
> withResourceFromAdvChan ach f = do res <- readAdvChan ach
>                                   (res_processed, result) <- f res
>                                   writeAdvChan ach res_processed
>                                   return result
>
> isEmptyAdvChan :: AdvChan a -> IO Bool
> isEmptyAdvChan = acIsEmpty
>
> microDelta = 50
>
> tryReadAdvChan :: AdvChan a -> IO (Maybe a)
> tryReadAdvChan ach = emp2Maybeness $ do mb_inst <- tryTakeMVar  
> (acInst ach)
>                                        case mb_inst of
>                                            Nothing   -> emp2Maybeness
> (threadDelay microDelta >> tryReadAdvChan ach)
>                                            Just chan -> do emp <-
> isEmptyChan ch
>                                                            result <-  
> case
> emp of
>
> True  -> return Nothing
>
> False -> Just `liftM` readChan ch
>                                                            putMVar  
> (acInst
> ach) chan
>                                                            return  
> result
>      where emp2Maybeness f = do emp <- isEmptyAdvChan ach
>                                 case emp of
>                                     True  -> return Nothing
>                                     False -> f
>
> -------------------------------------------
> -------------------------------------------
>
> Later after writing my own code, and understanding the problem I  
> checked
> Hackage. Found "synchronous-channels" package there
> (http://hackage.haskell.org/cgi-bin/hackage-scripts/package/synchronous-channels 
> ),
> but it isn't any further in solving my the unbalacedness problems.
>
> Any suggestions on the fresh matter are welcome.
> Belka.
> -- 
> View this message in context: http://www.nabble.com/-tryReadAdvChan-%3A%3A-AdvChan-a--%3E-IO-%28Maybe-a%29--problems-tp23328237p23328237.html
> Sent from the Haskell - Haskell-Cafe mailing list archive at  
> Nabble.com.
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe



More information about the Haskell-Cafe mailing list