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

2009-05-02 Thread Neil Davies

Belka

Now that you've got some metrics to know when you have a successful  
design, start examining the trades.


Most systems have a turning point in their performance as load is  
increased, you need manage the traffic so that the offered load does  
not push the system over that point (or if it does, not for too long -  
it doesn't have to be perfect all the time, just suitably good - this  
is where stochastic come it, another story).


What you are doing here is trading efficient use of the infrastructure  
(e.g. you are not going to try and run the servers close to 100%) for  
responsive behaviour.


This is one of the reasons why people create multi-levelled web manage  
architectures - you could think of the design as having an initial  
stage that can analyse and identify the traffic an characterise it -  
ideally it should be able to cope with line rate or at least a known  
upper bound (which the load balancer in front knows and can be  
configured for), it can then pass the real traffic on for processing.


This all comes down to creating back pressure: typically by mediating  
between producer and consumer with a finite queue - then configuring  
that queue to have the right length so that the back pressure is felt  
at an appropriate point, too long and the experienced delay is too  
large, too short and you are changing modes of behaviour too quickly -  
again it that stochastics/queueing theory stuff.


Avoiding starvation is easy, FIFO service does that - but you'll find  
that's not enough you also need to bound the service time for certain  
requests people often think that 'priority' is the right answer but  
usually that is too naive. Resources are finite, giving one source of  
demand 'priority' means that the other sources loose out and that  
trade is highly non-linear and creates its own denial-of-service.


Neil

On 2 May 2009, at 06:27, Belka wrote:



Thanks, Niel. :)
You actually motivated me to determine/specify defense requirements  
- that

I should have done long before writing here.
Now I'm not experienced in DDoSs defending, so my reasoning here  
might be a

bit voulnerable. Few basic requirements:
1. Server has services that shouldn't be endangered by computational
resource starvation. That is why I use load balancing for SAR  
(Services
under Attack Risk). I even use 2 types of load controls: one per  
each SAR,

and the second - above all ARSes.
2. Even when under attack SAR should be able to serve. Of course, it's
effective input capability becomes much lower, but requirement here  
is to

provide possible maximum of effectiveness. That is why
2.1. identification of bad request should be fast, and
2.2. request processing should be fair (without starvation on  
acceptance

time).

After projecting this /\ specification on architecture plan, the  
need in
*good* tryReadChan is now less sharp. However, it still would be  
very useful

- I also have other applications for it.

The *good* tryReadChan would be atomic, immediate, and with  
determinate

result (of type Maybe)...
--
By the way, for

Actually, am I wrong thinking, that it can't be helped - and the
degradation
from cute concurency synchronization model of Chan is unavoidable?

I have an idea of such solution (without getting down to lower level
programming), - called it fishing: one should complicate the flow  
unit
(FlowUnit), that is being passed in the Channel. The FlowUnit  
diversifies to
real bizness data, and service data. That way I now may gain control  
over

blocking

But this solution is not simple and lightweight.  If anybody is  
interested,

I could describe the concept in more details.

Belka


Neil Davies-2 wrote:


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




--
View this message in context: 
http://www.nabble.com/-tryReadAdvChan-%3A%3A-AdvChan-a--%3E-IO-%28Maybe-a%29--problems-tp23328237p23343213.html
Sent from the Haskell - Haskell-Cafe mailing list archive at  
Nabble.com.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-05-01 Thread Neil Davies

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 

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

2009-05-01 Thread Belka

Thanks, Niel. :)
You actually motivated me to determine/specify defense requirements - that
I should have done long before writing here. 
Now I'm not experienced in DDoSs defending, so my reasoning here might be a
bit voulnerable. Few basic requirements:
1. Server has services that shouldn't be endangered by computational
resource starvation. That is why I use load balancing for SAR (Services
under Attack Risk). I even use 2 types of load controls: one per each SAR,
and the second - above all ARSes.
2. Even when under attack SAR should be able to serve. Of course, it's
effective input capability becomes much lower, but requirement here is to
provide possible maximum of effectiveness. That is why 
2.1. identification of bad request should be fast, and 
2.2. request processing should be fair (without starvation on acceptance
time).

After projecting this /\ specification on architecture plan, the need in
*good* tryReadChan is now less sharp. However, it still would be very useful
- I also have other applications for it.

The *good* tryReadChan would be atomic, immediate, and with determinate
result (of type Maybe)... 
--
By the way, for
 Actually, am I wrong thinking, that it can't be helped - and the
 degradation
 from cute concurency synchronization model of Chan is unavoidable? 
I have an idea of such solution (without getting down to lower level
programming), - called it fishing: one should complicate the flow unit
(FlowUnit), that is being passed in the Channel. The FlowUnit diversifies to
real bizness data, and service data. That way I now may gain control over
blocking

But this solution is not simple and lightweight.  If anybody is interested,
I could describe the concept in more details.

Belka


Neil Davies-2 wrote:
 
 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
 
 

-- 
View this message in context: 
http://www.nabble.com/-tryReadAdvChan-%3A%3A-AdvChan-a--%3E-IO-%28Maybe-a%29--problems-tp23328237p23343213.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-04-30 Thread Belka

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@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe