yesod-fay-0.10.0: Utilities for using the Fay Haskell-to-JS compiler with Yesod.

Safe HaskellNone
LanguageHaskell98

Yesod.Fay

Contents

Description

Utility functions for using Fay from a Yesod application.

This module is intended to be used from your Yesod application, not from your Fay programs.

We assume a specific file structure, namely that there is a fay folder containing client-side code, and fay-shared containing code to be used by both the client and server.

The Fay.Yesod module (part of this package) is required by both client and server code. However, since Fay does not currently have package management support, we use a bit of a hack: the TH calls in this package will automatically create the necessary fay/Fay/Yesod.hs file. Ultimately, we will use a more elegant solution.

In the future, if this package proves popular enough, Fay support will likely be built into the scaffolding. In the meantime, you must manually integrate it. In order to take advantage of this module, you should modify your Yesod application as follows:

  • Modify your cabal file to include the fay-shared folder when compiling. This can be done by adding a hs-source-dirs: ., fay-shared line to your library section.
  • Create the module SharedTypes in fay-shared and create a Command datatype. For an example of what this file should look like, see https://github.com/snoyberg/yesod-fay/blob/master/sample/fay-shared/SharedTypes.hs.
  • Add the function fayFile to your Import module. See https://github.com/snoyberg/yesod-fay/blob/master/sample/Import.hs for an example.
  • Add a new route at for the Fay subsite. Generally, it will look like /fay-command FaySiteR FaySite getFaySite.
  • Import the SharedTypes and Yesod.Fay modules into your Foundation.hs module. Add an instance of YesodFay for your application. You should set the YesodFayCommand associated type to the Command datatype you created. (You may also need to add a YesodJquery instance.) Note that this instance must appear after your parseRoutes. Set the method fayRoute to FaySiteR (or whatever you called the subsite route), and implement yesodFayCommand. It will generally look something like yesodFayCommand render command = case command of { ... }.
  • In order to use Fay, add $(fayFile "MyModule") to a widget, and then write the corresponding fay/MyModule.hs file. For an example, see https://github.com/snoyberg/yesod-fay/blob/master/sample/fay/Home.hs.
Synopsis

Typeclass

class YesodJquery master => YesodFay master where Source #

Type class for applications using Fay.

We depend on YesodJquery since the generated client-side code uses jQuery for making Ajax calls. We have an associated type stating the command datatype. Since this datatype must be used by both the client and server, you should place its definition in the fay-shared folder.

Minimal complete definition

yesodFayCommand, fayRoute

Methods

yesodFayCommand :: CommandHandler master Source #

User-defined function specifying how to respond to commands. Using the above datatype, this might look like:

yesodFayCommand render command =
    case command of
        GetFib index r = render r $ fibs !! index

fayRoute :: Route FaySite -> Route master Source #

Where in the routing tree our Fay subsite is located. This is generally named FaySiteR, e.g.:

mkYesod "YourSite" [parseRoutes
...
/fay-command FaySiteR FaySite getFaySite
|]

instance YesodFay YourSite where
    fayRoute = FaySiteR

fayEncode :: Data a => master -> a -> Maybe Value Source #

User-defined function specifying how to encode data as json for fay.

Most users won't need to define this, the default is const showToFay. Custom definitions will usually be in terms of encodeFay.

data YesodFaySettings Source #

A setttings data type for indicating whether the generated Javascript should contain a copy of the Fay runtime or not.

Constructors

YesodFaySettings 

Fields

Include Fay programs

fayFileProd :: YesodFaySettings -> Q Exp Source #

Does a full compile of the Fay code via GHC for type checking, and then embeds the Fay-generated Javascript as a static string. File changes during runtime will not be reflected.

fayFileReload :: YesodFaySettings -> Q Exp Source #

Performs no type checking on the Fay code. Each time the widget is requested, the Fay code will be compiled from scratch to Javascript.

fayFileProdWithConfig :: (Config -> Config) -> YesodFaySettings -> Q Exp Source #

Like fayFileProd, but also takes a function so that the fay configuration can be modified.

Since 0.6.1

fayFileReloadWithConfig :: Name -> YesodFaySettings -> Q Exp Source #

Like fayFileReload, but also takes the name of a function used to modify the fay configuration can be modified. The type of this function is expected to be (Config -> Config).

Since 0.6.1

type FayFile = String -> Q Exp Source #

A function that takes a String giving the Fay module name, and returns an TH splice that generates a Widget.

Commands

type CommandHandler master = forall s. (forall a. Data a => Returns a -> a -> HandlerFor master s) -> Value -> HandlerFor master s Source #

A function provided by the developer describing how to answer individual commands from client-side code.

Due to restrictions of the type system in Fay, we use a relatively simple approach for encoding the return type. In order to specify this, an extra parameter- Returns- is passed around, with a phantom type variable stating the expected return type.

The first argument to your function is the "respond" function: it takes the extra Returns parameter as well as the actual value to be returned, and produces the expected result.

data Returns a Source #

A proxy type for specifying what type a command should return. The final field for each data constructor in a command datatype should be Returns.

Instances
Eq (Returns a) Source # 
Instance details

Defined in Fay.Yesod

Methods

(==) :: Returns a -> Returns a -> Bool #

(/=) :: Returns a -> Returns a -> Bool #

Data a => Data (Returns a) Source # 
Instance details

Defined in Fay.Yesod

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Returns a -> c (Returns a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Returns a) #

toConstr :: Returns a -> Constr #

dataTypeOf :: Returns a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Returns a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Returns a)) #

gmapT :: (forall b. Data b => b -> b) -> Returns a -> Returns a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Returns a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Returns a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Returns a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Returns a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Returns a -> m (Returns a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Returns a -> m (Returns a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Returns a -> m (Returns a) #

Read (Returns a) Source # 
Instance details

Defined in Fay.Yesod

Show (Returns a) Source # 
Instance details

Defined in Fay.Yesod

Methods

showsPrec :: Int -> Returns a -> ShowS #

show :: Returns a -> String #

showList :: [Returns a] -> ShowS #

Subsite

data FaySite Source #

The Fay subsite.

Instances
ParseRoute FaySite Source # 
Instance details

Defined in Yesod.Fay.Data

Methods

parseRoute :: ([Text], [(Text, Text)]) -> Maybe (Route FaySite)

RenderRoute FaySite Source # 
Instance details

Defined in Yesod.Fay.Data

Associated Types

data Route FaySite :: Type #

Methods

renderRoute :: Route FaySite -> ([Text], [(Text, Text)])

RouteAttrs FaySite Source # 
Instance details

Defined in Yesod.Fay.Data

YesodFay master => YesodSubDispatch FaySite master 
Instance details

Defined in Yesod.Fay

Methods

yesodSubDispatch :: YesodSubRunnerEnv FaySite master -> Application

Eq (Route FaySite) Source # 
Instance details

Defined in Yesod.Fay.Data

Read (Route FaySite) Source # 
Instance details

Defined in Yesod.Fay.Data

Show (Route FaySite) Source # 
Instance details

Defined in Yesod.Fay.Data

data Route FaySite Source # 
Instance details

Defined in Yesod.Fay.Data

getFaySite :: a -> FaySite Source #

To be used from your routing declarations.

data family Route a :: Type #

Instances
RedirectUrl master (Route master) 
Instance details

Defined in Yesod.Core.Handler

Methods

toTextUrl :: (MonadHandler m, HandlerSite m ~ master) => Route master -> m Text

(key ~ Text, val ~ Text) => RedirectUrl master (Route master, [(key, val)]) 
Instance details

Defined in Yesod.Core.Handler

Methods

toTextUrl :: (MonadHandler m, HandlerSite m ~ master) => (Route master, [(key, val)]) -> m Text

(key ~ Text, val ~ Text) => RedirectUrl master (Route master, Map key val) 
Instance details

Defined in Yesod.Core.Handler

Methods

toTextUrl :: (MonadHandler m, HandlerSite m ~ master) => (Route master, Map key val) -> m Text

Eq (Route LiteApp) 
Instance details

Defined in Yesod.Core.Internal.LiteApp

Methods

(==) :: Route LiteApp -> Route LiteApp -> Bool #

(/=) :: Route LiteApp -> Route LiteApp -> Bool #

Eq (Route WaiSubsite) 
Instance details

Defined in Yesod.Core.Types

Methods

(==) :: Route WaiSubsite -> Route WaiSubsite -> Bool #

(/=) :: Route WaiSubsite -> Route WaiSubsite -> Bool #

Eq (Route WaiSubsiteWithAuth) 
Instance details

Defined in Yesod.Core.Types

Methods

(==) :: Route WaiSubsiteWithAuth -> Route WaiSubsiteWithAuth -> Bool #

(/=) :: Route WaiSubsiteWithAuth -> Route WaiSubsiteWithAuth -> Bool #

Eq (Route FaySite) Source # 
Instance details

Defined in Yesod.Fay.Data

Eq (Route Static) 
Instance details

Defined in Yesod.Static

Methods

(==) :: Route Static -> Route Static -> Bool #

(/=) :: Route Static -> Route Static -> Bool #

Ord (Route LiteApp) 
Instance details

Defined in Yesod.Core.Internal.LiteApp

Methods

compare :: Route LiteApp -> Route LiteApp -> Ordering #

(<) :: Route LiteApp -> Route LiteApp -> Bool #

(<=) :: Route LiteApp -> Route LiteApp -> Bool #

(>) :: Route LiteApp -> Route LiteApp -> Bool #

(>=) :: Route LiteApp -> Route LiteApp -> Bool #

max :: Route LiteApp -> Route LiteApp -> Route LiteApp #

min :: Route LiteApp -> Route LiteApp -> Route LiteApp #

Ord (Route WaiSubsite) 
Instance details

Defined in Yesod.Core.Types

Methods

compare :: Route WaiSubsite -> Route WaiSubsite -> Ordering #

(<) :: Route WaiSubsite -> Route WaiSubsite -> Bool #

(<=) :: Route WaiSubsite -> Route WaiSubsite -> Bool #

(>) :: Route WaiSubsite -> Route WaiSubsite -> Bool #

(>=) :: Route WaiSubsite -> Route WaiSubsite -> Bool #

max :: Route WaiSubsite -> Route WaiSubsite -> Route WaiSubsite #

min :: Route WaiSubsite -> Route WaiSubsite -> Route WaiSubsite #

Ord (Route WaiSubsiteWithAuth) 
Instance details

Defined in Yesod.Core.Types

Methods

compare :: Route WaiSubsiteWithAuth -> Route WaiSubsiteWithAuth -> Ordering #

(<) :: Route WaiSubsiteWithAuth -> Route WaiSubsiteWithAuth -> Bool #

(<=) :: Route WaiSubsiteWithAuth -> Route WaiSubsiteWithAuth -> Bool #

(>) :: Route WaiSubsiteWithAuth -> Route WaiSubsiteWithAuth -> Bool #

(>=) :: Route WaiSubsiteWithAuth -> Route WaiSubsiteWithAuth -> Bool #

max :: Route WaiSubsiteWithAuth -> Route WaiSubsiteWithAuth -> Route WaiSubsiteWithAuth #

min :: Route WaiSubsiteWithAuth -> Route WaiSubsiteWithAuth -> Route WaiSubsiteWithAuth #

Read (Route LiteApp) 
Instance details

Defined in Yesod.Core.Internal.LiteApp

Methods

readsPrec :: Int -> ReadS (Route LiteApp) #

readList :: ReadS [Route LiteApp] #

readPrec :: ReadPrec (Route LiteApp) #

readListPrec :: ReadPrec [Route LiteApp] #

Read (Route WaiSubsite) 
Instance details

Defined in Yesod.Core.Types

Methods

readsPrec :: Int -> ReadS (Route WaiSubsite) #

readList :: ReadS [Route WaiSubsite] #

readPrec :: ReadPrec (Route WaiSubsite) #

readListPrec :: ReadPrec [Route WaiSubsite] #

Read (Route WaiSubsiteWithAuth) 
Instance details

Defined in Yesod.Core.Types

Methods

readsPrec :: Int -> ReadS (Route WaiSubsiteWithAuth) #

readList :: ReadS [Route WaiSubsiteWithAuth] #

readPrec :: ReadPrec (Route WaiSubsiteWithAuth) #

readListPrec :: ReadPrec [Route WaiSubsiteWithAuth] #

Read (Route FaySite) Source # 
Instance details

Defined in Yesod.Fay.Data

Read (Route Static) 
Instance details

Defined in Yesod.Static

Methods

readsPrec :: Int -> ReadS (Route Static) #

readList :: ReadS [Route Static] #

readPrec :: ReadPrec (Route Static) #

readListPrec :: ReadPrec [Route Static] #

Show (Route LiteApp) 
Instance details

Defined in Yesod.Core.Internal.LiteApp

Methods

showsPrec :: Int -> Route LiteApp -> ShowS #

show :: Route LiteApp -> String #

showList :: [Route LiteApp] -> ShowS #

Show (Route WaiSubsite) 
Instance details

Defined in Yesod.Core.Types

Methods

showsPrec :: Int -> Route WaiSubsite -> ShowS #

show :: Route WaiSubsite -> String #

showList :: [Route WaiSubsite] -> ShowS #

Show (Route WaiSubsiteWithAuth) 
Instance details

Defined in Yesod.Core.Types

Methods

showsPrec :: Int -> Route WaiSubsiteWithAuth -> ShowS #

show :: Route WaiSubsiteWithAuth -> String #

showList :: [Route WaiSubsiteWithAuth] -> ShowS #

Show (Route FaySite) Source # 
Instance details

Defined in Yesod.Fay.Data

Show (Route Static) 
Instance details

Defined in Yesod.Static

Methods

showsPrec :: Int -> Route Static -> ShowS #

show :: Route Static -> String #

showList :: [Route Static] -> ShowS #

data Route LiteApp 
Instance details

Defined in Yesod.Core.Internal.LiteApp

data Route LiteApp = LiteAppRoute [Text]
data Route WaiSubsite 
Instance details

Defined in Yesod.Core.Types

data Route WaiSubsite = WaiSubsiteRoute [Text] [(Text, Text)]
data Route WaiSubsiteWithAuth 
Instance details

Defined in Yesod.Core.Types

data Route WaiSubsiteWithAuth = WaiSubsiteWithAuthRoute [Text] [(Text, Text)]
data Route FaySite Source # 
Instance details

Defined in Yesod.Fay.Data

data Route Static 
Instance details

Defined in Yesod.Static

data Route Static = StaticRoute [Text] [(Text, Text)]

Reexports

class YesodJquery a where #

Minimal complete definition

Nothing

Orphan instances

YesodFay master => YesodSubDispatch FaySite master Source # 
Instance details

Methods

yesodSubDispatch :: YesodSubRunnerEnv FaySite master -> Application