Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- class LensPragmaOptions a where
- getPragmaOptions :: a -> PragmaOptions
- setPragmaOptions :: PragmaOptions -> a -> a
- mapPragmaOptions :: (PragmaOptions -> PragmaOptions) -> a -> a
- lensPragmaOptions :: Lens' a PragmaOptions
- modifyPragmaOptions :: MonadTCState m => (PragmaOptions -> PragmaOptions) -> m ()
- class LensVerbosity a where
- getVerbosity :: a -> Verbosity
- setVerbosity :: Verbosity -> a -> a
- mapVerbosity :: (Verbosity -> Verbosity) -> a -> a
- modifyVerbosity :: MonadTCState m => (Verbosity -> Verbosity) -> m ()
- putVerbosity :: MonadTCState m => Verbosity -> m ()
- class LensCommandLineOptions a where
- getCommandLineOptions :: a -> CommandLineOptions
- setCommandLineOptions :: CommandLineOptions -> a -> a
- mapCommandLineOptions :: (CommandLineOptions -> CommandLineOptions) -> a -> a
- modifyCommandLineOptions :: MonadTCState m => (CommandLineOptions -> CommandLineOptions) -> m ()
- type SafeMode = Bool
- class LensSafeMode a where
- getSafeMode :: a -> SafeMode
- setSafeMode :: SafeMode -> a -> a
- mapSafeMode :: (SafeMode -> SafeMode) -> a -> a
- modifySafeMode :: MonadTCState m => (SafeMode -> SafeMode) -> m ()
- putSafeMode :: MonadTCState m => SafeMode -> m ()
- builtinModulesWithSafePostulates :: Set FilePath
- builtinModulesWithUnsafePostulates :: Set FilePath
- primitiveModules :: Set FilePath
- builtinModules :: Set FilePath
- isPrimitiveModule :: MonadIO m => FilePath -> m Bool
- isBuiltinModule :: MonadIO m => FilePath -> m Bool
- isBuiltinModuleWithSafePostulates :: MonadIO m => FilePath -> m Bool
- class LensIncludePaths a where
- getIncludePaths :: a -> [FilePath]
- setIncludePaths :: [FilePath] -> a -> a
- mapIncludePaths :: ([FilePath] -> [FilePath]) -> a -> a
- getAbsoluteIncludePaths :: a -> [AbsolutePath]
- setAbsoluteIncludePaths :: [AbsolutePath] -> a -> a
- mapAbsoluteIncludePaths :: ([AbsolutePath] -> [AbsolutePath]) -> a -> a
- modifyIncludePaths :: MonadTCState m => ([FilePath] -> [FilePath]) -> m ()
- putIncludePaths :: MonadTCState m => [FilePath] -> m ()
- modifyAbsoluteIncludePaths :: MonadTCState m => ([AbsolutePath] -> [AbsolutePath]) -> m ()
- putAbsoluteIncludePaths :: MonadTCState m => [AbsolutePath] -> m ()
- type PersistentVerbosity = Verbosity
- class LensPersistentVerbosity a where
- getPersistentVerbosity :: a -> PersistentVerbosity
- setPersistentVerbosity :: PersistentVerbosity -> a -> a
- mapPersistentVerbosity :: (PersistentVerbosity -> PersistentVerbosity) -> a -> a
- modifyPersistentVerbosity :: MonadTCState m => (PersistentVerbosity -> PersistentVerbosity) -> m ()
- putPersistentVerbosity :: MonadTCState m => PersistentVerbosity -> m ()
Pragma options
class LensPragmaOptions a where Source #
getPragmaOptions :: a -> PragmaOptions Source #
setPragmaOptions :: PragmaOptions -> a -> a Source #
mapPragmaOptions :: (PragmaOptions -> PragmaOptions) -> a -> a Source #
Instances
modifyPragmaOptions :: MonadTCState m => (PragmaOptions -> PragmaOptions) -> m () Source #
Verbosity in the local pragma options
class LensVerbosity a where Source #
getVerbosity :: a -> Verbosity Source #
setVerbosity :: Verbosity -> a -> a Source #
mapVerbosity :: (Verbosity -> Verbosity) -> a -> a Source #
Instances
LensVerbosity PragmaOptions Source # | |
Defined in Agda.Interaction.Options.Lenses getVerbosity :: PragmaOptions -> Verbosity Source # setVerbosity :: Verbosity -> PragmaOptions -> PragmaOptions Source # mapVerbosity :: (Verbosity -> Verbosity) -> PragmaOptions -> PragmaOptions Source # | |
LensVerbosity TCState Source # | |
Defined in Agda.Interaction.Options.Lenses |
modifyVerbosity :: MonadTCState m => (Verbosity -> Verbosity) -> m () Source #
putVerbosity :: MonadTCState m => Verbosity -> m () Source #
Command line options
class LensCommandLineOptions a where Source #
getCommandLineOptions :: a -> CommandLineOptions Source #
setCommandLineOptions :: CommandLineOptions -> a -> a Source #
mapCommandLineOptions :: (CommandLineOptions -> CommandLineOptions) -> a -> a Source #
Instances
modifyCommandLineOptions :: MonadTCState m => (CommandLineOptions -> CommandLineOptions) -> m () Source #
Safe mode
class LensSafeMode a where Source #
getSafeMode :: a -> SafeMode Source #
setSafeMode :: SafeMode -> a -> a Source #
mapSafeMode :: (SafeMode -> SafeMode) -> a -> a Source #
Instances
LensSafeMode CommandLineOptions Source # | |
Defined in Agda.Interaction.Options.Lenses getSafeMode :: CommandLineOptions -> SafeMode Source # setSafeMode :: SafeMode -> CommandLineOptions -> CommandLineOptions Source # mapSafeMode :: (SafeMode -> SafeMode) -> CommandLineOptions -> CommandLineOptions Source # | |
LensSafeMode PragmaOptions Source # | |
Defined in Agda.Interaction.Options.Lenses getSafeMode :: PragmaOptions -> SafeMode Source # setSafeMode :: SafeMode -> PragmaOptions -> PragmaOptions Source # mapSafeMode :: (SafeMode -> SafeMode) -> PragmaOptions -> PragmaOptions Source # | |
LensSafeMode PersistentTCState Source # | |
Defined in Agda.Interaction.Options.Lenses getSafeMode :: PersistentTCState -> SafeMode Source # setSafeMode :: SafeMode -> PersistentTCState -> PersistentTCState Source # mapSafeMode :: (SafeMode -> SafeMode) -> PersistentTCState -> PersistentTCState Source # | |
LensSafeMode TCState Source # | |
Defined in Agda.Interaction.Options.Lenses |
modifySafeMode :: MonadTCState m => (SafeMode -> SafeMode) -> m () Source #
putSafeMode :: MonadTCState m => SafeMode -> m () Source #
builtinModulesWithSafePostulates :: Set FilePath Source #
These builtins may use postulates, and are still considered --safe
builtinModulesWithUnsafePostulates :: Set FilePath Source #
These builtins may not use postulates under --safe. They are not automatically unsafe, but will be if they use an unsafe feature.
primitiveModules :: Set FilePath Source #
builtinModules :: Set FilePath Source #
isPrimitiveModule :: MonadIO m => FilePath -> m Bool Source #
isBuiltinModule :: MonadIO m => FilePath -> m Bool Source #
isBuiltinModuleWithSafePostulates :: MonadIO m => FilePath -> m Bool Source #
Include directories
class LensIncludePaths a where Source #
getIncludePaths :: a -> [FilePath] Source #
setIncludePaths :: [FilePath] -> a -> a Source #
mapIncludePaths :: ([FilePath] -> [FilePath]) -> a -> a Source #
getAbsoluteIncludePaths :: a -> [AbsolutePath] Source #
setAbsoluteIncludePaths :: [AbsolutePath] -> a -> a Source #
mapAbsoluteIncludePaths :: ([AbsolutePath] -> [AbsolutePath]) -> a -> a Source #
Instances
modifyIncludePaths :: MonadTCState m => ([FilePath] -> [FilePath]) -> m () Source #
putIncludePaths :: MonadTCState m => [FilePath] -> m () Source #
modifyAbsoluteIncludePaths :: MonadTCState m => ([AbsolutePath] -> [AbsolutePath]) -> m () Source #
putAbsoluteIncludePaths :: MonadTCState m => [AbsolutePath] -> m () Source #
Include directories
type PersistentVerbosity = Verbosity Source #
class LensPersistentVerbosity a where Source #
getPersistentVerbosity :: a -> PersistentVerbosity Source #
setPersistentVerbosity :: PersistentVerbosity -> a -> a Source #
mapPersistentVerbosity :: (PersistentVerbosity -> PersistentVerbosity) -> a -> a Source #
Instances
modifyPersistentVerbosity :: MonadTCState m => (PersistentVerbosity -> PersistentVerbosity) -> m () Source #
putPersistentVerbosity :: MonadTCState m => PersistentVerbosity -> m () Source #