Search code examples
haskellservant

How to identify required extensions for Servant


I am reading a servant tutorial but do not understand which extension is used for what parts of the code. The tutorial starts by adding ~10 extensions at the beginning of the file but the first example only requires 3. When I go and implement my own server in Servant, I would like to use the minimal number of extensions required. Is there a method to identify the minimal required extensions?


Solution

  • As per @GeorgeLyubenov's answer, it's perfectly permissible to let the compiler tell you what you need. A good 80-90% of the time, a compiler error message will suggest an extension, if that will solve your problem. There are a few cases where it can't figure it out, and you just have to learn how to identify those. When I'm working on code, I'll often end up adding more extensions than I need, as I try things out and then abandon them. At the end, if I want to trim down the set of extensions, I just try deleting them one by one and see if the compiler complains (so the opposite of George's approach). This works great for tutorials or packages that have a big list of recommended extensions, since you can just include them all and then try deleting them one-by-one. It helps to use an IDE or editor mode (I use Emacs dante) that can quickly type check the file (e.g., every time you save), so you don't have to manually run GHC 20 times.

    There isn't any compiler flag that I know of to dump the list of extensions used, so the trial-and-error method is the best you can do...

    ...unless you actually want to try to understand what the extensions mean. It's not as if they enable random bits of the compiler code with no rhyme or reason. They enable well-documented, understandable features, and while you may not understand and remember all of them, it's not hard to understand most of them.

    Of the list given in the Servant tutorial:

    {-# LANGUAGE DataKinds #-}
    {-# LANGUAGE DeriveGeneric #-}
    {-# LANGUAGE FlexibleInstances #-}
    {-# LANGUAGE GeneralizedNewtypeDeriving #-}
    {-# LANGUAGE MultiParamTypeClasses #-}
    {-# LANGUAGE OverloadedStrings #-}
    {-# LANGUAGE RankNTypes #-}
    {-# LANGUAGE ScopedTypeVariables #-}
    {-# LANGUAGE TypeOperators #-}
    

    two are critical for writing a Servant API like:

    type UserAPI1 = "users" :> Get '[JSON] [User]
    

    The easiest to understand is TypeOperators, which is what let's you use an infix operator like :> in the API type. Without it, you'd need to write the API as:

    type UserAPI1 = (:>) "users" (Get '[JSON] [User])
    

    which pretty much defeats the purpose of having a nice operator-based syntax in the first place. The second critical extension, DataKinds, is a little harder to understand, but it's what allows you to use values, like the string "users" (and the "ticked list" '[...], though not the unticked list [User] or the JSON type itself), as types.

    So, any Servant program that specifies an API is almost certain to need:

    {-# LANGUAGE DataKinds #-}
    {-# LANGUAGE TypeOperators #-}
    

    If you ever write ... deriving (Generic), you need DeriveGeneric. In Servant programs, this is most likely to come up if you want to serve JSON using a ToJSON instance derived automatically from your data type. For the User data type in the tutorial, the instance:

    instance ToJson User
    

    requires that User have a Generic instance, and you would be expected to automatically derive this with data User = ... deriving (Generic), which in turn requires:

    {-# LANGUAGE DeriveGeneric #-}
    

    The OverloadedStrings extension is needed any time you use a string literal "whatever" as something other than a String. In the Servant tutorial, this first comes up when writing:

    {-# LANGUAGE OverloadedStrings #-}
    
    instance Accept HTMLLucid where
        contentType _ = "text" // "html" /: ("charset", "utf-8")
    

    Here, the // and /: operators expect to work with ByteString types:

    (//) :: ByteString -> ByteString -> MediaType
    (//) :: MediaType -> (ByteString, ByteString) -> MediaType
    

    Without the OverloadedStrings extension you'd need to provide explicit conversions from your String literals to ByteString types:

    import qualified Data.ByteString.Char8 as C
    
    instance Accept HTMLLucid where
        contentType _ = C.pack "text" // C.pack "html" /: (C.pack "charset", C.pack "utf-8")
    

    Next up are MultiParamTypeClasses and FlexibleInstances as required by the MimeRender instance for HTMLLucid:

    {-# LANGUAGE MultiParamTypeClasses #-}
    {-# LANGUAGE FlexibleInstances #-}
    
    instance ToHtml a => MimeRender HTMLLucid a where
        mimeRender _ = renderBS . toHtml
    

    The MultiParamTypeClasses extension is a commonly used extension required whenever you try to define a class or instance (or use a class constraint) that takes multiple parameters. The MimeRender class actually takes two parameters. The first is a type-level tag for an accepted MIME type, here HTMLLucid. The second is the type that will be rendered by the instance to content of that MIME type. Because this is a two-parameter class, you need the MultiParamTypeClasses extension to write instances for it.

    In addition, in standard Haskell, you can only write instances for parameters of the form SomeType var1 var2 var3 (possibly with zero variables). So, you could write a specific instance where the first parameter is of form SomeType and the second is of the same form:

    instance MimeRender HTMLLucid Int where ...
    

    or even where the second parameter is of the form SomeType var1:

    instance MimeRender HTMLLucid (Maybe var) where ...
    

    but that second parameter can't be a plain variable a, unless you enable FlexibleInstances.

    So, the list:

    {-# LANGUAGE DataKinds #-}
    {-# LANGUAGE DeriveGeneric #-}
    {-# LANGUAGE FlexibleInstances #-}
    {-# LANGUAGE MultiParamTypeClasses #-}
    {-# LANGUAGE OverloadedStrings #-}
    {-# LANGUAGE TypeOperators #-}
    

    covers most of what you need for the server tutorial.

    As far as I can see, RankNTypes is only needed to write:

    type (~>) m n = forall a. m a -> n a
    

    which is only used to illustrate a general concept before introducing hoistServer and isn't actually needed for anything else. I also don't see that ScopedTypeVariables or GeneralizedNewtypeDeriving are needed anywhere in the server tutorial.