dyna-gloss-0.1.0.0: FRP for gloss graphics and animation library
Safe HaskellNone
LanguageHaskell2010

Dyna.Gloss.Frp

Description

FRP main types and combinators

Synopsis

Events

data Evt a Source #

Event stream. The meaning of an event is a callback consumer function. If we give callback to it it will do something useful based on it.

The main function is runEvt:

runEvt :: Evt m a -> (a -> m ()) -> m ()
runEvt events callback = ...

Let's look at simple examples of the event streams:

Event that never produce anything:

never = Evt {
   runEvt _ = pure ()
 }

So it just ignores the callback and returns right away.

Event that happens only once:

once :: m a -> Evt m a
once get = Evt {
    runEvt go = go =<< get
 }

It just gets the value right away and applies callback to it. We can try it out in the interpreter:

putStrLnE $ fmap ("Your message: " <> ) $ once getLine

We have useful functions to print out the events: putStrLnE and printE.

Also we have event streams that happen periodically:

printE $ clock 1  -- prints time every second

## Duplication of the events.

Note that event streams are functions that do side-effects within some monad. We use them as values but it means that two values with the same event stream definition can produce different results. For example:

a = toRandomR (0, 10) $ clock 1
b = a

Note that a and b will each have their own copy of underlying random event stream. So if you use it in the code don't expect values to be the same.

But if we want them to be the same we can copy event from it's definition with function:

newEvt :: Evt m a -> m (Evt m a)

It starts the underying event stream process n background and sends all events to the result by channel. With nice property of when we shut down the result event the background process also shuts down.

a <- newEvt toRandomR (0, 10) $ clock 1
b = a

In this example event streams a and b will have the same events during execution.

Instances

Instances details
Monad Evt Source # 
Instance details

Defined in Dyna.Gloss.Types

Methods

(>>=) :: Evt a -> (a -> Evt b) -> Evt b #

(>>) :: Evt a -> Evt b -> Evt b #

return :: a -> Evt a #

Functor Evt Source # 
Instance details

Defined in Dyna.Gloss.Types

Methods

fmap :: (a -> b) -> Evt a -> Evt b #

(<$) :: a -> Evt b -> Evt a #

Applicative Evt Source # 
Instance details

Defined in Dyna.Gloss.Types

Methods

pure :: a -> Evt a #

(<*>) :: Evt (a -> b) -> Evt a -> Evt b #

liftA2 :: (a -> b -> c) -> Evt a -> Evt b -> Evt c #

(*>) :: Evt a -> Evt b -> Evt b #

(<*) :: Evt a -> Evt b -> Evt a #

RunFunctor Evt Source # 
Instance details

Defined in Dyna.Gloss.Frp

Methods

fmap' :: (a -> Run b) -> Evt a -> Evt b Source #

Semigroup (Evt a) Source # 
Instance details

Defined in Dyna.Gloss.Types

Methods

(<>) :: Evt a -> Evt a -> Evt a #

sconcat :: NonEmpty (Evt a) -> Evt a #

stimes :: Integral b => b -> Evt a -> Evt a #

Monoid (Evt a) Source # 
Instance details

Defined in Dyna.Gloss.Types

Methods

mempty :: Evt a #

mappend :: Evt a -> Evt a -> Evt a #

mconcat :: [Evt a] -> Evt a #

Loop (Evt a) Source # 
Instance details

Defined in Dyna.Gloss.Types

Methods

loop :: Evt a -> Evt a #

Limit (Evt a) Source # 
Instance details

Defined in Dyna.Gloss.Types

Methods

lim :: DurOf (Evt a) -> Evt a -> Evt a #

Compose (Evt a) Source # 
Instance details

Defined in Dyna.Gloss.Types

Harmony (Evt a) Source # 
Instance details

Defined in Dyna.Gloss.Types

Methods

har :: [Evt a] -> Evt a #

(=:=) :: Evt a -> Evt a -> Evt a #

Melody (Evt a) Source # 
Instance details

Defined in Dyna.Gloss.Types

Methods

mel :: [Evt a] -> Evt a #

(+:+) :: Evt a -> Evt a -> Evt a #

type DurOf (Evt a) Source # 
Instance details

Defined in Dyna.Gloss.Types

type DurOf (Evt a) = Float

once :: Run a -> Evt a Source #

Event that happens only once and happens right away.

never :: Evt a Source #

Event that never happens. Callback function is ignored.

Dynamics

data Dyn a Source #

Dynamic step-wise continuous process

Instances

Instances details
Functor Dyn Source # 
Instance details

Defined in Dyna.Gloss.Types

Methods

fmap :: (a -> b) -> Dyn a -> Dyn b #

(<$) :: a -> Dyn b -> Dyn a #

Applicative Dyn Source # 
Instance details

Defined in Dyna.Gloss.Types

Methods

pure :: a -> Dyn a #

(<*>) :: Dyn (a -> b) -> Dyn a -> Dyn b #

liftA2 :: (a -> b -> c) -> Dyn a -> Dyn b -> Dyn c #

(*>) :: Dyn a -> Dyn b -> Dyn b #

(<*) :: Dyn a -> Dyn b -> Dyn a #

RunFunctor Dyn Source # 
Instance details

Defined in Dyna.Gloss.Frp

Methods

fmap' :: (a -> Run b) -> Dyn a -> Dyn b Source #

Fractional a => Fractional (Dyn a) Source # 
Instance details

Defined in Dyna.Gloss.Types

Methods

(/) :: Dyn a -> Dyn a -> Dyn a #

recip :: Dyn a -> Dyn a #

fromRational :: Rational -> Dyn a #

Num a => Num (Dyn a) Source # 
Instance details

Defined in Dyna.Gloss.Types

Methods

(+) :: Dyn a -> Dyn a -> Dyn a #

(-) :: Dyn a -> Dyn a -> Dyn a #

(*) :: Dyn a -> Dyn a -> Dyn a #

negate :: Dyn a -> Dyn a #

abs :: Dyn a -> Dyn a #

signum :: Dyn a -> Dyn a #

fromInteger :: Integer -> Dyn a #

IsString a => IsString (Dyn a) Source # 
Instance details

Defined in Dyna.Gloss.Types

Methods

fromString :: String -> Dyn a #

Semigroup a => Semigroup (Dyn a) Source # 
Instance details

Defined in Dyna.Gloss.Types

Methods

(<>) :: Dyn a -> Dyn a -> Dyn a #

sconcat :: NonEmpty (Dyn a) -> Dyn a #

stimes :: Integral b => b -> Dyn a -> Dyn a #

Monoid a => Monoid (Dyn a) Source # 
Instance details

Defined in Dyna.Gloss.Types

Methods

mempty :: Dyn a #

mappend :: Dyn a -> Dyn a -> Dyn a #

mconcat :: [Dyn a] -> Dyn a #

Boolean a => Boolean (Dyn a) Source # 
Instance details

Defined in Dyna.Gloss.Types

Methods

true :: Dyn a #

false :: Dyn a #

notB :: Dyn a -> Dyn a #

(&&*) :: Dyn a -> Dyn a -> Dyn a #

(||*) :: Dyn a -> Dyn a -> Dyn a #

IfB a => IfB (Dyn a) Source # 
Instance details

Defined in Dyna.Gloss.Types

Methods

ifB :: bool ~ BooleanOf (Dyn a) => bool -> Dyn a -> Dyn a -> Dyn a #

EqB a => EqB (Dyn a) Source # 
Instance details

Defined in Dyna.Gloss.Types

Methods

(==*) :: bool ~ BooleanOf (Dyn a) => Dyn a -> Dyn a -> bool #

(/=*) :: bool ~ BooleanOf (Dyn a) => Dyn a -> Dyn a -> bool #

OrdB a => OrdB (Dyn a) Source # 
Instance details

Defined in Dyna.Gloss.Types

Methods

(<*) :: bool ~ BooleanOf (Dyn a) => Dyn a -> Dyn a -> bool #

(<=*) :: bool ~ BooleanOf (Dyn a) => Dyn a -> Dyn a -> bool #

(>*) :: bool ~ BooleanOf (Dyn a) => Dyn a -> Dyn a -> bool #

(>=*) :: bool ~ BooleanOf (Dyn a) => Dyn a -> Dyn a -> bool #

AdditiveGroup a => AdditiveGroup (Dyn a) Source # 
Instance details

Defined in Dyna.Gloss.Types

Methods

zeroV :: Dyn a #

(^+^) :: Dyn a -> Dyn a -> Dyn a #

negateV :: Dyn a -> Dyn a #

(^-^) :: Dyn a -> Dyn a -> Dyn a #

VectorSpace a => VectorSpace (Dyn a) Source # 
Instance details

Defined in Dyna.Gloss.Types

Associated Types

type Scalar (Dyn a) #

Methods

(*^) :: Scalar (Dyn a) -> Dyn a -> Dyn a #

AffineSpace a => AffineSpace (Dyn a) Source # 
Instance details

Defined in Dyna.Gloss.Types

Associated Types

type Diff (Dyn a) #

Methods

(.-.) :: Dyn a -> Dyn a -> Diff (Dyn a) #

(.+^) :: Dyn a -> Diff (Dyn a) -> Dyn a #

HasCross3 a => HasCross3 (Dyn a) Source # 
Instance details

Defined in Dyna.Gloss.Types

Methods

cross3 :: Dyn a -> Dyn a -> Dyn a #

HasCross2 a => HasCross2 (Dyn a) Source # 
Instance details

Defined in Dyna.Gloss.Types

Methods

cross2 :: Dyn a -> Dyn a #

HasNormal a => HasNormal (Dyn a) Source # 
Instance details

Defined in Dyna.Gloss.Types

Methods

normalVec :: Dyn a -> Dyn a #

(BasisArity a, HasBasis a) => HasBasis (Dyn a) Source # 
Instance details

Defined in Dyna.Gloss.Types

Associated Types

type Basis (Dyn a) #

Methods

basisValue :: Basis (Dyn a) -> Dyn a #

decompose :: Dyn a -> [(Basis (Dyn a), Scalar (Dyn a))] #

decompose' :: Dyn a -> Basis (Dyn a) -> Scalar (Dyn a) #

type BooleanOf (Dyn a) Source # 
Instance details

Defined in Dyna.Gloss.Types

type BooleanOf (Dyn a) = Dyn (BooleanOf a)
type Scalar (Dyn a) Source # 
Instance details

Defined in Dyna.Gloss.Types

type Scalar (Dyn a) = Scalar (Dyn Run a)
type Diff (Dyn a) Source # 
Instance details

Defined in Dyna.Gloss.Types

type Diff (Dyn a) = Diff (Dyn Run a)
type Basis (Dyn a) Source # 
Instance details

Defined in Dyna.Gloss.Types

type Basis (Dyn a) = Basis (Dyn Run a)

constDyn :: Run a -> Dyn a Source #

Dyn that is constructed from effectful callback.

Observing the Dyn

data DynRef a Source #

Reference to running dynamic process by which we can query values (readDyn). Also note that we no longer need the reference we should release the resources by calling cancelDyn.

runDyn :: Dyn a -> Run (DynRef a) Source #

Executes dynamic for observation. The dynamic is step-wise constant function that is driven by some event stream. The function runs the event stream process in background and samples the updated state.

We can observe the value with readDyn. We need to shut down the stream when we no longer need it with cancelDyn function.

readDyn :: DynRef a -> Run a Source #

Reads current dynamic value.

cancelDyn :: DynRef a -> Run () Source #

Shuts down the background process for dynamic and releases resulrces for event stream that drives the dynamic.

Control

newEvt :: Evt a -> Run (Evt a) Source #

Runs the argument event stream as background process and produces event stream that is fed with events over channel (unagi-channel package). When result event stream shuts down the background process also shuts down.

newDyn :: Dyn a -> Run (Dyn a) Source #

Runs the dynamic process in background and returns dynamic that just samples the background proces with readDyn.

API

Event API

scan :: (a -> b -> b) -> b -> Evt a -> Evt b Source #

scan over event stream. Example:

naturals = scan (+) 0 pulse

scanMay :: (a -> b -> Maybe b) -> b -> Evt a -> Evt b Source #

scan combined with filter. If accumulator function produces Nothing on event then that event is ignored and state is kept to previous state.

mapMay :: (a -> Maybe b) -> Evt a -> Evt b Source #

Map with filtering. When Nothing is produced event is omitted from the stream.

foldMap :: (Foldable t, Monoid m) => (a -> m) -> t a -> m #

Map each element of the structure to a monoid, and combine the results.

accum :: (a -> s -> (b, s)) -> s -> Evt a -> Evt b Source #

Accumulate over event stream.

accumB :: a -> Evt (a -> a) -> Dyn a Source #

Accumulates the values with event stream that produce functions.

accumMay :: (a -> s -> Maybe (b, s)) -> s -> Evt a -> Evt b Source #

Accumulate over event stream.

filters :: (a -> Bool) -> Evt a -> Evt a Source #

Filtering of the event strewams. Only events that produce True remain in the stream.

filterJust :: Evt (Maybe a) -> Evt a Source #

Filters based on Maybe. If Nothing is produced forthe event it is omitted from the stream.

whens :: Dyn Bool -> Evt a -> Evt a Source #

Filters with dynamic. When dynamic is true events pass through and when it's false events are omitted.

splits :: Evt (Either a b) -> (Evt a, Evt b) Source #

Splits the either event stream.

lefts :: Evt (Either a b) -> Evt a Source #

Gets all left events from the stream

rights :: Evt (Either a b) -> Evt b Source #

Gets all right events from the stream

iterates :: (a -> a) -> a -> Evt b -> Evt a Source #

Iterates over event stream. It's like scan but it ignores the values of underying stream and starts with initial value as first element.

withIterates :: (a -> a) -> a -> Evt b -> Evt (a, b) Source #

fix1 :: (Evt a -> Run (Evt a)) -> Evt a Source #

Recursion on event streams. As event streams are functions we can not use normal recursion that haskell provides. It will stuck the execution. But we can use fix1 to create event stream that feeds back the events to itself.

Note that any sort of recursion can be implemented with fix1. For example if we need 3-recursive event stream:

fixE3 ::
     (Evt a -> Evt b -> Evt c -> (Evt a, Evt b, Evt c))
  -> (Evt a, Evt b, Evt c)

we can use sum tpye tags to join it to single stream:

data Tag a b c = TagA a | TagB b | TagC c
fix3 f = unwrap $ fix1 g
  where
     g x = wrap (f (unwrapA x) (unwrapB x) (unwrapC x))

     wrap a b c = mconcat [TagA <$> a, TagB <$> b, TagC <$> c]
     unwrap evt = (unwrapA evt, unwrapB evt, unwrapC evt)

     unwrapA = flip mapMay $ \x -> case x of
                                 TagA a -> Just a
                                 _      -> Nothing

We can use this trck with any number of streams. There are helper functions: fix2, fix3, fix4

fix2 :: (Evt a -> Evt b -> Run (Evt a, Evt b)) -> (Evt a, Evt b) Source #

Recursion for binary functions

fix3 :: (Evt a -> Evt b -> Evt c -> Run (Evt a, Evt b, Evt c)) -> (Evt a, Evt b, Evt c) Source #

Recursion for ternary functions

fix4 :: (Evt a -> Evt b -> Evt c -> Evt d -> Run (Evt a, Evt b, Evt c, Evt d)) -> (Evt a, Evt b, Evt c, Evt d) Source #

Recursion for functions of four arguments

switch :: Evt (Evt a) -> Evt a Source #

Flattens event stream producer by switching between event streams. When next event stream happens it shuts down the previous one.

joins :: Evt (Evt a) -> Evt a Source #

Joins event stream of streams. If stream is started it runs until the end.

delay :: NominalDiffTime -> Evt a -> Evt a Source #

Delays in the thread of execution. Note that it can interfere and screw up functions like clock, timer, pulse, ticks

delayFork :: NominalDiffTime -> Evt a -> Evt a Source #

Delays in background by forking on each event. Note tht if delayed event was put into background prior to stopping of the main event stream it will fire anyway. There is no way to stop it.

sums :: Num a => Evt a -> Evt a Source #

Sums all the elements in the event stream

sumD :: Num a => Float -> Dyn a -> Dyn a Source #

Sums all the elements in the event stream

integrate :: (VectorSpace v, Scalar v ~ Float) => Float -> Dyn v -> Dyn v Source #

products :: Num a => Evt a -> Evt a Source #

Finds the product of all elements in the event stream.

count :: Evt a -> Evt Int Source #

Counts how many events accured so far on the stream.

withCount :: Evt a -> Evt (Int, a) Source #

appends :: Monoid a => Evt a -> Evt a Source #

Monoidal append of all elements in the stream

takes :: Int -> Evt a -> Evt a Source #

Takes only so many events from the stream

drops :: Int -> Evt a -> Evt a Source #

Takes only so many events from the stream

takesWhile :: (a -> Bool) -> Evt a -> Evt a Source #

Takes events only while predicate is true.

dropsWhile :: (a -> Bool) -> Evt a -> Evt a Source #

Takes events only while predicate is true.

cycles :: [a] -> Evt b -> Evt a Source #

Cycles the values in the list over event sream.

listAt :: [a] -> Evt Int -> Evt a Source #

Takes elements from the list by index. If index is out of bounds the event is omitted.

toToggle :: Evt a -> Evt Bool Source #

Turns event stream to toggle stream. It produce cyclic sequence of [True, False]

races :: Evt a -> Evt a -> Evt a Source #

Repeatedly executes the same event stream

forks :: Evt a -> Evt a Source #

Repeatedly executes the same event stream

forevers :: Evt a -> Evt a Source #

Repeatedly executes the same event stream

folds :: Monoid a => Evt a -> Run a Source #

Monoidal fold for event streams, note that stream have to be finite for the function to complete

foldls :: (b -> a -> b) -> b -> Evt a -> Run b Source #

Left fold for event streams, note that stream have to be finite for the function to complete

foldls' :: (b -> a -> Run b) -> b -> Evt a -> Run b Source #

Effectful left fold

foldrs :: (a -> b -> b) -> b -> Evt a -> Run b Source #

Right fold for event streams, note that stream have to be finite for the function to complete

foldrs' :: (a -> b -> Run b) -> b -> Evt a -> Run b Source #

Effectful right fold

prints :: Show a => Evt a -> Run () Source #

Starts event stream process and as callback prints it values.

putStrLns :: Evt String -> Run () Source #

Starts event stream process and as callback prints it values.

Event/Dynamic interaction

hold :: a -> Evt a -> Dyn a Source #

Turns event stream to dynamic. It holds the values of events until the next event happen. It starts with initial value.

hold initVal events = ...

unhold :: Dyn a -> Evt a Source #

Turns dynamic into event stream of underlying events that trigger dynamic updates.

scanD :: (a -> b -> b) -> b -> Evt a -> Dyn b Source #

scans over event stream and converts it to dynamic.

scanMayD :: (a -> b -> Maybe b) -> b -> Evt a -> Dyn b Source #

Dynamic scan that can also filter out events. If Nothing is produced then the event is skipped.

switchD :: Dyn a -> Evt (Dyn a) -> Dyn a Source #

Switches between dynamic producers.

switchDyn :: Dyn (Evt a) -> Evt a Source #

Queries the event stream form dynamic and runs it all next event streams are ignored.

apply :: Dyn (a -> b) -> Evt a -> Evt b Source #

Applies a function to event stream value. The function is sampled from dynamic process.

applyMay :: Dyn (a -> Maybe b) -> Evt a -> Evt b Source #

Apply combined with filter.

snap :: Dyn a -> Evt b -> Evt a Source #

Snapshot of dynamic process with event stream. All values in the event stream are substituted with current value of dynamic.

attach :: Dyn a -> Evt b -> Evt (a, b) Source #

Kind of zipWith function for dynamics and event streams.

attachWith :: (a -> b -> c) -> Dyn a -> Evt b -> Evt c Source #

Kind of zipWith function for dynamics and event streams.

attachWithMay :: (a -> b -> Maybe c) -> Dyn a -> Evt b -> Evt c Source #

Attach with filtering. When Nothing is produced event is omitted from the stream.

(<@>) :: Dyn (a -> b) -> Evt a -> Evt b infixl 4 Source #

Infix variant of apply

(<@) :: Dyn a -> Evt b -> Evt a infixl 4 Source #

Infix variant of snap.

Effectful API

class RunFunctor f where Source #

Methods

fmap' :: (a -> Run b) -> f a -> f b Source #

Instances

Instances details
RunFunctor Dyn Source # 
Instance details

Defined in Dyna.Gloss.Frp

Methods

fmap' :: (a -> Run b) -> Dyn a -> Dyn b Source #

RunFunctor Evt Source # 
Instance details

Defined in Dyna.Gloss.Frp

Methods

fmap' :: (a -> Run b) -> Evt a -> Evt b Source #

foreach :: (a -> Run ()) -> Evt a -> Evt a Source #

Adds some procedure to callback. Procedure is called prior to callback execution.

posteach :: (a -> Run ()) -> Evt a -> Evt a Source #

Adds some procedure to callback. Procedure is called after callback execution.

iterates' :: (a -> Run a) -> a -> Evt b -> Evt a Source #

Effectful version for iterateE.

scan' :: (a -> b -> Run b) -> b -> Evt a -> Evt b Source #

scan over event stream with effectful function.

scanMay' :: (a -> b -> Run (Maybe b)) -> b -> Evt a -> Evt b Source #

scan combined with filter for effectful function. See scanMay for details.

accum' :: (a -> s -> Run (b, s)) -> s -> Evt a -> Evt b Source #

Accumulate over event stream.

accumMay' :: (a -> s -> Run (Maybe (b, s))) -> s -> Evt a -> Evt b Source #

Accumulate over event stream.

filters' :: (a -> Run Bool) -> Evt a -> Evt a Source #

Effectful filtering for event streams.

mapMay' :: (a -> Run (Maybe b)) -> Evt a -> Evt b Source #

Map with filtering. When Nothing is produced event is omitted from the stream.

apply' :: Dyn (a -> Run b) -> Evt a -> Evt b Source #

Effectful variant of apply.

applyMay' :: Dyn (a -> Run (Maybe b)) -> Evt a -> Evt b Source #

Effectful applyMay.

Utilities

Channels (interaction with the world)

mchanEvt :: Chan a -> Evt a Source #

Creates the event stream that listens to MVar based channel. If any value is put chan the event stream fires the callback.

tchanEvt :: TChan a -> Evt a Source #

Creates the event stream that listens to MVar based channel. If any value is put chan the event stream fires the callback.

uchanEvt :: InChan a -> Evt a Source #

Creates the event stream that listens to unagi channel (package unagi-chan). If any value is put chan the event stream fires the callback.

Clock

clock :: NominalDiffTime -> Evt UTCTime Source #

Queries current time periodically with given period in seconds.

pulse :: NominalDiffTime -> Evt () Source #

Produces pulse events with given period in seconds.

ticks :: Float -> Evt Float Source #

Produces pulse events with given period in seconds and also tells how many seconds exactly has passed. It can be useful for simulations of models that are based on differential equations. As event streams carries how much time has passed between simulation steps.

timer :: Float -> Evt Float Source #

Timer behaves like tocks only it produces accumulated time since beginning of the process. It calculates them by querying current time and suntracting start time from it.

It can be though of as:

sumE ticks

timerD :: Float -> Dyn Float Source #

Continuous timeline updated at given interval.

Random

toRandom :: Random b => Evt a -> Evt b Source #

Substitutes values in event stream with random values.

toRandomR :: Random b => (b, b) -> Evt a -> Evt b Source #

Substitutes values in event stream with random values from the given range.

withRandom :: Random b => Evt a -> Evt (b, a) Source #

Substitutes values in event stream with random values.

withRandomR :: Random b => (b, b) -> Evt a -> Evt (b, a) Source #

Substitutes values in event stream with random values from the given range.

oneOf :: [a] -> Evt b -> Evt a Source #

Picks at random one element from the list

withOneOf :: [a] -> Evt b -> Evt (a, b) Source #

Picks at random one element from the list

freqOf :: Dyn [(a, Rational)] -> Evt b -> Evt a Source #

Picks at random one element from the list. We also provide distribution of events. Probability to pick up the element. Sum of probabilities should equal to 1.

withFreqOf :: Dyn [(a, Rational)] -> Evt b -> Evt (a, b) Source #

Picks at random one element from the list. We also provide distribution of events. Probability to pick up the element. Sum of probabilities should equal to 1.

randSkip :: Dyn Double -> Evt a -> Evt a Source #

Skips at random elements from the list. We provide frequency to skip events with dynamic first argument.

randSkipBy :: Dyn (a -> Double) -> Evt a -> Evt a Source #

Skips elements at random. The probability to skip element depends on the element itself.

Re-exports

liftA2 :: Applicative f => (a -> b -> c) -> f a -> f b -> f c #

Lift a binary function to actions.

Some functors support an implementation of liftA2 that is more efficient than the default one. In particular, if fmap is an expensive operation, it is likely better to use liftA2 than to fmap over the structure and then use <*>.

This became a typeclass method in 4.10.0.0. Prior to that, it was a function defined in terms of <*> and fmap.

Using ApplicativeDo: 'liftA2 f as bs' can be understood as the do expression

do a <- as
   b <- bs
   pure (f a b)

liftA3 :: Applicative f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d #

Lift a ternary function to actions.

Using ApplicativeDo: 'liftA3 f as bs cs' can be understood as the do expression

do a <- as
   b <- bs
   c <- cs
   pure (f a b c)