Search results
compose2 :: forall a b x y. (a -> b) -> (x -> y -> a) -> x -> y -> b
\f g x y -> f (g x y)
composeSecondFlipped :: forall a b x y. (y -> b) -> (x -> b -> a) -> x -> y -> a
over2 :: forall t a s b. Newtype t a => Newtype s b => (a -> t) -> (a -> a -> b) -> t -> t -> s
Lifts a binary function to operate over newtypes.
newtype Meter = Meter Int
derive newtype instance newtypeMeter :: Newtype Meter _
newtype SquareMeter = SquareMeter Int
derive newtype instance newtypeSquareMeter :: Newtype SquareMeter _
area :: Meter -> Meter -> SquareMeter
area = over2 Meter (*)
The above example also demonstrates that the return type is polymorphic here too.
under2 :: forall t a s b. Newtype t a => Newtype s b => (a -> t) -> (t -> t -> s) -> a -> a -> b
The opposite of over2: lowers a binary function that operates on Newtyped
values to operate on the wrapped value instead.
traverse :: forall f t a. Coercible (f a) (f t) => Newtype t a => (a -> t) -> (a -> f a) -> t -> f t
Similar to the function from the Traversable class, but operating within
a newtype instead.
applySecondFlipped :: forall x y a. x -> (y -> x -> a) -> y -> a
compose :: forall c b a. (b -> c) -> (a -> b) -> (a -> c)
Returns a new function that calls the first function with the result of calling the second.
let addTwo x = x + 2
let double x = x * 2
let addTwoThenDouble x = addTwo :compose double
addTwoThenDouble 3 -- 10
This is function composition.
finch :: forall c b a. a -> (c -> a -> b) -> c -> b
F combinator - finch
ETTET
Λ a b c . a → b → (b → a → c) → c
λ x y f . f y x
robin :: forall c b a. a -> (b -> a -> c) -> b -> c
R combinator - robin
BBT
Λ a b c . a → (b → a → c) → b → c
λ x f y . f y x
over :: forall t a s b. Newtype t a => Newtype s b => (a -> t) -> (a -> b) -> t -> s
Lifts a function operate over newtypes. This can be used to lift a
function to manipulate the contents of a single newtype, somewhat like
map does for a Functor:
newtype Label = Label String
derive instance newtypeLabel :: Newtype Label _
toUpperLabel :: Label -> Label
toUpperLabel = over Label String.toUpper
But the result newtype is polymorphic, meaning the result can be returned as an alternative newtype:
newtype UppercaseLabel = UppercaseLabel String
derive instance newtypeUppercaseLabel :: Newtype UppercaseLabel _
toUpperLabel' :: Label -> UppercaseLabel
toUpperLabel' = over Label String.toUpper
under :: forall t a s b. Newtype t a => Newtype s b => (a -> t) -> (t -> s) -> a -> b
The opposite of over: lowers a function that operates on Newtyped
values to operate on the wrapped value instead.
newtype Degrees = Degrees Number
derive instance newtypeDegrees :: Newtype Degrees _
newtype NormalDegrees = NormalDegrees Number
derive instance newtypeNormalDegrees :: Newtype NormalDegrees _
normaliseDegrees :: Degrees -> NormalDegrees
normaliseDegrees (Degrees deg) = NormalDegrees (deg % 360.0)
asNormalDegrees :: Number -> Number
asNormalDegrees = under Degrees normaliseDegrees
As with over the Newtype is polymorphic, as illustrated in the example
above - both Degrees and NormalDegrees are instances of Newtype,
so even though normaliseDegrees changes the result type we can still put
a Number in and get a Number out via under.
memoCompose :: forall a b c. (a -> b) -> (b -> c) -> a -> c
Memoize the composition of two functions
foldingWithIndex :: forall f i x y z. FoldingWithIndex f i x y z => f -> i -> x -> y -> z
mapmap :: forall f g a b. Functor f => Functor g => (a -> b) -> f (g a) -> f (g b)
mmap :: forall a b f g. Functor f => Functor g => (a -> b) -> f (g a) -> f (g b)
foldingWithIndex :: forall f i x y z. FoldingWithIndex f i x y z => f -> i -> x -> y -> z
new3 :: forall b a3 a2 a1 o. o -> a1 -> a2 -> a3 -> b
worbler :: forall b a. b -> (b -> b -> a) -> a
W1 combinator - converse warbler
CW
Λ a b . a → (a → a → b) → b
λ x f = f x x
for :: forall a b m t. Applicative m => Traversable t => t a -> (a -> m b) -> m (t b)
A version of traverse with its arguments flipped.
This can be useful when running an action written using do notation for every element in a data structure:
For example:
for [1, 2, 3] \n -> do
print n
return (n * n)
mkQ :: forall a b r. Typeable a => Typeable b => r -> (b -> r) -> a -> r
bind :: forall m a b. Bind m => m a -> (a -> m b) -> m b
discard :: forall a f b. Discard a => Bind f => f a -> (a -> f b) -> f b
catchError :: forall e m a. MonadError e m => m a -> (e -> m a) -> m a
apApplyFlipped :: forall f b a. Apply f => f a -> f (a -> b) -> f b
applyOp :: forall event a b. Applicative event => event a -> event (a -> b) -> event b
sampleOnLeft :: forall event a b. IsEvent event => event a -> event (a -> b) -> event b
sampleOnRight :: forall event a b. IsEvent event => event a -> event (a -> b) -> event b
sampleOn :: forall event b a. IsEvent event => event a -> event (a -> b) -> event b
bind' :: forall v1 v0 m c. HasBind c m => ObjectOf c v0 => ObjectOf c (m v1) => Restrictable Function c => m v0 -> (v0 -> (m v1)) -> m v1
bind :: forall c b a. HasChain a => a b -> (b -> a c) -> a c
A version of chain with the arguments flipped. This is provided only to
support desugaring do notation. It is not recommended to use explicitly.
controlError :: forall f g e a. ErrorControl f g e => f a -> (e -> g a) -> g a
fairConjunction :: forall b a m. MonadLogic m => m a -> (a -> m b) -> m b
hummingbird :: forall m b a. Bind m => m a -> (a -> m b) -> m b
H combinator - hummingbird
BW(BC)
Λ a b c (a → b → a → c) → a → b → c
λ f x y . f x y x
when :: forall b a m. MonadLogic m => m a -> (a -> m b) -> m b
apply :: forall a b. (a -> b) -> a -> b
Applies a function to an argument. This is primarily used as the operator
($) which allows parentheses to be omitted in some cases, or as a
natural way to apply a chain of composed functions to a value.
liftA1 :: forall f a b. Applicative f => (a -> b) -> f a -> f b
liftA1 provides a default implementation of (<$>) for any
Applicative functor, without using (<$>) as provided
by the Functor-Applicative superclass
relationship.
liftA1 can therefore be used to write Functor instances
as follows:
instance functorF :: Functor F where
map = liftA1
liftM1 :: forall m a b. Monad m => (a -> b) -> m a -> m b
liftM1 provides a default implementation of (<$>) for any
Monad, without using (<$>) as provided by the
Functor-Monad superclass relationship.
liftM1 can therefore be used to write Functor instances
as follows:
instance functorF :: Functor F where
map = liftM1
map :: forall f a b. Functor f => (a -> b) -> f a -> f b
un :: forall t a. Newtype t a => (a -> t) -> t -> a
Given a constructor for a Newtype, this returns the appropriate unwrap
function.
all :: forall a b f. Foldable f => HeytingAlgebra b => (a -> b) -> f a -> b
all f is the same as and <<< map f; map a function over the structure,
and then get the conjunction of the results.
any :: forall a b f. Foldable f => HeytingAlgebra b => (a -> b) -> f a -> b
any f is the same as or <<< map f; map a function over the structure,
and then get the disjunction of the results.
foldMap :: forall f a m. Foldable f => Monoid m => (a -> m) -> f a -> m
foldMap1 :: forall t a m. Foldable1 t => Semigroup m => (a -> m) -> t a -> m
foldMap1DefaultL :: forall t m a. Foldable1 t => Functor t => Semigroup m => (a -> m) -> t a -> m
A default implementation of foldMap1 using foldl1.
Note: when defining a Foldable1 instance, this function is unsafe to use
in combination with foldl1Default.
foldMap1DefaultR :: forall t m a. Foldable1 t => Functor t => Semigroup m => (a -> m) -> t a -> m
A default implementation of foldMap1 using foldr1.
Note: when defining a Foldable1 instance, this function is unsafe to use
in combination with foldr1Default.
foldMapDefault :: forall i f a m. FoldableWithIndex i f => Monoid m => (a -> m) -> f a -> m
A default implementation of foldMap using foldMapWithIndex
foldMapDefaultL :: forall f a m. Foldable f => Monoid m => (a -> m) -> f a -> m
A default implementation of foldMap using foldl.
Note: when defining a Foldable instance, this function is unsafe to use
in combination with foldlDefault.
foldMapDefaultR :: forall f a m. Foldable f => Monoid m => (a -> m) -> f a -> m
A default implementation of foldMap using foldr.
Note: when defining a Foldable instance, this function is unsafe to use
in combination with foldrDefault.
mapDefault :: forall i f a b. FunctorWithIndex i f => (a -> b) -> f a -> f b
A default implementation of Functor's map in terms of mapWithIndex
cmap :: forall f a b. Contravariant f => (b -> a) -> f a -> f b
cmapFlipped :: forall a b f. Contravariant f => f a -> (b -> a) -> f b
cmapFlipped is cmap with its arguments reversed.
asks :: forall e1 e2 w a. ComonadAsk e1 w => (e1 -> e2) -> w a -> e2
Get a value which depends on the environment.
tracks :: forall w a t. ComonadTraced t w => (a -> t) -> w a -> a
Extracts a value at a relative position which depends on the current value.
squigglyMap :: forall f a b. Functor f => (a -> b) -> f a -> f b
memoize :: forall a b. Tabulate a => (a -> b) -> a -> b
Memoize a function of one argument
delay :: forall m a b. Delay m => a -> (a -> m b) -> m b
areads :: forall m r s a. MonadEffect m => Refer s r => (s -> a) -> r -> m a
map :: forall p q a b. Dissect p q => (a -> b) -> p a -> p b
A tail-recursive map operation, implemented in terms of Dissect.
memoize :: forall b a. Tabulate a => (a -> b) -> a -> b
Memoize a function of one argument
over :: forall s t a b @sym lenses. IsSymbol sym => ParseSymbol sym lenses => ConstructBarlow lenses Function s t a b => (a -> b) -> s -> t
applicator :: forall b a. (a -> b) -> a -> b
A combinator - applicator
Λ a b . (a → b) → a → b
λ f x . f x
defaultFilter :: forall a h f. BooleanEq h => Applicative f => Foldable f => Monoid (f a) => (a -> h) -> f a -> f a
filter :: forall f h a. Filterable f => BooleanEq h => (a -> h) -> f a -> f a
foldMap :: forall a b s. Convert s (Statements a) => Monoid b => (a -> b) -> s -> b
idstar :: forall b a. (a -> b) -> a -> b
I* combinator - id bird once removed
S(SK)
Λ a b . (a → b) → a → b
λ f x . f x
intercept :: forall a e g f. ErrorControl f g e => f a -> (e -> a) -> g a
liftF :: forall b a f. Applicative f => (a -> b) -> a -> f b
local :: forall a b r. (a -> b) -> (Ask b => r) -> (Ask a => r)
Run a function over an implicit parameter
Note: Be careful while using this to map over the value without updating the type.
-- evaluates to `1`, not `2` provide 1 (local ((*) 2) (ask @Int))
map :: forall a c b. HasMap a => (b -> c) -> a b -> a c
map :: forall f a b. Functor f => (a -> b) -> f a -> f b
mapUndefined :: forall b a. (a -> b) -> a -> b
memoize :: forall a b. (a -> b) -> a -> b
Memoize the function f. If the argument of f differs from the previous call, then f is recomputed.
moldMap :: forall t e m. Moldable t e => Monoid m => (e -> m) -> t -> m
moldMapDefaultL :: forall m e t. Moldable t e => Monoid m => (e -> m) -> t -> m
moldMapDefaultR :: forall m e t. Moldable t e => Monoid m => (e -> m) -> t -> m
A default implementation of moldMap based on moldr
nmap :: forall fa fb a b. NestedFunctor fa fb a b => (a -> b) -> fa -> fb
on :: forall evt obj callback out proxy. On evt obj callback out => proxy evt -> obj -> callback -> out
mapFlipped :: forall f a b. Functor f => f a -> (a -> b) -> f b
mapFlipped is map with its arguments reversed. For example:
[1, 2, 3] <#> \n -> n * n
modify :: forall t a. Newtype t a => (a -> a) -> t -> t
This combinator unwraps the newtype, applies a monomorphic function to the contained value and wraps the result back in the newtype
enumFromThenTo :: forall f a. Unfoldable f => Functor f => BoundedEnum a => a -> a -> a -> f a
Returns a sequence of elements from the first value, taking steps according to the difference between the first and second value, up to (but not exceeding) the third value.
enumFromThenTo 0 2 6 = [0, 2, 4, 6]
enumFromThenTo 0 3 5 = [0, 3]
Note that there is no BoundedEnum instance for integers, they're just
being used here for illustrative purposes to help clarify the behaviour.
The example shows Array return values, but the result can be any type
with an Unfoldable1 instance.
censor :: forall w m a. MonadWriter w m => (w -> w) -> m a -> m a
Modify the final accumulator value by applying a function.
local :: forall e w a. ComonadEnv e w => (e -> e) -> w a -> w a
local :: forall r m a. MonadReader r m => (r -> r) -> m a -> m a
peeks :: forall s a w. ComonadStore s w => (s -> s) -> w a -> a
Extract a value from a position which depends on the current position.
seeks :: forall s a w. ComonadStore s w => (s -> s) -> w a -> w a
Reposition the focus at the specified position, which depends on the current position.
flippedMap :: forall f a b. Functor f => f a -> (a -> b) -> f b
transAnaT :: forall t f. Recursive t f => Corecursive t f => (t -> t) -> t -> t
transCataT :: forall t f. Recursive t f => Corecursive t f => (t -> t) -> t -> t
amodify :: forall m r s. MonadEffect m => Refer s r => (s -> s) -> r -> m s
censorAccum :: forall acc html a. Accum acc html => (acc -> acc) -> html a -> html a
setCtx :: forall ctx html a. Ctx ctx html => (ctx -> ctx) -> html a -> html a
mapErr :: forall e m a. MonadError e m => (e -> e) -> m a -> m a
everywhere :: forall a. Data a => (forall b. Data b => b -> b) -> a -> a
Apply a transformation everywhere, bottom-up
everywhere' :: forall a. Data a => (forall b. Data b => b -> b) -> a -> a
Apply a transformation everywhere, top-down
gmapT :: forall a. Data a => (forall b. Data b => b -> b) -> a -> a
A generic transformation that maps over the immediate subterms
iterate :: forall a u. Unfoldable1 u => (a -> a) -> a -> u a
Create an infinite Unfoldable1 by repeated application of a function to a seed value.
Analogous to iterateN, but with no iteration limit.
This should only be used to produce either lazy types (like lazy Lists) or
types with truncating Unfoldable1 instances (like Maybe).
mkT :: forall a b. Typeable a => Typeable b => (b -> b) -> a -> a
applyFlipped :: forall a b. a -> (a -> b) -> b
Applies an argument to a function. This is primarily used as the (#)
operator, which allows parentheses to be omitted in some cases, or as a
natural way to apply a value to a chain of composed functions.
clamp :: forall a. Ord a => a -> a -> a -> a
Clamp a value between a minimum and a maximum. For example:
let f = clamp 0 10
f (-5) == 0
f 5 == 5
f 15 == 10
asks :: forall r m a. MonadAsk r m => (r -> a) -> m a
Projects a value from the global context in a MonadAsk.