AsyncRattus-0.1.0.3: An asynchronous modal FRP language
Safe HaskellSafe-Inferred
LanguageHaskell2010

AsyncRattus.Plugin

Description

The plugin to make it all work.

Synopsis

Documentation

plugin :: Plugin Source #

Use this to enable Asynchronous Rattus' plugin, either by supplying the option -fplugin=AsyncRattus.Plugin directly to GHC, or by including the following pragma in each source file:

{-# OPTIONS -fplugin=AsyncRattus.Plugin #-}

data AsyncRattus Source #

Use this type to mark a Haskell function definition as an Asynchronous Rattus function:

{-# ANN myFunction AsyncRattus #-}

Or mark a whole module as consisting of Asynchronous Rattus functions only:

{-# ANN module AsyncRattus #-}

If you use the latter option, you can mark exceptions (i.e. functions that should be treated as ordinary Haskell function definitions) as follows:

{-# ANN myFunction NotAsyncRattus #-}

By default all Asynchronous Rattus functions are checked for use of lazy data types, since these may cause memory leaks. If any lazy data types are used, a warning is issued. These warnings can be disabled by annotating the module or the function with AllowLazyData

{-# ANN myFunction AllowLazyData #-}

{-# ANN module AllowLazyData #-}

Asynchronous Rattus only allows guarded recursion, i.e. recursive calls must occur in the scope of a tick. Structural recursion over strict data types is safe as well, but is currently not checked. To disable the guarded recursion check, annotate the module or function with AllowRecursion.

Instances

Instances details
Data AsyncRattus Source # 
Instance details

Defined in AsyncRattus.Plugin.Annotation

Methods

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

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

toConstr :: AsyncRattus -> Constr #

dataTypeOf :: AsyncRattus -> DataType #

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

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

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

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

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

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

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

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

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

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

Show AsyncRattus Source # 
Instance details

Defined in AsyncRattus.Plugin.Annotation

Eq AsyncRattus Source # 
Instance details

Defined in AsyncRattus.Plugin.Annotation

Ord AsyncRattus Source # 
Instance details

Defined in AsyncRattus.Plugin.Annotation