Safe Haskell | None |
---|---|
Language | Haskell2010 |
The bare-bones Rattus language. To program with streams and events, you can use Rattus.Stream and Rattus.Events; to program with Yampa-style signal functions, you can use Rattus.Yampa.
Rattus language primitives
module Rattus.Primitives
Strict data types
module Rattus.Strict
Annotation
Use this type to mark a Haskell function definition as a Rattus function:
{-# ANN myFunction Rattus #-}
Or mark a whole module as consisting of Rattus functions only:
{-# ANN module Rattus #-}
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 NotRattus #-}
By default all 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 #-}
Instances
Eq Rattus Source # | |
Data Rattus Source # | |
Defined in Rattus.Plugin.Annotation gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Rattus -> c Rattus # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Rattus # toConstr :: Rattus -> Constr # dataTypeOf :: Rattus -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Rattus) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Rattus) # gmapT :: (forall b. Data b => b -> b) -> Rattus -> Rattus # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Rattus -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Rattus -> r # gmapQ :: (forall d. Data d => d -> u) -> Rattus -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Rattus -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Rattus -> m Rattus # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Rattus -> m Rattus # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Rattus -> m Rattus # | |
Show Rattus Source # | |
Applicative operators
(|##) :: Stable a => Box (a -> b) -> a -> Box b Source #
Variant of |#|
where the argument is of a stable type..
(<##) :: Stable a => O (a -> b) -> a -> O b Source #
Variant of <#>
where the argument is of a stable type..