[Haskell-beginners] Help me with designing my daemon, please.
Michael Litchard
michael at schmong.org
Thu Sep 8 05:15:55 CEST 2011
I think I've come up with something that's more simple and makes more
sense. I will probably want to run it by the list for a sanity check.
I'll update this thread when it's ready to display.
On Wed, Sep 7, 2011 at 3:21 PM, Michael Litchard <michael at schmong.org> wrote:
> I need to provide more detail. Keep in mind that what I want to do,
> and the way I'm doing it may not fit at all. This code is using Chans
> and MVars, but could be using TChans and TVars easily enough. I kept
> things the way they are to just express what I'm trying to do
>
>> data ServerModel = PRODUCT1
>> | PRODUCT2
>> | PRODUCT3
>> | PRODUCT4
>> | PRODUCT5
>> deriving Show
>
>> newtype ProcessStep = PStep (ServerModel -> FilePath -> IO ())
>
>> type Cookie = String
>
>> type ProcessState = MVar ([ProcessStep],ProcessConfig)
>
>> data ProcessConfig = PConfig { model :: ServerModel
>> , ipAddress :: String
>> , rootDirectory :: FilePath
>> , cookie :: Cookie
>> } deriving Show
>
>> preProcess :: ServerModel -> FilePath -> IO ()
>> preProcess sModel fPath = putStrLn ("preProcessing" ++ show sModel)
>
>> initiatedJob :: ServerModel -> FilePath -> IO ()
>> initiatedJob sModel fPath = putStrLn ("in progress" ++ show sModel)
>
>> makeChart :: ServerModel -> FilePath -> IO ()
>> makeChart sModel fPath = putStrLn ("chart making" ++ show sModel)
>
> main :: IO ()
> main = do
> pState <- make
> world <- newEmptyMVar :: IO (ProcessState)
> worldQueue <- newChan :: IO (Chan ProcessState)
> installHandler userDefinedSignal2 (Catch $ worldHandler world worldQueue) N
> othing
> installHandler userDefinedSignal1 (Catch $ emptyQueue worldQueue
> ) Nothing ---- This is for testing purposes. I just want to be able
> to empty the Chan and see if expected behavior holds
> installHandler nullSignal (Catch $ emptyMVar world ) Nothing
> ---- For testing as well, same reason as above.
> sequence_ $ repeat $ queueCheck
>
>
>> worldHandler :: ProcessState -> Chan ProcessState -> IO ()
>> worldHandler world worldQueue = do
>>
>> mvarState <- isEmptyMVar world
>> let tStep = PStep undefined
>> let tConfig = PConfig { model = undefined,
>> ipAddress = undefined,
>> rootDirectory = undefined,
>> cookie = undefined
>> }
>>
>> let tState = undefined
>> case (mvarState) of
>> True -> putMVar world tState
>> False -> growQueue
>> where growQueue = do
>> newWorld <- newMVar ([tStep], tConfig)
>> writeChan worldQueue newWorld
>
>
>
> On Wed, Sep 7, 2011 at 1:37 PM, David McBride <dmcbride at neondsl.com> wrote:
>> I'm imagining this:
>>
>> data TestInfo = {
>> testname :: String,
>> etc..
>> }
>> data TestResult = {
>> success :: Bool,
>> etc...
>> }
>>
>> data Test = Test (TestInfo -> IO ())
>> type Tests = [Test]
>>
>> main = do
>> let tests = [whatever] :: Tests
>> testchan <- newTChanIO :: IO (TChan TestInfo)
>> resultchan <- newTChanIO :: IO (TChan TestResult)
>> exceptionwhatever $ queuetest testchan
>> forkIO $ testThread (testchan,resultchan) tests
>> printTestResults resultChan
>>
>> queuetest chan = atomically $ writeTchan (TestInfo .....)
>>
>> testThread (testchan, resultchan) tests = forever $ do
>> newtest <- atomically $ readTChan testchan
>> results <- mapM tests newTest
>> atomically $ writeTChan resultchan results
>>
>> printTestResults chan = forever $ do
>> x <- atomically $ readTChan chan
>> print x
>>
>> Something like that perhaps?
>>
>>
>> On Wed, Sep 7, 2011 at 3:31 PM, Michael Litchard <michael at schmong.org> wrote:
>>> This is what I am trying to do.
>>> I have tests to run and manage. I'm only running one test at a time.
>>> When my daemon gets a signal, it will either prep a test and run it,
>>> or queue the request. After it runs the test, I want it to check the
>>> queue for other tests that may have been requested.
>>> This is my first expedition into this domain. I'm trying to collect
>>> MVars and putting tem in a TChan is the way that seemed right, but I'm
>>> not sure at all. This is my first guess.
>>> I thought I needed a forked thread for the eventuality that I get a
>>> signal while my transaction is being executed.
>>> Have I clarified or further obfuscated?
>>>
>>> On Wed, Sep 7, 2011 at 12:22 PM, David McBride <dmcbride at neondsl.com> wrote:
>>>> It sounds bizarre. Why pass around an mvar in tchan, when you could
>>>> just pass a maybe around and pattern match to see if it is Nothing or
>>>> not? Also, why have forkio and tchan at all if they are only going to
>>>> operate in sequence, one at a time?
>>>>
>>>> What exactly are you trying to do?
>>>>
>>>> On Wed, Sep 7, 2011 at 3:01 PM, Michael Litchard <michael at schmong.org> wrote:
>>>>> I have a daemon I need to build, and need to work out some design
>>>>> details I am having difficulty with. Here's what the design looks like
>>>>> right now
>>>>>
>>>>> When the daemon starts it creates an empty MVar and an empty TChan.
>>>>> Then it listens for a usrSIG1.
>>>>> when it gets one, it checks to see if the MVar is empty. If it is, it
>>>>> does some stuff to fill the MVar, which is then used to pass around
>>>>> state for a list of functions. These functions are always the same.
>>>>> After evaluating these functions, the TChan is checked. As long as the
>>>>> TChan has something in it,
>>>>> it populates an MVar and the same three functions are evaluated in the
>>>>> same order again.
>>>>>
>>>>> If the MVar is full, it creates another MVar of the same type and puts
>>>>> it in the TChan.
>>>>>
>>>>> Is this a sound design? Does it prompt any questions from you? Here's
>>>>> my question. If this is basically a sound design, I know I will need
>>>>> use forkIO. I'm not sure where.
>>>>> If this is not a sound design, please ask questions or give other
>>>>> feedback so I can make changes and restore sanity.
>>>>>
>>>>> _______________________________________________
>>>>> Beginners mailing list
>>>>> Beginners at haskell.org
>>>>> http://www.haskell.org/mailman/listinfo/beginners
>>>>>
>>>>
>>>
>>> _______________________________________________
>>> Beginners mailing list
>>> Beginners at haskell.org
>>> http://www.haskell.org/mailman/listinfo/beginners
>>>
>>
>
More information about the Beginners
mailing list