Skip to content

Instantly share code, notes, and snippets.

View ocharles's full-sized avatar
🥳

Ollie Charles ocharles

🥳
View GitHub Profile

Magic

It’s folklore that if you’re summing a list of numbers, then you should always use strict foldl. Is that really true though? foldr is useful for lists when the function we use is lazy in its second argument. For (+) :: Int -> Int -> Int this is tyically not the case, but in some sense that’s because Int is “too strict”. An alternative representation of numbers is to represent them inductively. If we do this, sumation can be lazy, and foldr can do things that foldl simply can’t!

First, let’s define natural numbers inductively, and say how to add them:

data Nat = Zero | OnePlus Nat deriving Show

one :: Nat
{-# language LambdaCase #-}
import Control.Monad.Trans.Class ( lift )
import Control.Monad.Trans.State.Strict
import Data.Functor.Identity
import ListT
-- | Choose as many elements as required to "fill" an applicative functor:
--
{-# language GADTs #-}
{-# language GeneralizedNewtypeDeriving #-}
{-# language QuasiQuotes #-}
{-# language TemplateHaskell #-}
{-# language TypeFamilies #-}
module Bug where
import Settings ( settings )
import Yesod.Persist ( share, mkPersist, persistUpperCase )
begin_version
3
end_version
begin_metric
0
end_metric
7
# This is probably a ball
begin_variable

Solving Planning Problems with Fast Downward and Haskell

In this post I'll demonstrate my new fast-downward library to solve planning problems. The name "Fast Downward" comes from the backend solver - Fast Downward. But what's a planning problem?

Roughly speaking, planning problems are a subclass of AI problems where we have:

  • A known starting state - information about the world we know to be true right now.
  • A set of possible effects - deterministic ways we can change the world.
  • A goal state that we wish to reach.
  • A solution to a planning problem is a plan - a totally ordered sequence of steps that converge the starting state into the goal state.
{-# language ConstraintKinds #-}
{-# language FlexibleContexts #-}
{-# language FlexibleInstances #-}
{-# language GADTs #-}
{-# language MultiParamTypeClasses #-}
{-# language GeneralizedNewtypeDeriving #-}
{-# language RankNTypes #-}
{-# language QuantifiedConstraints #-}
{-# language TypeApplications #-}
{-# language TypeOperators #-}

MonadError via MonadCatch and MonadThrow

First, the code

newtype Exceptional e m a = Exceptional { deExceptional :: m a }
  deriving (Functor, Applicative, Monad)

instance (Exception e, MonadThrow m) => MonadError e (Exceptional e m) where
 throwError = Exceptional . throwM
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
import Control.Monad.IO.Class
import Control.Monad.Trans.Class
import Prelude hiding (log)
--------------------------------------------------------------------------------
-- The API for cloud files.
class Monad m => MonadCloud m where
saveFile :: Path -> Bytes -> m ()
> import Control.Monad.Trans
> import Control.Monad.Trans.Iter
The completely iterative free monad transformer lets us capture non-termination as an effect. Furthermore, it's a monad *transformer*, so we can add non-termination on top of other effects.
A convenient combinator is
> untilSuccess :: Monad m => m (Maybe a) -> IterT m a
> untilSuccess f = maybe (delay (untilSuccess f)) return =<< lift f