[Haskell-cafe] Using tiny (atomic) mutables between multiple threads

2009-09-13 Thread Belka

Hello, Haskell Cafe!

I used an MVar to signalize to many threads, when it's time to finish their
business (I called it a LoopBreaker). Recently I realized, that it might be
too expensive (to use MVar) for cases when threads are many and all of them
read my LoopBreaker intensively. This assumption appeared in a case, where I
widely (in many threads) used my stopableThreadDelay, which checks
LoopBreaker every d = 100 milliseconds.

So I decided that I don't really need all the great features, that MVar
provides, and that a simpler memory usage concept might be applied here. In
a most (machinely) reduced view, all I need is a mutable byte. It would be
thread safe, since reading and writing are atomic operations. I then wrote a
simple experimental module (my first experience with Ptr in Haskell):
-
import Control.Monad
import Foreign.Marshal.Utils
import Foreign.Ptr
import Foreign.Storable

newtype MyVar a = MyVar { mvPtr :: Ptr a }

newMyVar :: Storable a = a - IO (MyVar a)
newMyVar val = MyVar `liftM` new val

readMyVar :: Storable a = (MyVar a) - IO a
readMyVar val = peek $ mvPtr val

writeMyVar :: Storable a = (MyVar a) - a - IO ()
writeMyVar var val = poke (mvPtr var) val
-

Now, please, help me to answer few questions about all it:
1. Might readMVar really be computationally expensive under heavy load,
(with all it's wonderful blocking features)? How much (approximately) more
expensive, comparing to a assembler's mov?
2. Are the above readMyVar and writeMyVar really atomic? Or are they atomic
only if I apply them to MyVar Word8 type?
3. Are the above readMyVar and writeMyVar safe against asynchronous
exceptions? Or again, only if I use MyVar Word8 type?

Belka
-- 
View this message in context: 
http://www.nabble.com/Using-tiny-%28atomic%29-mutables-between-multiple-threads-tp25420972p25420972.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


Re: [Haskell-cafe] Using tiny (atomic) mutables between multiple threads

2009-09-13 Thread Belka

Thank you, Bulat, for both your suggestions!

1. Since Haskell uses 1 byte for Bool (I confidently guess) and it's safe,
it would also be safe to use IORef Word8. Moreover, I found 
http://hackage.haskell.org/packages/archive/ArrayRef/0.1.3.1/doc/html/Data-Ref-Unboxed.html#v%3AmodifyIOURef
your module  and  http://www.haskell.org/haskellwiki/Library/ArrayRef the
corresponding article in HaskellWiki , so I plan to use IOURef Word8. I
wonder, however, what's the difference between Foreign.Ptr Word8 and
IORef Word8 (or IOURef Word8)?

2. As for architecture, I'm not sure that understood the whole suggestion,
but got inspired for new ideas for sure! :) 
My thread's iterations mostly are to acquire resource from load-balancers'
chans, and then to react on outer world state changes - networking and DB. I
put all the blocking operations to be stoppable by LoopBreaker. There's no
real need in job production/execution separation (in most cases) for now (I
guess my architecture is not yet mature enough to consist of generalized
workers and small business-concept-specific initiative sources; my threads
still are very specific to what they are meant to), but I am in need of good
resources production/utilization separation. 
Now in a better architecture I could exchange [stopableThreadDelays between
iterations of threads] on [timely sending the LoopBreaker through Chans
alone or together with resources (like network handle or the load balancer's
permission)]... This way I would definitely minimize some repeating patterns
in code, minimize load on LoopBreaker itself, centralize my timing and
configuration application management and simplify some resource management
processes (like acquiring network handle, when it's required).
Added in a ToDo list for next version!.. =)

Thanks again! 
Belka
-- 
View this message in context: 
http://www.nabble.com/Using-tiny-%28atomic%29-mutables-between-multiple-threads-tp25420972p25430039.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


Re: [Haskell-cafe] Seeking for an extention (functional incapsulation)

2009-08-07 Thread Belka

 Exponentially? Now I'm missing something...
I meant: in as-is version you have 3 declarations (data, sdtField2 :: ...,
sdtField2 = ...), but in a proposed one - only one, with subdeclarations. My
perception is more oriented on that compositional criterion, than calculates
char counts. Besides, syntactically proposed version sticks together
entities that are very closely related.
-- 
View this message in context: 
http://www.nabble.com/Seeking-for-an-extention-%28functional-incapsulation%29-tp24856249p24861049.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


Re: [Haskell-cafe] Seeking for an extention (functional incapsulation)

2009-08-07 Thread Belka



Belka wrote:
 
 Exponentially? Now I'm missing something...
 I meant: in as-is version you have 3 declarations (data, sdtField2 :: ...,
 sdtField2 = ...), but in a proposed one - only one, with subdeclarations.
 My perception is more oriented on that compositional criterion, than
 calculates char counts. Besides, syntactically proposed version sticks
 together entities that are very closely related.
 

I guess, I was too fast calling it (growth of code units with LOC in as-is
version against proposed one) exponential. :)
It is not. 
Proportional. 

But that's not that important.

-- 
View this message in context: 
http://www.nabble.com/Seeking-for-an-extention-%28functional-incapsulation%29-tp24856249p24861154.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] Seeking for an extention (functional incapsulation)

2009-08-06 Thread Belka

Hello, cafe visitors! :)

This is a double topic:
1. Can't find any good informative resource with descriptions of Haskell
extensions. Could anybody please share good one if it exists?
The only good one I found:
http://hackage.haskell.org/trac/haskell-prime/wiki/HaskellExtensions
But it's a bit too old and not that full... 
I undestand, that Haskell is kind of boiling language, in a sense of being
neverending experiment. It develops all the time, extensions show up and
drop out. So it's not that easy to support community with a fresh
information about them. But on the other side, the property (of being
boiling language) makes such information really important for community
members... I think. :)

2. Consider situation:
---
data SomeDataType = SomeDataType { sdtField1 :: SDT_Field1Type, sdtField2 ::
SDT_Field2Type}
sdtField3 :: SomeDataType - SDT_Field3Type
sdtField3 sdt = f (sdtField1 sdt) (sdtField2 sdt)
---
I induced recently, that it would be very comfortable if I could perform in
a way like this:
---
data SomeDataType = SomeDataType { sdtField1 :: SDT_Field1Type, sdtField2 ::
SDT_Field2Type, sdtField3 :: SDT_Field2Type, sdtField3 = f sdtField1
sdtField2}
---
The situation is not that rare, when dealing with nonprimitive data
constructions. Moreover would be really comfortable to reduce
---
data SomeDataType = SomeDataType_111 { sdtField1 :: SDT_Field1Type,
sdtField2 :: SDT_Field2Type} | SomeDataType_222 { sdtField1 ::
SDT_Field1Type, sdtField2 :: SDT_Field2Type, sdtField5 :: SDT_Field5Type}

sdtField3 :: SomeDataType - SDT_Field3Type
sdtField3 sdt = case sdt of {SomeDataType_111 - f (sdtField1 sdt)
(sdtField2 sdt) ; SomeDataType_222 - g (sdtField1 sdt) (sdtField2 sdt)
(sdtField5 sdt)}

\/ \/ \/ \/ \/ \/ \/ \/ \/ \/

data SomeDataType = SomeDataType_111 { sdtField1 :: SDT_Field1Type,
sdtField2 :: SDT_Field2Type, sdtField3 :: SDT_Field3Type, sdtField3 = f
sdtField1 sdtField2} | SomeDataType_222 { sdtField1 :: SDT_Field1Type,
sdtField2 :: SDT_Field2Type, sdtField5 :: SDT_Field5Type, sdtField3 ::
SDT_Field3Type, sdtField3 = g sdtField1 sdtField2 sdtField5}
---

Usable mechanics for realization would be:
1. Funtion similar to Data.Function.on (example: (*) `on` f = \x y - f x *
f y), but opposite - I called it under. 
t `under` f = \x y - (x f) `t` (y f)
2. currying and uncurrying

Is there any such extension?

Belka
-- 
View this message in context: 
http://www.nabble.com/Seeking-for-an-extention-%28functional-incapsulation%29-tp24856249p24856249.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


Re: [Haskell-cafe] Seeking for an extention (functional incapsulation)

2009-08-06 Thread Belka

Thank you, for your reply, Dan! :)

 You don't really need this inline in the record syntax, do you?
In fact, that was the point. To enclose direct functional dependants into
the record declaration. To achieve better pithiness - it's valuable, and the
value grows exponentially with LOC (lines of code) count. :)

 sdtField3 sdt = f $ sdtField1 * sdtField2
Doesn't look much better than my under function (t `under` f = \x y - (x
f) `t` (y f)). What did I miss?
I believe, there are good reasons to use Control.Applicative for lots
purposes, but unfortunately, yet haven't had time to try it in my practice.

Belka
-- 
View this message in context: 
http://www.nabble.com/Seeking-for-an-extention-%28functional-incapsulation%29-tp24856249p24856983.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] typeclasses comprehension problems: situation classes?

2009-05-16 Thread Belka

Hello, cafe visitors!

I'm trying to learn Haskell typeclasses, - about how to use them, - but
can't handle some conceptiual problems, which confuses me a lot. I took one
real problem (ErrorInfo gragual gathering), to tackle it in my studies: I
have a class of situations: there is an object, and it gets cumulatively
filled (or updated) with content. The code is in the end - it consists of 3
versions:
1. My first try. Fast written, based on intuitive understanding. Failed.
2. The second try - exploring an open world assumption. I hoped this would
set me on the right path. Failure.
3. Surrendered to compiler - statisfied all it's requirements. This code
looks absurd to me: parameter-never-to-be-used, unwanted-defaults. Compiler
accepted this one though.

Problems: 
1. How to define *fillerRole* correctly, so that it depends on the
type-value of src_t?
2. How to define *initFillable* correctly, so that it depends only on the
type-value filled_t, which is specified by the context of evaluation?
3. What are my misconcepts in the use of Haskell typeclasses here? 
4. Maybe I should distinguish *situation class* (as this one), as something
unavailable in Haskell? This assumption is the last one to make... I'd
rather belive, that there is something I'm not aware of (for a considerably
long time already) in Haskell. A lack of some programming technique

Please, Help!

Regards, 
Belka

==TRY=1===DOESN'T=COMPILE==

{-# LANGUAGE MultiParamTypeClasses  #-}

class FillsConsideringRoles src_t filled_t role_t where
 initFillable :: filled_t
 fillerRole   :: role_t
 fill :: src_t - filled_t - filled_t



data Role = Role1 | Role2 deriving (Show)
data FillableObject = FillableObject 
{ foData1 :: Maybe (Int, Role)
, foData2 :: Maybe (Int, Role)
} deriving (Show)

newEmptyFillableObject :: FillableObject
newEmptyFillableObject = FillableObject Nothing Nothing

data Constructor1 = Constructor1 Int
data Constructor2 = Constructor2 Int

instance FillsConsideringRoles Constructor1 FillableObject Role where
 initFillable = newEmptyFillableObject
 fillerRole = Role1
 fill c fo = let (Constructor1 i) = c in fo { foData1 = Just (i,
fillerRole) }

instance FillsConsideringRoles Constructor2 FillableObject Role where
 initFillable = newEmptyFillableObject
 fillerRole = Role2
 fill c fo = let (Constructor2 i) = c in fo { foData2 = Just (i,
fillerRole) }

main = putStrLn $ show $ fill c2 $ fill c1 initFillable
   where
  c1 = Constructor1 76
  c2 = Constructor2 43

==TRY=1==[END]===

==TRY=2===DOESN'T=COMPILE
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverlappingInstances #-}

class FillsConsideringRoles src_t filled_t role_t where
 initFillable :: filled_t
 fillerRole   :: role_t
 fill :: src_t - filled_t - filled_t

--

data Role = DefaultRole | Role1 | Role2 deriving (Show)
data FillableObject = FillableObject 
{ foData1 :: Maybe (Int, Role)
, foData2 :: Maybe (Int, Role)
} deriving (Show)

newEmptyFillableObject :: FillableObject
newEmptyFillableObject = FillableObject Nothing Nothing

data Constructor1 = Constructor1 Int
data Constructor2 = Constructor2 Int

instance FillsConsideringRoles filler_t filled_t Role where
 fillerRole = DefaultRole
instance FillsConsideringRoles Constructor2 filled_t Role where
 fillerRole = Role2
instance FillsConsideringRoles Constructor1 filled_t Role where
 fillerRole = Role1

instance FillsConsideringRoles filler_t FillableObject role_t where
 initFillable = newEmptyFillableObject

instance FillsConsideringRoles Constructor1 FillableObject Role where
 fill c fo = let (Constructor1 i) = c in fo { foData1 = Just (i,
fillerRole) }

instance FillsConsideringRoles Constructor2 FillableObject Role where
 fill c fo = let (Constructor2 i) = c in fo { foData2 = Just (i,
fillerRole) }

main = putStrLn $ show $ fill c2 $ fill c1 initFillable
   where
  c1 = Constructor1 76
  c2 = Constructor2 43
==TRY=2==[END]===

==TRY=3===WORKS=
{-# LANGUAGE MultiParamTypeClasses  #-}

class FillsConsideringRoles src_t filled_t role_t where
 initFillable :: ((),src_t, role_t) - filled_t
 fillerRole   :: ((),src_t, filled_t) - role_t
 fill :: ((),role_t) - src_t - filled_t - filled_t



data Role = DefaultRole | Role1 | Role2 deriving (Show)
data FillableObject = FillableObject

[Haskell-cafe] Classes: functional dependency (type - value)

2009-05-10 Thread Belka

Hello, communion people!

I seek for your advice in a matter, where it's really hard for me to
determine a good programming style.
Here's the problem. I'm generalizing multiple authorization procedures to
one, using class definition. (if of any interest, the code is in the end.) 
The problem essense is folowing:

data SomeRole = Role1 | Role2 | Role3

class SomeClass a b c | a - b, c where
  f1 :: ...
  f2 :: ...
  ...
  fn :: ...
  role :: SomeRole -- -- here is the problem

I want to have a fuctional dependency from a type a on a value of *role*,
so that I could easily inspect the *role* from within any other class
members.
Is it possible? Or do I rougly violate some style traditions?

Some real code using wished feature:
---
data AuthentificationPurpose = JustValidateInput | JustGenerateForOutput |
ValidateInputAndGenerateForOutput
type AuthSucceded = Bool

class AuthentificationStructure t_env t_realInput t_assumption t_keySet |
t_realInput - t_assumptionInput, t_keySet where
authentificationPurpose :: AuthentificationPurpose
makeAssumption  :: t_env - t_realInput - IO (Either ErrorMessage
t_assumption)
makeFinalKeySet :: (t_realInput, t_assumption) - t_keySet
validateRealKeySet_with_Assumed :: t_realInput - t_keySet - Maybe
ErrorMessage
tryLogTheValidKey :: t_env - (t_realInput, t_assumption)  
- IO (Maybe ErrorMessage)
tryLogTheAuthTry  :: t_env - (t_realInput, t_assumption,
AuthSucceded) - IO (Maybe ErrorMessage)

authentificate :: AuthentificationStructure t_env t_realInput
t_assumptionInput t_keySet = t_env - t_businessInput - IO (Either
ErrorMessage (t_assumption, t_keySet))
authentificate env realInput = do err_or_assumption - makeAssumption env
realInput
  case err_or_assumption of
  Left err_msg - return $ Left Error!
Assumption maker failed. Lower level error message:  ++ err_msg
  Just assumption - do
  key_set - makeFinalKeySet
(realInput, assumption)
  err_or_keyset1 - case
authentificationPurpose of
   
JustGenerateForOutput - return $ Right key_set
   
JustValidateInput - do
   
mb_failure - validateRealKeySet_with_Assumed t_realInput key_set 
   
case mb_failure of 

   
Just err_msg - return $ Left Error! Invalid set of auth keys. Lower level
error message:  ++ err_msg

   
Nothing - return $ Right key_set
   
ValidateInputAndGenerateForOutput
  err_or_keyset2 - case
err_or_keyset1 of
Left 
err_msg - return err_or_keyset1
   
Right key_set - do

 
mb_failure - tryLogTheValidKey env (realInput, assumption)

 
case mb_failure of 

 
Just err_msg - return $ Left Error! Could not log valid key. Lower level
error message:  ++ err_msg

 
Nothing  - return err_or_keyset1
  mb_failure -
tryLogTheAuthTry env (realInput, assumption, isRight err_or_keyset2)
  case mb_failure of
  Just err_msg1 - case
err_or_keyset2 of
 
Left err_msg2 - return $ Left (1.  ++ err_msg2 ++ \n2.  ++ err_msg1)
 
Right   _ - return $ Left err_msg1
  Nothing   - case
err_or_keyset2 of
 
Left  err_msg - return $ Left err_msg
 
Right key_set - return $ Right (assumption, key_set)
-

Best regards, Belka
-- 
View this message in context: 
http://www.nabble.com

Re: [Haskell-cafe] using haskell for a project

2009-05-03 Thread Belka

Welcome to Haskell! =)

 But now I don't know how to dynamically add new spells (new spells can be
 created in my gameplay). Since I can't assign a new value to the `spells'
 variable (Data.Map.insert returns a new map), I just don't know where to
 go.

Do distinguish *pure function* concept and *action with side effects*
concept. 
The default in FP (Funct. Progr.) paradigm usualy is *pure function*, if
*action with side effects* is avoidable. Pure functions deal with immutable
memory objects. So in your case, whenever you add a new spell, you get a
new character (since your chacter's essence is a spell list). That way
after calculating *addNewSpell* you will have 2 versions of character: a new
one (with spells list bigger), an the original one. Since old one usualy
drop out of the scope (while program evaluation progresses) it gets *garbage
collected* (note: garbage collection showed up in FP already in 1960s).

addNewSpell :: Character - Spell - Character
addNewSpell char_old_version spell_to_add = ... 

main = let char_new_version = addNewSpell char_old_version new_spell in
putStrLn $ show char_new_version
  where char_old_version = Charcter {...}
   new_spell = Spell {  }

Have luck, with the brain rewriting! =) 
Belka
-- 
View this message in context: 
http://www.nabble.com/using-haskell-for-a-project-tp23348425p23352598.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


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


Re: [Haskell-cafe] controlling timeout for Network.Socket.connect - how?

2009-02-26 Thread Belka

Thanks, Manlio!

What system?
ArchLinux (2.6.27)

Is the timeout the same with a plain C program?
Didn't try yet... ^__^

 I know that controlling timeout is somehow connected to select(2) 
Yes.
The only working method is to set the socket to non blocking mode, and 
use select (or poll/epoll/kqueue).

Thanks, now I'm confident, that am on the right way! ^__^
I wonder, if *select* really blocks the whole process... or blocks just the
green thread, that called it?.. 
It doesn't depend from being safe/unsafe FFI-ed, does it?

Belka
-- 
View this message in context: 
http://www.nabble.com/controlling-timeout-for-Network.Socket.connect---how--tp22139581p22235312.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


Re: [Haskell-cafe] controlling timeout for Network.Socket.connect - how?

2009-02-26 Thread Belka

Thanks, Manlio!

What system?
A r c h Linux (2.6.27)

Is the timeout the same with a plain C program?
Didn't try yet... ^__^

 I know that controlling timeout is somehow connected to select(2)
Yes.
The only working method is to set the socket to non blocking mode, and
use select (or poll/epoll/kqueue).

Thanks, now I'm confident, that am on the right way! ^__^
I wonder, if *select* really blocks the whole process... or blocks just the
green thread, that called it?..
It doesn't depend from being safe/unsafe FFI-ed, does it?

Belka
-- 
View this message in context: 
http://www.nabble.com/controlling-timeout-for-Network.Socket.connect---how--tp22139581p22236279.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


Re: [Haskell-cafe] controlling timeout for Network.Socket.connect - how?

2009-02-24 Thread Belka

It's hard to belive, that nobody ever tackled/solved the subj. problem. I
still can delay a bit solving it, in hope somebody would share experience. 

Regards,
Belka


Belka wrote:
 
 Hello, communion people!
 
 I have a problem and ask for an advice. 
 I'm dealing with sockets on *Linux* platform (Network.Socket). The problem
 is that I can't fully control timeout for (connect :: Socket - SockAddr
 - IO ()) operation. 
 On my system the timeout is - 3 seconds - I want to be able to change that
 in run-time. Well I managed to find out how to make it LESS THAN 3 seconds
 - using System.Timeout. But how to make timeout bigger (for example 9
 seconds) is a mystery.
 (Notice: in order to achieve 9 seconds timeout - just repeating *connect*
 3 times won't be effective for long-slow-way-connections. So it's not a
 solution.)
 
 The source code of Network.Socket.connect, taken from darcs:
 -
 -- Connecting a socket
 --
 -- Make a connection to an already opened socket on a given machine
 -- and port.  assumes that we have already called createSocket,
 -- otherwise it will fail.
 --
 -- This is the dual to $bindSocket$.  The {\em server} process will
 -- usually bind to a port number, the {\em client} will then connect
 -- to the same port number.  Port numbers of user applications are
 -- normally agreed in advance, otherwise we must rely on some meta
 -- protocol for telling the other side what port number we have been
 -- allocated.
 
 connect :: Socket -- Unconnected Socket
   - SockAddr -- Socket address stuff
   - IO ()
 
 connect sock@(MkSocket s _family _stype _protocol socketStatus) addr = do
  modifyMVar_ socketStatus $ \currentStatus - do
  if currentStatus /= NotConnected 
   then
ioError (userError (connect: can't peform connect on socket in status
  ++
  show currentStatus))
   else do
withSockAddr addr $ \p_addr sz - do
 
let  connectLoop = do
  r - c_connect s p_addr (fromIntegral sz)
  if r == -1
  then do 
  rc - c_getLastError
  case rc of
10093 - do -- WSANOTINITIALISED
  withSocketsDo (return ())
  r - c_connect s p_addr (fromIntegral sz)
  if r == -1
   then (c_getLastError = throwSocketError connect)
   else return r
_ - throwSocketError connect rc
  else return r
 
   connectBlocked = do 
 #if !defined(__HUGS__)
  threadWaitWrite (fromIntegral s)
 #endif
  err - getSocketOption sock SoError
  if (err == 0)
   then return 0
   else do ioError (errnoToIOError connect 
   (Errno (fromIntegral err))
   Nothing Nothing)
 
connectLoop
return Connected
 
 -
 I know that controlling timeout is somehow connected to select(2) (I'm
 currently investigating this matter...), but it's not in the Network or
 Network.Socket libs (but in the libs that they FFI with). 
 Hope I won't have to rewrite these low-level functions __
 Could anybody, please share some experience on how to adjust timeout for
 *connect*? 
 
 Thanks in advance,
 Best regards,
 Belka
 

-- 
View this message in context: 
http://www.nabble.com/controlling-timeout-for-Network.Socket.connect---how--tp22139581p22181071.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] controlling timeout for Network.Socket.connect - how?

2009-02-21 Thread Belka

Hello, communion people!

I have a problem and ask for an advice. 
I'm dealing with sockets on *Linux* platform (Network.Socket). The problem
is that I can't fully control timeout for (connect :: Socket - SockAddr -
IO ()) operation. 
On my system the timeout is - 3 seconds - I want to be able to change that
in run-time. Well I managed to find out how to make it LESS THAN 3 seconds -
using System.Timeout. But how to make timeout bigger (for example 9 seconds)
is a mystery.
(Notice: in order to achieve 9 seconds timeout - just repeating *connect* 3
times won't be effective for long-slow-way-connections. So it's not a
solution.)

The source code of Network.Socket.connect, taken from darcs:
-
-- Connecting a socket
--
-- Make a connection to an already opened socket on a given machine
-- and port.  assumes that we have already called createSocket,
-- otherwise it will fail.
--
-- This is the dual to $bindSocket$.  The {\em server} process will
-- usually bind to a port number, the {\em client} will then connect
-- to the same port number.  Port numbers of user applications are
-- normally agreed in advance, otherwise we must rely on some meta
-- protocol for telling the other side what port number we have been
-- allocated.

connect :: Socket   -- Unconnected Socket
- SockAddr -- Socket address stuff
- IO ()

connect sock@(MkSocket s _family _stype _protocol socketStatus) addr = do
 modifyMVar_ socketStatus $ \currentStatus - do
 if currentStatus /= NotConnected 
  then
   ioError (userError (connect: can't peform connect on socket in status 
++
 show currentStatus))
  else do
   withSockAddr addr $ \p_addr sz - do

   let  connectLoop = do
   r - c_connect s p_addr (fromIntegral sz)
   if r == -1
   then do 
   rc - c_getLastError
   case rc of
 10093 - do -- WSANOTINITIALISED
   withSocketsDo (return ())
   r - c_connect s p_addr (fromIntegral sz)
   if r == -1
then (c_getLastError = throwSocketError connect)
else return r
 _ - throwSocketError connect rc
   else return r

connectBlocked = do 
#if !defined(__HUGS__)
   threadWaitWrite (fromIntegral s)
#endif
   err - getSocketOption sock SoError
   if (err == 0)
then return 0
else do ioError (errnoToIOError connect 
(Errno (fromIntegral err))
Nothing Nothing)

   connectLoop
   return Connected

-
I know that controlling timeout is somehow connected to select(2) (I'm
currently investigating this matter...), but it's not in the Network or
Network.Socket libs (but in the libs that they FFI with). 
Hope I won't have to rewrite these low-level functions __
Could anybody, please share some experience on how to adjust timeout for
*connect*? 

Thanks in advance,
Best regards,
Belka
-- 
View this message in context: 
http://www.nabble.com/controlling-timeout-for-Network.Socket.connect---how--tp22139581p22139581.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] estimating the speed of operation

2009-02-18 Thread Belka

Hello, communion people!

I have a little problem and ask for an advice. I'm trying to estimate the
performance speed of one pure function, but get some strange results.
-
import qualified module Data.ByteString.Lazy.Char8 as L8
import module Data.Digest.Pure.MD5
import module System.IO.Unsafe
import module System.Time
import module System.Random
import module Data.Char

clockTime2Tuple (TOD sec pic) = (sec, pic)
getClockTimeTuple = getClockTime = (\ x - return $ clockTime2Tuple x)
subTimeTuples (s2,ps2) (s1,ps1) = let dps = ps2-ps1 in let (s,ps) =
(s2-s1-(if dps0 then 1 else 0), if dps0 then dps+(10^12) else dps) in (s,
(div) ps (10^6))

test_md5 test_input n = flip mapM test_input
( \ input_row - do
t1 - getClockTimeTuple
sequence_ (replicate n (return $ md5 input_row))
t2 - getClockTimeTuple 
dt - subTimeTuples t2 t1
return (dt)
)

test_list = 
[ pack Hello world!] ++ 
[L8.replicate 100 ':']
-
The results are (iterations_count, microseconds):
(1000,  [105,105]) (+/- 10)
(1, [1000,950]) (+/- 50)
(10, [9050,9000]) (+/- 50)
(100, [89200,89150]) (+/- 100)
-
I suspect following problems, which make the results non-objective:
1. I cant get out of laziness
2. I don't turn off GHC internal optimizers
So, perhaps, GHC evaluates the MD5 once, but cycles on something else?.. For
now I can only guess. Could anybody, please clarify and maybe suggest
configuration, which would allow objective speed estimation?

Thanks in advance,
Best regards,
Belka
-- 
View this message in context: 
http://www.nabble.com/estimating-the-speed-of-operation-tp22075843p22075843.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


Re: [Haskell-cafe] estimating the speed of operation

2009-02-18 Thread Belka

Thanks alot, Bulat!

New results are much better:
---
test_list =
[L8.pack Hello world!] ++
[L8.replicate 100 ':'] 
---
The results are (iterations_count, microseconds):
(1000,  [300 +/- 200 , 18400  +/- 100])
(1, [1030 +/- 10 , 19950 +/- 50 ])
(10, [9100 +/- 100 , 55000 +/- 15000])
(100, [89850 +/- 500 ,185000 +/- 500 ]) 

I also played a bit with bang patterns, to make input stricter, but this
gave the same result.
---
For the first test string time grow almost linearly, what can't be said
about the second string. I still wonder if (and how) GHC optimizes the
process.

Belka
-- 
View this message in context: 
http://www.nabble.com/estimating-the-speed-of-operation-tp22075843p22078560.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


Re: Re[Haskell-cafe] cursive referencing

2009-01-30 Thread Belka

Great thanks, Ryan and Yevgeny! 

1. For sumAA 10 $ f 1 2 and for sumAA 1000 $ f 1 2 - does the used
memory amounts differ? 
2. Does it create in memory only 2 data objects, or creates 10s and 1000s
and garbage collects unneeded?

--

Also consider
   fix (\p - (AA somedata1 $ snd p, BB somedata2 $ fst p))
and my mod (added some_very_expensive_f)
   fix (\p - (AA (some_very_expensive_f somedata1) $ snd p, BB
(some_very_expensive_f somedata2) $ fst p))

2. Does the sumAA evaluates this some_very_expensive_f every iteration of
recursion, or is it evaluated only once?

Belka 


Your definition with fix isn't lazy enough, so it goes into an
infinite loop.  You need to match lazily on the pair; here's a better
body for fix:

fix (\p - (AA somedata1 $ snd p, BB somedata2 $ fst p))

To prove that the structure really turns out cyclic, you can use
Debug.Trace:

import Debug.Trace (trace)
import Data.Function (fix)

data AA = AA Int BB deriving Show
data BB = BB Int AA deriving Show

f = \data1 data2 - fst $ fix $ \p -
(trace eval_aa $ AA data1 $ snd p,
  trace eval_bb $ BB data2 $ fst p)

sumAA 0 _ = 0
sumAA n (AA v bb) = trace sumAA (v + sumBB (n-1) bb)
sumBB 0 _ = 0
sumBB n (BB v aa) = trace sumBB (v + sumAA (n-1) aa)

main = print $ sumAA 10 $ f 1 2

*Main main
eval_aa
sumAA
eval_bb
sumBB
sumAA
sumBB
sumAA
sumBB
sumAA
sumBB
sumAA
sumBB
15
-- 
View this message in context: 
http://www.nabble.com/Recursive-referencing-tp21722002p21756221.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


Re: Re[Haskell-cafe] cursive referencing

2009-01-29 Thread Belka

Yes.
f somedata1 somedata2 = aa
  where aa = AA somedata1 bb
bb = BB somedata2 aa

Spasibo, Yevgeny!

Originally I was thinking theoretically about a single plain
lambda-expression, like 
(\ somedata1 somedata2 -
(\ aa bb - aa (bb aa))
  (\ b - AA somedata1 b)
  (\ a - BB somedata2 a) 
)   
But in the code aa (bb aa) last aa stays lacking an argument, of course,
if we don't consider 1st application aa ( as having a side effect on aa. 
And that's where separate and rule shows up it's power (speaking about
where and namespacing in general). =)

Belka
-- 
View this message in context: 
http://www.nabble.com/Recursive-referencing-tp21722002p21722503.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


Re[Haskell-cafe] cursive referencing

2009-01-28 Thread Belka

Hello! 
I'm puzzled, if in Haskell it's possible to create a (pure) data structure,
consisting of 2 substructures referencing each other: 
-
data AA = AA {
someData1 :: SomeData1
bb :: BB
}

data BB = BB { 
someData2 :: SomeData2
aa :: AA
} 

f :: SomeData1 - SomeData2 - AA
f somedata1 somedata2 = ??

-- Always True:
ghci f == aa $ bb f
True
-
Any ideas?

Belka
-- 
View this message in context: 
http://www.nabble.com/Recursive-referencing-tp21722002p21722002.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


Re: [Haskell-cafe] how to implement daemon start and stop directives?

2009-01-24 Thread Belka

If you want a normal daemon, you want to look at System.Posix.Process  
to create a proper daemon (forkProcess, createSession; don't forget to  
close stdOutput (and, errr, Haskell library types:  stdin and stderr  
are where?  not System.Posix.IO with stdOutput) and reopen them on / 
dev/null, at least if they're ttys as determined by  
System.Posix.Terminal.queryTerminal).  You also want to write out a  
pidfile (/var/run/programname.pid) for use by startproc / killproc,  
and you want to install a handler for sigTERM  
(System.Posix.Signals.installHandler) which sets the exit flag (TVar,  
MVar, IORef, Chan, take your pick).  Ideally you also catch sigHUP and  
reload your state.

Thanks for the guide, Brandon !!

By the way, I found a piece of code with function (daemonize :: IO () - IO
()) (http://sneakymustard.com/2008/12/11/haskell-daemons), which is close to
the subject. 

I guess now I'm ready to implement my own daemon! 
Thanks for your help, everyboby!! =)
-- 
View this message in context: 
http://www.nabble.com/how-to-implement-daemon-start-and-stop-directives--tp21598690p21647723.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


Re: [Haskell-cafe] how to implement daemon start and stop directives?

2009-01-22 Thread Belka

 You can abstract this pattern:
 
 -- runs its argument in an infinite loop, and returns an action that stops
 the loop
 daemon :: IO () - IO (IO ())
 daemon action = do
 stopvar - atomically $ newTVar False
 let run = do
   stop - atomically $ readTVar stopvar
   if stop then return () else (action  run)
 forkIO run
 return (atomically $ writeTVar stopvar True)
 
 TVars are overkill here, actually, an IORef would be just fine, I think.
 
 Luke

Thanks, Luke!

Why do you write return (atomically $ writeTVar stopvar True) in the end?

Actually, I'm more interested in technical details how to communicate from
shell with background process - how to send commands to it. Currently
looking into POSIX libraries hope to find answers there... 
Also, maybe a FIFO-pipe-file would solve my problem. Imagine writing a
command in it, while one of daemon's thread is locked-while-awaits for
anything to come out from the other side of the pipe...

Belka
-- 
View this message in context: 
http://www.nabble.com/how-to-implement-daemon-start-and-stop-directives--tp21598690p21599567.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] how to implement daemon start and stop directives?

2009-01-21 Thread Belka

Hi!

Could somebody please share some experience on how to implement daemon start
and stop directives. In theory I need something like this:
1. my_daemon start - starts my app with an infinite loop of serving
inside.
2. my_daemon stop - puts in some TVar a value signalizing, that stop is
given - infinite loop brakes.
3. ...it on Linux platform.

Thanks in advance!
-- 
View this message in context: 
http://www.nabble.com/how-to-implement-daemon-start-and-stop-directives--tp21598690p21598690.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] Connect to DBMS - what's the cost

2009-01-04 Thread Belka

Hello, community people!

Is anybody aware, what aproximately is the cost for the acquiring connection
to DB (and also disconnecting from it)? I guess that may differ from DBMS to
DBMS, so I mostly am interested in PostgreSQL case, but for other DBMS it's
also good to know. 

Actually, since all Haskell libraries, that provide interfaces to DBMS, use
foreign functions, - the question should be focused on commonly used C
libraries.

Thanks in advance!
-- 
View this message in context: 
http://www.nabble.com/Connect-to-DBMS---what%27s-the-cost-tp21275600p21275600.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] Haskell, successing crossplatform API standart: first feedback

2009-01-04 Thread Belka

Thanks everybody for your responses, they helped a lot. And sorry for my
misconcept on JSON. ;]

Sterling Clover, Nov 30, 2008:
These days, however, web services seem to be moving towards a RESTful  
model with a JSON layer and there are plenty of JSON libraries on  
hackage, which you could just throw over the fastCGI bindings.  
Alternately you could try JSON over one of the really lightweight  
haskell web servers, such as shed [2] or lucu [3]. If you go the  
atter route, I'd love to hear how it went.

So here is my first feedback. I hope that's something like an introduction
to my futher feedbacks.

1. I started with HAppS. But found it lacking some good definitions.
Moreover, I'm still a newbie and not yet confident with monads, so when I
accidently saw this: Author's Note: Due to my inexperience with Monads,
these explanations are probably lacking. Feel free to improve them. (HAppS
tutorial2, sect. 1.1), I felt myself standing on a risky ground, where the
risk is to get Monads wronger than wrong. So I decided to check Lucu and
return to HAppS later (when I'm invincible).

2. I loved Lucu, and feel respect to it's developer. The code is nice and
tidy, one can feel good style in it. Looks like Lucu author achieved great
technique in Haskell, knew, how to use Monads and laziness in full power.  
However I still didn't understand some aspects (simply becase of lacking
experience).
I sucessfully managed to write a helloworld which connected to DB and
provided simple WEB interface.

3. I also tried shed httpd, which is the most minimalistic WEB server. This
looks like the best start for a newbie, who isn't confident with monads yet.
I manager a small comparison of Lucu and Shed responce times - Lucu was 2
times faster for 1 simple query, which returned 5 rows from small DB.

Now I'm planning 
1. To try some modification of Lucu, so it has a DB connection in it's
environment and some basic triggering (providing conditioned actions after
WEB interaction process). 
2. Implement one simple project on it. 

Regards,
Belka
-- 
View this message in context: 
http://www.nabble.com/Haskell%2C-successing-crossplatform-API-standart-tp20742743p21280480.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] Haskell, successing crossplatform API standart

2008-11-29 Thread Belka

Hello!
 
(1) Is anybody aware of SOA approach being supported in Haskell? Found HAIFA
package (SOAP, WEB services), but it seems to be a RIP project (with it's
last updated in 2006) - trying to install it is a total mess (for me, a
newby).

(2) Please, perhaps experienced developers could suggest any better
crossplatform (crosslanguage) API standart supported in Haskell? For me the
main priority is orientation on being supported everywhere in far
future...

Thanks in advance
-- 
View this message in context: 
http://www.nabble.com/Haskell%2C-successing-crossplatform-API-standart-tp20742743p20742743.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] Could not find module ... which is hidden problem

2008-11-29 Thread Belka

Hello!

START--
$ sudo runghc Setup configure --user
Configuring HCL-1.2...

$ sudo runghc Setup build
Preprocessing library HCL-1.2...
Preprocessing executables for HCL-1.2...
Building HCL-1.2...

HCL.hs:302:7:
Could not find module `System.Random':
  it is a member of package random-1.0.0.1, which is hidden

$ sudo ghc-pkg expose random
Saving old package config file... done.
Writing new package config file... done.

$ sudo runghc Setup configure --user
Configuring HCL-1.2...

$ sudo runghc Setup build
Preprocessing library HCL-1.2...
Preprocessing executables for HCL-1.2...
Building HCL-1.2...

HCL.hs:302:7:
Could not find module `System.Random':
  it is a member of package random-1.0.0.1, which is hidden

-THE-END

Perhaps, i'm 1000th, who asks how to solve this. Sorry that didn't search
better, but it's really tiring for a newby. :-(
[ http://www.haskell.org/haskellwiki/Upgrading_packages/Updating_to_GHC_6.8
Here ] found something, which maybe called a gentle explaination of what's
going on. I have ghc ver: 6.8.2, base ver: 3.0.1.0.

So there are 2 questions of mine:
(1) Is there any centralized and well organized Haskell Knowledge Base,
where it would be much easier to find solutions for popular problems?
Anybody, please, your recommendations.
(2) As for the topic: the only option for me would be obtaining older GHC
(base?) - is that correct? So that require me reinstalling every Haskell
package I have installed so far?

Thanks in advance.
-- 
View this message in context: 
http://www.nabble.com/%22Could-not-find-module-...-which-is-hidden%22-problem-tp20742582p20742582.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


Re: [Haskell-cafe] What *not* to use Haskell for

2008-11-29 Thread Belka

(1) Function as a system of N concurrent inputs and 1 output is easy essence.
How about function as N concurrent inputs and M concurrent outputs? I think
it's not native to lambda calculus. So system's programming (if we ever
had such paradigm) would solve this issue, while criticizing all FP.

(2) For me, I hope this category (What *not* to use Haskell for) won't
include SOA. That's what I'am currently trying to decide.

(3) I think if CPU's would be lambda-based, not imperative, and paradigm be
stronger, most of the why *not* to use Haskell's would be solved, and
imperative would be in opposition instead.. with it's enthusiasts. =) They
would have good answers for your question.
-- 
View this message in context: 
http://www.nabble.com/What-*not*-to-use-Haskell-for-tp20436980p20755239.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