Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
A module for working with Firefox profiles. Firefox profiles are manipulated in pure code and then "prepared" for network transmission.
Synopsis
- data Firefox
- data Profile b = Profile {}
- data PreparedProfile b
- defaultProfile :: Profile Firefox
- data ProfilePref
- = PrefInteger !Integer
- | PrefDouble !Double
- | PrefString !Text
- | PrefBool !Bool
- class ToPref a where
- toPref :: a -> ProfilePref
- addPref :: ToPref a => Text -> a -> Profile b -> Profile b
- getPref :: Text -> Profile b -> Maybe ProfilePref
- deletePref :: Text -> Profile b -> Profile b
- addExtension :: FilePath -> Profile b -> Profile b
- deleteExtension :: String -> Profile b -> Profile b
- hasExtension :: String -> Profile b -> Bool
- addFile :: FilePath -> FilePath -> Profile b -> Profile b
- deleteFile :: FilePath -> Profile b -> Profile b
- hasFile :: String -> Profile b -> Bool
- unionProfiles :: Profile b -> Profile b -> Profile b
- onProfileFiles :: Profile b -> (HashMap FilePath FilePath -> HashMap FilePath FilePath) -> Profile b
- onProfilePrefs :: Profile b -> (HashMap Text ProfilePref -> HashMap Text ProfilePref) -> Profile b
- prepareProfile :: MonadBaseControl IO m => Profile Firefox -> m (PreparedProfile Firefox)
- prepareTempProfile :: MonadBaseControl IO m => (Profile Firefox -> Profile Firefox) -> m (PreparedProfile Firefox)
- loadProfile :: MonadBaseControl IO m => FilePath -> m (Profile Firefox)
- prepareLoadedProfile :: MonadBaseControl IO m => FilePath -> (Profile Firefox -> Profile Firefox) -> m (PreparedProfile Firefox)
- prepareLoadedProfile_ :: MonadBase IO m => FilePath -> m (PreparedProfile a)
- prepareZippedProfile :: MonadBase IO m => FilePath -> m (PreparedProfile a)
- prepareZipArchive :: Archive -> PreparedProfile a
- prepareRawZip :: ByteString -> PreparedProfile a
- newtype ProfileParseError = ProfileParseError String
Profiles
Phantom type used in the parameters of Profile
and PreparedProfile
This structure allows you to construct and manipulate profiles in pure code, deferring execution of IO operations until the profile is "prepared". This type is shared by both Firefox and Opera profiles; when a distinction must be made, the phantom type parameter is used to differentiate.
Profile | |
|
data PreparedProfile b Source #
Represents a profile that has been prepared for network transmission. The profile cannot be modified in this form.
Instances
FromJSON (PreparedProfile s) Source # | |
Defined in Test.WebDriver.Common.Profile parseJSON :: Value -> Parser (PreparedProfile s) # parseJSONList :: Value -> Parser [PreparedProfile s] # | |
ToJSON (PreparedProfile s) Source # | |
Defined in Test.WebDriver.Common.Profile toJSON :: PreparedProfile s -> Value # toEncoding :: PreparedProfile s -> Encoding # toJSONList :: [PreparedProfile s] -> Value # toEncodingList :: [PreparedProfile s] -> Encoding # | |
Show (PreparedProfile b) Source # | |
Defined in Test.WebDriver.Common.Profile showsPrec :: Int -> PreparedProfile b -> ShowS # show :: PreparedProfile b -> String # showList :: [PreparedProfile b] -> ShowS # | |
Eq (PreparedProfile b) Source # | |
Defined in Test.WebDriver.Common.Profile (==) :: PreparedProfile b -> PreparedProfile b -> Bool # (/=) :: PreparedProfile b -> PreparedProfile b -> Bool # |
defaultProfile :: Profile Firefox Source #
Default Firefox Profile, used when no profile is supplied.
Preferences
data ProfilePref Source #
A profile preference value. This is the subset of JSON values that excludes arrays, objects, and null.
Instances
FromJSON ProfilePref Source # | |
Defined in Test.WebDriver.Common.Profile parseJSON :: Value -> Parser ProfilePref # parseJSONList :: Value -> Parser [ProfilePref] # | |
ToJSON ProfilePref Source # | |
Defined in Test.WebDriver.Common.Profile toJSON :: ProfilePref -> Value # toEncoding :: ProfilePref -> Encoding # toJSONList :: [ProfilePref] -> Value # toEncodingList :: [ProfilePref] -> Encoding # | |
Show ProfilePref Source # | |
Defined in Test.WebDriver.Common.Profile showsPrec :: Int -> ProfilePref -> ShowS # show :: ProfilePref -> String # showList :: [ProfilePref] -> ShowS # | |
Eq ProfilePref Source # | |
Defined in Test.WebDriver.Common.Profile (==) :: ProfilePref -> ProfilePref -> Bool # (/=) :: ProfilePref -> ProfilePref -> Bool # | |
ToPref ProfilePref Source # | |
Defined in Test.WebDriver.Common.Profile toPref :: ProfilePref -> ProfilePref Source # |
A typeclass to convert types to profile preference values
toPref :: a -> ProfilePref Source #
Instances
addPref :: ToPref a => Text -> a -> Profile b -> Profile b Source #
Add a new preference entry to a profile, overwriting any existing entry with the same key.
getPref :: Text -> Profile b -> Maybe ProfilePref Source #
Retrieve a preference from a profile by key name.
deletePref :: Text -> Profile b -> Profile b Source #
Delete an existing preference entry from a profile. This operation is silent if the preference wasn't found.
Extensions
addExtension :: FilePath -> Profile b -> Profile b Source #
Add a new extension to the profile. The file path should refer to a .xpi file or an extension directory on the filesystem.
deleteExtension :: String -> Profile b -> Profile b Source #
Delete an existing extension from the profile. The string parameter should refer to an .xpi file or directory located within the extensions directory of the profile. This operation has no effect if the extension was never added to the profile.
hasExtension :: String -> Profile b -> Bool Source #
Determines if a profile contains the given extension. specified as an .xpi file or directory name
Other files and directories
addFile :: FilePath -> FilePath -> Profile b -> Profile b Source #
Add a file to the profile directory. The first argument is the source of the file on the local filesystem. The second argument is the destination as a path relative to a profile directory. Overwrites any file that previously pointed to the same destination
deleteFile :: FilePath -> Profile b -> Profile b Source #
Delete a file from the profile directory. The first argument is the name of file within the profile directory.
hasFile :: String -> Profile b -> Bool Source #
Determines if a profile contains the given file, specified as a path relative to the profile directory.
Miscellaneous profile operations
unionProfiles :: Profile b -> Profile b -> Profile b Source #
Takes the union of two profiles. This is the union of their HashMap
fields.
onProfileFiles :: Profile b -> (HashMap FilePath FilePath -> HashMap FilePath FilePath) -> Profile b Source #
Modifies the profileFiles
field of a profile
onProfilePrefs :: Profile b -> (HashMap Text ProfilePref -> HashMap Text ProfilePref) -> Profile b Source #
Modifies the profilePrefs
field of a profile.
Loading and preparing profiles
prepareProfile :: MonadBaseControl IO m => Profile Firefox -> m (PreparedProfile Firefox) Source #
Prepare a firefox profile for network transmission. Internally, this function constructs a Firefox profile within a temp directory, archives it as a zip file, and then base64 encodes the zipped data. The temporary directory is deleted afterwards.
NOTE: because this function has to copy the profile files into a
a temp directory before zip archiving them, this operation is likely to be slow
for large profiles. In such a case, consider using prepareLoadedProfile_
or
prepareZippedProfile
instead.
prepareTempProfile :: MonadBaseControl IO m => (Profile Firefox -> Profile Firefox) -> m (PreparedProfile Firefox) Source #
Apply a function on a default profile, and prepare the result. The Profile passed to the handler function is the default profile used by sessions when Nothing is specified
Preparing profiles from disk
loadProfile :: MonadBaseControl IO m => FilePath -> m (Profile Firefox) Source #
Load an existing profile from the file system. Any prepared changes made to
the Profile
will have no effect to the profile on disk.
To make automated browser run smoothly, preferences found in
defaultProfile
are automatically merged into the preferences of the on-disk-- profile. The on-disk profile's preference will override those found in the
default profile.
prepareLoadedProfile :: MonadBaseControl IO m => FilePath -> (Profile Firefox -> Profile Firefox) -> m (PreparedProfile Firefox) Source #
Convenience function to load an existing Firefox profile from disk, apply a handler function, and then prepare the result for network transmission.
NOTE: like prepareProfile
, the same caveat about large profiles applies.
prepareLoadedProfile_ :: MonadBase IO m => FilePath -> m (PreparedProfile a) Source #
Efficiently load an existing profile from disk and prepare it for network transmission.
Preparing zip archives
prepareZippedProfile :: MonadBase IO m => FilePath -> m (PreparedProfile a) Source #
Prepare a zip file of a profile on disk for network transmission. This function is very efficient at loading large profiles from disk.
prepareZipArchive :: Archive -> PreparedProfile a Source #
Prepare a zip archive of a profile for network transmission.
prepareRawZip :: ByteString -> PreparedProfile a Source #
Prepare a ByteString of raw zip data for network transmission
Preferences parsing error
newtype ProfileParseError Source #
An error occured while attempting to parse a profile's preference file.
Instances
Exception ProfileParseError Source # | |
Defined in Test.WebDriver.Common.Profile | |
Read ProfileParseError Source # | |
Defined in Test.WebDriver.Common.Profile | |
Show ProfileParseError Source # | |
Defined in Test.WebDriver.Common.Profile showsPrec :: Int -> ProfileParseError -> ShowS # show :: ProfileParseError -> String # showList :: [ProfileParseError] -> ShowS # | |
Eq ProfileParseError Source # | |
Defined in Test.WebDriver.Common.Profile (==) :: ProfileParseError -> ProfileParseError -> Bool # (/=) :: ProfileParseError -> ProfileParseError -> Bool # |