| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.FunctionBuilder
Contents
Description
A builder for functions of variable parameters
FunctionBuilder values can be composed, and eventually rendered
into a function by toFunction.
For example the composition of:
fb1 :: FunctionBuilder MyMonoid composeMe (Int -> composeMe) fb1 = addParameter ... fb2 :: FunctionBuilder MyMonoid composeMe (String -> composeMe) fb2 = addParameter ... fb3 :: FunctionBuilder MyMonoid composeMe (Bool -> composeMe) fb3 = addParameter ... fb :: FunctionBuilder MyMonoid composeMe (Int -> String -> Bool -> composeMe) fb = fb1 . fb2 . fb3 f :: Int -> String -> Bool -> MyMonoid f = toFunction fb123
FunctionBuilders are composed via . from Category and <> from Semigroup.
This module provides Functor, Applicative, Monad, Semigroup, Monoid and
Category instances;
The smart-constructors immediate and addParameter create FunctionBuilders
that either write a hard coded constant to the output Monoid or add a function
that will be applied to an additional runtime parameter.
Further glue-code is provided to allow changing the underlying Monoid, see bind.
Synopsis
- newtype FunctionBuilder acc next f_make_next = FB {
- runFunctionBuilder :: (acc -> next) -> f_make_next
- toFunction :: FunctionBuilder output output make_output -> make_output
- immediate :: m -> FunctionBuilder m r r
- fillParameter :: FunctionBuilder m r (a -> b) -> a -> FunctionBuilder m r b
- tagParameter :: forall tag m r a b. FunctionBuilder m r (a -> b) -> FunctionBuilder m r (Tagged tag a -> b)
- bind :: FunctionBuilder m g_next f_g_next -> (m -> FunctionBuilder n next g_next) -> FunctionBuilder n next f_g_next
- mapAccumulator :: (m -> n) -> FunctionBuilder m a b -> FunctionBuilder n a b
- mapNext :: (s -> r) -> FunctionBuilder m r a -> FunctionBuilder m s a
- class HasFunctionBuilder m a where
- type ToFunction m a r
- toFunctionBuilder :: a -> FunctionBuilder m r (ToFunction m a r)
- class (HasFunctionBuilder w a, ToFunction w a r ~ (b -> r)) => HasParameter w a b r
- class StaticContent m a where
- addStaticContent :: a -> FunctionBuilder m next next
- class DynamicContent m a parameter | m a -> parameter where
- addParameter :: a -> FunctionBuilder m next (parameter -> next)
Documentation
newtype FunctionBuilder acc next f_make_next Source #
A tricky newtype wrapper around a function that carries out a computation resulting in a monoidal output value that is passed to a continuation.
Type parameters:
acc- Type of monoidal value that is build from the parameters of the function
returned by
toFunction. For example: In aprintfstyle formatting libraryacccould beString. next- The trick- parameter that allows composing
FunctionBuilders. Also note thatFunctionBuilders are contravarient in this parameter;nextis the output of the continuationacc -> next, hence this is an input from the perspective of theFunctionBuilder. f_make_next- This is usually a function type that returns
next, this is the type of the output function returned bytoFunction.
A FunctionBuilder acc next f is a newtype wrapper around functions of type
(acc -> next) -> f.
The immediate return value of the function is usually a function type,
that takes zero or more arguments: a_0 -> .. -> a_N -> next.
The FunctionBuilders that addParameter returns are polymorphic in next.
And next is the key for composition.
For example:
fb1 :: FunctionBuilder MyMonoid next (Int -> next) fb1 = addParameter undefined fb2 :: FunctionBuilder MyMonoid next (String -> next) fb2 = addParameter undefined newtype MyMonoid = MyMonoid () deriving (Semigroup, Monoid)
When we desugar with ghci:
>>>:t (runFunctionBuilder fb1)(runFunctionBuilder fb1) :: (MyMonoid -> next) -> Int -> next
>>>:t (runFunctionBuilder fb2)(runFunctionBuilder fb2) :: (MyMonoid -> next) -> String -> next
Composition comes in two flavours:
- By using
.to add to the accumulator a value passed to an additional argument of the resulting output function (see example below). - By using
<>to append a fixed value to the accumulator directly.
When composing fb1 and fb2 using . we get:
>>>:t (fb1 . fb2)(fb1 . fb2) :: FunctionBuilder MyMonoid a (Int -> String -> a)
And desugared:
>>>:t runFunctionBuilder (fb1 . fb2)runFunctionBuilder (fb1 . fb2) :: (MyMonoid -> next) -> Int -> String -> next
What happened during composition was that the next in fb1 was used to insert
into Int -> next the String -> other_next from fb2; such that this results in
Int -> (String -> other_next).
(Note: For clarity I renamed the type local type parameter next to other_next from fb2)
Also, there is the StaticContent type class for types that have function builders.
Constructors
| FB | |
Fields
| |
Instances
| Monoid m => Category (FunctionBuilder m :: Type -> Type -> Type) Source # | Compose |
Defined in Data.FunctionBuilder Methods id :: FunctionBuilder m a a # (.) :: FunctionBuilder m b c -> FunctionBuilder m a b -> FunctionBuilder m a c # | |
| Monad (FunctionBuilder m r) Source # | |
Defined in Data.FunctionBuilder Methods (>>=) :: FunctionBuilder m r a -> (a -> FunctionBuilder m r b) -> FunctionBuilder m r b # (>>) :: FunctionBuilder m r a -> FunctionBuilder m r b -> FunctionBuilder m r b # return :: a -> FunctionBuilder m r a # fail :: String -> FunctionBuilder m r a # | |
| Functor (FunctionBuilder m r) Source # | |
Defined in Data.FunctionBuilder Methods fmap :: (a -> b) -> FunctionBuilder m r a -> FunctionBuilder m r b # (<$) :: a -> FunctionBuilder m r b -> FunctionBuilder m r a # | |
| Applicative (FunctionBuilder m r) Source # | |
Defined in Data.FunctionBuilder Methods pure :: a -> FunctionBuilder m r a # (<*>) :: FunctionBuilder m r (a -> b) -> FunctionBuilder m r a -> FunctionBuilder m r b # liftA2 :: (a -> b -> c) -> FunctionBuilder m r a -> FunctionBuilder m r b -> FunctionBuilder m r c # (*>) :: FunctionBuilder m r a -> FunctionBuilder m r b -> FunctionBuilder m r b # (<*) :: FunctionBuilder m r a -> FunctionBuilder m r b -> FunctionBuilder m r a # | |
| Semigroup m => Semigroup (FunctionBuilder m r r) Source # | Allow appending a |
Defined in Data.FunctionBuilder Methods (<>) :: FunctionBuilder m r r -> FunctionBuilder m r r -> FunctionBuilder m r r # sconcat :: NonEmpty (FunctionBuilder m r r) -> FunctionBuilder m r r # stimes :: Integral b => b -> FunctionBuilder m r r -> FunctionBuilder m r r # | |
| Monoid m => Monoid (FunctionBuilder m r r) Source # | Allow appending a |
Defined in Data.FunctionBuilder Methods mempty :: FunctionBuilder m r r # mappend :: FunctionBuilder m r r -> FunctionBuilder m r r -> FunctionBuilder m r r # mconcat :: [FunctionBuilder m r r] -> FunctionBuilder m r r # | |
toFunction :: FunctionBuilder output output make_output -> make_output Source #
Get the composed output function of a FunctionBuilder.
The FunctionBuilder passed to this function must match this signature:
FunctionBuilder m m (arg0 -> .. -> m)
This means that the result of the generated function arg0 -> .. -> m MUST be
m, the underlying Monoid.
The FunctionBuilders generated by addParameter and immediate are parametric
in the second type parameter and match the type signature required by this function.
Example 1:
fb :: FunctionBuilder String String (Int -> Double -> Int -> String) fb = undefined example :: Int -> Double -> Int -> String example = toFunction fb
Example 2:
example :: Int -> Double -> Int -> String example = toFunction (i . d . i) s :: String -> FunctionBuilder String a a s x = FB (\k -> k x) i :: FunctionBuilder String next (Int -> next) i = FB (\k x -> k $ show x) d :: FunctionBuilder String next (Double -> next) d = FB (\k x -> k $ show x)
Building FunctionBuilders
immediate :: m -> FunctionBuilder m r r Source #
Create a FunctionBuilder that appends something to the (monoidal-) output value.
This is a smart constructor for a FunctionBuilder.
This functions is probably equal to:
immediate x = FB (\k -> k x)
The generated builder can be passed to toFunction since it is parametric
in its second type parameter.
Example:
When building a String formatting FunctionBuilder
the function to append a literal string could be:
s :: String -> FunctionBuilder String a a s = immediate
c :: Char -> FunctionBuilder String a a c = immediate . (:[])
example :: String example = toFunction (s "hello" . c ' ' . s "world")
>>>example"hello world"
See the example in toFunction.
Modifying Parameters of FunctionBuilders
fillParameter :: FunctionBuilder m r (a -> b) -> a -> FunctionBuilder m r b Source #
Take away a function parameter added with addParameter by pre - applying it to some
value.
For example:
intArg :: FunctionBuilder MyMonoid a (Int -> a) intArg = addParameter undefined stringArg :: FunctionBuilder MyMonoid a (String -> a) stringArg = addParameter undefined twoInt :: FunctionBuilder MyMonoid a (Int -> String -> a) twoInt = intArg . stringArg example :: FunctionBuilder MyMonoid a (String -> a) example = fillParameter twoInt 42
This is equivalent to:
fillParameter f x = f * pure x
tagParameter :: forall tag m r a b. FunctionBuilder m r (a -> b) -> FunctionBuilder m r (Tagged tag a -> b) Source #
Convert a FunctionBuilder for a function (a -> b) to (Tagged tag a -> b).
FunctionBuilder Transformations
bind :: FunctionBuilder m g_next f_g_next -> (m -> FunctionBuilder n next g_next) -> FunctionBuilder n next f_g_next Source #
Compose to FunctionBuilders such that the second FunctionBuilder may depend on the intermediate result
of the first. Similar to a monadic bind >>= but more flexible sind the underlying
Monoid may change too, for example:
intText :: FunctionBuilder Text next (Int -> next) intText = addParameter undefined unpackB :: Text -> FunctionBuilder String next next unpackB = immediate . unpack intStr :: FunctionBuilder String next (Int -> next) intStr = intText `bind` unpackB
mapAccumulator :: (m -> n) -> FunctionBuilder m a b -> FunctionBuilder n a b Source #
Convert the accumulated (usually monoidal-) value, this allows to change the underlying accumlator type.
mapNext :: (s -> r) -> FunctionBuilder m r a -> FunctionBuilder m s a Source #
Convert the output of a FunctionBuilder value; since most
FunctionBuilders are parameteric in r they also have r in a
in a, such that a always either is r or is a
function returning r eventually.
In order to get from a FunctionBuilder that can accept a continuation returning it an r
to a FunctionBuilder that accepts continuations returning an s instead, we need to
apply a function s -> r to the return value of the continuation.
Note that a mapNext will not only change the r to an s but
probably also the the a, when it is parametric, as in this contrived example:
example :: Int -> x -> Sum Int example = toFunction (ign add) add :: FunctionBuilder (Sum Int) next (Int -> next) add = FB (\k x -> k $ Sum x) ign :: FunctionBuilder m (x -> r) a -> FunctionBuilder m r a ign = mapNext const
Here the extra parameter x is pushed down into the a of the add FunctionBuilder.
class HasFunctionBuilder m a where Source #
Types a that can be turned into FunctionBuilders
for a base monoid m.
This is the abstract version of StaticContent and DynamicContent
Since: 0.1.2.0
Methods
toFunctionBuilder :: a -> FunctionBuilder m r (ToFunction m a r) Source #
Make a FunctionBuilder from some value.
class (HasFunctionBuilder w a, ToFunction w a r ~ (b -> r)) => HasParameter w a b r Source #
Types a that one parameter to a FunctionBuilders for a base monoid m.
Since: 0.1.2.0
class StaticContent m a where Source #
Types a that can be turned into FunctionBuilders
for a base monoid m.
These type can provide a function to work on the internal monoid,
They can be constructed using immediate.
Of course they can incorporate information statically known at compile time or via type class dictionaries (through singletons for instance).
For example:
instance forall s . (KnownSymbol s) => StaticContent String (Proxy s) where addStaticContent = immediate (symbolVal (Proxy @s))
Since: 0.2.0.0
Methods
addStaticContent :: a -> FunctionBuilder m next next Source #
Return a FunctionBuilder that can work on the underlying monoid.
Instances
| StaticContent m m Source # | Create a This is a smart constructor for a immediate x = FB (\k -> k x) The generated builder can be passed to Example: When building a s :: String -> FunctionBuilder String a a s = immediate c :: Char -> FunctionBuilder String a a c = immediate . (:[]) example :: String example = toFunction (s "hello" . c ' ' . s "world")
See the example in |
Defined in Data.FunctionBuilder Methods addStaticContent :: m -> FunctionBuilder m next next Source # | |
class DynamicContent m a parameter | m a -> parameter where Source #
Types that have a FunctionBuilder with a runtime parameter
for a base monoid m.
For example:
If an instance adds an Int parameter, it will define this family instance:
instance DynamicContent String (Proxy "%i") Int where addParameter _ = addParameter
Since: 0.2.0.0
Methods
addParameter :: a -> FunctionBuilder m next (parameter -> next) Source #
Create a FunctionBuilder that adds a parameter to the output function,
and converts that argument to a value that can be accumulated in the
resulting monoidal value.
Instances
| DynamicContent m (a -> m) a Source # | This instance is basically a smart constructor for a This functions is probably equal to: addParameter f = FB (\k x -> k (f x)) The generated builder can be passed to Example: When building a showing :: Show a => FunctionBuilder String r (a -> r) showing = addParameter show example :: (Show a, Show b) => a -> b -> String example = toFunction (showing . showing)
See the example in |
Defined in Data.FunctionBuilder Methods addParameter :: (a -> m) -> FunctionBuilder m next (a -> next) Source # | |