yesod-core-1.4.9.1: Creation of type-safe, RESTful web applications.

Safe HaskellNone
LanguageHaskell98

Yesod.Core

Contents

Synopsis

Type classes

class RenderRoute site => Yesod site where Source

Define settings for a Yesod applications. All methods have intelligent defaults, and therefore no implementation is required.

Minimal complete definition

Nothing

Methods

approot :: Approot site Source

An absolute URL to the root of the application. Do not include trailing slash.

Default value: ApprootRelative. This is valid under the following conditions:

  • Your application is served from the root of the domain.
  • You do not use any features that require absolute URLs, such as Atom feeds and XML sitemaps.

If this is not true, you should override with a different implementation.

errorHandler :: ErrorResponse -> HandlerT site IO TypedContent Source

Output error response pages.

Default value: defaultErrorHandler.

defaultLayout :: WidgetT site IO () -> HandlerT site IO Html Source

Applies some form of layout to the contents of a page.

urlRenderOverride :: site -> Route site -> Maybe Builder Source

Override the rendering function for a particular URL. One use case for this is to offload static hosting to a different domain name to avoid sending cookies.

isAuthorized Source

Arguments

:: Route site 
-> Bool

is this a write request?

-> HandlerT site IO AuthResult 

Determine if a request is authorized or not.

Return Authorized if the request is authorized, Unauthorized a message if unauthorized. If authentication is required, return AuthenticationRequired.

isWriteRequest :: Route site -> HandlerT site IO Bool Source

Determines whether the current request is a write request. By default, this assumes you are following RESTful principles, and determines this from request method. In particular, all except the following request methods are considered write: GET HEAD OPTIONS TRACE.

This function is used to determine if a request is authorized; see isAuthorized.

authRoute :: site -> Maybe (Route site) Source

The default route for authentication.

Used in particular by isAuthorized, but library users can do whatever they want with it.

cleanPath :: site -> [Text] -> Either [Text] [Text] Source

A function used to clean up path segments. It returns Right with a clean path or Left with a new set of pieces the user should be redirected to. The default implementation enforces:

  • No double slashes
  • There is no trailing slash.

Note that versions of Yesod prior to 0.7 used a different set of rules involing trailing slashes.

joinPath Source

Arguments

:: site 
-> Text

application root

-> [Text]

path pieces

-> [(Text, Text)]

query string

-> Builder 

Builds an absolute URL by concatenating the application root with the pieces of a path and a query string, if any. Note that the pieces of the path have been previously cleaned up by cleanPath.

addStaticContent Source

Arguments

:: Text

filename extension

-> Text

mime-type

-> ByteString

content

-> HandlerT site IO (Maybe (Either Text (Route site, [(Text, Text)]))) 

This function is used to store some static content to be served as an external file. The most common case of this is stashing CSS and JavaScript content in an external file; the Yesod.Widget module uses this feature.

The return value is Nothing if no storing was performed; this is the default implementation. A Just Left gives the absolute URL of the file, whereas a Just Right gives the type-safe URL. The former is necessary when you are serving the content outside the context of a Yesod application, such as via memcached.

maximumContentLength :: site -> Maybe (Route site) -> Maybe Word64 Source

Maximum allowed length of the request body, in bytes.

If Nothing, no maximum is applied.

Default: 2 megabytes.

makeLogger :: site -> IO Logger Source

Creates a Logger to use for log messages.

Note that a common technique (endorsed by the scaffolding) is to create a Logger value and place it in your foundation datatype, and have this method return that already created value. That way, you can use that same Logger for printing messages during app initialization.

Default: Sends to stdout and automatically flushes on each write.

messageLoggerSource Source

Arguments

:: site 
-> Logger 
-> Loc

position in source code

-> LogSource 
-> LogLevel 
-> LogStr

message

-> IO () 

Send a message to the Logger provided by getLogger.

Default implementation: checks if the message should be logged using shouldLog and, if so, formats using formatLogMessage.

jsLoader :: site -> ScriptLoadPosition site Source

Where to Load sripts from. We recommend the default value, BottomOfBody. Alternatively use the built in async yepnope loader:

BottomOfHeadAsync $ loadJsYepnope $ Right $ StaticR js_modernizr_js

Or write your own async js loader.

makeSessionBackend :: site -> IO (Maybe SessionBackend) Source

Create a session backend. Returning Nothing disables sessions. If you'd like to change the way that the session cookies are created, take a look at customizeSessionCookies.

Default: Uses clientsession with a 2 hour timeout.

fileUpload :: site -> RequestBodyLength -> FileUpload Source

How to store uploaded files.

Default: When the request body is greater than 50kb, store in a temp file. For chunked request bodies, store in a temp file. Otherwise, store in memory.

shouldLog :: site -> LogSource -> LogLevel -> Bool Source

Should we log the given log source/level combination.

Default: Logs everything at or above logLevel

shouldLogIO :: site -> LogSource -> LogLevel -> IO Bool Source

Should we log the given log source/level combination.

Note that this is almost identical to shouldLog, except the result lives in IO. This allows you to dynamically alter the logging level of your application by having this result depend on, e.g., an IORef.

The default implementation simply uses shouldLog. Future versions of Yesod will remove shouldLog and use this method exclusively.

Since 1.2.4

yesodMiddleware :: ToTypedContent res => HandlerT site IO res -> HandlerT site IO res Source

A Yesod middleware, which will wrap every handler function. This allows you to run code before and after a normal handler.

Default: the defaultYesodMiddleware function.

Since: 1.1.6

yesodWithInternalState :: site -> Maybe (Route site) -> (InternalState -> IO a) -> IO a Source

How to allocate an InternalState for each request.

The default implementation is almost always what you want. However, if you know that you are never taking advantage of the MonadResource instance in your handler functions, setting this to a dummy implementation can provide a small optimization. Only do this if you really know what you're doing, otherwise you can turn safe code into a runtime error!

Since 1.4.2

Instances

class Yesod site => YesodDispatch site where Source

This class is automatically instantiated when you use the template haskell mkYesod function. You should never need to deal with it directly.

class Eq (Route a) => RenderRoute a where Source

Associated Types

data Route a Source

The type-safe URLs associated with a site argument.

Methods

renderRoute Source

Arguments

:: Route a 
-> ([Text], [(Text, Text)])

The path of the URL split on forward slashes, and a list of query parameters with their associated value.

class RenderRoute a => ParseRoute a where Source

Methods

parseRoute Source

Arguments

:: ([Text], [(Text, Text)])

The path of the URL split on forward slashes, and a list of query parameters with their associated value.

-> Maybe (Route a) 

class RenderRoute a => RouteAttrs a where Source

Methods

routeAttrs Source

Arguments

:: Route a 
-> Set Text

A set of attributes associated with the route.

Breadcrumbs

class YesodBreadcrumbs site where Source

A type-safe, concise method of creating breadcrumbs for pages. For each resource, you declare the title of the page and the parent resource (if present).

Methods

breadcrumb :: Route site -> HandlerT site IO (Text, Maybe (Route site)) Source

Returns the title and the parent resource, if available. If you return a Nothing, then this is considered a top-level page.

breadcrumbs :: YesodBreadcrumbs site => HandlerT site IO (Text, [(Route site, Text)]) Source

Gets the title of the current page and the hierarchy of parent pages, along with their respective titles.

Types

data Approot master Source

How to determine the root of the application for constructing URLs.

Note that future versions of Yesod may add new constructors without bumping the major version number. As a result, you should not pattern match on Approot values.

Constructors

ApprootRelative

No application root.

ApprootStatic !Text 
ApprootMaster !(master -> Text) 
ApprootRequest !(master -> Request -> Text) 

data FileUpload Source

Constructors

FileUploadMemory !(BackEnd ByteString) 
FileUploadDisk !(InternalState -> BackEnd FilePath) 
FileUploadSource !(BackEnd (Source (ResourceT IO) ByteString)) 

data ErrorResponse Source

Responses to indicate some form of an error occurred.

Utitlities

maybeAuthorized Source

Arguments

:: Yesod site 
=> Route site 
-> Bool

is this a write request?

-> HandlerT site IO (Maybe (Route site)) 

Return the same URL if the user is authorized to see it.

Built on top of isAuthorized. This is useful for building page that only contain links to pages the user is allowed to see.

widgetToPageContent :: (Eq (Route site), Yesod site) => WidgetT site IO () -> HandlerT site IO (PageContent (Route site)) Source

Convert a widget to a PageContent.

Defaults

defaultErrorHandler :: Yesod site => ErrorResponse -> HandlerT site IO TypedContent Source

The default error handler for errorHandler.

defaultYesodMiddleware :: Yesod site => HandlerT site IO res -> HandlerT site IO res Source

Default implementation of yesodMiddleware. Adds the response header "Vary: Accept, Accept-Language" and performs authorization checks.

Since 1.2.0

authorizationCheck :: Yesod site => HandlerT site IO () Source

Check if a given request is authorized via isAuthorized and isWriteRequest.

Since 1.2.0

Data types

unauthorizedI :: (MonadHandler m, RenderMessage (HandlerSite m) msg) => msg -> m AuthResult Source

Return an Unauthorized value, with the given i18n message.

Logging

logOther :: Text -> Q Exp

Sessions

newtype SessionBackend Source

Constructors

SessionBackend 

Fields

sbLoadSession :: Request -> IO (SessionMap, SaveSession)

Return the session data and a function to save the session

customizeSessionCookies :: (SetCookie -> SetCookie) -> SessionBackend -> SessionBackend Source

Customize the cookies used by the session backend. You may use this function on your definition of makeSessionBackend.

For example, you could set the cookie domain so that it would work across many subdomains:

makeSessionBackend site =
    (fmap . fmap) (customizeSessionCookies addDomain) ...
  where
    addDomain cookie = cookie { setCookieDomain = Just ".example.com" }

Default: Do not customize anything (id).

envClientSessionBackend Source

Arguments

:: Int

minutes

-> String

environment variable name

-> IO SessionBackend 

Create a SessionBackend which reads the session key from the named environment variable.

This can be useful if:

  1. You can't rely on a persistent file system (e.g. Heroku)
  2. Your application is open source (e.g. you can't commit the key)

By keeping a consistent value in the environment variable, your users will have consistent sessions without relying on the file system.

Note: A suitable value should only be obtained in one of two ways:

  1. Run this code without the variable set, a value will be generated and printed on devstdout/
  2. Use clientsession-generate

Since 1.4.5

sslOnlySessions :: IO (Maybe SessionBackend) -> IO (Maybe SessionBackend) Source

Defends against session hijacking by setting the secure bit on session cookies so that browsers will not transmit them over http. With this setting on, it follows that the server will regard requests made over http as sessionless, because the session cookie will not be included in the request. Use this as part of a total security measure which also includes disabling HTTP traffic to the site or issuing redirects from HTTP urls, and composing sslOnlyMiddleware with the site's yesodMiddleware.

Since 1.4.7

sslOnlyMiddleware Source

Arguments

:: Yesod site 
=> Int

minutes

-> HandlerT site IO res 
-> HandlerT site IO res 

Apply a Strict-Transport-Security header with the specified timeout to all responses so that browsers will rewrite all http links to https until the timeout expires. For security, the max-age of the STS header should always equal or exceed the client sessions timeout. This defends against hijacking attacks on the sessions of users who attempt to access the site using an http url. This middleware makes a site functionally inaccessible over vanilla http in all standard browsers.

Since 1.4.7

clientSessionDateCacher Source

Arguments

:: NominalDiffTime

Inactive session valitity.

-> IO (IO ClientSessionDateCache, IO ()) 

data Header Source

Headers to be added to a Result.

JS loaders

type BottomOfHeadAsync master Source

Arguments

 = [Text]

urls to load asynchronously

-> Maybe (HtmlUrl (Route master))

widget of js to run on async completion

-> HtmlUrl (Route master)

widget to insert at the bottom of head

Subsites

class MonadResource m => MonadHandler m where Source

Associated Types

type HandlerSite m Source

Methods

liftHandlerT :: HandlerT (HandlerSite m) IO a -> m a Source

Instances

MonadHandler m => MonadHandler (MaybeT m) 
MonadHandler m => MonadHandler (ListT m) 
MonadHandler m => MonadHandler (IdentityT m) 
(Monoid w, MonadHandler m) => MonadHandler (WriterT w m) 
(Monoid w, MonadHandler m) => MonadHandler (WriterT w m) 
MonadHandler m => MonadHandler (StateT s m) 
MonadHandler m => MonadHandler (StateT s m) 
MonadHandler m => MonadHandler (ReaderT r m) 
(Error e, MonadHandler m) => MonadHandler (ErrorT e m) 
MonadResourceBase m => MonadHandler (WidgetT site m) 
MonadResourceBase m => MonadHandler (HandlerT site m) 
MonadHandler m => MonadHandler (ConduitM i o m) 
(Monoid w, MonadHandler m) => MonadHandler (RWST r w s m) 
(Monoid w, MonadHandler m) => MonadHandler (RWST r w s m) 
MonadHandler m => MonadHandler (Pipe l i o u m) 

class MonadHandler m => MonadWidget m where Source

Methods

liftWidgetT :: WidgetT (HandlerSite m) IO a -> m a Source

Instances

MonadWidget m => MonadWidget (MaybeT m) 
MonadWidget m => MonadWidget (ListT m) 
MonadWidget m => MonadWidget (IdentityT m) 
(Monoid w, MonadWidget m) => MonadWidget (WriterT w m) 
(Monoid w, MonadWidget m) => MonadWidget (WriterT w m) 
MonadWidget m => MonadWidget (StateT s m) 
MonadWidget m => MonadWidget (StateT s m) 
MonadWidget m => MonadWidget (ReaderT r m) 
(Error e, MonadWidget m) => MonadWidget (ErrorT e m) 
MonadResourceBase m => MonadWidget (WidgetT site m) 
MonadWidget m => MonadWidget (ConduitM i o m) 
(Monoid w, MonadWidget m) => MonadWidget (RWST r w s m) 
(Monoid w, MonadWidget m) => MonadWidget (RWST r w s m) 
MonadWidget m => MonadWidget (Pipe l i o u m) 

getRouteToParent :: Monad m => HandlerT child (HandlerT parent m) (Route child -> Route parent) Source

defaultLayoutSub :: Yesod parent => WidgetT child IO () -> HandlerT child (HandlerT parent IO) Html Source

Misc

yesodRender Source

Arguments

:: Yesod y 
=> y 
-> ResolvedApproot 
-> Route y 
-> [(Text, Text)]

url query string

-> Text 

runFakeHandler :: (Yesod site, MonadIO m) => SessionMap -> (site -> Logger) -> site -> HandlerT site IO a -> m (Either ErrorResponse a) Source

Deprecated: import runFakeHandler from Yesod.Core.Unsafe

LiteApp

onMethod :: Method -> Writer LiteApp () -> Writer LiteApp () Source

Low-level

yesodRunner :: (ToTypedContent res, Yesod site) => HandlerT site IO res -> YesodRunnerEnv site -> Maybe (Route site) -> Application Source

Re-exports

formatW3 :: UTCTime -> Text Source

Format a UTCTime in W3 format.

formatRFC1123 :: UTCTime -> Text Source

Format as per RFC 1123.

formatRFC822 :: UTCTime -> Text Source

Format as per RFC 822.

class MonadTrans t where

The class of monad transformers. Instances should satisfy the following laws, which state that lift is a transformer of monads:

Methods

lift :: Monad m => m a -> t m a

Lift a computation from the argument monad to the constructed monad.

Instances

MonadTrans MaybeT 
MonadTrans ListT 
MonadTrans IdentityT 
MonadTrans ResourceT 
MonadTrans NoLoggingT 
MonadTrans LoggingT 
MonadTrans CatchT 
Monoid w => MonadTrans (WriterT w) 
Monoid w => MonadTrans (WriterT w) 
MonadTrans (StateT s) 
MonadTrans (StateT s) 
MonadTrans (ReaderT r) 
Error e => MonadTrans (ErrorT e) 
MonadTrans (ContT r) 
MonadTrans (ExceptT e) 
MonadTrans (WidgetT site) 
MonadTrans (HandlerT site) 
MonadTrans (ConduitM i o) 
Monoid w => MonadTrans (RWST r w s) 
Monoid w => MonadTrans (RWST r w s) 
MonadTrans (Pipe l i o u) 

class Monad m => MonadIO m where

Monads in which IO computations may be embedded. Any monad built by applying a sequence of monad transformers to the IO monad will be an instance of this class.

Instances should satisfy the following laws, which state that liftIO is a transformer of monads:

Methods

liftIO :: IO a -> m a

Lift a computation from the IO monad.

Instances

MonadIO IO 
MonadIO Acquire 
MonadIO m => MonadIO (MaybeT m) 
MonadIO m => MonadIO (ListT m) 
MonadIO m => MonadIO (IdentityT m) 
MonadIO m => MonadIO (ResourceT m) 
MonadIO m => MonadIO (NoLoggingT m) 
MonadIO m => MonadIO (LoggingT m) 
MonadIO m => MonadIO (CatchT m) 
(Monoid w, MonadIO m) => MonadIO (WriterT w m) 
(Monoid w, MonadIO m) => MonadIO (WriterT w m) 
MonadIO m => MonadIO (StateT s m) 
MonadIO m => MonadIO (StateT s m) 
MonadIO m => MonadIO (ReaderT r m) 
(Error e, MonadIO m) => MonadIO (ErrorT e m) 
MonadIO m => MonadIO (ContT r m) 
MonadIO m => MonadIO (ExceptT e m) 
MonadIO m => MonadIO (WidgetT site m) 
MonadIO m => MonadIO (HandlerT site m) 
MonadIO m => MonadIO (ConduitM i o m) 
(Monoid w, MonadIO m) => MonadIO (RWST r w s m) 
(Monoid w, MonadIO m) => MonadIO (RWST r w s m) 
MonadIO m => MonadIO (Pipe l i o u m) 

class (Applicative b, Applicative m, Monad b, Monad m) => MonadBase b m | m -> b where

Methods

liftBase :: b α -> m α

Instances

MonadBase [] [] 
MonadBase IO IO 
MonadBase IO Acquire 
MonadBase STM STM 
MonadBase Maybe Maybe 
MonadBase Identity Identity 
MonadBase b m => MonadBase b (ResourceT m) 
MonadBase b m => MonadBase b (NoLoggingT m) 
MonadBase b m => MonadBase b (LoggingT m) 
MonadBase b m => MonadBase b (MaybeT m) 
MonadBase b m => MonadBase b (ListT m) 
MonadBase b m => MonadBase b (IdentityT m) 
(Monoid w, MonadBase b m) => MonadBase b (WriterT w m) 
(Monoid w, MonadBase b m) => MonadBase b (WriterT w m) 
MonadBase b m => MonadBase b (StateT s m) 
MonadBase b m => MonadBase b (StateT s m) 
MonadBase b m => MonadBase b (ReaderT r m) 
MonadBase b m => MonadBase b (ExceptT e m) 
(Error e, MonadBase b m) => MonadBase b (ErrorT e m) 
MonadBase b m => MonadBase b (ContT r m) 
MonadBase b m => MonadBase b (HandlerT site m) 
MonadBase b m => MonadBase b (WidgetT site m) 
MonadBase base m => MonadBase base (ConduitM i o m) 
(Monoid w, MonadBase b m) => MonadBase b (RWST r w s m) 
(Monoid w, MonadBase b m) => MonadBase b (RWST r w s m) 
MonadBase base m => MonadBase base (Pipe l i o u m) 
MonadBase ((->) r) ((->) r) 
MonadBase (Either e) (Either e) 
MonadBase (ST s) (ST s) 
MonadBase (ST s) (ST s) 

class MonadBase b m => MonadBaseControl b m | m -> b

Minimal complete definition

liftBaseWith, restoreM

Instances

MonadBaseControl [] [] 
MonadBaseControl IO IO 
MonadBaseControl STM STM 
MonadBaseControl Maybe Maybe 
MonadBaseControl Identity Identity 
MonadBaseControl b m => MonadBaseControl b (ResourceT m) 
MonadBaseControl b m => MonadBaseControl b (MaybeT m) 
MonadBaseControl b m => MonadBaseControl b (ListT m) 
MonadBaseControl b m => MonadBaseControl b (IdentityT m) 
MonadBaseControl b m => MonadBaseControl b (NoLoggingT m) 
MonadBaseControl b m => MonadBaseControl b (LoggingT m) 
(Monoid w, MonadBaseControl b m) => MonadBaseControl b (WriterT w m) 
(Monoid w, MonadBaseControl b m) => MonadBaseControl b (WriterT w m) 
MonadBaseControl b m => MonadBaseControl b (StateT s m) 
MonadBaseControl b m => MonadBaseControl b (StateT s m) 
MonadBaseControl b m => MonadBaseControl b (ReaderT r m) 
MonadBaseControl b m => MonadBaseControl b (ExceptT e m) 
(Error e, MonadBaseControl b m) => MonadBaseControl b (ErrorT e m) 
MonadBaseControl b m => MonadBaseControl b (HandlerT site m)

Note: although we provide a MonadBaseControl instance, lifted-base's fork function is incompatible with the underlying ResourceT system. Instead, if you must fork a separate thread, you should use resourceForkIO.

Using fork usually leads to an exception that says "Control.Monad.Trans.Resource.register': The mutable state is being accessed after cleanup. Please contact the maintainers."

MonadBaseControl b m => MonadBaseControl b (WidgetT site m) 
(Monoid w, MonadBaseControl b m) => MonadBaseControl b (RWST r w s m) 
(Monoid w, MonadBaseControl b m) => MonadBaseControl b (RWST r w s m) 
MonadBaseControl ((->) r) ((->) r) 
MonadBaseControl (Either e) (Either e) 
MonadBaseControl (ST s) (ST s) 
MonadBaseControl (ST s) (ST s) 

class (MonadThrow m, MonadIO m, Applicative m, MonadBase IO m) => MonadResource m where

Methods

liftResourceT :: ResourceT IO a -> m a

Instances

MonadResource m => MonadResource (MaybeT m) 
MonadResource m => MonadResource (ListT m) 
MonadResource m => MonadResource (IdentityT m) 
(MonadThrow m, MonadBase IO m, MonadIO m, Applicative m) => MonadResource (ResourceT m) 
MonadResource m => MonadResource (NoLoggingT m) 
MonadResource m => MonadResource (LoggingT m) 
(Monoid w, MonadResource m) => MonadResource (WriterT w m) 
(Monoid w, MonadResource m) => MonadResource (WriterT w m) 
MonadResource m => MonadResource (StateT s m) 
MonadResource m => MonadResource (StateT s m) 
MonadResource m => MonadResource (ReaderT r m) 
(Error e, MonadResource m) => MonadResource (ErrorT e m) 
MonadResource m => MonadResource (ContT r m) 
MonadResource m => MonadResource (ExceptT e m) 
(Applicative m, MonadIO m, MonadBase IO m, MonadThrow m) => MonadResource (WidgetT site m) 
(MonadIO m, MonadBase IO m, MonadThrow m) => MonadResource (HandlerT site m) 
MonadResource m => MonadResource (ConduitM i o m) 
(Monoid w, MonadResource m) => MonadResource (RWST r w s m) 
(Monoid w, MonadResource m) => MonadResource (RWST r w s m) 
MonadResource m => MonadResource (Pipe l i o u m) 

class Monad m => MonadLogger m

Minimal complete definition

monadLoggerLog

Instances

MonadLogger m => MonadLogger (MaybeT m) 
MonadLogger m => MonadLogger (ListT m) 
MonadLogger m => MonadLogger (IdentityT m) 
MonadLogger m => MonadLogger (ResourceT m) 
Monad m => MonadLogger (NoLoggingT m) 
MonadIO m => MonadLogger (LoggingT m) 
(MonadLogger m, Monoid w) => MonadLogger (WriterT w m) 
(MonadLogger m, Monoid w) => MonadLogger (WriterT w m) 
MonadLogger m => MonadLogger (StateT s m) 
MonadLogger m => MonadLogger (StateT s m) 
MonadLogger m => MonadLogger (ReaderT r m) 
(MonadLogger m, Error e) => MonadLogger (ErrorT e m) 
MonadLogger m => MonadLogger (ContT r m) 
MonadLogger m => MonadLogger (ExceptT e m) 
MonadIO m => MonadLogger (WidgetT site m) 
MonadIO m => MonadLogger (HandlerT site m) 
MonadLogger m => MonadLogger (ConduitM i o m) 
(MonadLogger m, Monoid w) => MonadLogger (RWST r w s m) 
(MonadLogger m, Monoid w) => MonadLogger (RWST r w s m) 
MonadLogger m => MonadLogger (Pipe l i o u m) 

Commonly referenced functions/datatypes

type Application = Request -> (Response -> IO ResponseReceived) -> IO ResponseReceived

Utilities

Shakespeare

Hamlet

type HtmlUrl url = Render url -> Html

Julius

type JavascriptUrl url = (url -> [(Text, Text)] -> Text) -> Javascript

renderJavascriptUrl :: (url -> [(Text, Text)] -> Text) -> JavascriptUrl url -> Text

Cassius/Lucius

type CssUrl url = (url -> [(Text, Text)] -> Text) -> Css

renderCssUrl :: (url -> [(Text, Text)] -> Text) -> CssUrl url -> Text