arXiv:1708.09158v1 [cs.PL] 30 Aug 2017 © .Teatoscos opaei ntepbi domain. public the in it place to choose authors The ACM. / h au a easrn,als fsrns e fstrings, of a strings, of list a string, a be can value The ( developed. was 1 C Concepts CCS of class a for statically dis happen and cannot errors the type in that values guarantees of types families, of type track closed keeps and literals including er- type-level monad, runtime techniques indexed a programming signals type-level exploit- expect, Haskell by not ing that, language does domain-specific it a fetching develop type when We ror. command, a to a of re-associated and value and type, a different discarded a be of can value key a a — typed cally inllanguages tional oefo h Authors: the from Note Store Key-Value Safety, Keywords systems tion aaae ihaHselinterface Haskell a with database, Redis Abstract e snticue ntewrso rceig ulse by published proceedings workshop the in UK. included Oxford, not 2017, is per 3, September 2017), (TyDe Development rahs al fsrns t.Hwvr tigi h only the is string However, etc. strings, of table hash a or htcnb sda aaae ah,admsaeboe.A broker. message and cache, database, Redis as used be can that Redis Introduction 1 ob,ti oki eesdudrteC0Pbi oanDedication Domain Public of CC0 copy avoidance the all For under paper. waived released this have is to authors work rights this the neighboring doubt, or law, related under and possible right extent the To work this of part when Taiwan, Univ., Tung Chiao National Engineering, ∗ ye1,Spebr3 07 xod UK Oxford, 2017, 3, September purp TyDe’17, commercial for permission. even asking work, without all this perform and distribute modify, hp://creativecommons.org/publicdomain/zero/1.0/ igYnLiwsasme nenfo h nt fCmue cec and Science Computer of Inst. the from intern summer a was Lai Ting-Yan hps://redis.io aeSuyo yeLvlPormigi Haskell in Programming Type-Level of Study Case A oCprgt hswr si h ulcdomain. public the in is work This Copyright. No hswr st epeetda the at presented be to is work This programs. 1 nttt fIfrainScience Information of Institute aasoecnb huh fa e fkyvlepairs. key-value of set a as of thought be can store data sa nmmr aasrcuesoe fe sda a as used often store, structure data in-memory an is agn,Tie iy Taiwan City, Taipei Nangang, sa pnsuc,i-eoydt tutr store structure data in-memory source, open an is [email protected] akl,Rds yeLvlPormig Type Programming, Type-Level Redis, Haskell, cdmaSinica Academia igYnLai Ting-Yan → • ur languages Query otaeadisengineering its and Software ; oanseiclanguages specific Domain ∗ n okhpo Type-Driven on Workshop 2nd yeSf ei Queries: Redis Safe Type ; Hedis . .Ayn a copy, can Anyone ). Redis nttt fIfrainScience Information of Institute ; agn,Tie iy Taiwan City, Taipei Nangang, • sdynami- is Informa- → ygRe Chuang Tyng-Ruey [email protected] hspa- This Func- cdmaSinica Academia oses, Re- the - eb,Sakvro,adFlickr. and StackOverflow, Weibo, hr h type the where h olwn rga mlmnstepeiu example: previous the implements program following The h function The h keys The iae httecmuainete eun au ftype of value a returns a either computation the that dicates to type t C rtcl o akl,tems oua irr is library popular most the Haskell, Hedis For protocol. TCP access its to languages programming purpose sigbfr h alto call the before isting ad,etrdtruhteitrcieitraeof interface interactive the through entered mands, e fpplr aue evcs nldn wte,GitHub, Twitter, including services, is matured popular, concept of the ber While with. manipulated simple, be back to parsed and numbers store, data to the in t saved being serialized before are strings example, for Numbers, datatype. primitive e fsrns h w al ocommand to calls two The strings. of set 2 oieta h keys the that Notice before sets, two the to intersection: strings their takes two and three add hps://hackage.haskell.org/package/hedis rfiswt nerrmsaerpeetdb type by represented message error an with fails or , program program sadd aytidprylbaispoieitrae o general for interfaces provide libraries party third Many o neape osdrtefloigsqec fcom- of sequence following the consider example, an For SADD a . 2 srpeetdi akl by Haskell in represented is )"b" 2) "a" another-set 1) some-set SINTER redis> b 2 a (integer) another-set SADD c redis> b 3 a (integer) some-set SADD redis> :: Redis eunteszso h eutn sets. resulting the of sizes the return (normal) A ByteString some-set :: = Redis Redis do sue sa seta opnn nanum- a in component essential an as used is Redis sadd sadd sinter ( ihrRpyInteger Reply Either ( Redis ihrReply Either and [ → some-set nttt fIfrainScience Information of Institute "some-set" "another-set" samnd while monad, a is agn,Tie iy Taiwan City, Taipei Nangang, [ SADD "some-set" another-set ByteString optto eunn au of value a returning computation [email protected] hnCegMu Shin-Cheng rae nst.Tecalls The site. on created are , cdmaSinica Academia and [ ByteString [ another-set Redis → ] "a" , "another-set" [ ) r ohasge a assigned both are , "a" "b" ihrReply Either SADD ( ihrReply Either , Redis "b" ] ]) respectively , "c" fntex- not if , through SINTER ] Redis Reply ] a . in- a o ) , . . TyDe’17,September3,2017,Oxford,UK Ting-YanLai,Tyng-Ruey Chuang, and Shin-Cheng Mu takes a key and a list of values as arguments, and returns a embedded language (DSEL) that exploits the rich type sys- Redis computation yielding Integer. Keys and values, being tem of Haskell to not only ensure the absence of Redis type nothing but binary strings in Redis, are represented using errors (at least in the simplified situation where there is one Haskell ByteString. client accessing the store), but also provides better documen- tations. We wish to be sure that a program calling INCR, for The Problems Most commands work only with data of example, can be type checked only if we can statically guar- certain types. In the following example, the key some-string antee that the value to be accessed is indeed an integer. We is assigned a string foo — the command SET always assigns wish to see from the type of operators such as LLEN when it a string to a key. The subsequent call to SADD, which adds a canbecalled,andallowittobeusedonlyincontextsthatare value to a set, thus raises a runtime error. safe. We may even want to explicitly declare a fresh key and redis> SET some-string foo its type, to avoid reusing an existing key by accident, and to OK prevent it from unexpectedly being used as some other type. redis> SADD some-string bar This paper discusses the techniques we used and the expe- (error) WRONGTYPE Operation against a key riences we learned from building such a language, Edis. We holding the wrong kind of value constructed an indexed monad, on top of the monad Redis, For another source of type error, the command INCR key in- which is indexed by a dictionary that maintains the set of crements the value associated with key by one. With strings currently defined keys and their types. To represent the dic- being the only primitive type, Redis parses the stored string tionary, we need to encode variable bindings with type-level to an integer and, after incrementation, stores a string back. lists and strings. And to manipulate the dictionary, we ap- If the string cannot be parsed as an integer, a runtime error plied various type-level programming techniques. To sum- is raised. marize our contributions: We point out a peculiar pattern of value creation and up- dating in Redis: the same command is used both to create a Edis key-value pair and to update them. Similar to SADD,the com- • We present , a statically typed domain-specific mand LPUSH appends a value (a string) to a list, or creates language embedded in Haskell (with extension pro- one if the key does not exist: vided by the Glasgow Haskell Compiler) and built on Hedis redis> LPUSH some-list bar . Serializable Haskell datatypes are automatically Redis (integer) 1 converted before being written to data store. Available keys and their types are kept track of in Another command LLEN returns the length of the list, and type-level dictionaries. The types of embedded com- signals an error if the key is not associated with a list: mands state clearly their preconditions and postcon- redis> LLEN some-list ditions on the available keys and types, and a program (integer) 1 is allowed to be constructed only if it is guaranteed redis> SET some-string foo not to fail with a type error, assuming that it is the OK only client accessing the store. redis> LLEN some-string • We demonstrate the use of various type-level program- (error) WRONGTYPE Operation against a key ming techniques, including data kinds, singleton types holding the wrong kind of value and proxies, closed type families, etc., to define type- Curiously, however, when applied to a key not yet created, level lists and operations that observe and manipulate Redis designers chose to let LLEN return 0: the lists. redis> LLEN nonexistent • This is (yet another) example of encoding effects and (integer) 0 constraints of programs in types, using indexed monad [1], Being a simple wrapper on top of the TCP protocol of Re- closed type-families [5] and constraint kinds [16]. dis, Hedis inherits all the behaviors. Executing the follow- ing program yields the same error, but wrapped in a Haskell In Section 2 we introduce indexed monads, to reason about constructor: Le (Error "WRONGTYPE Operation against pre and postconditions of stateful programs, and in Section 3 a key holding the wrong kind of value"). we review the basics of type-level programming in Haskell program :: Redis (Either Reply Integer) that allows us to build type-level dictionaries to keep track program = do set "some-string" "foo" of keys and types. Embeddings of Redis commands are pre- sadd "some-string" ["a"] . sented in Section 4. In Section 5 we discuss various issues re- garding design choices, limitations of this approach, as well Such a programming model is certainly very error-prone. as possible future works, before we review related work in Working within Haskell, a host language with a strong typ- Section 6. ing system, one naturally wishes to build a domain-specific Type Safe Redis eries: A Case Study of Type-Level Programming in Haskell TyDe’17, September 3, 2017, Oxford, UK 2 Indexed Monads The command PING in Redis does nothing but replying a Hedis Stateful computations are often reasoned using Hoare logic. message PONG if the connection is alive. In , ping has Edis A Hoare triple {P}S{Q} denotes the following proposition: if type Redis (R ⊎ Status). The version of ping simply Hedis the statement S is executed in a state satisfying predicate P, applies an additional constructor (functions from are when it terminates, the state must satisfy predicate Q. Pred- qualified with Hedis to prevent name clashing): icates P and Q are respectively called the precondition and :: the postcondition of the Hoare triple. ping Edis xs xs (R ⊎ Status) In Haskell, stateful computations are represented by mon- ping = Edis Hedis.ping . ads. To reason about them within the type system, we wish to label a state monad with its pre and postcondition. An Since ping does not alter the data store, the postcondition indexed monad [1] (also called a parameterised monad or and precondition are the same. Commands that are more in- monadish) is a monad that, in addition to the type of its re- teresting will be introduced after we present our type-level sult, takes two more type parameters representing an initial encoding of constraints on states. state and a final state, to be interpreted like a Hoare triple: 3 Type-Level Dictionaries class IMonad m where One of the challenges of statically ensuring type correctness unit :: a → mppa ofstatefullanguagesis thatthetypeofthevalueofakeycan :: . bind mpqa →(a → mqrb) → mprb be altered by updating. In Redis, one may delete an existing The intention is that a computation of type mpqa is a state- key and create it again by assigning to it a value of a differ- ful computation such that, if it starts execution in a state ent type. To ensure type correctness, we keep track of the satisfying p and terminates, it yields a value of type a, and types of all existing keys in a dictionary. A dictionary is a fi- the new state satisfies q. The operator unit lifts a pure com- nite map, which can be represented by an associate list, or a putation to a stateful computation that does not alter the list of pairs of keys and some encoding of types. For example, "A", , "B", , "C", state. In x ‘bind‘ f , a computation x :: mpqa is followed we may use the dictionary [( Int) ( Char) ( Bool)] by f :: a → mqrb — the postcondition of x matches the to represent a predicate, or a constraint, stating that “the "A" "B" "C" precondition of the computation returned by f . The result keys in the data store are , , and , respectively is a computation mprb. assigned values of type Int, Char, and Bool.” (This represen- We define a new indexed monad Edis. At term level, the tation will be refined in the next section.) "A" unit and bind methods are not interesting: they merely make The dictionary above mixes values (strings such as , "B" calls to return and (>>=) of Redis, and extract and re-apply ) and types. Furthermore, as mentioned in Section 2, the the constructor Edis when necessary. With Edis being a newtype, dictionaries will be parameters to the indexed monad Edis. they can be optimized away in runtime. The purpose is to In a dependently typed (without the add the pre/postconditions at type level: so-called “phase distinction” — separation between types and terms), this would pose no problem. In Haskell how- newtype Edis p q a = Edis {unEdis :: Redis a} , ever, the dictionaries, to index a monad, has to be a type as well. instance IMonad Edis where In this section we describe how to construct a type-level unit = Edis · return dictionary, to be used with the indexed monad in Section 2. bind m f = Edis (unEdis m >>= unEdis · f ) .

The properties of the state we care about are the set of 3.1 Datatype Promotion currently allocated keys and types of their values. We will Haskell maintains the distinction between values, types, and present, in Section 3, techniques that allow us to specify kinds: values are categorized by types, and types are catego- properties such as “the keys in the data store are "A", "B", rized by kinds. The kinds are relatively simple: ∗ is the kind and "C", respectively assigned values of type Int, Char, and of all lifted types, while type constructors have kinds such 3 Bool.” For now, however, let us look at the simplest Redis as ∗ → ∗, or ∗→∗→∗, etc. Consider the datatype defini- command. tions below: Redis commands can be executed in two contexts: the normal context, or a transaction. In Hedis, a commandyield- data Nat = Zero | Suc Nat , data [a] = []| a : [a] . ing value of type a in the normal case is represented by Redis (Either Reply a), as mentioned in Section 1; in a trans- The left-hand side is usually seen as having defined a type action, the command is represented by two other datatypes Nat :: ∗, and two value constructors Zero :: Nat and Suc :: RedisTx (ƒeued a). In this paper we focus on the former Nat → Nat. The right-hand side is how Haskell lists are case. For brevity we abbreviate Either Reply a to R ⊎ a. understood. The kind of [·] is ∗ → ∗, since it takes a lifted TyDe’17,September3,2017,Oxford,UK Ting-YanLai,Tyng-Ruey Chuang, and Shin-Cheng Mu type a to a lifted type [a]. The two value constructors re- recent versions of GHC, indexed type families, or type fami- spectively have types [] :: [a] and (:) :: a → [a]→[a], for lies for short, are considered a cleaner solution. all types a. For example, compare disjunction (∨) and its type-level The GHC extension data kinds [20], however, automati- counterpart Or: cally promotes certain “suitable” types to kinds.4 With the (∨) :: Bool → Bool → Bool extension, the data definitions above has an alternative read- True ∨ b = True ing: Nat is a new kind, Zero :: Nat is a type having kind Nat, = and Suc :: Nat → Nat is a type constructor, taking a type a ∨ b b , in kind Nat to another type in Nat. When one sees a con- :: :: :: structor in an expression, whether it is promoted can often type family Or (a Bool)(b Bool) Bool be inferred from the context. When one needs to be more where 'True ‘Or‘ b = 'True specific, prefixing a constructor with a single quote, such as a ‘Or‘ b = b . ' ' in Zero and Suc, denotes that it is promoted. The first is a typical definition of (∨) by pattern matching. [ ] The situation of lists is similar: for all kinds k, k is also In the second definition, Bool is not a type, but a type lifted '[] [ ] a kind. For all kinds k, is a type of kind k . Given a type to a kind, while True and False are types of kind Bool. The [ ] ': a of kind k and a type as of kind k , a as is again a type declaration says that Or is a family of types, indexed by two [ ] ( ':) :: → [ ]→[ ] of kind k . Formally, k k k . For example, parameters a and b of kind Bool. The type with index 'True ': ( ': ( ': '[])) [∗] Int Char Bool is a type having kind — it and b is 'True, and all other indices lead to b. For our purpose, is a list of (lifted) types. The optional quote denotes that the we can read Or as a function from types to types — observe constructors are promoted. The same list can be denoted by how it resembles the term-level (∨). We present two more '[ , , ] a syntax sugar Int Char Bool . type-level functions about Bool — negation, and conditional, Tuples are also promoted. Thus we may put two types in that we will use later: a pair to form another type, such as in '(Int, Char), a type having kind (∗, ∗). type family Not a where Strings in Haskell are nothing but lists of Chars. Regard- Not 'False = 'True ing promotion, however, a string can be promoted to a type Not 'True = 'False , having kind Symbol. In the expression: type family If (c :: Bool)(t :: a)(f :: a) :: a where "this is a type-level string literal" :: Symbol , If 'True tru fls = tru the string on the left-hand side of (::) is a type whose kind If 'False tru fls = fls . is Symbol. With all of these ingredients, we are ready to build our As a remark, type families in GHC come in many flavors. dictionaries, or type-level associate lists: One can define families of data types, as well as families of type synonyms. They can appear inside type classes [3, 4] type DictEmpty = '[] , or at toplevel. Top-level type families can be open [18] or type Dict0 = '[ '("key", Bool)] , closed [5]. The flavor we choose is top-level, closed type type Dict1 = '[ '("A", Int), '("B", "A")] . synonym families, since it allows overlapping instances, and since we need none of the extensibility provided by open All the entities defined above are types, where Dict0 has type families. Notice that the instance 'True ‘Or‘ b could kind [(Symbol, ∗)]. In Dict1, while Int has kind ∗ and "A" be subsumed under the more general instance, a ‘Or‘ b. In has kind Symbol, the former kind subsumes the later. Thus a closed type family we may resolve the overlapping in or- Dict1 also has kind [(Symbol, ∗)]. der, just like how cases overlapping is resolved in term-level functions. 3.2 Type-Level Functions Now we can define operations on type-level dictionaries. Now that we can represent dictionaries as types, the next Let us begin with: step is to define operations on them. A function that inserts :: , :: :: an entry to a dictionary, for example, is a function from a type family Get (xs [(Symbol ∗)]) (k Symbol) ∗where ' ': = type to a type. While it was shown that it is possible to sim- Get ( (k, x) xs) k x ulate type-level functions using Haskell type classes [13], in Get ('(t, x) ': xs) k = Get xs k .

3 Get xs k returns the entry associated with key k in the dic- In Haskell, the opposite of lifted types are unboxed types, which are not tionary xs. Notice, in the first case, how type-level equality represented by a pointer to a heap object, and cannot be stored in a poly- morphic data type. can be expressed by unifying type variables with the same 4It is only informally described in the GHC manual what types are name. Note also that Get is a partial function on types: while “suitable”. Get '['("A", Int)] "A" evaluates to Int, when Get '['("A", Int)] "B" Type Safe Redis eries: A Case Study of Type-Level Programming in Haskell TyDe’17, September 3, 2017, Oxford, UK

-- inserts or updates an entry Del xs key, since key is a runtime value and not a type. How type family Set (xs :: [(Symbol, ∗)]) (k :: Symbol)(x :: ∗) do we smuggle a runtime value to type-level? :: [(Symbol, ∗)] where In a language with phase distinction like Haskell, it is cer- tainly impossible to pass the value of key to the type checker Set '[] k x = '['(k, x)] if it truly is a runtime value, for example, a string read from Set ('(k, y) ': xs) k x = '(k, x) ': xs the user. If the value of key can be determined statically, ' , ': = ' , ': Set ( (t y) xs) k x (t y) Set xs k x however, singleton types [6] can be used to represent a type -- removes an entry as a value, thus build a connection between the two realms. type family Del (xs :: [(Symbol, ∗)]) (k :: Symbol) A singleton type is a type that has only one term. When :: [(Symbol, ∗)] where thetermis built, itcarriesatypethatcanbeinspectedbythe Del '[] k = '[] type checker. The term can be thought of as a representative Del ('(k, y) ': xs) k = xs of its type at the realm of runtime values. For our purpose, Del ('(t, y) ': xs) k = '(t, y) ': Del xs k we will use the following type Proxy: -- membership data Proxy t = Proxy . type family Member (xs :: [(Symbol, ∗)]) (k :: Symbol) :: For every type t, Proxy t is a type that has only one term: Bool where 5 Member '[] k = 'False Proxy. To call del, instead of passing a key as a String value, Member ('(k, x) ': xs) k = 'True we give it a proxy with a specified type: ' , ': = Member ( (t x) xs) k Member xs k del (Proxy :: Proxy "A") ,

Figure 1. Some operations on type-level dictionaries. where "A" is not a value, but a string lifted to a type (of kind Symbol). Now that the type checker has access to the key, appears in a type expression, there are no applicable rules the type of del can be Proxy k → Edis xs (Del xs k)(R ⊎ to reduce it. The expression thus stays un-reduced. Integer). Some other dictionary-related functions are defined in The next problem is that, del, at term level, gets only a Figure 1. The function Set either updates an existing entry value constructor Proxy without further information, while or inserts a new entry, Del removes an entry matching a it needs to pass a ByteString key to Hedis.del. Every con- given key, while Member checks whether a given key ex- crete string literal lifted to a type, for example, "A", belongs ists in the dictionary. to a type class KnownSymbol. For all types k in KnownSymbol, the function symbolVal: 4 Embedding Hedis Commands symbolVal :: KnownSymbol k ⇒ proxy k → String , Having the indexed monads and type-level dictionaries, in this section we present our embedding of Hedis commands retrieves the string associated with a type-level literal that into Edis, while introducing necessary concepts when they is known at compile time. In summary, del can be imple- are used. mented as:

4.1 Proxies and Singleton Types del :: KnownSymbol k ⇒ The Hedis function del::[ByteString] → Redis (R⊎Integer) Proxy k → Edis xs (Del xs k)(R ⊎ Integer) takes a list of keys (encoded to ByteString) and removes the del key = Edis (Hedis.del [encodeKey key ]) , entries having those keys in the database. For some reason to be explained later, we consider an Edis counterpart that where encodeKey = encode · symbolVal. takes only one key. A first attempt may lead to something A final note: the function encode, from the Haskell library like the following: cereal, helps to convert certain datatypes that are serializ- able into ByteString. The function and its dual decode will :: ? del String → Edis xs (Del xs )(R ⊎ Integer) be used more later. del key = Edis (Hedis.del [encode key ]) , encode :: Serialize a ⇒ a → ByteString , where the function encode converts String to ByteString. At :: . term-level, our del merely calls Hedis.del. At type-level, if decode Serialize a ⇒ ByteString → Either String a the status of the database before del is called meets the con- straint represented by the dictionary xs, the status afterwards should meet the constraint Del xs ?. The question, however, 5While giving the same name to both the type and the term can be very is what to fill in place of the question mark. It cannot be confusing, it is unfortunately a common practice in the Haskell community. TyDe’17,September3,2017,Oxford,UK Ting-YanLai,Tyng-Ruey Chuang, and Shin-Cheng Mu

4.2 Automatic Serialization type family IsList (t :: ∗) :: Bool where As mentioned before, while Redis provide a number of con- IsList (ListOf a) = 'True tainer types including lists, sets, and hash, etc., the primitive IsList t = 'False type is string. Hedis manually convert data of type family IsSet (t :: ∗) :: Bool where other types to strings before saving them into the data store. IsSet (SetOf a) = 'True Edis In , we wish to save some of the effort for the program- IsSet t = 'False mers, as well as keeping a careful record of the intended type family IsString (t :: ∗) :: Bool where types of the strings in the data store. IsString (StringOf a) = 'True To keep track of intended types of strings in the data store, = ' we define the following types (that have no terms): IsString t False type ListOrNX xs k = :: data StringOf ∗ → ∗ , (IsList (Get xs k) ‘Or‘ Not (Member xs k)) ∼ 'True :: data ListOf ∗ → ∗ , type SetOrNX xs k = :: data SetOf ∗ → ∗ ... (IsSet (Get xs k) ‘Or‘ Not (Member xs k)) ∼ 'True = If a key is associated with, for example, StringOf Int in our type StringOrNX xs k ‘ ‘ ' dictionary, we mean that its value in the data store was se- (IsString (Get xs k) Or Not (Member xs k)) ∼ True rialized from an Int and should be used as an Int. Types ListOf a and SetOf a, respectively, denotes that the value is Figure 2. The “well-typed, or non-existent” constraints. a list or a set of type a. While the set command in Hedis always writes a string to the data store, the corresponding set in Redis applies to any 4.3 Disjunctive Constraints serializable type (those in the class Serialize), and performs Recall, from Section 1, that commands LPUSH key val and the encoding for the user: LLEN key succeed either when key appears in the data store and is assigned a list, or when key does not appear at all. :: set (KnownSymbol k, Serialize a) ⇒ Proxy k → a → What we wish to have in their constraint is thus a predicate Edis xs (Set xs k (StringOf a))(Either Reply Status) equivalent to Get xs k == ListOf a ∨¬(Member xs k). set key v = Edis (Hedis.set (encodeKey key)(encode v)) , To impose a conjunctive constraint P ∧ Q, one may sim- ply put them both in the type: (P, Q) ⇒ .... Expressing dis- :: For example, executing set (Proxy Proxy "A") True updates junctive constraints is only slightly harder, thanks to our ' the dictionary with an entry ("A", StringOf Bool). If "A" is type-level functions. We may thus write the predicate as: not in the dictionary, this entry is added; otherwise the old type of "A" is updated to StringOf Bool. Get xs k ∼ ListOf a ‘Or‘ Not (Member xs k) . Redis INCR command reads the (string) value of the given To avoid referring to a, which might not exist, we define key, parses it as an integer, and increments it by one, before an auxiliary predicate IsList :: ∗ → Bool such that IsList t INCRBYFLOAT storing it back. The command increments the reduces to 'True only if t = ListOf a. As many Redis com- floating point value of a key by a given amount. They are Edis mands are invokable only under such “well-typed, or non- defined in below: existent” precondition, we give names to such constraints, incr :: (KnownSymbol k, Get xs k ∼ StringOf Integer) ⇒ as seen in Figure 2. Proxy k → Edis xs xs (R ⊎ Integer) The Edis counterpart of LPUSH and LLEN are therefore: incr key = Edis (Hedis.incr (encodeKey key)) , incrbyfloat :: (KnownSymbol k, Get xs k ∼ StringOf Double) :: , , ⇒ Proxy k → Double → Edis xs xs (R ⊎ Double) lpush (KnownSymbol k Serialize a ListOrNX xs k) ⇒ incrbyfloat key eps = Proxy k → a → Edis (Hedis.incrbyfloat (encodeKey key) eps) . Edis xs (Set xs k (ListOf a))(R ⊎ Integer) lpush key val = Notice the use of (∼), equality constraints [19], to enforce Edis (Hedis.lpush (encodeKey key)[encode val ]) , that the intended type of the value of k must respectively llen :: (KnownSymbol k, ListOrNX xs k) ⇒ be Integer and Double. The function incr is only allowed Proxy k → Edis xs xs (R ⊎ Integer) to be called in a context where the type checker is able to llen key = Edis (Hedis.llen (encodeKey key)) . reduce Get xs k to StringOf Integer — recall that when k is not in xs, Get xs k cannot be fully reduced. The type of Similarly, the type of sadd, a function we have talked about incrbyfloat works in a similar way. a lot, is given below: Type Safe Redis eries: A Case Study of Type-Level Programming in Haskell TyDe’17, September 3, 2017, Oxford, UK sadd :: (KnownSymbol k, Serialize a, SetOrNX xs k) ⇒ that, instead of hmset (available in Hedis), we provide a Proxy k → a → function hset that assigns fields and values one pair at a Edis xs (Set xs k (SetOf a))(R ⊎ Integer) time. sadd key val = :: Edis (Hedis.sadd (encodeKey key)[encode val ]) , hset (KnownSymbol k, KnownSymbol f , Serialize a, HashOrNX xs k) To see a command with a more complex type, consider ⇒ Proxy k → Proxy f → a setnx, which uses the type-level function If defined in Sec- → ( ( ))( ⊎ ) tion 3.2: Edis xs SetHash xs k f StringOf a R Bool hset key field val = :: ( , ) ⇒ → → setnx KnownSymbol k Serialize a Proxy k a Edis (Hedis.hset (encodeKey key) ( ( ) ( ( ))) Edis xs If Member xs k xs Set xs k StringOf a (encodeKey field)(encode val)) , (Either Reply Bool) hget :: (KnownSymbol k, KnownSymbol f , Serialize a, setnx key val = StringOf a ∼ GetHash xs k f ) ⇒ Edis (Hedis.setnx (encodeKey key)(encode val)) . Proxy k → Proxy f → Edis xs xs (R ⊎ Maybe a) From the type one can see that setnx key val creates a new hget key field = ( , ) entry key val in the data store only if key is fresh. The Edis (Hedis.hget (encodeKey key)(encodeKey field) >>= type of setnx computes a postcondition for static checking, decodeAsMaybe) , as well as serving as a good documentation for its semantics.

4.4 Hashes where Hash is a useful datatype supported by Redis. While the Re- :: dis data store can be seen as a set of key/value pairs, a hash decodeAsMaybe Serialize a ⇒(R ⊎ Maybe ByteString) → is itself a set of field/value pairs. The following commands Redis (R ⊎ Maybe a) , assigns a hash to key user. The fields are name, birthyear, and verified,respectively with values banacorn, 1992, and using the function decode mentioned in Section 4.1, parses 1. the ByteString in R ⊎ Maybe to type a. The definition is a redis> hmset user name banacorn bit tedious but routine. birthyear 1992 verified 1 We will talk about difficulties of implementing hmset in OK Section 5. redis> hget user name "banacorn" 4.5 Assertions redis> hget user birthyear Finally, the creation/update behavior of Redis functions is, "1992" in our opinion, very error-prone. It might be preferable if For a hash to be useful, we should allow the fields to have we can explicit declare some new keys, after ensuring that different types. To keep track of types of fields in a hash, they do not already exist (in our types). This can be done HashOf takes a list of (Symbol, ∗) pairs: below: data HashOf :: [(Symbol, ∗)] → ∗ . declare :: (KnownSymbol k, Member xs k ∼ False) ⇒ By having an entry (k, HashOF ys) in a dictionary, we de- Proxy k → Proxy a → Edis xs (Set xs k a)() note that the value of key k is a hash whose fields and their declare key typ = Edis (return ()) . types are specified by ys, which is also a dictionary. Figure 3 presents some operations we need on dictionar- The command declare key typ, where typ is the proxy of ies when dealing with hashes. Let xs be a dictionary, GetHash xs ka f, adds a fresh key with type a into the dictionary. Notice returns the type of field f in the hash assigned to key k, that declare does nothing at term level, but simply returns if both k and f exists. SetHash xs k f a assigns the type (), since it only has effects on types. a to the field f of hash k; if either f or k does not exist, Another command for type level assertion, start, initial- the hash/field is created. Del xs k f removes a field, while izes the dictionary to the empty list, comes in handy when MemHash xs k f checks whether the key k exists in xs, and starting a series of Edis commands: its value is a hash having field f . Their definitions make use of functions Get, Set, and Member defined for dictionaries. start :: Edis '[] '[]() Once those type-level functions are defined, embedding start = Edis (return ()) . of Hedis commands for hashes is more or less routine. For example, functions hset and hget are shown below. Note TyDe’17,September3,2017,Oxford,UK Ting-YanLai,Tyng-Ruey Chuang, and Shin-Cheng Mu

type family GetHash (xs :: [(Symbol, ∗)]) (k :: Symbol)(f :: Symbol) :: ∗where GetHash ('(k, HashOf hs) ': xs) k f = Get hs f GetHash ('(l, y) ': xs) k f = GetHash xs k f type family SetHash (xs :: [(Symbol, ∗)]) (k :: Symbol)(f :: Symbol)(a :: ∗) :: [(Symbol, ∗)] where SetHash '[] k f a = '(k, HashOf (Set '[] f a)) ': '[] SetHash ('(k, HashOf hs) ': xs) k f a = '(k, HashOf (Set hs f a)) ': xs SetHash ('(l, y) ': xs) k f a = '(l, y) ': SetHash xs k f a type family DelHash (xs :: [(Symbol, ∗)]) (k :: Symbol)(f :: Symbol) :: [(Symbol, ∗)] where DelHash '[] k f = '[] DelHash ('(k, HashOf hs) ': xs) k f = '(k, HashOf (Del hs f )) ': xs DelHash ('(l, y) ': xs) k f = '(l, y) ': DelHash xs k f type family MemHash (xs :: [(Symbol, ∗)]) (k :: Symbol)(f :: Symbol) :: Bool where MemHash '[] k f = 'False MemHash ('(k, HashOf hs) ': xs) k f = Member hs f MemHash ('(k, x) ': xs) k f = 'False MemHash ('(l, y) ': xs) k f = MemHash xs k f

Figure 3. Type-level operations for dictionaries with hashes.

4.6 A Slightly Larger Example k‰eue :: Proxy "queue" We present a slightly larger example as a summary. The task k‰eue = Proxy . is to store a queue of messages in Redis. Messages are rep- 6 To pop a message we use the function rpop which, given a resented by a ByteString and an Integer identifier: key associated with a list, extracts the rightmost element of the list data Message = Msg ByteString Integer deriving (Show, Generic) , pop :: (Get xs "queue" ∼ ListOf Message) ⇒ instance Serialize Message where . Edis xs xs (R ⊎ Maybe Message) pop = rpop k‰eue , In the data store, the queue is represented by a list. Before rpop :: (KnownSymbol k, Serialize a, Get xs k ∼ ListOf a) ⇒ pushing a message into the queue, we increment counter, a key storing a counter, and use it as the identifier of the Proxy k → Edis xs xs (R ⊎ Maybe a) = = message: rpop key Edis (Hedis.rpop (encodeKey key) >> decodeAsMaybe) . push :: (StringOfIntegerOrNX xs "counter", Our sample program is shown below: ListOrNX xs "queue") ⇒ = :: ByteString → Edis xs (Set xs "queue" prog declare kCounter (Proxy Proxy Integer) :: (ListOf Message))(R ⊎ Integer) >>> declare k‰eue (Proxy Proxy (ListOf Message)) push msg = incr kCounter ‘bind‘ λi → >>> push "hello" lpush k‰eue (Msg msg (fromRight i)) , >>> push "world" >>> pop , where fromRight::Either ab → b extracts the value wrapped where the monadic sequencing operator (>>>) is defined by: by constructor Right, and the constraint StringOfIntegerOrNX xs k holds if either k appears in xs and is converted from an (>>>) :: IMonad m ⇒ mpqa → mqrb → mprb Integer, or k does not appear in xs. For brevity, the proxies m1 >>> m2 = m1 ‘bind‘ (λ → m2) . are given names: Use of declare in prog ensures that neither "counter" nor "queue" exist before the execution of prog. The program kCounter :: Proxy "counter" simply stores two strings in "queue", before extracting the kCounter = Proxy , first string. GHC is able to infer the type of prog: prog :: Edis '[] '['("counter", Integer), 6Message is made an instance of Generic in order to use the generic imple- '("queue", ListOf Message)] mentation of methods of Serialize. (R ⊎ Maybe Message) . Type Safe Redis eries: A Case Study of Type-Level Programming in Haskell TyDe’17, September 3, 2017, Oxford, UK To get things going, the main program builds a connec- It takes a list of keys, values of which are all supposed to tion with the Redis server, runs prog, and prints the result: be sets, and computes their intersection (the returned list is the intersected set). :: main IO () In Edis, for a function to accept a list of keys as input, we = main do conn ← connect defaultConnectInfo havetospecifythatallthekeysarein theclass KnownSymbol. result ← runRedis conn (unEdis (start >>> prog)) It can be done by defining a datatype, indexed by the keys, print result . serving as a witness that they are all in KnownSymbol. We currently have not implemented such feature and leave it The command start in main guarantees that the program is as a possible future work. For now, we offer commands that given a fresh run without previously defined keys at all. All take fixed numbers of inputs. The Edis version of sinter has type-level constraints in start >>> prog are stripped away by type: unEdis. The untyped program stored in Edis,oftype Redis (R⊎ Maybe Message), is passed to the Redis function runRedis, sinter :: (KnownSymbol k1, KnownSymbol k2, Serialize a, of type Connection → Redis a → IO a. In this case the SetOf x ∼ Get xs k1, SetOf x ∼ Get xs k2) ⇒ output is Right (Just "hello"). Proxy k1 → Proxy k2 → Edis xs xs (R ⊎[a]) . 5 Discussion The function hmset in Hedis allows one to set the values of many fields in a hash, while hgetall returns all the field- Returning Inferrable Types. GET is yet another command value pairs of a hash. They have the following types: that is invokable only under a “well-typed or non-existent” precondition, mentioned in Section 4.3. It fetches the value Hedis.hmset :: ByteString → of a key and, if the key does not exist, returns a special value [(ByteString, ByteString)] → Redis (R ⊎ Status) , nil. An error is raised if the value is not a string. In Edis the Hedis.hgetall :: ByteString → situation is made slightly complex, since we parse the string Redis (R ⊎[(ByteString, ByteString)]) . to the type it was supposed to have encoded from. The Edis version of get could be typed: Proper implementations of them in Edis should accept or return a heterogeneous list [9] — a list whose elements can get :: (KnownSymbol k, Serialize a, StringOrNX xs k) ⇒ be of different types. We also leave such functions as a future Proxy k → Edis xs xs (R ⊎ Maybe a) . work. where StringOrNX is defined in Figure 2. Not All Safe Redis Programs Can Be Typechecked. En- The problem with such typing, however, is that a cannot forcing a typing discipline rules out some erroneous pro- be inferred from xs and k when k does not appear in xs. In grams, and reduces the number of programs that are allowed. such situations, to avoid Haskell complaining about ambigu- Like all type systems, our type system takes a conservative ous type, a has to be specified by the caller of get. The user estimation: there are bound to be some Redis programs that will then be forced to spell out the complete type signature, are not typable in our type system, but do not actually throw only to make a explicit. a type error. We demand that elements in our lists must be We think it is more reasonable to enforce that, when get of the same type, for example, while a Redis program could is called, the key should exist in the data store. Thus get in store in a list different types of data, encoded as strings, and Redis has the following type: still work well. One innate limitation is that we cannot allow dynamic get :: (KnownSymbol k, Serialize a, Get xs k ∼ StringOf a) ⇒ generation of keys. In Hedis, the Haskell program is free to , Proxy k → Edis xs xs (R ⊎ Maybe a) generate arbitrary sequence of keys to be used in the data which requires that (k, a) presents in xs and thus a is in- store, which is in general not possible due to the static na- Edis ferrable from xs and k. ture of . Redis Variable Number of Input/Outputs. Recall that, in Sec- Transactions. Commands in canbewrappedin trans- Redis tion 4.1, the Redis command DEL takes a variable number actions. offers two promises regarding commands in of keys, while our Edis counterpart takes only one. Some a transaction. Firstly, all commands in a transaction are seri- Redis commands take a variable number of arguments as alized and executed sequentially, without interruption from inputs, and some returns multiple results. Most of them are another client. Secondly, either all of the commands or none accurately implemented in Hedis. For another example of a are processed. Edis variable-number input command, the type of sinter in Hedis Support of transactions in is a future work. We ex- is shown below: pect that there would not be too much difficulty — in an early experiment, we have implemented a runtime type checker Hedis.sinter :: [ByteString] → Redis (R ⊎[ByteString]) . specifically targeting Redis transactions, and we believe that TyDe’17,September3,2017,Oxford,UK Ting-YanLai,Tyng-Ruey Chuang, and Shin-Cheng Mu

the experience should be applicable to static type checking [2] Björn Bringert, Anders Höckersten, Conny Andersson, Martin Ander- as well. sson, Mary Bergman, Victor Blomqvist, and Torbjörn Martin. 2004. Student paper: HaskellDB improved, See [15], 108–115. [3] Manuel MT Chakravarty, Gabriele Keller, and Simon Peyton Jones. 6 Conclusions and Related Work 2005. Associated type synonyms. In International Conference on Func- By exploiting various recent extensions and type-level pro- tional Programming, Benjamin C. Pierce (Ed.). ACM Press, 241–253. gramming techniques, we have designed a domain-specific [4] Manuel MT Chakravarty, Gabriele Keller, Simon Peyton Jones, and Edis Simon Marlow. 2005. Associated types with class. In Symposium on embedded language which enforces typing disciplines Principles of Programming Languages, Jens Palsberg and Martin Abadi that keep track of available keys and their types. The type of (Eds.). ACM Press, Long Beach, California, USA, 1–13. a command clearly specifies which keys must or must not [5] Richard A Eisenberg, Dimitrios Vytiniotis, Simon Peyton Jones, and present in the data store, what their types ought to be, as Stephanie Weirich. 2014. Closed type families with overlapping equa- well as how the keys and types are updated after the execu- tions. In Symposium on Principles of Programming Languages, Peter Sewell (Ed.). ACM Press, 671–683. tion. A program can be constructed only if it does not throw [6] Richard A Eisenberg and Stephanie Weirich. 2012. Dependently typed a runtime type error when it is run with a store whose sta- programming with singletons. In Symposium on Haskell, Robby Find- tus matches its precondition and when it is the sole client ler (Ed.). ACM Press, 117–130. interacting with the store. The type also serves as documen- [7] James Hook and PeterThiemann(Eds.).2008. International Conference tation of the commands. We believe that it is a neat case on Functional Programming. ACM Press. [8] Oleg Kiselyov, Simon Peyton Jones, and Chung-chieh Shan. 2010. study of application of type-level programming. Fun with type functions. In Reflections on the Work of C.A.R. Hoare, Redis identifies itself as a data structure store/server, rather A. William Roscoe, Cliff B. Jones, and Kenneth R. Wood (Eds.). than a database. Nevertheless, there has been attempts to de- Springer, 301–331. sign DSELs for relational that guarantee all queries [9] Oleg Kiselyov, Ralf Lämmel, and Keean Schupke. 2004. Strongly typed made are safe. Among them, HaskellDB [2, 11] dynami- heterogeneous collections, See [15], 96–107. [10] Oleg Kiselyov and Chung-chieh Shan. 2007. Lightweight Static Re- cally generates, from monad comprehensions, SQL queries sources: Sexy types for embedded and systems programming. In Sym- to be executed on ODBC database servers. With the expres- posium on Trends in Functional Programming. siveness of dependent types, Oury and Swierstra [17] build a [11] Daan Leijen and Erik Meijer. 1999. Domain specific embedded com- DSEL in Agda for relational algebra. Eisenberg and Weirich [6] pilers. In Domain-Specific Languages, Thomas Ball (Ed.). ACM Press, ported the result to Haskell using singleton types, after GHC 109–122. [12] Sam Lindley and Conor McBride. 2013. Hasochism: the pleasure and introduced more features facilitating type-level programming. pain of dependently typed Haskell programming. In Symposium on None of the type-level programming techniques we used Haskell, Chung-chieh Shan (Ed.). ACM Press, 81–92. in this paper are new. Indexed monads (also called parame- [13] Conor McBride. 2002. Faking it: simulating dependent types in terized monads) have been introduced by Atkey [1]. McBride [14] Haskell. Journal of Functional Programming 12, 5 (July 2002), 375– showed how to construct indexed free-monads from Hoare 392. [14] Conor McBride. 2011. Functional pearl: Kleisli arrows of outrageous Logic specifications. Kiselyov et al. [8] used indexed mon- fortune. (2011). ads to track the locks held among a given finite set. The [15] Henrik Nilsson (Ed.). 2004. Haskell Workshop. ACM Press. same paper also demonstrated implementation of a variety [16] Dominic Orchard and Tom Schrijvers. 2010. Haskell type constraints of features including memorization, generic maps, session unleashed. In Functional and Logic Programming. Springer, 56–71. types, typed printf and sprintf, etc., by type-level pro- [17] Nicolas Oury and Wouter Swierstra. 2008. The power of Pi, See [7], 39–50. gramming. Before the introduction of type families, Kise- [18] Tom Schrijvers, Simon Peyton Jones, Manuel Chakravarty, and Mar- lyov and Shan [10] used type classes and functional depen- tin Sulzmann. 2008. Type checking with open type functions, See [7], dencies to implement type-level functions, and showed that 51–62. they are sufficient to track resources in device drivers. [19] Martin Sulzmann, Manuel MT Chakravarty, Simon Peyton Jones, and Lindley and McBride [12] provided a thorough analysis Kevin Donnelly. 2007. System F with type equality coercions. In Pro- ceedings of the 2007 ACM SIGPLAN international workshop on Types in and summary of the dependent-type-like features currently languages design and implementation. ACM, 53–66. in Haskell, and compared them with dependently typed lan- [20] Brent A. Yorgey, Stephanie Weirich, Julien Cretin, Simon L. Pey- guages without phase distinction such as Agda. It turns out ton Jones, Dimitrios Vytiniotis, and José Pedro Magalhães. 2012. Giv- that GHC’s constraint solver works surprisingly well as an ing Haskell a promotion. In Types in Language Design and Implemen- automatic theorem prover. tation, Benjamin C. Pierce (Ed.). ACM Press, 53–66. References [1] Robert Atkey. 2009. Parameterised notions of computation. Journal of Functional Programming 19, 3-4 (2009), 335–376.