Skip to content

Commit

Permalink
Refactor the code, add TODOs
Browse files Browse the repository at this point in the history
  • Loading branch information
harendra-kumar committed Apr 19, 2023
1 parent 3d45808 commit e24dd87
Show file tree
Hide file tree
Showing 2 changed files with 118 additions and 46 deletions.
32 changes: 26 additions & 6 deletions src/Streamly/Coreutils/Chmod.hs
Original file line number Diff line number Diff line change
Expand Up @@ -51,7 +51,19 @@
-- the owner? But we cannot do the same on windows.

module Streamly.Coreutils.Chmod
( chmod
(
-- * Roles
Role (..)

-- * Permissions
, Permissions
, setReadable
, setWritable
, setExecutable
, reset

-- * Chmod
, chmod
)
where

Expand All @@ -63,7 +75,7 @@ modifyBit :: Bool -> Posix.FileMode -> Posix.FileMode -> Posix.FileMode
modifyBit False b m = m .&. complement b
modifyBit True b m = m .|. b

chmodWith :: UserType -> Permissions -> FilePath -> IO ()
chmodWith :: Role -> Permissions -> FilePath -> IO ()
chmodWith utype (Permissions r w e) path = do
case utype of
Owner -> setOwnerPermissions
Expand Down Expand Up @@ -108,8 +120,16 @@ chmodWith utype (Permissions r w e) path = do
setGroupPermissions
setOthersPermissions

-- | Supports only override permissions bits
-- >> chmod [perm|a=rwx|] "a.txt"
-- | Change the file permission modes for specified roles using the specified
-- permission modifier functions.
--
-- You can use the @mode@ quasiquoter to build the mode conveniently, for
-- example:
--
-- >> chmod [mode|a=rwx|] "a.txt"
--
chmod :: UserTypePerm -> FilePath -> IO ()
chmod pat = chmodWith (utype pat) (permssions pat)
chmod :: [(Role, Permissions -> Permissions)] -> FilePath -> IO ()
-- To implement this, get the file mode. Transform the FileMode using the roles
-- and permissions, and then use a single setFileMode call to set the mode in
-- the end.
chmod pat = undefined
132 changes: 92 additions & 40 deletions src/Streamly/Coreutils/StringQ.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,12 +9,16 @@
--
-- change file mode bits.

-- XXX Rename to "Permissions" or "AccessControl"

module Streamly.Coreutils.StringQ
(
perm
, UserType(..)
Role(..)
, Permissions(..)
, UserTypePerm(..)
, setReadable
, setWritable
, setExecutable
, reset
)
where

Expand All @@ -31,9 +35,63 @@ import Streamly.Internal.Data.Parser (Parser)
import qualified Streamly.Internal.Data.Fold as Fold
import qualified Streamly.Internal.Data.Parser as Parser
import qualified Streamly.Internal.Data.Stream.IsStream as Stream
import qualified Streamly.Internal.Unicode.Char.Parser as Parser
import qualified Streamly.Internal.Unicode.Parser as Parser

-------------------------------------------------------------------------------
-- Permissions
-------------------------------------------------------------------------------

-- | Permissions for access control
data Permissions = Permissions
{ readable :: Bool
, writable :: Bool
, executable :: Bool
-- , searchable :: Bool -- for portability, keep it separate
} deriving (Eq, Ord, Read, Show, Data)

strParser :: MonadCatch m => Parser m Char String
{-
defaultPermissions =
Permissions
{ readable = False
, writable = False
, executable = False
}
-}

-- | Enable @read@ permission.
setReadable :: Bool -> Permissions -> Permissions
setReadable x perms = perms { readable = x }

-- | Enable @write@ permission.
setWritable :: Bool -> Permissions -> Permissions
setWritable x perms = perms { writable = x }

-- | Enable @execute@ permission.
setExecutable :: Bool -> Permissions -> Permissions
setExecutable x perms = perms { executable = x }

-- | Disable all permissions.
reset :: Permissions -> Permissions
reset = setReadable False . setWritable False . setExecutable False

-------------------------------------------------------------------------------
-- Roles
-------------------------------------------------------------------------------

-- | Roles to whom access is granted.
data Role =
Owner
| Group
| Others
| All
deriving (Eq, Ord, Read, Show, Data)

-------------------------------------------------------------------------------
-- Mode parser
-------------------------------------------------------------------------------

{-
strParser :: MonadCatch m => Parser Char m String
strParser =
let ut = Parser.char 'u'
<|> Parser.char 'g'
Expand All @@ -57,33 +115,7 @@ expandVars ln =
Left _ -> fail "Parsing of perm quoted string failed."
Right _ -> return ()
data Permissions = Permissions
{ readable :: Bool
, writable :: Bool
, executable :: Bool
} deriving (Eq, Ord, Read, Show, Data)

data UserType =
Owner
| Group
| Others
| All
deriving (Eq, Ord, Read, Show, Data)

data UserTypePerm =
UserTypePerm
{ utype :: UserType
, permssions :: Permissions
} deriving (Eq, Ord, Read, Show, Data)

instance Default Permissions where
def = Permissions
{ readable = False
, writable = False
, executable = False
}

parseExpr :: MonadIO m => String -> m UserTypePerm
parseExpr :: MonadIO m => String -> m [(Role, Permissions)]
parseExpr s = do
liftIO $ expandVars s
let ut = head s
Expand Down Expand Up @@ -119,15 +151,35 @@ quoteExprPat s = do
expr <- parseExpr s
dataToPatQ (const Nothing) expr
perm :: QuasiQuoter
perm =
-- TODO: perms can have a single letter from the set ugo, in that case the
-- existing permissions are copied from that role.
-- When we get a "=" use 'reset', when we get a '+' use an operation with
-- argument True, else use False.
-- | The format of a symbolic mode is [roles][-+=][perms...], where roles is
-- either zero or more letters from the set ugoa. perms is either zero or more
-- letters from the set rwxXst. Multiple symbolic modes can be given, separated
-- by commas.
--
-- Examples:
--
-- @
-- -
-- -rwx
-- g-rx
-- g-x+r
-- go-x+rw
-- go-x+rw,u+r
-- @
--
-- If the role is omitted it is assumed to be 'a'.
mode :: QuasiQuoter
mode =
QuasiQuoter
{ quoteExp = quoteExprExp
, quotePat = quoteExprPat
, quoteType = notSupported
, quoteDec = notSupported
, quoteType = error "mode: quoteType not supported."
, quoteDec = error "mode: quoteDec not supported."
}

where

notSupported = error "perm: Not supported."
-}

0 comments on commit e24dd87

Please sign in to comment.