Card expiry

Uninteresting fact: the expiration date of a credit card is printed as something like "02/20", but it is valid until the end of the month. Of course the last day of February could be 28 or 29 depending on year, which can make calculating this day painful. Luckily Purescript has a great library for handling dates. Though the strongly typed nature of these constructs—like all things Haskell—means we have to jump through some hoops to parse a plain string like "02/20" into a full Date type.

Consider the signature of canonicalDate.

canonicalDate :: Year -> Month -> Day -> Date

In order to create a Date, we first require explicit Year, Month, and Day enums. We can get those with toEnum, which has the following signature.

toEnum :: forall a. BoundedEnum a => Int -> Maybe a

This requires an Int, which is derived from a string with fromString. It looks like

fromString :: String -> Maybe Int

Going from a string to a Date means

  1. Splitting the expiration string into separate month and year fields.
  2. Turning those fields into Int.
  3. Turning those Int values into Month and Year enums.
  4. Getting a Day value from the Month and Year.
  5. Generating a complete Date from Day, Month, and Year.
  6. Composing gracefully against Maybe, so that the parsing may short circuit to Nothing if the process fails at any point.

It seems like a hassle, but I am pleased with the solution I came up with. The procedure below leverages a lot of cool concepts, which is why I found it worth documenting here.

module ExpiryDate where

import Prelude (($), (<*>), (<<<), (>=>))
import Control.Apply (lift3, lift2)
import Data.Date (Date, canonicalDate, lastDayOfMonth)
import Data.Enum (toEnum)
import Data.Int (fromString)
import Data.Maybe (Maybe)
import Data.Profunctor.Strong((&&&), (***))
import Data.Semigroup (append)
import Data.String.CodeUnits (take, takeRight)
import Data.Tuple (uncurry)

expiryDate :: String -> Maybe Date
expiryDate = toDate <<< toEnums <<< splitDate
  where
    splitDate = (append "20" <<< takeRight 2) &&& (take 2)
    toEnums   = (fromString >=> toEnum) *** (fromString >=> toEnum)
    toDate    = (uncurry $ lift3 canonicalDate) <*> (uncurry $ lift2 lastDayOfMonth)

It's by no means a simple function, but I do think its control flow is easily analyzed in three parts.

splitDate

splitDate = (append "20" <<< takeRight 2) &&& (take 2)

expiryDate is tacit, but you can see from its signature that it accepts one parameter: a string to parse. The expiration dates in the database I was accessing were actually of the form "0220", meaning it wasn't enough to simply call split over a slash. take and takeRight gave me the strings needed for the month and year respectively. The latter needed a "20" appended to it to be parsed into a valid year.

> take 2 "0220"
"02"

> (append "20" <<< takeRight 2) "0220"
"2020"

This is all very elementary stuff, but it presented me with a problem; I needed to run both these strings through an independent series of transformations, but then have access to them simultaneously in order to derive a Day, and ultimately a Date. In any imperative language I would have performed these transforms on their own lines then accessed the result, but Haskell let me express this branching and merging in a single composition chain with a Bifunctor.

A Functor is a context with an fmap procedure that lets one map functions against it. Maybe, List, etc: you probably know them well. A Bifunctor is a similar context with two such values. Think Either, or a tuple. You can still fmap into a Bifunctor, but this operation is biased to one value, like how the fmap instance of Either only modifies Right. Bifunctors also boast a function bimap, with the signature

bimap :: forall a b c d f. (a -> b) -> (c -> d) -> f a c -> f b d

This can map two separate functions into the context, each operating on their respective value. Needless to say, Bifunctors are very useful in representing branched computations.

splitDate hinges on the &&& (fanout) operator.

(&&&) :: forall p a b c. Category p => Strong p => p a b -> p a c -> p a (Tuple b c)

The signature is intimidating, but it makes sense in the context of splitDate if you imagine each p as a function arrow itself.

(&&&) :: forall a b c. (a -> b) -> (a -> c) -> (a -> Tuple b c)

fanout takes two functions f and g, and composes them into a single function that runs f and g against the same parameter, collecting these respective computations in a single tuple. This allowed me to capture the month and year portions of a string and perform a transformation exclusively on the latter part. Various other Bifunctor operations then made it trivial to access these computations individually or in tandem.

toEnums

toEnums = (fromString >=> toEnum) *** (fromString >=> toEnum)

Each string had to be parsed into an Int, which in turn had to be made into a Month or Year enum. Since fromString and toEnum both return Maybe, it makes sense to perform a monadic bind between them.

toYear :: String -> Maybe Year
toYear x = fromString x >>= toEnum

> toYear "2020"
(Just (Year 2020))

> toYear "!"
Nothing

But since the entire function is one point-free composition, the bind operation >>= had to be replaced by a Kleisli composition >=>.

fromString >=> toEnum

This operates much like a normal function composition <<<, but within a monadic context like Maybe.

You can see this code phrase repeated twice in toEnums, but each instance is not the same procedure; one toEnum returns a Maybe Year and the other a Maybe Month. Much like with pure, it is context-sensitive.

The *** (splitStrong) operator can be considered a tuple-specific version of bimap.

(***) :: forall a b c d. (a -> b) -> (c -> d) -> (Tuple a c) -> (Tuple b d)

It composes the separate Kleisli compositions into a single function that operates on the tuple of strings. This function yielded a new tuple of Maybe Year and Maybe Month and passed it along as input to the final composition.

toDate

toDate = (uncurry $ lift3 canonicalDate) <*> (uncurry $ lift2 lastDayOfMonth)

If you aren't having fun yet, you will here. I had to use the Year and Month values in the tuple twice: once to generate a Day with lastDayOfMonth, and then to make an actual Date with canonicalDate. Of course the ultimate function also required access to the output of lastDayOfMonth. How did I compose with three parameters? A Trifunctor?

Consider the rightmost phrase first. lastDayOfMonth gives a Day. The order of the Bifunctor (year, month) finally makes sense when you examine its type signature.

lastDayOfMonth :: Year -> Month -> Day

Of course I provided Maybe Year and Maybe Month instead. That's where lift2 came in; it raises a dyadic function into a monadic context.

lift2 :: forall a b c f. Apply f => (a -> b -> c) -> f a -> f b -> f c

It is functionally equivalent to Applicative Functor usage like

f <$> x <*> y

but is nice and composable. lift2 can also take on another important role in tacit programming. I didn't make use of it in expiryDate, but examine the signature (substituting for f where need be) and see if you can figure it out.

lift2 expects two parameters, but it was provided a single Bifunctor. So I used uncurry.

uncurry :: forall a b c. (a -> b -> c) -> Tuple a b -> c

It takes a dyadic function and turns it into a procedure that accepts a single tuple parameter. The phrase

uncurry $ lift2 lastDayOfMonth

is a function that uses the entire Bifunctor for a single operation with one output value, in contrast to the parallel processing I was doing earlier. It's easy enough to see how this produces a Day.

The other phrase

(uncurry $ lift3 canonicalDate)

is applied across three Maybe contexts: the aforementioned Year and Month, but also the Day from lastDayOfMonth. lift3 should be self-explanatory, but if you really need a visualization

canonicalDate <$> Maybe Year <*> Maybe Month <*> Maybe Day

should do it. uncurry is again needed to "unwrap" the Bifunctor, though it is actually turning lift3 canonicalDate into a dyadic function that requires a tuple and a Day.

uncurry $ lift3 canonicalDate :: Tuple (Maybe Year) (Maybe Month) -> Maybe Day -> Maybe Date

In any case, the great question is still unanswered: how did I compose a function of three parameters, where the final argument was itself the output of a function? It would be easy if I had a J style hook like

hook :: forall a b c. (a -> b -> c) -> (a -> b) -> a -> c
hook f g = \x -> f x (g x)

This hook, also known as the S combinator, is a control flow pattern so common that it implicitly takes place in J whenever one pairs two functions next to one another. It doesn't appear in expiryDate at first glance, but it's worth taking a look at <*>.

(<*>) :: forall a b f. Apply f => f (a -> b) -> f a -> f b

Change all instances of a to b, and b to c.

(<*>) :: forall b c f. f (b -> c) -> f b -> f c

Change all occurrences of f to a function a ->. Remember that parentheses don't really matter in a curried language.

(<*>) :: forall a b c. (a -> b -> c) -> (a -> b) -> a -> c

It turns out that the Applicative instance of a function is a hook. Perfect. It was then really easy to run

(uncurry $ lift3 canonicalDate) (Maybe Year, Maybe Month) ((uncurry $ lift2 lastDayOfMonth) (Maybe Year, Maybe Month))

entirely tacitly, just like

f x (g x)

I now had an expiration date.

Conclusion

It took me 180 lines of English to explain six lines of code. All to parse a stupid date. "Map this up your functor and smoke it nerd", you might say. But I think the flow of the function body does wonders to mask the complexity of a convoluted process.

toDate <<< toEnums <<< splitString

About as plain as it can be; any intermediate variables would only be noise. Think of it as one big Unix shell pipe. Throw in a basic understanding of Bifunctors and it's really not that bad.

おまけ

lift2 can be used as a J style monadic fork, where fork is

fork :: (a -> b -> c) -> (d -> a) -> (d -> b) -> d -> c
fork f g h = \x -> f (g x) (h x)

Take a look at the signature again.

lift2 :: forall a b c f. Apply f => (a -> b -> c) -> f a -> f b -> f c

Change f to d -> this time and rearrange the parentheses as you please.

lift2 :: forall a b c d. (a -> b -> c) -> (d -> a) -> (d -> b) -> d -> c

See this brilliant discussion for more tacit insanity.