Commit 4a66d66f authored by Alexandre Delanoë's avatar Alexandre Delanoë

rights management first files.

parent fa516072
{-|
Module : DAC
Description : Decentralized Autonomous Collaboration (DAC)
Copyright : (c) Alexandre Delanoe, 2017
License : AGPL + CECILL v3
Maintainer : alexandre.delanoe@iscpif.fr
Stability : experimental
Portability : POSIX
Main modules of the collaboraction
-}
-- Entities
-- Collaboration
{-|
Module : Collaborativ
Description : Collaborativ framework
Copyright : (c) Alexandre Delanoe, 2017
License : AGPL + CECILL v3
Maintainer : alexandre.delanoe@iscpif.fr
Stability : experimental
Portability : POSIX
Collaborativ framework describing main functions (in a perspective of a
Decentralized Autonomous Organization in mind).
-}
module Collaborativ where
type Proba = Double
-- Proba :: somme == 1
-- Main Concepts
-- BlockChain | SideChain | NodeChain
-- Inside the Node Chain: we have the history of all decisions
-- Axiom 1 : all Nodes have a Citizen at least
type Citizen = NodeUser
-- Community is a Node of
type Community = NodeCommunity
-- | Rights
data Rights = Read | Write | Execute | Share | Clone
-- | Main policies implemented
-- Public policy: means anyone can RWES
type Free = Public
data Policy = Public | Ancestor | DictatorShip
| PreferenceMajority | BoolMajority | Unanimity
runPolicy :: Citizen -> Node -> Bool
runPolicy = undefined
hasCitizen :: Node -> Set User
hasCitizen = undefined
isCitizen :: User -> Node -> Bool
isCitizen user node = member user (citizens node)
hasPolicy :: Node -> Policy
hasPolicy = undefined
--
-- | For a given Node, citizenShip is shared by Citizen according to a Policy
citizenRights ::
ownership :: Node -> Map User Proba
ownership = undefined
nodePolicy :: Node -> Map User (Proba, Bool)
nodePolicy = undefined
-- | Starting from the simple case:
-- one can share a Node only, with Node th
-- One user can not share to himself (useless)
-- One user can not share a Shareable ressource to all the world
-- One user can not share a Shareable ressource to a group according
-- -> to anybody in the group
-- -> according to policy rules (dictatorship of one User, majority rule or others)
-- One user can share a Shareable ressource individually
-- -> to anybody individually if he knows his uniq ID
share :: for all Shareable a => User -> a -> Set User -> Bool
share = undefined
instance Shareable User where
policy = undefined
-- Right Management
-----------------------------------------------------------------
-- data Management = RolesRights | NodesRights | OperationsRights
-----------------------------------------------------------------
-----------------------------------------------------------------
-- Role Rights Management
-- rights to create roles (group)
-- Node Rights Management
-- rights to read/write Node
-- Operation Rights Management
-- rights for which operations
-----------------------------------------------------------------
-- Roles Rights Management
-----------------------------------------------------------------
-- 2 main roles
-- admin : can create group and assign Node Rights to it
-- user : can not create group and assign Node rights inside his group (if he has the rights)
-- Use cases:
-- if all user are in public and have read/write permissions: everything is free inside the public group
-- else:
-- in X institution x admin can create an gx group or a gy group for each department and assign user to it
-- users y can share with user y withing the group if he has the rights for it
-- an admin can give admin group to a user
-- Roles Rights Management are stored in "User Node"
-- right to read on group called "x" == can share permissions inside group x
-- right to write on group called "x" == can modify group x itself
-- Question: how to manage the hierarchy of roles/groups ?
-- Example: use can create a group inside a group but not outside of it
-----------------------------------------------------------------
-- Node Rights Management
-----------------------------------------------------------------
-- Les actions sur un Node (if /= Graph) depends on the rights of his parent
-- | rightsOf:
-- technically : get the column Node (in table nodes) with rights (ACL)
rightsOf :: Node -> Rights
rightsOf n = undefined
rightsOfNode :: User -> Node -> Rights
rightsOfNode u n = case n of
UserNode -> rightsOf n
ProjectNode -> rightsOf n
CorpusNode -> rightsOf n
GraphNode -> rightsOf n
_ -> rightsOf (parentOf n)
rightsOfNodeNgram :: User -> NodeNgram -> Rights
rightsOfNodeNgram u n = rightsOf n'
where
n' = nodeOf n
rightsOfNodeNgramNgram :: User -> NodeNgramNgram -> Rights
rightsOfNodeNgramNgram u n = rightsOf n'
where
n' = nodeOf n
rightsOfNodeNodeNgram
rightsOfNodeNode
-----------------------------------------------------------------
-- Operation Rights Management
-----------------------------------------------------------------
data Operation = Read | Write
-- Starting with simple case:
-- type ModifyRights = Write
-- type Exec = Write
data Rights = { _rightsRead :: Bool
, _rightsWrite :: Bool
}
deriving (Show, Read, Eq)
data LogRightsMessage = RightsSuccess | RightsError
deriving (Show, Read, Eq)
type Read = Bool
type Write = Bool
-----------------------------------------------------------------
-- | TODO
-- find the tables where there is the relation Node / User / Rights
getRightsOfNodeWithUser :: Node -> User -> IO Rights
getRightsOfNodeWithUser n u = undefined
userCan :: Operation -> User -> Node -> IO Bool
userCan op u n = do
rights <- getRightsOfNodeWithUser u n
r = case op of
Read -> _rightsRead rights
Write -> _rightsWrite rights
pure (r == True)
-- | User can (or can not) give/change rights of the Node
userCanModifyRights :: User -> Node -> IO Bool
userCanModifyRights u n = True `==` <$> userCan Write u n
-- | User can see who has access to the Node
userCanReadRights :: User -> Node -> IO Bool
userCanReadRights u n = True `==` <$> userCan Read u n
chmod :: Rights -> User -> Node -> IO LogRightsMessage
chmod r u n = undefined
chmod' :: Read -> Write -> User -> Node -> IO LogRightsMessage
chmod' r w u n = chmod rights u n
where
rights = Rights r w
readAccessOnly :: User -> Node -> IO LogRightsMessage
readAccessOnly u n = chmod r u n
where
r = Rights True False
stopAccess :: User -> Node -> IO LogRightsMessage
stopAccess =
chmodAll :: Rights -> User -> [Node] -> IO [LogRightsMessage]
chmd b r u ns = map (chmod b r u n) ns
chmodChildren :: Rights -> User -> [Node] -> IO [LogRightsMessage]
chmodChildren b r u n = map (chmod br u n) ns'
where
ns' = childrenOf n
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment