Luminescent Dreams

GTK+ Programming in Haskell

January 01, 0001

Earlier this evening I gave a presentation on doing GTK+ programming in Haskell. Here is the presentation for all those who could not be there.

Handling Errors in Haskell

January 01, 0001

Thursday night I gave a new presentation on handling errors in Haskell. My understanding of this concept has evolved radically in the last two years, though it is still incomplete.

While I have little additional commentary right now, my presentation will be evolving over time to include new information. To this page, I will add a a full prose explanation for the information in the slides over the course of this next week.

Haskell Error HandlingPDF Slides

I have written previous articles [here](Exceptions and Errors, Part 1) and [here](Exception Handling in Haskell, Part 2). My understanding now deprecates both of those articles, though not completely.

Haskell Application Monad

January 01, 0001

We want to get productive in Haskell very quickly. Most non-trivial applications will have configuration, connections to the outside world, can hit exceptional conditions, and benefit from having their operations logged. If your application has sensible logs at both high an low levels of detail, your devops team will thank you and your life of debugging a production application will be a happier one.

I want to get all of these things at once, and so it would be nice to provide a nearly boilerplate application stack that provides them all. I define the “application stack” as a group of attributes that contain the context and all of the common behaviors for an application. In Haskell, you do that with a monad stack, though work on extensible effects shows a great deal of promise and has been used to great effect in Purescript.

That said, I use monads and monad transformers, and I’ll not explain either of them today. I feel that the best explanation is a non-trivial example implementation, which I will do in a future article, or refer you to a better tutorial.

While most of this article explains the process, the final result is this application stack, which may be all you need if you are already familiar with building monad transformer stacks.

data Context = Context { contextRoot :: FilePath } deriving Show

data AppError = AppError deriving Show

newtype AppM a = AppM (LoggingT (ReaderT Context (ExceptT AppError IO)) a)
    deriving ( Functor, Applicative, Monad, MonadIO
             , MonadError AppError, MonadReader Context, MonadLogger)

runAppM :: Context -> AppM a -> IO (Either AppError a)
runAppM ctx (AppM act) = runExceptT (runReaderT (runStderrLoggingT act) ctx)

The most basic stack

Almost every application needs IO. In Haskell it is difficult to do IO on top of anything (see MonadBaseControl for way), so I always put it at the bottom of the monad stack. A trivial application stack would look like this:

newtype AppM a = AppM (IO a) deriving (Functor, Applicative, Monad, MonadIO)

This is so trivial you will likely never do it, though it can be helpful in that it prevents confusion between your functions and system IO functions. Still, let’s build out what you need to make this work.

First of all, you do want AppM to be a monad, and you will need MonadIO in order to actually run IO operations. The primary use that I have for Monads in an application is to eliminate the boilerplate involved with a lot of threading context through a series of function calls. More to the point, though, you cannot get MonadExcept, MonadReader, or MonadLogger into this stack without having Monad to begin with.

newtype AppM a = AppM (IO a)
    deriving (Functor, Applicative, Monad, MonadIO)

runAppM :: AppM a -> IO a
runAppM (AppM act) = act

runAppM is the function that connects your application stack to the Haskell IO stack. This is everything you need in order to create a stack: the stack itself and the runner. Now let’s see it in action:

data Image = Image deriving Show

loadImage :: FilePath -> AppM Image
loadImage path = do 
    liftIO $ putStrLn $ "loadImage: " <> path
    pure Image
     

main :: IO ()
main = do
    res <- runAppM $ do
        img1 <- loadImage "image.png"
        img2 <- loadImage "image2.png"
        pure (img1, img2)
    print res

Injecting your context

IO a is too simple to make much sense. The whole point of having a stack is to unify a lot of effects within a common framework of behavior and with a common context. So, next we load and add a context.

In almost every circumstance, your context is read-only. This points us directly to ReaderT, since you will want to be able to ask for the context but never write back to it. Application state would seem like a thing that you would want to include, if your application stores state. I have generally found that it is easier to keep application state in something that is strictly IO, such as an IORef or a TVar. For now, we shall skip that.

So, change your stack to look like this:

data Context = Context { root :: FilePath } deriving Show

newtype AppM a = AppM (ReaderT Context IO a)
    deriving (Functor, Applicative, Monad, MonadIO, MonadReader Context)

runAppM :: Context -> AppM a -> IO a
runAppM ctx (AppM act) = runReaderT act ctx

The addition of MonadReader means that now you can call ask within your function to get back the context, and you don’t have to explicitely pass the context in. The remaining functions get updated like so:

loadImage :: FilePath -> AppM Image
loadImage path = do
    Context{..} <- ask
    liftIO $ putStrLn $ "loadImage: " <> (contextRoot </> path)
    pure Image

loadContext :: IO Context
loadContext = pure $ Context { contextRoot = "/home/savanni/Pictures/" }

main :: IO ()
main = do
    ctx <- loadContext
    res <- runAppM ctx $ do
        img1 <- loadImage "image.png"
        img2 <- loadImage "image2.png"
        pure (img1, img2)
    print res

Suddenly, everything in Context is available to every function that runs in AppM. You get the local effect of global parameters while still getting to isolate them, potentially calling the same functions with different contexts within the same application.

Add exception handling and logging

Exceptions happen. The Haskell community is split between what I call explicit vs. implicit exceptions. In short, implicit exceptions are not declared in the type signature, can happen from any function, and can only be caught in IO code. Explicit exceptions are explicitely stated in the type signature and can be caught just about anywhere. I prefer them for all of my application errors. I’ll give exception handling further treatment in a future article, and will show the use of explicit exceptions here.

Logging is almost always helpful for any application that is not of trivial size. And, once present, it can replace print for debugging, allowing debugging lines to remain present in the code for those cases when something starts going wrong in production.

First, the new application stack:

data AppError = AppError deriving Show

newtype AppM a = AppM (LoggingT (ReaderT Context (ExceptT AppError IO)) a)
    deriving ( Functor, Applicative, Monad, MonadIO
             , MonadError AppError, MonadReader Context, MonadLogger)

runAppM :: Context -> AppM a -> IO (Either AppError a)
runAppM ctx (AppM act) = runExceptT (runReaderT (runStderrLoggingT act) ctx)

This gets quite a bit more complicated with both the Logging and Exceptions being added. Remember that I use the term “stack” here, and each monad transformer involved represents another layer in the stack. When running the stack, you must peel off each layer in reverse order. I will illustrate with some types:

*Json> :t loadImage "img.png"
loadImage "img.png" :: AppM Image

*Json> :t unAppM $ loadImage "img.png"
unAppM $ loadImage "img.png"
  :: LoggingT (ReaderT Context (ExceptT AppError IO)) Image

*Json> :t runStderrLoggingT $ unAppM $ loadImage "img.png"
runStderrLoggingT $ unAppM $ loadImage "img.png"
  :: ReaderT Context (ExceptT AppError IO) Image

*Json> :t runReaderT (runStderrLoggingT $ unAppM $ loadImage "img.png") ctx
runReaderT (runStderrLoggingT $ unAppM $ loadImage "img.png") ctx
  :: ExceptT AppError IO Image

*Json> :t runExceptT $ runReaderT (runStderrLoggingT $ unAppM $ loadImage "img.png") ctx
runExceptT $ runReaderT (runStderrLoggingT $ unAppM $ loadImage "img.png") ctx
  :: IO (Either AppError Image)

The point of this is that in runAppM, the type of act is the entire stack, and the first thing to be called to begin unwrapping is runStderrLoggingT, then runReaderT, and finally runExceptT.

Notice, also, that the final type of runAppM has changed to IO (Either AppError a). runAppM will now return whatever exception gets thrown from within the context it is running, no matter where that exception is thrown, if that exception is thrown with throwException. Exceptions thrown with throw end up being the implicit exceptions I referred to, and those require some extra handling.

So, here is the rest of the code. In the places where I used to print output, I am now logging output. Note that the loggers require TemplateHaskell and have slightly odd syntax, but are otherwise nearly identical to print.

data Image = Image deriving Show

loadImage :: FilePath -> AppM Image
loadImage path = do
    Context{..} <- ask
    $(logInfo) (T.pack $ "loadImage: " <> (contextRoot </> path))
    pure Image

loadContext :: IO Context
loadContext = pure $ Context { contextRoot = "/home/savanni/Pictures/" }

main :: IO ()
main = do
    ctx <- loadContext
    do  res <- runAppM ctx $ do
            img1 <- loadImage "image.png"
            img2 <- loadImage "image2.png"
            pure (img1, img2)
        print res

    do  res <- runAppM ctx $ do
            img1 <- loadImage "image.png"
            throwError AppError
            img2 <- loadImage "image2.png"
            pure (img1, img2)
        print res 

This is the output from running main:

*Json> main
[Info] loadImage: /home/savanni/Pictures/image.png @(main:Json /home/savanni/src/haskell/src/Json.hs:76:7)
[Info] loadImage: /home/savanni/Pictures/image2.png @(main:Json /home/savanni/src/haskell/src/Json.hs:76:7)
Right (Image,Image)
[Info] loadImage: /home/savanni/Pictures/image.png @(main:Json /home/savanni/src/haskell/src/Json.hs:76:7)
Left AppError
*Json> 

So, the first block starting with do res <- runAppM runs to completion, returnin two images. The second block, runs loadImage for the first image, but then hits throwError and returns Left AppError, discarding the first image and not loading the second image at all.


This is nearly a application stack that I have used for more applications than I can count. Even if you need only one feature, such as exceptions, starting with a small stack hidden behind an application monad makes it very easy to add additional features as you need them, without needing to change the rest of your code. This pattern is trivial to extend, or contract, as needed, and so I think it starts every application on a good path.

Creative Commons License
Haskell Application Monad by Savanni D’Gerinel is licensed under a Creative Commons Attribution-NonCommercial-ShareAlike 4.0 International License.

Haskell Exceptions and Abstractions, or Part 2 of Abstracting the Monad Stack

January 01, 0001

Error handling is a big deal for me. I have probably studied this more than anything else in Haskell because I find it so important to carefully handle unexpected errors. I have presented on this before, but those older presentations lacked a nuance of understanding that I have developed in the last few years.

This article carries on from my previous one, Abstracting the Monad Stack. In that article, I was unable to get all the way to exception abstraction. That this article took me so long to write demonstrates that I was correct in my assessment that this was too much for me to roll into my previous article.

Abstracting out the Exception

Code for this section

I still want to throw exceptions from my library, and my library has the HealthException type:

data HealthException = TimeSeriesExc SeriesExc
                     | UnknownException String
                     deriving (Eq, Show)


type Health r m = (MonadIO m, MonadReader r m, HasHealthContext r)

However, the higher-level context of my application frequently has a different exception type, which may well encompass exceptions from other modules:

data WebExc = WebExcHealth HealthException
            | WebExcHttp HttpException
            | AppForbidden
            | AppUnauthorized

Typically, I would have to unwrap the monad stack for my library in order to rewrap the exception class into the WebExc exception. Again, this works, but it creates tedious boilerplate that we would like to remove:

handleGetHistory :: Interval UTCTime -> WebM ([Sample Weight], [Sample TimeDistance], [Sample Steps])
handleGetHistory interval = do
    WebContext{..} <- ask
    weightRes <- getWeights interval
    timeDistanceRes <- getTimeDistance interval
    stepRes <- getSteps interval

    case (weightRes, timeDistanceRes, stepRes) of
        (Left err, _, _) -> throwError $ WebExcHealth err
        (_, Left err, _) -> throwError $ WebExcHealth err
        (_, _, Left err) -> throwError $ WebExcHealth err
        (Right weights, Right timeDistances, Right steps) -> pure (weights, timeDistances, steps)

In order to make this goal, we can do something similar to HasHealthContext, but this time for writing. Start out by building a class that describes the process of “wrapping” this exception. We must also declare such an exception in our type constraints.

class AsHealthException exc where
    _HealthException :: HealthException -> exc
    _TimeSeriesExc :: SeriesExc -> exc
    _TimeSeriesExc = _HealthException . TimeSeriesExc
    _UnknownException :: String -> exc
    _UnknownException = _HealthException . UnknownException

type Health r exc m = (MonadIO m, MonadReader r m, HasHealthContext r, MonadError exc m, AsHealthException exc)

This class declares a generic function that wraps all health exceptions, and then two dedicated functions for simply creating and wrapping a TimeSeriesExc and an UnknownException. The new components to the type constraint both declare that the calling monad must implement MonadReader, and that the exceptions being raised in the monad must support AsHealthException.

In the library code, you use these exceptions like so:

getWeights :: Health r exc m => Interval UTCTime -> m a
getWeights = throwError $ _HealthException $ UnknownException "demonstrating with _HealthException"

getTimeDistance :: Health r exc m => Interval UTCTime -> m a
getTimeDistance = throwError $ _UnknownException "demonstrating with _UnknownException"

Note how the exception is no longer explicitely called out in the type signatures for getWeights or getTimeDistance. However, that an exception is thrown is still strictly type checked and even documented in the constrant on the exc parameter in Health r exc m.

The caller must implement this class to make the wrapping transparent.

instance AsHealthException WebExc where
    _HealthException = WebExc . WebExcHealth

With this one change, we almost magically see our calling code collapse into something quite reasonable.

handleGetHistory :: Interval UTCTime -> WebM ([Sample Weight], [Sample TimeDistance], [Sample Steps])
handleGetHistory interval = do
    WebContext{..} <- ask
    weights <- getWeights interval
    timeDistances <- getTimeDistance interval
    steps <- getSteps interval
    pure (weights, timeDistances, steps)

Handle an exception inside the monad

Code for this section

Let’s say that there are certain exceptions that you need to handle in place. For instance, assume that when I save a TimeDistance workout, I want to update some summary data. This is slightly contrived since in this case I would usually generate the summaries based on queries, but it serves to illustrate a point.

handleSaveTimeDistance got quite a few updates alongside handleGetHistory, so it has changed from our original example and looks like this:

handleSaveTimeDistance :: Maybe SampleID -> SetTimeDistanceParameters -> WebM (Sample TimeDistance)
handleSaveTimeDistance sampleId params =
    let workoutFromParams = undefined
        workout = workoutFromParams params
    in saveTimeDistance sampleId workout

Now I add the update function, keeping it within the Health monad for simplicity. I also add a fictitious rollback and commit functions. If written, they would assume that, like in any database setup, they are safely written to disk but in a way that does not take effect until a single monotonic commit function happens. Just for the fun of it, I’ll also add a checkAuthorization function, which would be run before actually saving any data to disk.

checkAuthorization :: WebM ()
checkAuthorization = undefined

updateTimeDistanceSummary :: Health r exc m => TimeDistance -> m a
updateTimeDistanceSummary _ = undefined

commit :: Health r exc m => m ()
commit = undefined

rollback :: Health r exc m => m ()
rollback = undefined

However, this turns out to be super simple. Remember that I am working in MonadError, and so I have access to the already-familiar catchError. I have no need for anything complicated.

handleSaveTimeDistance :: Maybe SampleID -> SetTimeDistanceParameters -> WebM (Sample TimeDistance)
handleSaveTimeDistance sampleId params =
    let workoutFromParams = undefined
        workout = workoutFromParams params
    in
    catchError (do checkAuthorization
                   res <- saveTimeDistance sampleId workout
                   updateTimeDistanceSummary workout
                   commit
                   pure res)
               handler
    where
    handler err@(WebExcHealth _) = do
        rollback
        throwError err
    handler exc = throwError exc

Sprinkling in a bit of Template Haskell

Code for this section

The class declaration for AsHealthException above still looks like boilerplate, but I present it as explanation. The Lens library actually provides a function that does exactly this. Note that introducing TemplateHaskell also requires introducing additional files. Code generation from the lenses (or any other TemplateHaskell code generation) does not become available in the file in which it is declared.

{-# LANGUAGE TemplateHaskell #-}

import Control.Lens (makeClassyPrisms, prism)

data HealthException = ...

makeClassyPrisms ''HealthException

The library code must be changed just a bit. The functions on AsHealthException actually create Prisms now, a fairly complex data structure that I only barely grasp. In order to throw the exception, it must first be injected appropriately into a prism, and so the code becomes this:

getWeights :: Health r m => Interval UTCTime -> m (Either HealthException a)
getWeights = throwError $ review _HealthException $ UnknownException "demonstrating with _HealthException"

getTimeDistance :: Health r m => Interval UTCTime -> m (Either HealthException a)
getTimeDistance = throwError $ review _UnknownException "demonstrating with _UnknownException"

Client code is a little different, also, but only in the AsHealthException instance:

instance AsHealthException WebExc where
    _HealthException = prism WebExcHealth unwrap
        where unwrap (WebExcHealth exc) = Right exc
              unwrap exc = Left exc

Again, _HeathException is now a prism, as are _TimeSeriesExc and _UnknownException. This adds some extra options for unwrapping the exception, but I do not currently use, or have a good example of, such a handler.

End of a journey

This has already been a long journey in the making. At the end of it, however, you have learned how to use type constraints to effectively abstract an entire monad stack, making a significantly more reusable and simultaneously much easier to read and use.

This is probably not the only way to set up reusable monad stacks, but it is the one that I find the easiest to understand, the easiest to build, and the easiest to use. I ask you to try this kind of setup for your own code to see where it works and where it breaks. I also would like feedback on how well this worked for you and whether you have a different means of building the same kind of flexibility.

While we have covered a lot of ground, there is much more to do. In my next article I will provide a summary template of everything we have built here.

After that, it is time to start designing architectures that can handle dependency injection for mocking out resources in test, or even allowing run-time configuration of resource backends.

Creative Commons License
Haskell Exceptions and Abstractions, or Part 2 of Abstracting the Monad Stack by Savanni D’Gerinel is licensed under a Creative Commons Attribution-NonCommercial-ShareAlike 4.0 International License.

Haskell's Foreign Function Interface

January 01, 0001

As part of a research project, I did a tiny bit of work to figure out the tiniest part of Haskell’s Foreign Function Interface today. This is just the tip of the iceburg, but I thought I would show off the extremely simple demo that I worked out. I present both the C and Haskell versions of a program that feeds “abc” and “def” into the standard Unix crypt() function.

Source material comes from The FFI Cookbook and from Foreign.C.String

C, Venerable C

I did not do things in this order. However, for demonstration, we should start with the C operation. First, crypt() has the data prototype `char *crypt(const char *key, const char *salt);’. The code to call it takes a mere eleven lines:

#include <unistd.h>
#include <stdlib.h>
#include <stdio.h>

int main (int argc, char **argv) {
    char *res;
    res = crypt("abc", "def");
    printf("%s\n", res);

    return EXIT_SUCCESS;
}

Compile this with gcc -o crypt crypt.c -lcrypt. When I compile I get the warning crypt.c:7:9: warning: assignment makes pointer from integer without a cast [enabled by default], which I do not understand unless crypt() is not actually present in unistd.h. But, the code works correctly and as expected.

An important note: crypt() apparently returns a pointer to an internal data structure that you MUST NOT deallocate. I read comments in the man page about a GNU version of crypt(), crypt_r(), that is re-entrant, which reenforces my belief. If you want to keep the result of crypt(), be sure to copy it away, but otherwise do not allocate it. Running the program against valgrind indicates no leaked memory, which really solidifies this understanding for me.

Haskell FFI

The Haskell FFI was pretty easy to use, ultimately, and the cookbook really shows what we need to make this work. It takes a little bit more code, though, because we have to do the marshalling to and from C data types:

{-# LANGUAGE ForeignFunctionInterface #-}
module Main where

import Foreign.C
import Foreign.Ptr
import Foreign.Marshal.Alloc

foreign import ccall "crypt" c_crypt :: CString -> CString -> CString
crypt key str = do
    keyC <- newCString key
    strC <- newCString str
    res <- peekCAString $ c_crypt keyC strC
    free keyC
    free strC
    return res

main = do
    crypt "abc" "def" >>= putStrLn

foreign import ccall is some serious magic, but it pretty much amounts to the same as dlopen(). The catch is that you absolutely must declare the data type. So, here is the structure:

foreign import ccall "<optional header file> <function name>" <haskell binding> :: <type>

According to the FFI cookbook, prepending the name of the function with c_ is simply a standard.

What I do not know is whether c_crypt should have been declared as above, or as c_crypt :: CString -> CString -> IO CString. I am not yet clear on when a C call should be within the IO context and when it should not. I suspect that the compiler will not enforce anything and that it is up to me to make a (potentially unsafe) judgement call in the matter.

What’s the Point?

I want to do Haskell on the new Ubuntu software stack for tablets. This uses QML (though the rest of Ubuntu seems to still use GTK). I have found a QML library for Haskell, but it is out of date and does not work with the current QT 5. So, I can either recode it from scratch, or I can fully understand it and update it for the modern QT. In both cases, I need to learn the FFI. But I’ve needed to learn the FFI for a long time, anyway.

http://i.creativecommons.org/l/by-nc-sa/3.0/88x31.png

Haskell FFI by Savanni D'Gerinel is licensed under a Creative Commons Attribution-NonCommercial-SharAlike 3.0 Unported License. You can link to it, copy it, redistribute it, and modify it, but don't sell it or the modifications and don't take my name from it.