module DefaultCreateOptions where

import CreateOptionsType (CreateOptions(..))
import FileSystemType (FileSystem (TemporaryFileSystem))
import NameType (Name)
import OnExecType (OnExec (RemainOpenOnExec))
import SealingType (Sealing (DoNotAllowSealing))

defaultCreateOptions :: Name -> CreateOptions
defaultCreateOptions :: Name -> CreateOptions
defaultCreateOptions Name
x =
  CreateOptions :: Name -> OnExec -> Sealing -> FileSystem -> CreateOptions
CreateOptions
    { name :: Name
name = Name
x
    , onExec :: OnExec
onExec = OnExec
RemainOpenOnExec
    , sealing :: Sealing
sealing = Sealing
DoNotAllowSealing
    , fileSystem :: FileSystem
fileSystem = FileSystem
TemporaryFileSystem
    }

-- ^
-- Default options for 'Memfd.create', corresponding to what you get what you use the C library and don't set any flags.
--
-- * 'onExec' = 'RemainOpenOnExec'
-- * 'sealing' = 'DoNotAllowSealing'
-- * 'fileSystem' = 'TemporaryFileSystem'