{-# LANGUAGE GeneralizedNewtypeDeriving, MultiParamTypeClasses, Rank2Types #-} module Bein.Web.Types.Local where import Control.Concurrent.STM import Database.HDBC.PostgreSQL import Data.Time import qualified Data.Map as M import Bein.Types import Happstack.Server import Control.Monad.Reader import Control.Concurrent import System.IO import Control.Monad.Writer data WebState = WebState { stDb :: Connection, stConfigT :: TVar Configuration, stDaemonPort :: MVar Handle, stUser :: Maybe User, stObject :: BeinObject } instance BeinState WebState where configT = stConfigT db = stDb type BeinServerPart = ServerPartT (ReaderT WebState IO) data FormResponse a = ContinuePage a | ContinuePageWithWrapper a (BeinServerPart Response -> BeinServerPart Response) | NewResponse Response | RedirectTo String type BeinFormPart a = WriterT [(String, BeinServerPart (FormResponse a))] BeinServerPart --type BeinForm a = XHtmlForm (ReaderT WebState IO) a --type BeinFormlet a = XHtmlFormlet (ReaderT WebState IO) a --instance (Applicative m, Monad m) => Applicative (ReaderT s m) where -- pure = return -- (<*>) = ap data AuthType = Password String | Host String | NoLogin deriving (Eq,Show,Read) data Group = Group { gid :: Int, groupName :: String } deriving (Eq,Show,Read) data User = User { uid :: Int, userName :: String, groups :: [Group], defaultGR :: Bool, defaultGW :: Bool, defaultWR :: Bool, defaultWW :: Bool, defaultGroup :: Group, isAdministrator :: Bool, authType :: AuthType } deriving (Eq,Show,Read) data BeinObject = BeinObject { objId :: Int, objHeader :: ObjectHeader, objBody :: Maybe ObjectBody } deriving (Eq,Show,Read) data ObjectHeader = ObjectHeader { label :: String, notes :: String, owner :: User, group :: Group, gr :: Bool, gw :: Bool, wr :: Bool, ww :: Bool, created :: LocalTime, lastModified :: LocalTime, objType :: ObjectType, immutable :: Bool } deriving (Eq,Show,Read) data ObjectType = File | Program | Execution deriving (Eq,Show,Read) data ObjectBody = FileBody { userFilename :: String, storedAs :: FilePath, contentType :: String } | ProgramBody { language :: ProgramLanguage, script :: String, programInputs :: M.Map String ProgramInput, programOutputs :: M.Map String ProgramOutput, resourceSpec :: ResourceSpec } | ExecutionBody { resourceSpec :: ResourceSpec, program :: Maybe BeinObject, status :: ExecutionStatus, executionInputs :: M.Map String ExecutionInput, executionOutputs :: M.Map String ExecutionOutput, executionLog :: [(LocalTime,String)] } deriving (Eq,Show,Read) data ExecutionInput = ExecutionStringInput (Maybe String) | ExecutionNumberInput (Maybe Double) | ExecutionObjectInput (Maybe BeinObject) deriving (Eq,Show,Read) data ExecutionOutput = ExecutionFileOutput BeinObject deriving (Eq,Show,Read) data ResourceSpec = ResourceSpec { resReq :: String, maxCpu :: Maybe Int, maxFileSize :: Maybe Int, maxRam :: Maybe Int, maxSwap :: Maybe Int, maxProcs :: Maybe Int } deriving (Eq,Show,Read) data ExecutionStatus = Waiting | Running | Complete | Failed | DependencyFailed Int deriving (Eq,Show,Read) data ProgramLanguage = Perl | R deriving (Eq,Show,Read) data ProgramInput = InputSequence | InputFile | InputString | InputNumber deriving (Eq,Show,Read) data ProgramOutput = OutputFile deriving (Eq,Show,Read) data UserQuery = WithUid Int | WithUserName String | WithHost String deriving (Eq,Show,Read) data GroupQuery = WithGid Int | WithGroupName String deriving (Eq,Show,Read) data PageTitle = JustTitle String | TitleSubtitle String String deriving (Eq,Show,Read) data RereadOnUpdate = NoReread | RereadUser | RereadObject | RereadUserAndObject deriving (Eq,Show,Read)