Older blog entries for joey (starting at number 578)

7drl 2015 day 6 must add more

Last night I put up a telnet server and web interface to play a demo of scroll and send me playtester feedback, and I've gotten that almost solid today. Try it!

Today was a scramble to add more features to Scroll and fix bugs. The game still needs some balancing, and generally seems a little too hard, so added a couple more spells, and a powerup feature to make it easier.

Added a way to learn new spells. Added a display of spell inventory on 'i'. For that, I had to write a quick windowing system (20 lines of code).

Added a system for ill effects from eating particular letters. Interestingly, since such a letter is immediately digested, it doesn't prevent the worm from moving forwards. So, the ill effects can be worth it in some situations. Up to the player to decide.

I'm spending a lot of time now looking at letter frequency historgrams to decide which letter to use for a new feature. Since I've several times accidentially used the same letter for two different things (most amusingly, I assigned 'k' to a spell, forgetting it was movement), I refactored all the code to have a single charSet which defines every letter and what it's used for, be that movement, control, spell casting, or ill effects. I'd like to use that to further randomize which letters are used for spell components, out of a set that have around the same frequency. However, I doubt that I'll have time to do that.

In the final push tonight/tomorrow, I hope to add an additional kind of level or two, make the curses viewport scroll when necessary instead of crashing, and hopefully work on game balance/playtester feedback.

I've written ~2800 lines of code so far this week!

Syndicated 2015-03-12 23:02:38 from see shy jo

7drl 2015 day 5 type directed spell system development

I want my 7drl game Scroll to have lots of interesting spells. So, as I'm designing its spell system, I've been looking at the types, and considering the whole universe of possible spells that fit within the constraints of the types.

My first throught was that a spell would be a function from World -> World. That allows any kind of spell that manipulates the game map. Like, for instance a "whiteout" that projects a stream of whitespace from the player's mouth.

Since Scroll has a state monad, I quickly generalized that; making spell actions a state monad M (), which lets spells reuse other monadic actions, and affect the whole game state, including the player. Now I could write a spell like "teleport", or "grow".

But it quickly became apparent this was too limiting: While spells could change the World map, the player, and even change the list of supported spells, they had no way to prompting for input.

I tried a few types of the Event -> M () variety, but they were all too limiting. Finally, I settled on this type for spell actions: M NextStep -> M NextStep.

And then I spent 3 hours exploring the universe of spells that type allows! To understand them, it helps to see what a NextStep is:

type Step = Event -> M NextStep
data NextStep = NextStep View (Maybe Step)

Since NextStep is a continuation, spells take the original continuation, and can not only modify the game state, but can return an altered continuation. Such as one that prompts for input before performing the spell, and then calls the original continuation to get on with the game.

That let me write "new", a most interesting spell, that lets the player add a new way to cast an existing spell. Spells are cast using ingredients, and so this prompts for a new ingredient to cast a spell. (I hope that "new farming" will be one mode of play to possibly win Scroll.)

And, it lets me write spells that fail in game-ending ways. (Ie, "genocide @"). A spell can cause the game to end by returning a continuation that has Nothing as its next step.

Even better, I could write spells that return a continuation that contains a forked background task, using the 66 line contiuation based threading system I built in day 3. This allows writing lots of fun spells that have an effect that lasts for a while. Things like letting the player quickly digest letters they eat, or slow down the speed of events.

And then I thought of "dream". This spell stores the input continuation and game state, and returns a modified continuation that lets the game continue until it ends, and then restores from the point it saved. So, the player dreams they're playing, and wakes back up where they cast the spell. A wild spell, which can have different variants, like precognitive dreams where the same random numbers are used as will be used upon awaking, or dreams where knowledge carries back over to the real world in different ways. (Supports Inception too..)

Look how easy it was to implement dreaming, in this game that didn't have any notion of "save" or "restore"!

runDream :: M NextStep -> M NextStep -> (S -> S) -> M NextStep
runDream sleepcont wakecont wakeupstate = go =<< sleepcont
   where
         go (NextStep v ms) = return $ NextStep v $ Just $
        maybe wake (go <=<) ms
         wake _evt = do
                 modify wakeupstate
                 wakecont

I imagine that, if I were not using Haskell, I'd have just made the spell be an action, that can do IO in arbitrary ways. Such a spell system can of course do everything I described above and more. But, I think that using a general IO action is so broad that it hides the interesting possibilities like "dream".

By starting with a limited type for spells, and exploring toward more featureful types, I was able to think about the range of possibilities of spells that each type allowed, be inspired with interesting ideas, and implement them quickly.

Just what I need when writing a roguelike in just 7 days!

Syndicated 2015-03-11 22:51:26 from see shy jo

7drl 2015 day 4 coding through exhaustion

Slow start today; I was pretty exhausted after yesterday and last night's work. Somehow though, I got past the burn and made major progress today.

All the complex movement of both the player and the scroll is finished now, and all that remains is to write interesting spells, and a system for learning spells, and to balance out the game difficulty.


I haven't quite said what Scroll is about yet, let's fix that:

In Scroll, you're a bookworm that's stuck on a scroll. You have to dodge between words and use spells to make your way down the page as the scroll is read. Go too slow and you'll get wound up in the scroll and crushed.

The character is multiple chars in size (size is the worm's only stat), and the worm interacts with the scroll in lots of ways, like swallowing letters, or diving through a hole to the other side of the scroll. While it can swallow some letters, if it gets too full, it can't move forward anymore, so letters are mostly consumed to be used as spell components.

I think that I will manage to get away without adding any kind of monsters to the game; the scroll (and whoever is reading it) is the antagonist.

As I'm writing this very post, I'm imagining the worm wending its way through my paragraphs. This dual experience of text, where you're both reading its content and hyper-aware of its form, is probably the main thing I wanted to explore in writing Scroll.

As to the text that fills the scroll, it's broadly procedurally generated, in what I hope are unusual and repeatedly surprising (and amusing) ways. I'm not showing any screenshots of the real text, because I don't want to give that surprise away. But, the other thing about Scroll is that it's scroll, a completely usable (if rather difficult..) Unix pager!

Syndicated 2015-03-10 23:07:45 from see shy jo

7drl 2015 day 3 movement at last

Got the player moving in the map! And, got the map to be deadly in its own special way.

        HeadCrush -> do
                showMessage "You die."
                endThread

Even winning the game is implemented. The game has a beginning, a middle, and an end.

I left the player movement mostly unconstrained, today, while I was working on things to do with the end of the game, since that makes it easier to play through and test them. Tomorrow, I will turn on fully constrained movement (an easy change), implement inventory (which is very connected to movement constraints in Scroll), and hope to start on the spell system too.


At this point, Scroll is 622 lines of code, including content. Of which, I notice, fully 119 are types and type classes.

Only 4 days left! Eep! I'm very glad that scroll's central antagonist is already written. I don't plan to add other creatures, which will save some time.


Last night as I was drifting off to sleep, it came to me a way to implement my own threading system for my roguelike. Since time in a roguelike happens in discrete ticks, as the player takes each action, normal OS threads are not suitable. And in my case, I'm doing everything in pure code anyway and certianly cannot fork off a thread for some background job.

But, since I'm using continuation passing style, I can just write my own fork, that takes two continuations and combines them, causing both to be run on each tick, and recursing to handle combining the resulting continuations.

It was really quite simple to implement. Typechecked on the first try even!

fork :: M NextStep -> M NextStep -> M NextStep
fork job rest = do
        jn <- job
        rn <- rest
        runthread jn rn
  where
        runthread (NextStep _ (Just contjob)) (NextStep v (Just contr)) =
                return $ NextStep v $ Just $ \i -> do
                        jn <- contjob i
                        rn <- contr i
                        runthread jn rn
        runthread (NextStep _ Nothing) (NextStep v (Just contr)) =
                return $ NextStep v (Just contr)
        runthread _ (NextStep v Nothing) =
                return $ NextStep v Nothing

endThread :: M NextStep
endThread = nextStep Nothing

background :: M NextStep -> M NextStep
background job = fork job continue

demo :: M NextStep
demo = do
    showMessage "foo"
    background $ next $ const $
        clearMessage >> endThread

That has some warts, but it's good enough for my purposes, and pretty awesome for a threading system in 66 LOC.

Syndicated 2015-03-09 23:33:59 from see shy jo

7drl 2015 day 2 level generation and game concept

Much as I want to get my @ displayed and moving around screen, last night and today have focused on level generation instead.

Scroll has kinda strange level generation method, compared to how I suppose most roguelikes do it. There are only 3 calls to rand in all of Scroll. Just a 3 random parameters, but that's enough to ensure a different level each time.

-- Random level generation function.
level :: Bool -> StdGen -> [String]
level randomize r = concat
        [ final (length tutorial + extra) $ concat $ rand mariner1body
        , concat $ rand mariner1end
        , concatMap rand kubla
        ]
  where
    -- here be spoilers

You could say there are two influences in Scroll's level generation method: Nick Montfort and Samuel Taylor Coleridge.


I have thought some about Scroll before starting the 7drl week, but my idea for the game was missing some key concepts. There was nothing to keep the player engaged in moving forward, an unclear victory condition, no clue how to generate appropriate random levels, a large potential for getting stuck, and no way to lose the game. This is all a problem for a roguelike.

But, I had an idea finally last night, about a single unified thing that all of that stuff falls out from. And it's right there in the name of the game!

Now that I understand Scroll better, I wrote the tutorial level. It's a very meta tutorial level that sets the scene well and serves more purposes than are at first apparent. I count a total of 6 things that this "tutorial level" will let the user do.

And interestingly, while the tutorial level is static, it interacts with the rest of the game in a way that will make it be experienced differently every time through.


The strangest line of code I wrote today is:

  import GPL

Somehow, I have never before, in all my time programming, written a line like that one.


Finally, after 7 hours of nonstop coding, I got ncurses to display the generated game world, scrolling around in the display viewport. No @ yet; that will need to wait for tonight or tomorrow!

Syndicated 2015-03-08 23:19:56 from see shy jo

7drl 2015 day 1 groundwork

Scroll is a roguelike, with a twist, which I won't reveal until I've finished building it. I'll just say: A playable roguelike pun, set in a filesystem near you.

I'm creating Scroll as part of the 7DRL Challange. If all goes well, I'll have a usable roguelike game finished in 7 days.

This is my first time developing a roguelike, and my first time writing a game in Haskell, and my first time writing a game to a time limit. Wow!


First, some groundwork. I'm writing Scroll in Haskell, so let's get the core data types and monads and IO squared away. Then I can spend days 2-7 writing entirely pure functional code, in the Haskell happy place.

To represent the current level, I'm using a Vector of Vectors of Chars. Actually, MVectors, which can be mutated safely by pure code running inside the ST monad, so it's fast and easy to read or write any particular location on the level.

-- Writes a Char to a position in the world.
writeWorld :: Pos -> Char -> M ()
writeWorld (x, y) c = modWorld $ \yv -> do
    xv <- V.read yv y
    V.write xv x c

showPlayer :: M ()
showPlayer = writeWorld (5,8) '@'

(I wish these Vectors had their size as part of their types. There are vector libraries on hackage that do, but not the standard vector library, which has mutable vectors. As it is, if I try to access outside the bounds of the world, it'll crash at runtime.)

Since the game will need some other state, I'm using the state monad. The overall monad stack is type M = StateT S (ST RealWorld). (It could be forall s. StateT S (ST s), but I had some trouble getting that to type check, so I fixed s to RealWorld, which is ok since it'll be run using stToIO.

Next, a concept of time, and the main event loop. I decided to use a continutation passing style, so the main loop takes the current continuation, and runs it to get a snapshot of the state to display, and a new continutation. The advantage of using continuations this way is that all the game logic can be handled in the pure code.

I should probably be using the Cont monad in my monad stack, but I've not learned it and lack time. For now I'm handling the continuations by hand, which seems ok.

updateWorld :: Step
updateWorld (Just 'Q') = do
        addMessage "Are you sure you want to quit? [yn]"
        next $ \i -> case i of
                Just 'y' -> quit
                _ -> continue
updateWorld input = do
        addMessage ("pressed " ++ show input)
        continue

Finally, I wrote some ncurses display code, which is almost working.


Start time: After midnight last night. Will end by midnight next Friday.

Lines of code written today: 368

Craziest type signature today: writeS :: forall a. ((Vec2 a -> ST RealWorld ()) -> M ()) -> Pos -> a -> M ()


By the way, there's a whole LambdaHack library for Haskell, targeted at just this kind of roguelike construction. It looks excellent. I'm not using it for two reasons:

  1. Scroll is going to be unusual in a lot of ways, and LambdaHack probably makes some assumptions that don't fit.
  2. mainSer :: (MonadAtomic m, MonadServerReadRequest m) => [String] -> COps -> (m () -> IO ()) -> (COps -> DebugModeCli -> ((FactionId -> ChanServer ResponseUI RequestUI -> IO ()) -> (FactionId -> ChanServer ResponseAI RequestAI -> IO ()) -> IO ()) -> IO ()) -> IO ()
    That's a lot of stuff to figure out! I only have a week, so it's probably easier to build my own framework, and this gives me an opportunity to learn more generally useful stuff, like how to use mutable Vectors.

Syndicated 2015-03-07 22:42:39 from see shy jo

making propellor safer with GADTs and type families

Since July, I have been aware of an ugly problem with propellor. Certain propellor configurations could have a bug. I've tried to solve the problem at least a half-dozen times without success; it's eaten several weekends.

Today I finally managed to fix propellor so it's impossible to write code that has the bug, bending the Haskell type checker to my will with the power of GADTs and type-level functions.

the bug

Code with the bug looked innocuous enough. Something like this:

foo :: Property
foo = property "foo" $
    unlessM (liftIO $ doesFileExist "/etc/foo") $ do
        bar <- liftIO $ readFile "/etc/foo.template"
        ensureProperty $ setupFoo bar

The problem comes about because some properties in propellor have Info associated with them. This is used by propellor to introspect over the properties of a host, and do things like set up DNS, or decrypt private data used by the property.

At the same time, it's useful to let a Property internally decide to run some other Property. In the example above, that's the ensureProperty line, and the setupFoo Property is run only sometimes, and is passed data that is read from the filesystem.

This makes it very hard, indeed probably impossible for Propellor to look inside the monad, realize that setupFoo is being used, and add its Info to the host.

Probably, setupFoo doesn't have Info associated with it -- most properties do not. But, it's hard to tell, when writing such a Property if it's safe to use ensureProperty. And worse, setupFoo could later be changed to have Info.

Now, in most languages, once this problem was noticed, the solution would probably be to make ensureProperty notice when it's called on a Property that has Info, and print a warning message. That's Good Enough in a sense.

But it also really stinks as a solution. It means that building propellor isn't good enough to know you have a working system; you have to let it run on each host, and watch out for warnings. Ugh, no!

the solution

This screams for GADTs. (Well, it did once I learned how what GADTs are and what they can do.)

With GADTs, Property NoInfo and Property HasInfo can be separate data types. Most functions will work on either type (Property i) but ensureProperty can be limited to only accept a Property NoInfo.

data Property i where
    IProperty :: Desc -> ... -> Info -> Property HasInfo
    SProperty :: Desc -> ... -> Property NoInfo

data HasInfo
data NoInfo

ensureProperty :: Property NoInfo -> Propellor Result

Then the type checker can detect the bug, and refuse to compile it.

Yay!

Except ...

Property combinators

There are a lot of Property combinators in propellor. These combine two or more properties in various ways. The most basic one is requires, which only runs the first Property after the second one has successfully been met.

So, what's it's type when used with GADT Property?

requires :: Property i1 -> Property i2 -> Property ???

It seemed I needed some kind of type class, to vary the return type.

class Combine x y r where
    requires :: x -> y -> r

Now I was able to write 4 instances of Combines, for each combination of 2 Properties with HasInfo or NoInfo.

It type checked. But, type inference was busted. A simple expression like "foo requires bar" blew up:

     No instance for (Requires (Property HasInfo) (Property HasInfo) r0)
      arising from a use of `requires'
    The type variable `r0' is ambiguous
    Possible fix: add a type signature that fixes these type variable(s)
    Note: there is a potential instance available:
      instance Requires
                 (Property HasInfo) (Property HasInfo) (Property HasInfo)
        -- Defined at Propellor/Types.hs:167:10

To avoid that, it needed "(foo requires bar) :: Property HasInfo" -- I didn't want the user to need to write that.

I got stuck here for an long time, well over a month.

type level programming

Finally today I realized that I could fix this with a little type-level programming.

class Combine x y where
    requires :: x -> y -> CombinedType x y

Here CombinedType is a type-level function, that calculates the type that should be used for a combination of types x and y. This turns out to be really easy to do, once you get your head around type level functions.

type family CInfo x y
type instance CInfo HasInfo HasInfo = HasInfo
type instance CInfo HasInfo NoInfo = HasInfo
type instance CInfo NoInfo HasInfo = HasInfo
type instance CInfo NoInfo NoInfo = NoInfo
type family CombinedType x y
type instance CombinedType (Property x) (Property y) = Property (CInfo x y)

And, with that change, type inference worked again! \o/

(Bonus: I added some more intances of CombinedType for combining things like RevertableProperties, so propellor's property combinators got more powerful too.)

Then I just had to make a massive pass over all of Propellor, fixing the types of each Property to be Property NoInfo or Property HasInfo. I frequently picked the wrong one, but the type checker was able to detect and tell me when I did.

A few of the type signatures got slightly complicated, to provide the type checker with sufficient proof to do its thing...

before :: (IsProp x, Combines y x, IsProp (CombinedType y x)) => x -> y -> CombinedType y x
before x y = (y `requires` x) `describe` (propertyDesc x)

onChange
    :: (Combines (Property x) (Property y))
    => Property x
    => Property y
    => CombinedType (Property x) (Property y)
onChange = -- 6 lines of code omitted

fallback :: (Combines (Property p1) (Property p2)) => Property p1 -> Property p2 -> Property (CInfo p1 p2)
fallback = -- 4 lines of code omitted

.. This mostly happened in property combinators, which is an acceptable tradeoff, when you consider that the type checker is now being used to prove that propellor can't have this bug.

Mostly, things went just fine. The only other annoying thing was that some things use a [Property], and since a haskell list can only contain a single type, while Property Info and Property NoInfo are two different types, that needed to be dealt with. Happily, I was able to extend propellor's existing (&) and (!) operators to work in this situation, so a list can be constructed of properties of several different types:

propertyList "foos" $ props
    & foo
    & foobar
    ! oldfoo    

conclusion

The resulting 4000 lines of changes will be in the next release of propellor. Just as soon as I test that it always generates the same Info as before, and perhaps works when I run it. (eep)

These uses of GADTs and type families are not new; this is merely the first time I used them. It's another Haskell leveling up for me.

Anytime you can identify a class of bugs that can impact a complicated code base, and rework the code base to completely avoid that class of bugs, is a time to celebrate!

Syndicated 2015-01-25 03:54:14 from see shy jo

a bug in my ear

True story: Two days ago, as I was about to drift off to sleep at 2 am, a tiny little bug flew into my ear. Right down to my eardrum, which it fluttered against with its wings.

It was a tiny little moth-like bug, the kind you don't want to find in a bag of flour, and it had been beating against my laptop screen a few minutes before.

This went on for 20 minutes, in which I failed to get it out with a cue tip and shaking my head. It is very weird to have a bug flapping in your head.

I finally gave up and put in eardrops, and stopped the poor thing flapping. I happen to know these little creatures mass almost nothing, and rapidly break up into nearly powder when dead. So while I've not had any bug bits come out, I'm going by the way my ear felt a little stopped up yesterday, and just fine today, and guessing it'll be ok. Oh, and I've been soaking it in the tub and putting in eardrops for good measure.

If I've seemed a little distracted lately, now you know why!

Syndicated 2015-01-06 01:36:24 from see shy jo

shell monad day 3

I have been hard at work on the shell-monad ever since it was born on Christmas Eve. It's now up to 820 lines of code, and has nearly comprehensive coverage of all shell features.

Time to use it for something interesting! Let's make a shell script and a haskell program that both speak a simple protocol. This kind of thing could be used by propellor when it's deploying itself to a new host. The haskell program can ssh to a remote host and run the shell program, and talk back and forth over stdio with it, using the protocol they both speak.

abstract beginnings

First, we'll write a data type for the commands in the protocol.

  data Proto
    = Foo String
    | Bar
    | Baz Integer
    deriving (Show)

Now, let's go type class crazy!

  class Monad t => OutputsProto t where
    output :: Proto -> t ()

instance OutputsProto IO where
    output = putStrLn . fromProto

So far, nothing interesting; this makes the IO monad an instance of the OutputsProto type class, and gives a simple implementation to output a line of the protocol.

  instance OutputsProto Script where
    output = cmd "echo" . fromProto

Now it gets interesting. The Script monad is now also a member of the OutputsProto. To output a line of the protocol, it just uses echo. Yeah -- shell code is a member of a haskell type class. Awesome -- most abstract shell code evar!

Similarly, we can add another type class for monads that can input the protocol:

  class Monad t => InputsProto t p where
    input :: t p

instance InputsProto IO Proto where
    input = toProto <$> readLn

instance InputsProto Script Var where
    input = do
        v <- newVar ()
        readVar v
        return v

While the IO version reads and deserializes a line back to a Proto, the shell script version of this returns a Var, which has the newly read line in it, not yet deserialized. Why the difference? Well, Haskell has data types, and shell does not ...

speaking the protocol

Now we have enough groundwork to write haskell code in the IO monad that speaks the protocol in arbitrary ways. For example:

  protoExchangeIO :: Proto -> IO Proto
protoExchangeIO p = do
    output p
    input

fooIO :: IO ()
fooIO = do
    resp <- protoExchangeIO (Foo "starting up")
    -- etc

But that's trivial and uninteresting. Anyone who has read to here certianly knows how to write haskell code in the IO monad. The interesting part is making the shell program speak the protocol, including doing various things when it receives the commands.

  foo :: Script ()
foo = do
    stopOnFailure True
    handler <- func (NamedLike "handler") $
        handleProto =<< input
    output (Foo "starting up")
    handler
    output Bar
    handler

handleFoo :: Var -> Script ()
handleFoo v = toStderr $ cmd "echo" "yay, I got a Foo" v

handleBar :: Script ()
handleBar = toStderr $ cmd "echo" "yay, I got a Bar"

handleBaz :: Var -> Script ()
handleBaz num = forCmd (cmd "seq" (Val (1 :: Int)) num) $
    toStderr . cmd "echo" "yay, I got a Baz"

serialization

I've left out a few serialization functions. fromProto is used in both instances of OutputsProto. The haskell program and the script will both use this to serialize Proto.

  fromProto :: Proto -> String
fromProto (Foo s) = pFOO ++ " " ++ s
fromProto Bar = pBAR ++ " "
fromProto (Baz i) = pBAZ ++ " " ++ show i

pFOO, pBAR, pBAZ :: String
(pFOO, pBAR, pBAZ) = ("FOO", "BAR", "BAZ")

And here's the haskell function to convert the other direction, which was also used earlier.

  toProto :: String -> Proto
toProto s = case break (== ' ') s of
    (w, ' ':rest)
        | w == pFOO -> Foo rest
        | w == pBAR && null rest -> Bar
        | w == pBAZ -> Baz (read rest)
        | otherwise -> error $ "unknown protocol command: " ++ w
    (_, _) -> error "protocol splitting error"

We also need a version of that written in the Script monad. Here it is. Compare and contrast the function below with the one above. They're really quite similar. (Sadly, not so similar to allow refactoring out a common function..)

  handleProto :: Var -> Script ()
handleProto v = do
    w <- getProtoCommand v
    let rest = getProtoRest v
    caseOf w
        [ (quote (T.pack pFOO), handleFoo =<< rest)
        , (quote (T.pack pBAR), handleBar)
        , (quote (T.pack pBAZ), handleBaz =<< rest)
        , (glob "*", do
            toStderr $ cmd "echo" "unknown protocol command" w
            cmd "false"
          )
        ]

Both toProto and handleProto split the incoming line apart into the first word, and the rest of the line, then match the first word against the commands in the protocol, and dispatches to appropriate actions. So, how do we split a variable apart like that in the Shell monad? Like this...

  getProtoCommand :: Var -> Script Var
getProtoCommand v = trimVar LongestMatch FromEnd v (glob " *")

getProtoRest :: Var -> Script Var
getProtoRest v = trimVar ShortestMatch FromBeginning v (glob "[! ]*[ ]")

(This could probably be improved by using a DSL to generate the globs too..)

conclusion

And finally, here's a main to generate the shell script!

  main :: IO ()
main = T.writeFile "protocol.sh" $ script foo

The pretty-printed shell script that produces is not very interesting, but I'll include it at the end for completeness. More interestingly for the purposes of sshing to a host and running the command there, we can use linearScript to generate a version of the script that's all contained on a single line. Also included below.

I could easily have written the pretty-printed version of the shell script in twice the time that it took to write the haskell program that generates it and also speaks the protocol itself.

I would certianly have had to test the hand-written shell script repeatedly. Code like for _x in $(seq 1 "${_v#[!\ ]*[\ ]}") doesn't just write and debug itself. (Until now!)

But, the generated scrpt worked 100% on the first try! Well, it worked as soon as I got the Haskell program to compile...

But the best part is that the Haskell program and the shell script don't just speak the same protocol. They both rely on the same definition of Proto. So this is fairly close to the kind of type-safe protocol serialization that Fay provides, when compiling Haskell to javascript.

I'm getting the feeling that I won't be writing too many nontrivial shell scripts by hand anymore! :)

the complete haskell program

Is here, all 99 lines of it.

the pretty-printed shell program

  #!/bin/sh
set -x
_handler () { :
    _v=
    read _v
    case "${_v%%\ *}" in FOO) :
        echo 'yay, I got a Foo' "${_v#[!\ ]*[\ ]}" >&2
    : ;; BAR) :
        echo 'yay, I got a Bar' >&2
    : ;; BAZ) :
        for _x in $(seq 1 "${_v#[!\ ]*[\ ]}")
        do :
            echo 'yay, I got a Baz' "$_x" >&2
        done
    : ;; *) :
        echo 'unknown protocol command' "${_v%%\ *}" >&2
        false
    : ;; esac
}
echo 'FOO starting up'
_handler
echo 'BAR '
_handler

the one-liner shell program

  set -p; _handler () { :;    _v=;    read _v;    case "${_v%%\ *}" in FOO) :;        echo 'yay, I got a Foo' "${_v#[!\ ]*[\ ]}" >&2;     : ;; BAR) :;        echo 'yay, I got a Bar' >&2;    : ;; BAZ) :;        for _x in $(seq 1 "${_v#[!\ ]*[\ ]}");      do :;           echo 'yay, I got a Baz' "$_x" >&2;      done;   : ;; *) :;      echo 'unknown protocol command' "${_v%%\ *}" >&2;       false;  : ;; esac; }; echo 'FOO starting up'; _handler; echo 'BAR '; _handler

Syndicated 2014-12-27 03:18:49 from see shy jo

generating shell scripts from haskell using a shell monad

Shell script is the lingua franca of Unix, it's available everywhere and often the only reasonable choice to Get Stuff Done. But it's also clumsy and it's easy to write unsafe shell scripts, that forget to quote variables, typo names of functions, etc.

Wouldn't it be nice if we could write code in some better language, that generated nicely formed shell scripts and avoided such gotchas? Today, I've built a Haskell monad that can generate shell code.

Here's a fairly involved example. This demonstrates several features, including the variadic cmd, the ability to define shell functions, to bind and use shell variables, to build pipes (with the -:- operator), and to factor out generally useful haskell functions like pipeLess and promptFor ...

santa = script $ do
    hohoho <- func $
        cmd "echo" "Ho, ho, ho!" "Merry xmas!"
    hohoho

    promptFor "What's your name?" $ \name -> pipeLess $ do
        cmd "echo" "Let's see what's in" (val name <> quote "'s") "stocking!"
        forCmd (cmd "ls" "-1" (quote "/home/" <> val name)) $ \f -> do
            cmd "echo" "a shiny new" f
            hohoho

    cmd "rm" "/table/cookies" "/table/milk"
    hohoho

pipeLess :: Script () -> Script ()
pipeLess c = c -|- cmd "less"

promptFor :: T.Text -> (Var -> Script ()) -> Script ()
promptFor prompt cont = do
    cmd "printf" (prompt <> " ")
    var <- newVar "prompt"
    readVar var
    cont var

When run, that haskell program generates this shell code. Which, while machine-generated, has nice indentation, and is generally pretty readable.

#!/bin/sh
f1 () { :
    echo 'Ho, ho, ho!' 'Merry xmas!'
}
f1
printf 'What'"'"'s your name?  '
read '_prompt1'
(
    echo 'Let'"'"'s see what'"'"'s in' "$_prompt1"''"'"'s' 'stocking!'
    for _x1 in $(ls '-1' '/home/'"$_prompt1")
    do :
        echo 'a shiny new' "$_x1"
        f1
    done
) | (
    less
)
rm '/table/cookies' '/table/milk'
f1

Santa has already uploaded shell-monad to hackage and git.

There's a lot of things that could be added to this library (if, while, redirection, etc), but I can already see using it in various parts of propellor and git-annex that need to generate shell code.

Syndicated 2014-12-24 21:55:05 from see shy jo

569 older entries...

New Advogato Features

New HTML Parser: The long-awaited libxml2 based HTML parser code is live. It needs further work but already handles most markup better than the original parser.

Keep up with the latest Advogato features by reading the Advogato status blog.

If you're a C programmer with some spare time, take a look at the mod_virgule project page and help us with one of the tasks on the ToDo list!