Skip to content

Commit

Permalink
introduce SingleProc/MultiProc/ProcDir, phase1, phase2, phase3
Browse files Browse the repository at this point in the history
  • Loading branch information
wavewave committed Jul 3, 2013
1 parent 008ac07 commit 8550ff1
Show file tree
Hide file tree
Showing 4 changed files with 133 additions and 37 deletions.
5 changes: 4 additions & 1 deletion evchain.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -17,6 +17,7 @@ Library
ghc-prof-options: -caf-all -auto-all
Build-Depends:
base>4, mtl>2, directory, filepath,
transformers > 0.3,
bytestring >= 0.9,
cmdargs,
LHEParser >= 0.999,
Expand All @@ -38,7 +39,8 @@ Library
containers >= 0.4,
pureMD5 >= 2.1,
zlib >= 0.5,
LHE-sanitizer
LHE-sanitizer,
pipeline-eventgen

Exposed-Modules:
HEP.Automation.EventChain.Driver
Expand All @@ -51,6 +53,7 @@ Library
HEP.Automation.EventChain.Simulator
HEP.Automation.EventChain.SpecDSL
HEP.Automation.EventChain.Type.Match
HEP.Automation.EventChain.Type.MultiProcess
HEP.Automation.EventChain.Type.Process
HEP.Automation.EventChain.Type.Skeleton
HEP.Automation.EventChain.Type.Spec
Expand Down
77 changes: 77 additions & 0 deletions lib/HEP/Automation/EventChain/Driver.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,6 +18,7 @@ import qualified Codec.Compression.GZip as GZ
import Control.Applicative
import Control.Monad
import Control.Monad.Error
import Control.Monad.Reader
import Control.Monad.State
import qualified Data.ByteString as B
import qualified Data.ByteString.Char8 as C8
Expand All @@ -38,10 +39,15 @@ import System.Process
import Text.XML.Stream.Parse
import Text.XML.Stream.Render
-- from hep-platform
import HEP.Automation.EventGeneration.Work
import HEP.Automation.MadGraph.Model
import HEP.Automation.MadGraph.Run
import HEP.Automation.MadGraph.SetupType
import HEP.Automation.MadGraph.Type
import HEP.Parser.LHE.Conduit
import HEP.Parser.LHE.Type
import HEP.Storage.WebDAV.Type
import HEP.Storage.WebDAV.CURL
-- from this package
import HEP.Automation.EventChain.File
import HEP.Automation.EventChain.LHEConn
Expand All @@ -50,6 +56,7 @@ import HEP.Automation.EventChain.Process
import HEP.Automation.EventChain.Process.Generator
import HEP.Automation.EventChain.Simulator
import HEP.Automation.EventChain.SpecDSL
import HEP.Automation.EventChain.Type.MultiProcess
import HEP.Automation.EventChain.Type.Skeleton
import HEP.Automation.EventChain.Type.Spec
import HEP.Automation.EventChain.Type.Process
Expand Down Expand Up @@ -108,3 +115,73 @@ evchainGen mdl sset rset (basename,procname) pset pmap cross = do
putStrLn $ "The resultant file " ++ (dir</>file) ++ " is generated."


-- |
genPhase1 :: (Model model) =>
model
-> ScriptSetup
-> ProcDir
-> SingleProc
-> ModelParam model
-> (NumOfEv,SetNum)
-> IO ()
genPhase1 mdl sset pdir sp pset (numev, sn) =
evchainGen mdl sset rset (bname, pname) pset (spProcSpecMap sp) (spCross sp)
where bname = pdWorkDirPrefix pdir ++ "_" ++ pname
pname = spName sp
rset = (spRunSetup sp) numev sn

-- |
genPhase2 :: (Model model) =>
model
-> ScriptSetup
-> ProcDir
-> SingleProc
-> ModelParam model
-> (NumOfEv,SetNum)
-> IO ()
genPhase2 mdl sset pdir sp pset (numev, sn) = do
r <- flip runReaderT wsetup . runErrorT $ do
ws <- ask
let (ssetup,psetup,param,rsetup) =
((,,,) <$> ws_ssetup <*> ws_psetup <*> ws_param <*> ws_rsetup) ws
cardPrepare
case (lhesanitizer rsetup,pythia rsetup) of
([],_) -> return ()
(_:_, RunPYTHIA) -> do
sanitizeLHE
runPYTHIA
runPGS
runClean
(_:_, NoPYTHIA) -> do
sanitizeLHE
cleanHepFiles
print r
return ()

where bname = pdWorkDirPrefix pdir ++ "_" ++ pname
pname = spName sp
rset = (spRunSetup sp) numev sn
wsetup' = getWorkSetupCombined mdl sset rset pset (bname,pname)
wsetup = wsetup' { ws_storage =
WebDAVRemoteDir
(pdRemoteDirBase pdir </> pdRemoteDirPrefix pdir ++ "_" ++ pname) }

-- |
genPhase3 :: (Model model) =>
model
-> ScriptSetup
-> ProcDir
-> SingleProc
-> ModelParam model
-> (NumOfEv,SetNum)
-> WebDAVConfig
-> IO Bool
genPhase3 mdl sset pdir sp pset (numev, sn) wdavcfg =
uploadEventFull NoUploadHEP wdavcfg wsetup
where bname = pdWorkDirPrefix pdir ++ "_" ++ pname
pname = spName sp
rset = (spRunSetup sp) numev sn
wsetup' = getWorkSetupCombined mdl sset rset pset (bname,pname)
wsetup = wsetup' { ws_storage =
WebDAVRemoteDir
(pdRemoteDirBase pdir </> pdRemoteDirPrefix pdir ++ "_" ++ pname) }
36 changes: 0 additions & 36 deletions lib/HEP/Automation/EventChain/Type/CVec.hs

This file was deleted.

52 changes: 52 additions & 0 deletions lib/HEP/Automation/EventChain/Type/MultiProcess.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,52 @@
-----------------------------------------------------------------------------
-- |
-- Module : HEP.Automation.EventChain.Type.MultiProcess
-- Copyright : (c) 2013 Ian-Woo Kim
--
-- License : BSD3
-- Maintainer : Ian-Woo Kim <[email protected]>
-- Stability : experimental
-- Portability : GHC
--
-- Types for MultiProcess Spec
--
-----------------------------------------------------------------------------

module HEP.Automation.EventChain.Type.MultiProcess
( NumOfEv (..)
, SetNum (..)
, SingleProc(..)
, ProcDir(..)
, MultiProc (..)
) where

import qualified Data.Map as M
--
import HEP.Automation.MadGraph.SetupType
--
import HEP.Automation.EventChain.Type.Spec
import HEP.Automation.EventChain.Type.Process

newtype NumOfEv = NumOfEv { unNumOfEv :: Int }

newtype SetNum = SetNum { unSetNum :: Int }

data SingleProc = SingleProc { spName :: String
, spCross :: DCross
, spProcSpecMap :: ProcSpecMap
, spRunSetup :: NumOfEv -> SetNum -> RunSetup
}

data ProcDir = ProcDir { pdWorkDirPrefix :: String
, pdRemoteDirBase :: FilePath
, pdRemoteDirPrefix :: String
}
data MultiProc = MultiProc { mpName :: String
, mpProcDir :: ProcDir
, mpMultiProcessMap :: M.Map String SingleProc
}

{-
mkSingleProc :: String -> DCross -> ProcSpecMap -> (NumOfEv -> SetNum -> RunSetup) -> SingleProc
mkSingleProc n c m r = MultiProcPart n c (mkCrossIDIdx (mkDICross c)) m r
-}

0 comments on commit 8550ff1

Please sign in to comment.