Copyright | (c) Fuzz Leonard 2025 |
---|---|
License | MIT |
Maintainer | cyborg@bionicfuzz.com |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Clod.AdvancedCapability
Description
This module implements an advanced capability-based security model using type-level programming features in Haskell. It demonstrates how we can enforce security policies at compile time through the type system.
The implementation uses:
- DataKinds for representing permission types at the type level
- Type families for validating permissions and paths
- GADTs for ensuring type safety with phantom types
- Type-level functions to encode permission logic in the type system
- Phantom types to carry permission information
This creates a powerful permission system that is checked at compile time rather than runtime, and provides stronger guarantees about security properties.
Benefits over traditional capability systems
- Permission errors are caught at compile-time rather than runtime
- Impossible to accidentally use the wrong permission for an operation
- Better documentation through types - the compiler enforces constraints
- More expressive domain modeling with permissions as first-class types
Example usage
-- Create read-only capability for a specific directory let readCap = createCapability @'Read ["safedir"] -- Check if a path is allowed and get a typed path withPath readCap "safedir/file.txt" $ \pathMaybe -> case pathMaybe of Nothing -> putStrLn "Access denied" Just typedPath -> do -- Type system ensures this is a valid read operation content <- readFile readCap typedPath print content -- This would be a compile-time error: -- writeFile readCap typedPath "New content"
Synopsis
- data Permission
- type ReadPerm = 'Read
- type WritePerm = 'Write
- type ExecutePerm = 'Execute
- type AllPerm = 'All
- type Path = String
- data TypedPath (p :: Permission) where
- TypedPath :: forall (p :: Permission). FilePath -> TypedPath p
- type PathWithPerm (p :: Permission) = TypedPath p
- data Capability (p :: Permission) = Capability {
- allowedDirs :: [FilePath]
- type FileCapability = Capability 'Read
- type DirsCapability = Capability 'All
- type family IsSafePath (path :: FilePath) (baseDir :: [FilePath]) :: Bool where ...
- type family PermissionFor (required :: Permission) (provided :: Permission) where ...
- class HasPermission (cap :: k) (p :: Permission) | cap -> p
- createCapability :: forall (p :: Permission). [FilePath] -> Capability p
- restrictCapability :: forall (p :: Permission) (p' :: Permission). Capability p -> Capability p'
- withPath :: forall (p :: Permission) m a. MonadIO m => Capability p -> FilePath -> (Maybe (TypedPath p) -> m a) -> m a
- unsafeAsPath :: forall (p :: Permission). FilePath -> TypedPath p
- readFile :: forall (p :: Permission) m. (MonadIO m, PermissionFor 'Read p) => Capability p -> TypedPath p -> m ByteString
- writeFile :: forall (p :: Permission) m. (MonadIO m, PermissionFor 'Write p) => Capability p -> TypedPath p -> ByteString -> m ()
Permission types
type ReadPerm = 'Read Source #
Type-level aliases for permissions | Read permission for read-only file access
type ExecutePerm = 'Execute Source #
Execute permission for executable files
Path types
data TypedPath (p :: Permission) where Source #
A path with type-level permission information
Constructors
TypedPath :: forall (p :: Permission). FilePath -> TypedPath p | Constructor for creating a path with permission p |
type PathWithPerm (p :: Permission) = TypedPath p Source #
Convenient type alias for paths with permissions
Capability tokens
data Capability (p :: Permission) Source #
Capability token that grants permissions
Constructors
Capability | |
Fields
|
type FileCapability = Capability 'Read Source #
Type alias for common file capabilities
type DirsCapability = Capability 'All Source #
Type alias for directory capabilities
Type-level path operations
type family IsSafePath (path :: FilePath) (baseDir :: [FilePath]) :: Bool where ... Source #
Type family to determine if a path is safe
Equations
IsSafePath path ('[] :: [FilePath]) = 'False | |
IsSafePath path (base ': rest) = OrF (IsSubPath path base) (IsSafePath path rest) |
type family PermissionFor (required :: Permission) (provided :: Permission) where ... Source #
Permission check at the type level
Equations
PermissionFor 'Read 'Read = () | |
PermissionFor 'Read 'All = () | |
PermissionFor 'Write 'Write = () | |
PermissionFor 'Write 'All = () | |
PermissionFor 'Execute 'Execute = () | |
PermissionFor 'Execute 'All = () | |
PermissionFor 'All 'All = () | |
PermissionFor a b = () |
class HasPermission (cap :: k) (p :: Permission) | cap -> p Source #
Type class for checking permissions
Runtime operations
createCapability :: forall (p :: Permission). [FilePath] -> Capability p Source #
Create a capability token for the given permission and directories
restrictCapability :: forall (p :: Permission) (p' :: Permission). Capability p -> Capability p' Source #
Restrict a capability to a more limited permission
withPath :: forall (p :: Permission) m a. MonadIO m => Capability p -> FilePath -> (Maybe (TypedPath p) -> m a) -> m a Source #
Check if a path is allowed by this capability and create a typed path if it is
unsafeAsPath :: forall (p :: Permission). FilePath -> TypedPath p Source #
Create a typed path without checking permissions (unsafe)
readFile :: forall (p :: Permission) m. (MonadIO m, PermissionFor 'Read p) => Capability p -> TypedPath p -> m ByteString Source #
Read a file with the given capability
writeFile :: forall (p :: Permission) m. (MonadIO m, PermissionFor 'Write p) => Capability p -> TypedPath p -> ByteString -> m () Source #
Write to a file with the given capability