-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Functional combinators for monadic actions that require allocation and de-allocation -- -- See module docs for more information, and cv-combinators -- package for example usage. @package allocated-processor @version 0.0.1 module Foreign.ForeignPtrWrap -- | A wrapper for newForeignPtr that handles nullPtrs, and can be chained -- to an IO Ptr creator. -- -- Example usage: -- --
--   myPtrCreator = (createForeignPtr deallocFunc) . allocFunc
--   
-- -- where, allocFunc :: a->b->c->...-> IO (Ptr z) createForeignPtr :: (FunPtr (Ptr a -> IO ())) -> IO (Ptr a) -> IO (ForeignPtr a) -- | Fails if the ptr is nullPtr checkPtr :: IO (Ptr a) -> IO (Ptr a) -- | Names a failure errorName :: String -> IO a -> IO a -- | Framework for expressing monadic actions that require initialization -- and finalization. This module provides a functional interface -- for defining and chaining a series of processors. -- -- Motivating example: in the IO monad, bindings to C libraries that use -- functions such as: f(foo *src, foo *dst), where the pointer -- dst must be pre-allocated. In this case we normally do: -- --
--   foo *dst = allocateFoo();
--   ... 
--   while (something) {
--      f(src, dst);
--      ...
--   }
--   releaseFoo(dst);
--   
-- -- You can use the runUntil function below to emulate that loop. -- -- Processor is an instance of Category, Functor, Applicative and Arrow. -- -- In addition to the general type Processor m a b, this -- module also defines (and gives a semantic model for) -- Processor IO a b, which has synonym -- IOProcessor a b. module Control.Processor -- | The type of Processors -- -- -- -- The arguments to the constructor are: -- --
    --
  1. a -> x ->m x - Processing function: Takes input and -- internal state, and returns new internal state.
  2. --
  3. a -> m x - Allocator for internal state (this is run -- only once): Takes (usually the first) input, and returns initial -- internal state.
  4. --
  5. x -> m b - Convertor from state x to output b: Takes -- internal state and returns the output.
  6. --
  7. x -> m () - Releaser for internal state (finalizer, -- run once): Run after processor is done being used, to release the -- internal state.
  8. --
-- -- TODO: re-define in terms that don't need the x existential -- (and the allocator), using a continuation-style processing function. data Processor m a b Processor :: (a -> x -> m x) -> (a -> m x) -> (x -> m b) -> (x -> m ()) -> Processor m a b -- | The semantic model for IOProcessor is a function: -- --
--   [[ 'IOProcessor' a b ]] = a -> b
--   
-- -- To satisfy this model, the Processor value (the implementation) must -- obey the rules: -- --
    --
  1. The processing function (a -> x -> m x) must act as -- if purely, so that indeed for a given input the output is always the -- same. One particular thing to be careful with is that the output does -- not depend on time (for example, you shouldn't use IOProcessor to -- implement an input device). The IOSource type is defined -- exactly for time-dependent processors. For pointer typed inputs and -- outputs, see next law.
  2. --
  3. For processors that work on pointers, [[ Ptr t ]] = t. -- This is guaranteed by the following implementation constraints for -- IOProcessor a b:
  4. --
  5. If a is a pointer type (a = Ptr p), then the -- processor must NOT write (modify) the referenced data.
  6. --
  7. If b is a pointer, the memory it points to (and its -- allocation status) is only allowed to change by the processor that -- created it (in the processing and releasing functions). In a way this -- generalizes the first constraint.
  8. --
-- -- Note, that unlike Yampa, this model does not allow -- transformations of the type (Time -> a) -> (Time -> -- b). The reason is that I want to prevent arbitrary time access -- (whether causal or not). This limitation means that everything is -- essentially point-wise in time. To allow memory-full operations -- under this model, scanlT is defined. See -- http://www.ee.bgu.ac.il/~noamle/_downloads/gaccum.pdf for more -- about arbitrary time access. type IOProcessor a b = Processor IO a b -- | IOSource a b is the type of time-dependent processors, -- such that: -- --
--   [[ 'IOSource' a b ]] = (a, Time) -> b
--   
-- -- Thus, it is ok to implement a processing action that outputs arbitrary -- time-dependent values during runtime regardless of input. (Although -- the more useful case is to calculate something from the input -- a that is also time-dependent. The a input is often -- not required and in those cases a = () is used. -- -- Notice that this means that IOSource doesn't qualify as an -- IOProcessor. However, currently the implementation does -- NOT enforce this, i.e. IOSource is not a newtype; I don't know how -- to implement it correctly. Also, one question is whether primitives -- like chain will have to disallow placing IOSource as the -- second element in a chain. Maybe they should, maybe they shouldn't. type IOSource a b = Processor IO a b -- | TODO: What's the semantic model for IOSink a? type IOSink a = IOProcessor a () -- | TODO: do we need this? we're exporting the data constructor anyway for -- now, so maybe we don't. processor :: (Monad m) => (a -> x -> m x) -> (a -> m x) -> (x -> m b) -> (x -> m ()) -> Processor m a b -- | Chains two processors serially, so one feeds the next. chain :: Processor m a b' -> Processor m b' b -> Processor m a b -- | A processor that represents two sub-processors in parallel (although -- the current implementation runs them sequentially, but that may change -- in the future) parallel :: Processor m a b -> Processor m c d -> Processor m (a, c) (b, d) -- | Constructs a processor that: given two processors, gives source as -- input to both processors and runs them independently, and after both -- have have finished, outputs their combined outputs. -- -- Semantic meaning, using Arrow's (&&&) operator: [[ -- forkJoin ]] = &&& Or, considering the Applicative instance -- of functions (which are the semantic meanings of a processor): [[ -- forkJoin ]] = liftA2 (,) Alternative implementation to consider: f -- &&& g = (,) & f * g forkJoin :: Processor m a b -> Processor m a b' -> Processor m a (b, b') -- | The identity processor: output = input. Semantically, [[ empty ]] = id empty :: (Monad m) => Processor m a a -- | Splits (duplicates) the output of a functor, or on this case a -- processor. split :: (Functor f) => f a -> f (a, a) -- | 'f --< g' means: split f and feed it into g. Useful for feeding -- parallelized (***'d) processors. For example, a -- (b *** c) = a -- >> (b &&& c) (--<) :: (Functor (cat a), Category cat) => cat a a1 -> cat (a1, a1) c -> cat a c -- | Runs the processor once: allocates, processes, converts to output, and -- deallocates. run :: (Monad m) => Processor m a b -> a -> m b -- | Keeps running the processing function in a loop until a predicate on -- the output is true. Useful for processors whose main function is after -- the allocation and before deallocation. runUntil :: (Monad m) => Processor m a b -> a -> (b -> m Bool) -> m b -- | Runs the processor once, but passes the processing + conversion action -- to the given function. runWith :: (Monad m) => (m b -> m b') -> Processor m a b -> a -> m b' -- | Creates a processor that operates around an inner processor. -- -- Useful for sharing resources between two actions, a pre and a post -- action. -- -- The outer processor has two processing functions, pre: -- a->b and post: c->d. The last argument is the -- inner processor, Processor b c. Thus, the resulting processor -- takes the a, processes it into a b, feeds that -- through the inner processor to get a c, and finally -- post-processes the c into a d. -- -- Example scenario: A singleton hardware device context, that -- cannot be duplicated or allocated more than once. You need to both -- read and write to that device. It's not possible to create two -- processors, one for reads and one for writes, because they need to use -- the same allocation (the device context). With wrapPrcessor you can -- have the read as the pre-processing and write as the post-processing. -- Let's call the result of calling wrapProcessor except the last -- argument, myDeviceProcessor. Thus, you have: -- --
--   [[ myDeviceProcessor innerProc ]] = read >>> innerProc >>> write
--   
wrapProcessor :: (Monad m) => (a -> x -> m x) -> (c -> x -> m x) -> (a -> m x) -> (x -> m b) -> (x -> m d) -> (x -> m ()) -> Processor m b c -> Processor m a d type DTime = Double type DClock m = m Double -- | scanlT provides the primitive for performing memory-full operations on -- time-dependent processors, as described in -- http://www.ee.bgu.ac.il/~noamle/_downloads/gaccum.pdf. -- -- Untested, and also doesn't implement the limit as dt -> -- 0 part of the model. scanlT :: DClock IO -> (b -> b -> DTime -> c -> c) -> c -> IOSource a b -> IOSource a c -- | Differentiate using scanlT. TODO: test, and also generalize for any -- monad (trivial change of types). differentiate :: (Real b) => DClock IO -> IOSource a b -> IOSource a Double integrate :: (Real b) => DClock IO -> IOSource a b -> IOSource a Double max_ :: (Ord b) => DClock IO -> b -> IOSource a b -> IOSource a b min_ :: (Ord b) => DClock IO -> b -> IOSource a b -> IOSource a b instance (Monad m) => Arrow (Processor m) instance (Monad m) => Applicative (Processor m a) instance (Monad m) => Functor (Processor m a) instance (Monad m) => Category (Processor m)