Copyright | (c) Fuzz Leonard 2025 |
---|---|
License | MIT |
Maintainer | fuzz@fuzz.ink |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Clod.Types
Description
This module defines the core types used throughout the Clod application. Clod is a utility for preparing and uploading files to Claude AI's Project Knowledge feature. It tracks file changes, respects .gitignore and .clodignore patterns, and optimizes filenames for Claude's UI.
The primary types include:
ClodConfig
- Configuration for file processing and stagingClodM
- A monad for handling errors during file operationsClodError
- Various error types that can occur during operationFileResult
- Result of processing a file (success or skipped)
Synopsis
- data ClodConfig = ClodConfig {
- _projectPath :: !FilePath
- _stagingDir :: !FilePath
- _configDir :: !FilePath
- _databaseFile :: !FilePath
- _timestamp :: !String
- _currentStaging :: !FilePath
- _previousStaging :: !(Maybe FilePath)
- _testMode :: !Bool
- _verbose :: !Bool
- _flushMode :: !Bool
- _lastMode :: !Bool
- _ignorePatterns :: ![IgnorePattern]
- data FileResult
- data ClodError
- data DatabaseErrorType
- type ClodM a = ReaderT ClodConfig (ExceptT ClodError IO) a
- data FileEntry = FileEntry {}
- data ClodDatabase = ClodDatabase {
- _dbFiles :: !(Map FilePath FileEntry)
- _dbChecksums :: !(Map String FilePath)
- _dbLastStagingDir :: !(Maybe FilePath)
- _dbLastRunTime :: !UTCTime
- data SerializableClodDatabase = SerializableClodDatabase {
- serializedFiles :: ![(FilePath, FileEntry)]
- serializedChecksums :: ![(String, FilePath)]
- serializedLastStagingDir :: !(Maybe FilePath)
- serializedLastRunTime :: !UTCTime
- toSerializable :: ClodDatabase -> SerializableClodDatabase
- fromSerializable :: SerializableClodDatabase -> ClodDatabase
- data Validated a
- validatedToEither :: Validated a -> Either ClodError a
- eitherToValidated :: Either ClodError a -> Validated a
- runClodM :: ClodConfig -> ClodM a -> IO (Either ClodError a)
- throwError :: MonadError e m => e -> m a
- catchError :: MonadError e m => m a -> (e -> m a) -> m a
- liftIO :: MonadIO m => IO a -> m a
- ask :: MonadReader r m => m r
- asks :: MonadReader r m => (r -> a) -> m a
- local :: MonadReader r m => (r -> r) -> m a -> m a
- runReaderT :: ReaderT r m a -> r -> m a
- runExceptT :: ExceptT e m a -> m (Either e a)
- newtype IgnorePattern = IgnorePattern {}
- newtype OptimizedName = OptimizedName {}
- newtype OriginalPath = OriginalPath {}
- newtype Checksum = Checksum {
- unChecksum :: String
- data FileReadCap = FileReadCap {
- _allowedReadDirs :: [FilePath]
- data FileWriteCap = FileWriteCap {}
- fileReadCap :: [FilePath] -> FileReadCap
- fileWriteCap :: [FilePath] -> FileWriteCap
- isPathAllowed :: [FilePath] -> FilePath -> IO Bool
- (^.) :: s -> Getting a s a -> a
- (.~) :: ASetter s t a b -> b -> s -> t
- (%~) :: ASetter s t a b -> (a -> b) -> s -> t
- (&) :: a -> (a -> b) -> b
- projectPath :: Lens' ClodConfig FilePath
- stagingDir :: Lens' ClodConfig FilePath
- configDir :: Lens' ClodConfig FilePath
- databaseFile :: Lens' ClodConfig FilePath
- timestamp :: Lens' ClodConfig String
- currentStaging :: Lens' ClodConfig FilePath
- previousStaging :: Lens' ClodConfig (Maybe FilePath)
- testMode :: Lens' ClodConfig Bool
- verbose :: Lens' ClodConfig Bool
- flushMode :: Lens' ClodConfig Bool
- lastMode :: Lens' ClodConfig Bool
- ignorePatterns :: Lens' ClodConfig [IgnorePattern]
- dbFiles :: Lens' ClodDatabase (Map FilePath FileEntry)
- dbChecksums :: Lens' ClodDatabase (Map String FilePath)
- dbLastStagingDir :: Lens' ClodDatabase (Maybe FilePath)
- dbLastRunTime :: Lens' ClodDatabase UTCTime
- entryPath :: Lens' FileEntry FilePath
- entryChecksum :: Lens' FileEntry Checksum
- entryLastModified :: Lens' FileEntry UTCTime
- entryOptimizedName :: Lens' FileEntry OptimizedName
- allowedReadDirs :: Lens' FileReadCap [FilePath]
- allowedWriteDirs :: Lens' FileWriteCap [FilePath]
Core Types
data ClodConfig Source #
Configuration for the clod program
Constructors
ClodConfig | |
Fields
|
Instances
data FileResult Source #
Result of processing a file
Constructors
Success | File was successfully processed |
Skipped !String | File was skipped with the given reason |
Instances
Generic FileResult Source # | |||||
Defined in Clod.Types Associated Types
| |||||
Show FileResult Source # | |||||
Defined in Clod.Types Methods showsPrec :: Int -> FileResult -> ShowS # show :: FileResult -> String # showList :: [FileResult] -> ShowS # | |||||
Eq FileResult Source # | |||||
Defined in Clod.Types | |||||
type Rep FileResult Source # | |||||
Defined in Clod.Types type Rep FileResult = D1 ('MetaData "FileResult" "Clod.Types" "clod-0.2.3-inplace" 'False) (C1 ('MetaCons "Success" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Skipped" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 String))) |
Errors that can occur during Clod operation
These represent the different categories of errors that can occur during file processing, allowing for specific error handling for each case.
Constructors
FileSystemError !FilePath !IOError | Error related to filesystem operations |
ConfigError !String | Error related to configuration (e.g., invalid settings) |
PatternError !String | Error related to pattern matching (e.g., invalid pattern) |
CapabilityError !FilePath !String | Error related to capability validation with the path |
DatabaseError !FilePath !DatabaseErrorType | Error related to checksums database with file and type |
ChecksumError !FilePath !String | Error related to checksum calculation with the file |
Instances
Generic ClodError Source # | |||||
Defined in Clod.Types Associated Types
| |||||
Show ClodError Source # | |||||
Eq ClodError Source # | |||||
type Rep ClodError Source # | |||||
Defined in Clod.Types type Rep ClodError = D1 ('MetaData "ClodError" "Clod.Types" "clod-0.2.3-inplace" 'False) ((C1 ('MetaCons "FileSystemError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 FilePath) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 IOError)) :+: (C1 ('MetaCons "ConfigError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 String)) :+: C1 ('MetaCons "PatternError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 String)))) :+: (C1 ('MetaCons "CapabilityError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 FilePath) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 String)) :+: (C1 ('MetaCons "DatabaseError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 FilePath) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 DatabaseErrorType)) :+: C1 ('MetaCons "ChecksumError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 FilePath) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 String))))) |
data DatabaseErrorType Source #
Database error types for more specific error reporting
Constructors
DBFileNotFound | Database file could not be found |
DBCorrupted String | Database file is corrupted with details |
DBVersionMismatch | Database version is incompatible |
DBOtherError String | Other database error with description |
Instances
Generic DatabaseErrorType Source # | |||||
Defined in Clod.Types Associated Types
Methods from :: DatabaseErrorType -> Rep DatabaseErrorType x # to :: Rep DatabaseErrorType x -> DatabaseErrorType # | |||||
Show DatabaseErrorType Source # | |||||
Defined in Clod.Types Methods showsPrec :: Int -> DatabaseErrorType -> ShowS # show :: DatabaseErrorType -> String # showList :: [DatabaseErrorType] -> ShowS # | |||||
Eq DatabaseErrorType Source # | |||||
Defined in Clod.Types Methods (==) :: DatabaseErrorType -> DatabaseErrorType -> Bool # (/=) :: DatabaseErrorType -> DatabaseErrorType -> Bool # | |||||
type Rep DatabaseErrorType Source # | |||||
Defined in Clod.Types type Rep DatabaseErrorType = D1 ('MetaData "DatabaseErrorType" "Clod.Types" "clod-0.2.3-inplace" 'False) ((C1 ('MetaCons "DBFileNotFound" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DBCorrupted" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 String))) :+: (C1 ('MetaCons "DBVersionMismatch" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DBOtherError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 String)))) |
type ClodM a = ReaderT ClodConfig (ExceptT ClodError IO) a Source #
The Clod monad
This monad stack combines:
- Reader for dependency injection of ClodConfig
- Error handling with ExceptT for
ClodError
- IO for filesystem, git, and other side effects
This replaces the previous effects-based approach with a simpler, more traditional monad stack.
File entry in the checksum database
Constructors
FileEntry | |
Fields
|
Instances
FromDhall FileEntry Source # | |||||
Defined in Clod.Types Methods autoWith :: InputNormalizer -> Decoder FileEntry # | |||||
ToDhall FileEntry Source # | |||||
Defined in Clod.Types Methods | |||||
Generic FileEntry Source # | |||||
Defined in Clod.Types Associated Types
| |||||
Show FileEntry Source # | |||||
Eq FileEntry Source # | |||||
FromJSON FileEntry Source # | |||||
Defined in Clod.Types | |||||
ToJSON FileEntry Source # | |||||
type Rep FileEntry Source # | |||||
Defined in Clod.Types type Rep FileEntry = D1 ('MetaData "FileEntry" "Clod.Types" "clod-0.2.3-inplace" 'False) (C1 ('MetaCons "FileEntry" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_entryPath") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 FilePath) :*: S1 ('MetaSel ('Just "_entryChecksum") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Checksum)) :*: (S1 ('MetaSel ('Just "_entryLastModified") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UTCTime) :*: S1 ('MetaSel ('Just "_entryOptimizedName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 OptimizedName)))) |
data ClodDatabase Source #
Main database structure
Constructors
ClodDatabase | |
Fields
|
Instances
Generic ClodDatabase Source # | |||||
Defined in Clod.Types Associated Types
| |||||
Show ClodDatabase Source # | |||||
Defined in Clod.Types Methods showsPrec :: Int -> ClodDatabase -> ShowS # show :: ClodDatabase -> String # showList :: [ClodDatabase] -> ShowS # | |||||
Eq ClodDatabase Source # | |||||
Defined in Clod.Types | |||||
type Rep ClodDatabase Source # | |||||
Defined in Clod.Types type Rep ClodDatabase = D1 ('MetaData "ClodDatabase" "Clod.Types" "clod-0.2.3-inplace" 'False) (C1 ('MetaCons "ClodDatabase" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_dbFiles") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map FilePath FileEntry)) :*: S1 ('MetaSel ('Just "_dbChecksums") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map String FilePath))) :*: (S1 ('MetaSel ('Just "_dbLastStagingDir") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe FilePath)) :*: S1 ('MetaSel ('Just "_dbLastRunTime") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UTCTime)))) |
data SerializableClodDatabase Source #
Serialization-friendly version of ClodDatabase
Constructors
SerializableClodDatabase | |
Fields
|
Instances
FromDhall SerializableClodDatabase Source # | |||||
Defined in Clod.Types Methods autoWith :: InputNormalizer -> Decoder SerializableClodDatabase # | |||||
ToDhall SerializableClodDatabase Source # | |||||
Defined in Clod.Types Methods injectWith :: InputNormalizer -> Encoder SerializableClodDatabase # | |||||
Generic SerializableClodDatabase Source # | |||||
Defined in Clod.Types Associated Types
Methods from :: SerializableClodDatabase -> Rep SerializableClodDatabase x # to :: Rep SerializableClodDatabase x -> SerializableClodDatabase # | |||||
Show SerializableClodDatabase Source # | |||||
Defined in Clod.Types Methods showsPrec :: Int -> SerializableClodDatabase -> ShowS # show :: SerializableClodDatabase -> String # showList :: [SerializableClodDatabase] -> ShowS # | |||||
Eq SerializableClodDatabase Source # | |||||
Defined in Clod.Types Methods (==) :: SerializableClodDatabase -> SerializableClodDatabase -> Bool # (/=) :: SerializableClodDatabase -> SerializableClodDatabase -> Bool # | |||||
FromJSON SerializableClodDatabase Source # | |||||
Defined in Clod.Types Methods parseJSON :: Value -> Parser SerializableClodDatabase # parseJSONList :: Value -> Parser [SerializableClodDatabase] # | |||||
ToJSON SerializableClodDatabase Source # | |||||
Defined in Clod.Types Methods toJSON :: SerializableClodDatabase -> Value # toEncoding :: SerializableClodDatabase -> Encoding # toJSONList :: [SerializableClodDatabase] -> Value # | |||||
type Rep SerializableClodDatabase Source # | |||||
Defined in Clod.Types type Rep SerializableClodDatabase = D1 ('MetaData "SerializableClodDatabase" "Clod.Types" "clod-0.2.3-inplace" 'False) (C1 ('MetaCons "SerializableClodDatabase" 'PrefixI 'True) ((S1 ('MetaSel ('Just "serializedFiles") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [(FilePath, FileEntry)]) :*: S1 ('MetaSel ('Just "serializedChecksums") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [(String, FilePath)])) :*: (S1 ('MetaSel ('Just "serializedLastStagingDir") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe FilePath)) :*: S1 ('MetaSel ('Just "serializedLastRunTime") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UTCTime)))) |
toSerializable :: ClodDatabase -> SerializableClodDatabase Source #
Convert to serializable form
fromSerializable :: SerializableClodDatabase -> ClodDatabase Source #
Convert from serializable form
Validation types and functions
Validation type for collecting multiple errors This allows us to accumulate errors instead of stopping at the first one
validatedToEither :: Validated a -> Either ClodError a Source #
Convert from Validated to Either for compatibility
eitherToValidated :: Either ClodError a -> Validated a Source #
Convert from Either to Validated for integration
Type conversions and runners
runClodM :: ClodConfig -> ClodM a -> IO (Either ClodError a) Source #
Run a ClodM computation, returning either an error or a result
throwError :: MonadError e m => e -> m a #
Is used within a monadic computation to begin exception processing.
catchError :: MonadError e m => m a -> (e -> m a) -> m a #
A handler function to handle previous errors and return to normal execution. A common idiom is:
do { action1; action2; action3 } `catchError` handler
where the action
functions can call throwError
.
Note that handler
and the do-block must have the same return type.
liftIO :: MonadIO m => IO a -> m a #
Lift a computation from the IO
monad.
This allows us to run IO computations in any monadic stack, so long as it supports these kinds of operations
(i.e. IO
is the base monad for the stack).
Example
import Control.Monad.Trans.State -- from the "transformers" library printState :: Show s => StateT s IO () printState = do state <- get liftIO $ print state
Had we omitted
, we would have ended up with this error:liftIO
• Couldn't match type ‘IO’ with ‘StateT s IO’ Expected type: StateT s IO () Actual type: IO ()
The important part here is the mismatch between StateT s IO ()
and
.IO
()
Luckily, we know of a function that takes an
and returns an IO
a(m a)
:
,
enabling us to run the program and see the expected results:liftIO
> evalStateT printState "hello" "hello" > evalStateT printState 3 3
ask :: MonadReader r m => m r #
Retrieves the monad environment.
Arguments
:: MonadReader r m | |
=> (r -> a) | The selector function to apply to the environment. |
-> m a |
Retrieves a function of the current environment.
Arguments
:: MonadReader r m | |
=> (r -> r) | The function to modify the environment. |
-> m a |
|
-> m a |
Executes a computation in a modified environment.
runReaderT :: ReaderT r m a -> r -> m a #
runExceptT :: ExceptT e m a -> m (Either e a) #
The inverse of ExceptT
.
Newtypes for type safety
newtype IgnorePattern Source #
Newtype for ignore patterns to prevent mixing with other string types
Constructors
IgnorePattern | |
Fields |
Instances
Monoid IgnorePattern Source # | |
Defined in Clod.Types Methods mempty :: IgnorePattern # mappend :: IgnorePattern -> IgnorePattern -> IgnorePattern # mconcat :: [IgnorePattern] -> IgnorePattern # | |
Semigroup IgnorePattern Source # | |
Defined in Clod.Types Methods (<>) :: IgnorePattern -> IgnorePattern -> IgnorePattern # sconcat :: NonEmpty IgnorePattern -> IgnorePattern # stimes :: Integral b => b -> IgnorePattern -> IgnorePattern # | |
IsString IgnorePattern Source # | |
Defined in Clod.Types Methods fromString :: String -> IgnorePattern # | |
Show IgnorePattern Source # | |
Defined in Clod.Types Methods showsPrec :: Int -> IgnorePattern -> ShowS # show :: IgnorePattern -> String # showList :: [IgnorePattern] -> ShowS # | |
Eq IgnorePattern Source # | |
Defined in Clod.Types Methods (==) :: IgnorePattern -> IgnorePattern -> Bool # (/=) :: IgnorePattern -> IgnorePattern -> Bool # | |
Ord IgnorePattern Source # | |
Defined in Clod.Types Methods compare :: IgnorePattern -> IgnorePattern -> Ordering # (<) :: IgnorePattern -> IgnorePattern -> Bool # (<=) :: IgnorePattern -> IgnorePattern -> Bool # (>) :: IgnorePattern -> IgnorePattern -> Bool # (>=) :: IgnorePattern -> IgnorePattern -> Bool # max :: IgnorePattern -> IgnorePattern -> IgnorePattern # min :: IgnorePattern -> IgnorePattern -> IgnorePattern # |
newtype OptimizedName Source #
Newtype for optimized filename used in Claude's UI
Constructors
OptimizedName | |
Fields |
Instances
FromDhall OptimizedName Source # | |||||
Defined in Clod.Types Methods | |||||
ToDhall OptimizedName Source # | |||||
Defined in Clod.Types Methods | |||||
Monoid OptimizedName Source # | |||||
Defined in Clod.Types Methods mempty :: OptimizedName # mappend :: OptimizedName -> OptimizedName -> OptimizedName # mconcat :: [OptimizedName] -> OptimizedName # | |||||
Semigroup OptimizedName Source # | |||||
Defined in Clod.Types Methods (<>) :: OptimizedName -> OptimizedName -> OptimizedName # sconcat :: NonEmpty OptimizedName -> OptimizedName # stimes :: Integral b => b -> OptimizedName -> OptimizedName # | |||||
IsString OptimizedName Source # | |||||
Defined in Clod.Types Methods fromString :: String -> OptimizedName # | |||||
Generic OptimizedName Source # | |||||
Defined in Clod.Types Associated Types
| |||||
Show OptimizedName Source # | |||||
Defined in Clod.Types Methods showsPrec :: Int -> OptimizedName -> ShowS # show :: OptimizedName -> String # showList :: [OptimizedName] -> ShowS # | |||||
Eq OptimizedName Source # | |||||
Defined in Clod.Types Methods (==) :: OptimizedName -> OptimizedName -> Bool # (/=) :: OptimizedName -> OptimizedName -> Bool # | |||||
Ord OptimizedName Source # | |||||
Defined in Clod.Types Methods compare :: OptimizedName -> OptimizedName -> Ordering # (<) :: OptimizedName -> OptimizedName -> Bool # (<=) :: OptimizedName -> OptimizedName -> Bool # (>) :: OptimizedName -> OptimizedName -> Bool # (>=) :: OptimizedName -> OptimizedName -> Bool # max :: OptimizedName -> OptimizedName -> OptimizedName # min :: OptimizedName -> OptimizedName -> OptimizedName # | |||||
FromJSON OptimizedName Source # | |||||
Defined in Clod.Types Methods parseJSON :: Value -> Parser OptimizedName # parseJSONList :: Value -> Parser [OptimizedName] # | |||||
ToJSON OptimizedName Source # | |||||
Defined in Clod.Types Methods toJSON :: OptimizedName -> Value # toEncoding :: OptimizedName -> Encoding # toJSONList :: [OptimizedName] -> Value # toEncodingList :: [OptimizedName] -> Encoding # omitField :: OptimizedName -> Bool # | |||||
type Rep OptimizedName Source # | |||||
Defined in Clod.Types type Rep OptimizedName = D1 ('MetaData "OptimizedName" "Clod.Types" "clod-0.2.3-inplace" 'True) (C1 ('MetaCons "OptimizedName" 'PrefixI 'True) (S1 ('MetaSel ('Just "unOptimizedName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) |
newtype OriginalPath Source #
Newtype for original filepath in the repository
Constructors
OriginalPath | |
Fields |
Instances
FromDhall OriginalPath Source # | |||||
Defined in Clod.Types Methods | |||||
ToDhall OriginalPath Source # | |||||
Defined in Clod.Types Methods | |||||
Monoid OriginalPath Source # | |||||
Defined in Clod.Types Methods mempty :: OriginalPath # mappend :: OriginalPath -> OriginalPath -> OriginalPath # mconcat :: [OriginalPath] -> OriginalPath # | |||||
Semigroup OriginalPath Source # | |||||
Defined in Clod.Types Methods (<>) :: OriginalPath -> OriginalPath -> OriginalPath # sconcat :: NonEmpty OriginalPath -> OriginalPath # stimes :: Integral b => b -> OriginalPath -> OriginalPath # | |||||
IsString OriginalPath Source # | |||||
Defined in Clod.Types Methods fromString :: String -> OriginalPath # | |||||
Generic OriginalPath Source # | |||||
Defined in Clod.Types Associated Types
| |||||
Show OriginalPath Source # | |||||
Defined in Clod.Types Methods showsPrec :: Int -> OriginalPath -> ShowS # show :: OriginalPath -> String # showList :: [OriginalPath] -> ShowS # | |||||
Eq OriginalPath Source # | |||||
Defined in Clod.Types | |||||
Ord OriginalPath Source # | |||||
Defined in Clod.Types Methods compare :: OriginalPath -> OriginalPath -> Ordering # (<) :: OriginalPath -> OriginalPath -> Bool # (<=) :: OriginalPath -> OriginalPath -> Bool # (>) :: OriginalPath -> OriginalPath -> Bool # (>=) :: OriginalPath -> OriginalPath -> Bool # max :: OriginalPath -> OriginalPath -> OriginalPath # min :: OriginalPath -> OriginalPath -> OriginalPath # | |||||
FromJSON OriginalPath Source # | |||||
Defined in Clod.Types | |||||
ToJSON OriginalPath Source # | |||||
Defined in Clod.Types Methods toJSON :: OriginalPath -> Value # toEncoding :: OriginalPath -> Encoding # toJSONList :: [OriginalPath] -> Value # toEncodingList :: [OriginalPath] -> Encoding # omitField :: OriginalPath -> Bool # | |||||
type Rep OriginalPath Source # | |||||
Defined in Clod.Types type Rep OriginalPath = D1 ('MetaData "OriginalPath" "Clod.Types" "clod-0.2.3-inplace" 'True) (C1 ('MetaCons "OriginalPath" 'PrefixI 'True) (S1 ('MetaSel ('Just "unOriginalPath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) |
Newtype for file checksums to prevent mixing with other string types
Constructors
Checksum | |
Fields
|
Instances
FromDhall Checksum Source # | |||||
Defined in Clod.Types Methods autoWith :: InputNormalizer -> Decoder Checksum # | |||||
ToDhall Checksum Source # | |||||
Defined in Clod.Types Methods | |||||
Monoid Checksum Source # | |||||
Semigroup Checksum Source # | |||||
IsString Checksum Source # | |||||
Defined in Clod.Types Methods fromString :: String -> Checksum # | |||||
Generic Checksum Source # | |||||
Defined in Clod.Types Associated Types
| |||||
Show Checksum Source # | |||||
Eq Checksum Source # | |||||
Ord Checksum Source # | |||||
Defined in Clod.Types | |||||
FromJSON Checksum Source # | |||||
Defined in Clod.Types | |||||
ToJSON Checksum Source # | |||||
type Rep Checksum Source # | |||||
Defined in Clod.Types |
Capability types
data FileReadCap Source #
Capability for reading files within certain directories
Constructors
FileReadCap | |
Fields
|
Instances
Show FileReadCap Source # | |
Defined in Clod.Types Methods showsPrec :: Int -> FileReadCap -> ShowS # show :: FileReadCap -> String # showList :: [FileReadCap] -> ShowS # | |
Eq FileReadCap Source # | |
Defined in Clod.Types |
data FileWriteCap Source #
Capability for writing files within certain directories
Constructors
FileWriteCap | |
Fields
|
Instances
Show FileWriteCap Source # | |
Defined in Clod.Types Methods showsPrec :: Int -> FileWriteCap -> ShowS # show :: FileWriteCap -> String # showList :: [FileWriteCap] -> ShowS # | |
Eq FileWriteCap Source # | |
Defined in Clod.Types |
fileReadCap :: [FilePath] -> FileReadCap Source #
Create a file read capability for specified directories
fileWriteCap :: [FilePath] -> FileWriteCap Source #
Create a file write capability for specified directories
Path validation
isPathAllowed :: [FilePath] -> FilePath -> IO Bool Source #
Check if a path is within allowed directories This improved version handles path traversal attacks by comparing canonical paths
Lens operators and accessors
(^.) :: s -> Getting a s a -> a infixl 8 #
View the value pointed to by a Getter
or Lens
or the
result of folding over all the results of a Fold
or
Traversal
that points at a monoidal values.
This is the same operation as view
with the arguments flipped.
The fixity and semantics are such that subsequent field accesses can be
performed with (.
).
>>>
(a,b)^._2
b
>>>
("hello","world")^._2
"world"
>>>
import Data.Complex
>>>
((0, 1 :+ 2), 3)^._1._2.to magnitude
2.23606797749979
(^.
) :: s ->Getter
s a -> a (^.
) ::Monoid
m => s ->Fold
s m -> m (^.
) :: s ->Iso'
s a -> a (^.
) :: s ->Lens'
s a -> a (^.
) ::Monoid
m => s ->Traversal'
s m -> m
(.~) :: ASetter s t a b -> b -> s -> t infixr 4 #
Replace the target of a Lens
or all of the targets of a Setter
or Traversal
with a constant value.
This is an infix version of set
, provided for consistency with (.=
).
f<$
a ≡mapped
.~
f$
a
>>>
(a,b,c,d) & _4 .~ e
(a,b,c,e)
>>>
(42,"world") & _1 .~ "hello"
("hello","world")
>>>
(a,b) & both .~ c
(c,c)
(.~
) ::Setter
s t a b -> b -> s -> t (.~
) ::Iso
s t a b -> b -> s -> t (.~
) ::Lens
s t a b -> b -> s -> t (.~
) ::Traversal
s t a b -> b -> s -> t
(%~) :: ASetter s t a b -> (a -> b) -> s -> t infixr 4 #
Modifies the target of a Lens
or all of the targets of a Setter
or
Traversal
with a user supplied function.
This is an infix version of over
.
fmap
f ≡mapped
%~
ffmapDefault
f ≡traverse
%~
f
>>>
(a,b,c) & _3 %~ f
(a,b,f c)
>>>
(a,b) & both %~ f
(f a,f b)
>>>
_2 %~ length $ (1,"hello")
(1,5)
>>>
traverse %~ f $ [a,b,c]
[f a,f b,f c]
>>>
traverse %~ even $ [1,2,3]
[False,True,False]
>>>
traverse.traverse %~ length $ [["hello","world"],["!!!"]]
[[5,5],[3]]
(%~
) ::Setter
s t a b -> (a -> b) -> s -> t (%~
) ::Iso
s t a b -> (a -> b) -> s -> t (%~
) ::Lens
s t a b -> (a -> b) -> s -> t (%~
) ::Traversal
s t a b -> (a -> b) -> s -> t
(&) :: a -> (a -> b) -> b infixl 1 #
&
is a reverse application operator. This provides notational
convenience. Its precedence is one higher than that of the forward
application operator $
, which allows &
to be nested in $
.
This is a version of
, where flip
id
id
is specialized from a -> a
to (a -> b) -> (a -> b)
which by the associativity of (->)
is (a -> b) -> a -> b
.
flipping this yields a -> (a -> b) -> b
which is the type signature of &
Examples
>>>
5 & (+1) & show
"6"
>>>
sqrt $ [1 / n^2 | n <- [1..1000]] & sum & (*6)
3.1406380562059946
Since: base-4.8.0.0
Field lenses for ClodConfig
projectPath :: Lens' ClodConfig FilePath Source #
Lens for projectPath field
stagingDir :: Lens' ClodConfig FilePath Source #
Lens for stagingDir field
databaseFile :: Lens' ClodConfig FilePath Source #
Lens for databaseFile field
currentStaging :: Lens' ClodConfig FilePath Source #
Lens for currentStaging field
previousStaging :: Lens' ClodConfig (Maybe FilePath) Source #
Lens for previousStaging field
ignorePatterns :: Lens' ClodConfig [IgnorePattern] Source #
Lens for ignorePatterns field
Field lenses for ClodDatabase
dbChecksums :: Lens' ClodDatabase (Map String FilePath) Source #
Lens for dbChecksums field
dbLastStagingDir :: Lens' ClodDatabase (Maybe FilePath) Source #
Lens for dbLastStagingDir field
dbLastRunTime :: Lens' ClodDatabase UTCTime Source #
Lens for dbLastRunTime field
Field lenses for FileEntry
entryOptimizedName :: Lens' FileEntry OptimizedName Source #
Lens for entryOptimizedName field
Field lenses for capability types
allowedReadDirs :: Lens' FileReadCap [FilePath] Source #
Lens for allowedReadDirs field
allowedWriteDirs :: Lens' FileWriteCap [FilePath] Source #
Lens for allowedWriteDirs field