| Safe Haskell | None | 
|---|
Snap.Snaplet.ActionLog
- data ActionLog
- initActionLog :: (HasActionLog (Handler b b), HasHeist b) => Snaplet (Heist b) -> SnapletInit b ActionLog
- class HasPersistPool m => HasActionLog m  where- alGetTenantId :: m Int
- alGetAuthUserId :: m Int
- alGetTime :: m UTCTime
- alGetName :: Int -> m Text
- alCustomCSplices :: [(Text, Promise (Entity LoggedAction) -> Splice m)]
- alCustomISplices :: Entity LoggedAction -> [(Text, Splice m)]
 
- data ActionType
- actionToInt :: ActionType -> Int
- intToAction :: Int -> Either Text ActionType
- class  DeltaField a  where- toBS :: a -> ByteString
 
- class  CanDelta a  where- deltaFields :: [(Text, a -> ByteString)]
 
- storeDeltas :: (HasPersistPool m, CanDelta a) => LoggedActionId -> a -> a -> m ()
- getDeltas :: CanDelta a => a -> a -> [(Text, ByteString, ByteString)]
- getLoggedAction :: HasPersistPool m => LoggedActionId -> m (Maybe LoggedAction)
- getEntityActions :: HasPersistPool m => Text -> Int -> m [Entity LoggedAction]
- getAllActions :: HasPersistPool m => m [Entity LoggedAction]
- getTenantActions :: HasActionLog m => [Filter LoggedAction] -> [SelectOpt LoggedAction] -> m [Entity LoggedAction]
- getTenantEntities :: HasActionLog m => m [Text]
- getTenantUids :: HasActionLog m => m [Int]
- logAction :: HasActionLog m => Text -> Int -> ActionType -> m (Key LoggedAction)
- loggedInsert :: (PersistEntity a, HasActionLog m, PersistEntityBackend a ~ SqlBackend) => a -> m (Key a)
- loggedReplace :: (PersistEntity a, CanDelta a, HasActionLog m, PersistEntityBackend a ~ SqlBackend) => Key a -> a -> m ()
- loggedUpdate :: (PersistEntity a, CanDelta a, HasActionLog m, PersistEntityBackend a ~ SqlBackend) => Key a -> [Update a] -> m ()
- loggedDelete :: forall m a. (HasActionLog m, PersistEntity a, PersistEntityBackend a ~ SqlBackend) => Entity a -> m ()
- loggedDeleteKey :: (PersistEntity a, HasActionLog m, PersistEntityBackend a ~ SqlBackend) => Key a -> m ()
- actionLogEntityDefs :: [EntityDef SqlType]
- migrateActionLog :: forall m. (MonadBaseControl IO m, MonadIO m, MonadLogger m) => Migration (SqlPersistT m)
- data LoggedActionGeneric backend = LoggedAction {}
- type LoggedAction = LoggedActionGeneric SqlBackend
- type LoggedActionId = KeyBackend SqlBackend LoggedAction
- data  LoggedActionDetailsGeneric backend = LoggedActionDetails {- loggedActionDetailsActionId :: !(KeyBackend backend (LoggedActionGeneric backend))
- loggedActionDetailsFieldName :: !Text
- loggedActionDetailsOldValue :: !Text
- loggedActionDetailsNewValue :: !Text
 
- type LoggedActionDetails = LoggedActionDetailsGeneric SqlBackend
- type LoggedActionDetailsId = KeyBackend SqlBackend LoggedActionDetails
Core types and functions
initActionLog :: (HasActionLog (Handler b b), HasHeist b) => Snaplet (Heist b) -> SnapletInit b ActionLogSource
Initializer for the action log snaplet. It sets up templates, routes, and compiled and interpreted splices.
Includes two built-in top level splices: actionLogListing and actionLogFilterForm
class HasPersistPool m => HasActionLog m whereSource
Type class that must be implemented to have an action log. You do not have to have any custom splices. If you don't need to add splices to what the snaplet provides by default, just have the custom splice functions return an empty list.
One potential use for the custom splices might be if you want to display your own custom information in action log lists. Maybe you want to display a user email address in addition to their name, or maybe instead of displaying raw entity IDs you want to do some DB query to get a different field for display. The custom splices allow you to make any runtime function of a LoggedAction into a splice that can be displayed in action log templates.
Methods
alGetTenantId :: m IntSource
Gets a tenant ID for the current user of your application. If your application is not multi-tenanted, then you can just return a constant here.
alGetAuthUserId :: m IntSource
Gets the current user's user ID. Again, if your application does not have the concept of a user, you can return a constant.
In latency sensitive applications where time stamps are used frequently, you may want to do the system call once and then cache the results. This function allows you to provide your own cache-aware version of getTime if you choose. Otherwise you can just lift the getCurrentTime function from Data.Time.Clock into your monad.
alGetName :: Int -> m TextSource
Function that takes a user ID and returns the user's name, email, or whatever you want the snaplet to call that user. This function is used to generate the user dropdown box in action log filter controls.
alCustomCSplices :: [(Text, Promise (Entity LoggedAction) -> Splice m)]Source
Complied version of any custom splices that you want to be available
 inside the actionLogListing splice.
alCustomISplices :: Entity LoggedAction -> [(Text, Splice m)]Source
Interpreted version of any custom splices that you want to be
 available inside the actionLogListing splice.
data ActionType Source
Enumeration of possible actions in the action log.
Constructors
| CreateAction | |
| UpdateAction | |
| DeleteAction | 
Instances
| Bounded ActionType | |
| Enum ActionType | |
| Eq ActionType | |
| Ord ActionType | |
| Show ActionType | Use human readable names for the Show instance. | 
| PersistFieldSql ActionType | |
| PersistField ActionType | We need to derive PersistField so ActionType can be a column in the LoggedAction table. | 
| Readable ActionType | Use human readable names for the Show instance. | 
| PrimSplice ActionType | Create primitive splices using the show instance. | 
actionToInt :: ActionType -> IntSource
Converts an ActionType into an Int to be stored in the database. We don't want to use fromEnum here because that will make the numbers sensitive to the ordering of the data type and easier to screw up.
intToAction :: Int -> Either Text ActionTypeSource
Converts an Int into an ActionType. Again, we want this to be explicit rather than implied by toEnum.
class DeltaField a whereSource
To store deltas, you need to be able to get Text representations of each field.
Methods
toBS :: a -> ByteStringSource
Instances
Methods
deltaFields :: [(Text, a -> ByteString)]Source
storeDeltas :: (HasPersistPool m, CanDelta a) => LoggedActionId -> a -> a -> m ()Source
Calculates a list of fields that changed along with ByteString representations of their old and new values.
getDeltas :: CanDelta a => a -> a -> [(Text, ByteString, ByteString)]Source
Calculates a list of fields that changed along with ByteString representations of their old and new values.
Retrieving actions
getLoggedAction :: HasPersistPool m => LoggedActionId -> m (Maybe LoggedAction)Source
Gets the LoggedAction entry for the specified entity and id.
getEntityActions :: HasPersistPool m => Text -> Int -> m [Entity LoggedAction]Source
Gets the LoggedAction entry for the specified entity and id.
getAllActions :: HasPersistPool m => m [Entity LoggedAction]Source
Gets all the actions in the action log. In multi-tenant applications you probably want this to only be accessible by the administrator of the whole site.
getTenantActions :: HasActionLog m => [Filter LoggedAction] -> [SelectOpt LoggedAction] -> m [Entity LoggedAction]Source
Gets all the logged actions for the current tenant.
getTenantEntities :: HasActionLog m => m [Text]Source
Gets a list of all entities for a specific tenant.
getTenantUids :: HasActionLog m => m [Int]Source
Gets a list of all uids for a specific tenant.
Storing actions
These functions provide a nice API for logging actions based on database
 operations.  Typically you should be able to simply substitute the
 loggedInsert, loggedUpdate, etc functions in the place of your existing
 calls to insert, update, etc from the persistent library.
Arguments
| :: HasActionLog m | |
| => Text | Entity name. If you are logging database modifications, then this might be the name of the table being operated on. | 
| -> Int | Entity ID. This is the primary key for the affected row. | 
| -> ActionType | Type of action, such as create, update, or delete. | 
| -> m (Key LoggedAction) | 
Low level function for logging an action.  Usually you will want to use
 one of the other functions like loggedInsert.  But when those aren't
 sufficient, this function provides you maximum control to log actions as
 you see fit.
loggedInsert :: (PersistEntity a, HasActionLog m, PersistEntityBackend a ~ SqlBackend) => a -> m (Key a)Source
Performs a logged insert into the database.  Just about everything should
 be inserted using this function instead of runPersist' . insert
loggedReplace :: (PersistEntity a, CanDelta a, HasActionLog m, PersistEntityBackend a ~ SqlBackend) => Key a -> a -> m ()Source
Performs a logged replace of a database record.
loggedUpdate :: (PersistEntity a, CanDelta a, HasActionLog m, PersistEntityBackend a ~ SqlBackend) => Key a -> [Update a] -> m ()Source
Performs a logged update of a database record.
loggedDelete :: forall m a. (HasActionLog m, PersistEntity a, PersistEntityBackend a ~ SqlBackend) => Entity a -> m ()Source
Performs a logged delete of an entity in the database.
loggedDeleteKey :: (PersistEntity a, HasActionLog m, PersistEntityBackend a ~ SqlBackend) => Key a -> m ()Source
Performs a logged delete of a key in the database.
Types
actionLogEntityDefs :: [EntityDef SqlType]Source
The list of entity definitions this snaplet exposes. You need them so that you can append to your application's list of entity definitions and perform the migration in one block.
Here's an example of how to combine your app's own entity definitions and the action log's in one migration block:
 share [mkMigrate "migrateAll"] $
    actionLogEntityDefs ++
    $(persistFileWith lowerCaseSettings "schema.txt")
migrateActionLog :: forall m. (MonadBaseControl IO m, MonadIO m, MonadLogger m) => Migration (SqlPersistT m)Source
data LoggedActionGeneric backend Source
Constructors
| LoggedAction | |
| Fields | |
Instances
| PrimSplice LoggedActionId | |
| PersistFieldSql (LoggedActionGeneric backend) | |
| PersistEntity (LoggedActionGeneric backend) | |
| PersistField (LoggedActionGeneric backend) | 
data LoggedActionDetailsGeneric backend Source
Constructors
| LoggedActionDetails | |
| Fields 
 | |
Instances
| PersistFieldSql (LoggedActionDetailsGeneric backend) | |
| PersistEntity (LoggedActionDetailsGeneric backend) | |
| PersistField (LoggedActionDetailsGeneric backend) |