I come from Java and want to know what monads are in Haskell

This is an introduction to monads. There are many of these. My goal today is to show how a simple class written in Java could be translated into equivalent functionality in Haskell using some monads, without getting into any of the theory stuff.

Hopefully some people coming from a non-Haskell background will get something out of this, though the Haskell syntax is likely to be very WTF-inducing for those who haven’t seen it before.

I should begin with a few things that this guide is not about:

  • Categories. The etymology of the word “monad” is a red herring. Trust me. Knowing a lot about category theory will make you a better programmer in the same way that playing a lot of checkers will make you better at chess: there’s probably some benefit, but it’s not a good way to get up and running with the basics.

    We will be treating monads as a design pattern instead of monoids in the category of endofunctors. The latter perspective is interesting to the people who like to design languages; the former perspective is interesting to people who like to write code.

  • The full generality of monads in programming. Lots of things are monads, and I will be ignoring most of them. I’m going to focus on how monads can be used to translate a particular Java class into Haskell, and what it looks like as we add functionality to both versions of the code.
  • Haskell evangelism. I’ve already written about the things in Haskell that I love. I love Haskell, and I use it to make my dreams come true. On the other hand, I’m not at all invested in whether or not you like Haskell.

    Though if you want to learn more about this language, I’d like to help you along your journey.

What I am going to talk about is how to use monads to do something in Haskell that is easy to do in Java.

Read the full post »

Haskell features I’d like to see in other languages

When I read Ben Hutchison‘s OO/Imperative programmers: ‘Study Functional Programming or Be Ignorant’ I knew I had too much to say for the comments, so I figured I’d put in my 2 cents here.

Haskell is my go-to language, both for scripting, and for getting work done. This is not because of any particular allegiance to the language. Haskell and I have an open relationship, and the moment I find a language that out-Haskells Haskell, you can be sure I’ll move on.

Here I want to describe my favorite things about Haskell. You’ll note that they are all about the type-system. I don’t feel too strongly one way or the other about laziness, or about monads (though I won’t give them up without first finding something to take their place). I don’t even particularly care that it’s a functional language, in as much as I can have these features in a non-functional environment.

Some of these features are already available elsewhere. This is wonderful! If you know of any examples of this, please tell me in the comments.

This is a list of my favorite things:

Read the full post »

Crypto in the classroom: digital signatures for homework

If you don’t know, I’m a graduate student at the University of Utah, which means I make a living my teaching classes. Recently a student charged that I lost a good deal of her homework. We wound up in a “he-said/she-said” situation where ultimately the dean concluded that we need to raise her grade by a letter under the assumption that I really was up to shenanigans (we ultimately gave her 100% credit in the “homework” column in the grade book, raising her grade from F to D). Not a pleasant situation: aside from a track record of strong teaching evaluations, there was nothing to defend my reputation.

Experienced teachers know that claims of “lost” work are frequent. If we want to be objective about this (and we do), the claims need to be taken seriously, since lost things rarely leave a trail. All we have when analyzing such claims is the following:

  • The missing work never seems to turn up. Not after a week, a month, a semester, a year, or ever.
  • If a person rarely finds that they misplace his own belongings, it’s hard to accept that he is misplacing student work (assuming they treat student work with a reasonable amount of care, as we typically do, given how terrible it would be to lose it!)
  • These claims never seem to come from students who are doing well on exams; they tend to come from students who are backed into a corner, grade-wise.

Of course, it is entirely conceivable that these claims are occasionally correct, and it would be terrible to allow such mistakes — our mistakes — to adversely effect our students.

Last Spring was the only time a student has accused me of losing their work. It was a lousy situation that I have no intention of ever repeating. So when I was assigned to teach a half-term class this summer, I decided it was time to try something new. I’ve recently finished teaching that class; here’s what I did.

Read the full post »

Syntactic support for Kaminsky’s Interpolique in Haskell

When I recently wrote about my first impressions of Kaminsky’s Interpolique, I mentioned that the only thing I didn’t like is that PHP doesn’t offer any way to protect against syntactic mistakes, such as where the programmer mistakenly uses a $ instead of a ^^.

Today we’ll look at how Interpolique can be implemented in Haskell in such a way that we force the developer to use Interpolique when creating a SQL query, precluding the possibility of the $/^^ mixup bug. In doing so we’ll see that we don’t need anything like PHP’s eval to get the job done.

All of the code for this post is on github: InterpoliqueQQ.

Read the full post »

First impressions: Serving statically with Snap

(This post refers to Snap 0.2.6.)

There’s been a lot of buzz about the Snap framework, so I thought I’d give it a look. My personal website doesn’t have anything dynamic going on, so arguably Snap is “overkill,” but then again so is Apache, so what the heck. Snap is entirely experimental at this time: in their own words, “it is early-stage software,” so every single critique given here should be read with an implied expiration date.

So the question is: how does one host a static site on Snap? At present time there’s no tutorial for this, so I fumbled around until I got something working. Here’s my code:

main = do
    putStrLn "ninj4net online"
    quickServer config site

site :: Snap ()
site =
    route [ ("kinetic", static "kinetic")
          , ("math1010", static "math1010")
          , ("math1030", static "math1030")
          , ("math1100", static "math1100")
          , ("math1210", static "math1210")
          , ("", static "")
          ] 
    (writeBS "general error")

static d = do
    let html_file = "static/" ++ d ++ "/index.html"
        xml_file  = "static/" ++ d ++ "/index.xml"
    html <- liftIO $ doesFileExist html_file
    xml  <- liftIO $ doesFileExist xml_file
    ( (ifTop (fileServeSingle $ if html then html_file else xml_file)) 
      (fileServe $ "static/" ++ d) )

Discussion

Some of my directories use an index.html file, while others use an index.xml file. I need to use System.Directory.doesFileExist function to determine whether or not these files exist — trying ifTop (fileServeSingle "something that doesn't exist") will not switch to the alternative using <|>, so an explicit check is needed (it will whine about an exception being thrown, completely undermining the choice operator!). This is presumably a bug (I submitted it to their github).

I’m sure there is a much more elegant approach, but this was the best I could muster during lunch.

A thing Snap is missing

I came across a design decision that makes me nervous. As with any web framework, there are facilities for getting strings from the user. Unfortunately, Snap does not use types to distinguish between user-provided strings (dirty) and programmer-provided strings (clean).

Why does this matter? Segregating user input into its own type is a formidable defense against (say) SQL injection, since it obviates that "select * from myData where foo='" ++ userInput ++ "'" isn’t well-typed (presumably SQL code should be its own type, say, SQLString, and the function UserString -> SQLString should be some kind of escape routine). It would be nice to see framework support for this types-based defense.

The most obvious example of this is in getParam, which simply returns a Maybe ByteString.

Another example is provided by getSafePath and fileServeSingle. The former returns a FilePath provided by the user (a “safe” path, which — looking at the source — means that the “/../”‘s get removed), and the latter takes a FilePath and opens the corresponding local file. I suppose the idea is that the code

do p <- getSafePath
   fileServeSingle p


shouldn’t escape the implied sandbox of the file system. Of course, if the application has tighter requirements than this, the type system isn’t there to help out. (For instance, perhaps a path is considered “safe” if it excludes certain keywords in addition to the constraints imposed by getSafePath).

A natural work-around is to build an application-specific wrapper around Snap, and perhaps this is the better approach; I’m not yet sure.

Conclusions

I’m glad that Snap has been announced, as it has proven interesting to look at. Of course, Haskell already has (at least) two other web frameworks (yesod and happstack) and it’s not clear which will win-out in mindshare, nor is it obvious (to me, anyway) which one would be the best choice for someone wanting to sit down and make a site. Of course, it’s possible that some mix-and-match might be the best approach: the web server of one project, the HTML generation of another, and the persistent storage of the third. (This possibility deserves some consideration, especially as projects like BlazeHTML really take off.) Hopefully in the coming months we’ll see more high-powered applications of these frameworks, giving us a fountain of lessons we can capitalize on, and providing some compelling show cases of Haskell’s power as a web development language.

Still solving string injection: first impressions of Kaminsky’s Interpolique

This past week Dan Kaminsky announced Interpolique, a technology for dealing with string injection problems in web applications. The basic idea is pretty sharp: instead of writing (say) PHP code like

$conn->query('insert into posts values($_POST[author] , $_POST[content] );');


we write

$conn->query(eval(b('insert into posts values(^^_POST[author] , ^^_POST[content] );')));


The b function is provided by interpolique. It essentially translates the input string into some PHP code (which is then reified using eval) that base64 encodes the user-input and wraps that encoding up in a call to the MySQL function for base64 decoding.

The idea is that the resulting query is given to MySQL in a format where the user input is base64 encoded. As Dan points out, there aren’t any known injection techniques that can escape the MySQL base64 decoder, and the decoder won’t try to evaluate the resulting string as a SQL expression, so no injection is possible.

I have mixed feelings about this approach. On the one hand, it’s really just another form of escaping (instead of inserting a bunch of \‘s into the string, we’re base64 encoding it), and escaping is an error-prone thing. After all, there’s nothing preventing a tired developer from accidentally mixing some $ in with their ^^, nor could there be — if the developer writes $ instead of ^^, PHP will interpolate the string before passing it off to the b function, so no run-time check will be able to save the day.

(I’m not elated about the use of eval, but (a) I see no way around it if the plan is to use a syntactic approach, as is currently the case, and (b) the only vector I can see for attacking it requires a programmer to leave out the call to b, which is something they’d likely catch during development unless they also used $ instead of ^^, and that double-accident seems unlikely, barring a stupid refactoring snafu.)

On the other hand, if this technique is applied correctly, it seems likely to be robust (peer review should weigh in on this pretty quickly).

When I look at interpolique, I see the next generation of escaping: if you forget to do it you’re screwed, but if you do it correctly you’re safe. interpolique’s contribution is that its style of escaping is much simpler than trying to scan strings for dangerous characters, hence less likely to contain silly errors and edge cases, and that it is cross-language ready, in that base64 encoding isn’t target-language-specific (unlike escaping, which certainly is).

interpolique does not improve upon escaping biggest failure, though: if you’ve got 50,000 lines of PHP, the only way to know that interpolique (or escaping) is being used throughout is to look through the code. This is a PHP shortcoming, of course. We could certainly produce some static analysis tool to check for this design pattern, but then again, if writing tools that understand strings in PHP were easy we wouldn’t have the code injection mess in the first place.

Future direction

interpolique does provide a novel improvement for how to move data across the language barrier. This makes the core idea useful even in situations where programmers aren’t using PHP (or other half-brained-but-common-anyway languages).

In the long term, however, we still need to address the fact that we’re abusing the String type. User-input should be its own distinct type. The fact that this isn’t the case in .Net and Java completely explains why those type-safe languages don’t fare any better than PHP in terms of code injection.

Following the interpolique idea, the only function from UserString to String could be a base64 encoder. Languages could provide syntactic sugar to allow things like

$conn->query('insert into posts values($_POST[author] , $_POST[content] );');


to implicitly denote the interpolique style, thereby preserving type-safety (in this case, separation of user-input from SQL code) without compromising string interpolation style.

(Of course, both of these ideas are already possible in Haskell using algebraic data types and Template Haskell, but this is of little comfort to the vast majority of programmers since (a) most haven’t heard of Haskell and (b) Haskell is still in its web-development-language infancy.)

Moving forward I am interested in seeing whether interpolique passes peer review (probably will), becomes a common practice and reduces the incidence of code injection. Regardless of how these questions fare, the core idea is elegant, doesn’t seem to have a performance penalty, and can likely be carried forward fruitfully in future technologies.

Announcing Potential: x86-64 assembler as a Haskell EDSL

Over the years there have been many projects which seek to use advanced types to provide better static-guarantees in low level languages. There are many examples of this in the literature; here are just a few:

  • Cyclone, perhaps the most-cited example of using types to protect memory in low-level settings.
  • Habit, a proposed Haskell dialect which uses a viable form of dependent types to model low-level data structures and their memory management which I recently learned about on reddit, coincidentally in a comment on an earlier post of mine.
  • Some work due to Oleg Kiselyov and Chung-chieh Shan showing that Haskell is a viable setting for embedding a low-level language.

(If you know of others, put them in the comments!)

In December of 2009 I became interested in typed assembly languages and began working on my own, quickly deciding to embed the language into Haskell. At present there are many facets of the language which work well, but there is still a good deal of work to be done.

When I started this, I was unaware of much of the work that had already been done in this direction (I especially wish I had been aware of the Kiselyov-Shan proof of concept). In the course of the project, I’ve learned a bunch of great tricks, and also have learned of a good deal of excellent work done by others that I hadn’t seen promoted elsewhere. Over the next few posts, my goals are threefold:

  • To describe my own project: where it is, what the challenges have been, where I hope for it to go. And to release some source (on github), such as it is.
  • To describe some of the general lessons I’ve learned working on an EDSL in Haskell, to evangelize this approach to problem solving, and to describe some caveats to conventional Haskell wisdom in this setting.
  • To promote some of the work others have done in this area, in the aim of showing just how far along this idea is.

Read the full post »

Optional class constraints in Haskell

Work on my Haskell EDSL is moving ever onward. Today I want to talk about a trick I found while working on it. (Along the way I’ll make some allusions to the EDSL, but I want to forestall announcing the EDSL for another week or so, in the interest of ensuring it’s fully baked.)

Read the full post »

Polymorphic first class labels

(This post uses GHC 6.12.1)

The expression “first class labels” refers to the idea that, for record data types, one should be able to pass around the labels just as they would any other type. For instance, if I have a record like

data Foo a b = { biz :: a, baz :: b }


the value biz shouldn’t just denote the function biz :: Foo a b -> a, but should also be usable as a way of updating records, that is, a function like biz' :: Foo a b -> a' -> Foo a' b.

The Mythical Haskell’ includes some proposals for updating the records system with features aimed at supporting this idea, but for the time being, many people prefer to use fclabels, which achieves much of this magic using Template Haskell.

Recently, while working on an EDSL, I found myself wishing I had first class labels. I ran into a problem, though, which (along with solution) I’ll now describe.

Consider the following code:

module Label where

data Foo a b = Foo a b deriving Show

updatea :: a' -> Foo a b -> Foo a' b
updatea a (Foo _ b) = Foo a b

updateb :: b' -> Foo a b -> Foo a b'
updateb b (Foo a _) = Foo a b

worksFine foo0 = let foo1 = updatea 'a' foo0
                     foo2 = updatea "a" foo1
                 in foo2

Here I’ve defined a data structure Foo with two fields, along with a pair of functions for updating these fields. Then I defined a function worksFine which uses updatea to modify a Foo.

Obviously I could also write the following function:

worksFine' foo0 = let foo1 = updateb 'a' foo0
                      foo2 = updateb "a" foo1
                  in foo2


which is exactly the same, except that it uses updateb instead, thereby modifying the other field in Foo.

So now we have an obvious place to generalize: instead of having both worksFine and worksFine', why not have a single function which takes the updater as a parameter?

If we try it out, the first attempt looks like this:

trouble u foo0 = let foo1 = u 'a' foo0
                     foo2 = u "a" foo1
                 in foo2


Only trouble is that this fails to type check:

    Couldn't match expected type `[Char]' against inferred type `Char'
      Expected type: [Char] -> t1 -> t
      Inferred type: Char -> t2 -> t1
    In the expression: u "a" foo1
    In the definition of `foo2': foo2 = u "a" foo1

The problem is that trouble doesn’t believe that the argument u is polymorphic enough. This is a typical rank-2 issue: we don’t want trouble to bind the type variables in the signature for u.

Using rank-2 types, we can get very close to a solution. We can write the functions

alsoWorksFinea :: (forall a a' . a' -> Foo a b -> Foo a' b)
               -> Foo a b -> Foo [Char] b
alsoWorksFinea u foo0 = let foo1 = u 'a' foo0
                            foo2 = u "a" foo1
                        in foo2

alsoWorksFineb :: (forall b b' . b' -> Foo a b -> Foo a b')
               -> Foo a b -> Foo a [Char]
alsoWorksFineb u foo0 = let foo1 = u 'a' foo0
                            foo2 = u "a" foo1
                        in foo2

but neither is able to accept both of our update functions, even though each function has exactly the same body. Worse, I wasn’t able to find a sufficiently general type signature that would allow me to have one function which would be able to accept both update functions.

Luckily, where rank-2 types have failed me, type families have saved me. Any time you need more flexibility in your type signatures than the syntax will allow, you might be in a box where type families are the way to go. Here’s what it looked like in my case.

First I defined some typed to represent the two fields of my Foo structure:

data A = A
data B = B


Obviously I can pass around these values in a first-class manner, no trouble at all.

Then I defined a class for describing updating and getting:

class Field f x y where
  type Updated f x y
  update :: f -> x -> y -> Updated f x y
  type Gotten f y
  get :: f -> y -> Gotten f y

Now there are two instances to give, one for each field in Foo:

instance Field A a' (Foo a b) where
  type Updated A a' (Foo a b) = Foo a' b
  update A a' (Foo a b) = Foo a' b
  type Gotten A (Foo a b) = a
  get A (Foo a b) = a

instance Field B b' (Foo a b) where
  type Updated B b' (Foo a b) = Foo a b'
  update B b' (Foo a b) = Foo a b'
  type Gotten B (Foo a b) = b
  get B (Foo a b) = b 

And we’re basically done. We can now write the function that started this whole mess:

shouldWorkFine f foo0 = let foo1 = update f 'a' foo0
                            foo2 = update f "a" foo1
                        in foo2

GHCi is able to give us a very promising type signature for it:

> :t shouldWorkFine 
shouldWorkFine
  :: (Field f [Char] (Updated f Char y), Field f Char y) =>
     f -> y -> Updated f [Char] (Updated f Char y)

While this technique introduces type classes and type families into our program (something which can make typing troublesome in other areas), it delivers something I don’t know how to otherwise get: polymorphic first class labels.

Clearly the next step is to implement a library like fclabels which uses Template Haskell to define instances of the Field class.

Some weird interactions between Monomorphism Restriction and Template Haskell

Today I’m going to look at a weird issue I encountered this past weekend while working on a DSL in Haskell.

I’ll start with the code. As this example uses Template Haskell, we need to have the source broken up into two files:

Testa.hs:

{-# LANGUAGE
        TemplateHaskell #-}
module Testa where

import Language.Haskell.TH

someth = [| () |]

unit = ()

mrIssue :: (Monad m) => b -> m b
mrIssue = return

Testb.hs:

{-# LANGUAGE
        NoMonomorphismRestriction,
        TemplateHaskell #-}
module Testb where

import Testa

g = $(someth)
foo1 = mrIssue $(someth)

f = ()
foo2 = mrIssue ()

h = unit
foo3 = mrIssue unit

Now, if we fire up ghci Testb.hs, we get the following:

$ ghci Testb.hs 
GHCi, version 6.10.4: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer ... linking ... done.
Loading package base ... linking ... done.
[1 of 2] Compiling Testa            ( Testa.hs, interpreted )
[2 of 2] Compiling Testb            ( Testb.hs, interpreted )
Loading package syb ... linking ... done.
Loading package array-0.2.0.0 ... linking ... done.
Loading package packedstring-0.1.0.1 ... linking ... done.
Loading package containers-0.2.0.1 ... linking ... done.
Loading package pretty-1.0.1.0 ... linking ... done.
Loading package template-haskell ... linking ... done.
Ok, modules loaded: Testb, Testa.
*Testb> :t foo1
foo1 :: (Monad m) => m ()
*Testb> :t g

:1:0:
    Ambiguous type variable `m' in the constraint:
      `Monad m' arising from a use of `g' at :1:0
    Probable fix: add a type signature that fixes these type variable(s)
*Testb>

Notice that, while we’re able to get the type for foo1, for some reason g is ill-typed with an ambiguous type variable in the constraint Monad m. The only problem, of course, is that when we look at our source we don’t see any way in which the type for g should have this constraint!

So maybe the problem is that g needs a type signature. But if we go in and modify Testb.hs, giving it

g :: ()
g = $(someth)

then we get the following from ghci:

Testb.hs:10:7:
    Could not deduce (Monad m) from the context ()
      arising from a use of `mrIssue' at Testb.hs:10:7-23
    Possible fix:
      add (Monad m) to the context of the type signature for `g'
    In the expression: mrIssue ($someth)
    In the definition of `foo1': foo1 = mrIssue ($someth)
Failed, modules loaded: Testa.
*Testa>

So now it's upset about the type for foo1. Fine. Let's give it a signature as well:

g :: ()
g = $(someth)
foo1 :: (Monad m) => m ()
foo1 = mrIssue $(someth)

Now we get a new error from ghci:

Testb.hs:11:0:
    Contexts differ in length
      (Use -XRelaxedPolyRec to allow this)
    When matching the contexts of the signatures for
      g :: ()
      foo1 :: forall (m :: * -> *). (Monad m) => m ()
    The signature contexts in a mutually recursive group should all be identical
    When generalising the type(s) for g, foo1
Failed, modules loaded: Testa.

If we add RelaxedPolyRec to our list of LANGUAGE extensions, the problem does, indeed, go away. In this case, we can even remove our type signature for g or for foo1, but not both -- we need to have at least one of them present.

Lastly, if we go back to our original source given above, but replace the signature for mrIssue with

mrIssue :: b -> IO b
mrIssue = return


then we can remove the NoMonomorphismRestriction, and everything works just fine (we can :t g and :t foo1 without any problems).

I'm entirely unsure of what's going on here. Any theories?