higgledy: Partial types as a type constructor.

[ data, library, mit ] [ Propose Tags ]

Use the generic representation of an ADT to get a higher-kinded data-style interface automatically.


[Skip to Readme]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

Versions [RSS] 0.1.0.0, 0.1.1.0, 0.1.1.1, 0.2.0.0, 0.2.0.1, 0.2.1.0, 0.3.0.0, 0.3.1.0, 0.4.0.0, 0.4.1.0, 0.4.1.1, 0.4.2.0, 0.4.2.1
Change log CHANGELOG.md
Dependencies barbies (>=1.1.0.0 && <1.2), base (>=4.12.0.0 && <4.13), generic-lens (>=1.1.0.0 && <1.2), QuickCheck (>=2.13.0 && <2.14) [details]
License MIT
Author Tom Harding
Maintainer tom.harding@habito.com
Category Data
Home page https://github.com/i-am-tom/higgledy
Uploaded by i_am_tom at 2019-04-13T00:02:06Z
Distributions
Reverse Dependencies 1 direct, 0 indirect [details]
Downloads 4391 total (46 in the last 30 days)
Rating 2.0 (votes: 1) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2019-04-13 [all 1 reports]

Readme for higgledy-0.1.0.0

[back to package description]

Higgledy 📚

Higher-kinded data via generics: all* the benefits, but none* of the boilerplate.

Introduction

When we work with higher-kinded data, we find ourselves writing types like:

data User f
  = User
      { name :: f String
      , age  :: f Int
      , ...
      }

This is good - we can use f ~ Maybe for partial data, f ~ Identity for complete data, etc - but it introduces a fair amount of noise, and we have a lot of boilerplate deriving to do. Wouldn't it be nice if we could get back to writing simple types as we know and love them, and get all this stuff for free?

data User
  = User
      { name :: String
      , age  :: Int
      , ...
      }
  deriving Generic

-- HKD for free!
type UserF f = HKD User f

As an added little bonus, any HKD-wrapped object is automatically an instance of all the Barbie classes, so no need to derive anything more than Generic!

API

All examples below were compiled with the following extensions, modules, and example data types:

{-# LANGUAGE DataKinds        #-}
{-# LANGUAGE DeriveGeneric    #-}
{-# LANGUAGE TypeApplications #-}
module Example where

import Control.Lens ((.~), (^.), (&), Const (..), Identity, anyOf)
import Data.Generic.HKD
import Data.Maybe (isJust, isNothing)
import Data.Monoid (Last (..))
import GHC.Generics (Generic)

-- An example of a record (with named fields):
data User
  = User
      { name      :: String
      , age       :: Int
      , likesDogs :: Bool
      }
  deriving (Generic, Show)

user :: User
user = User "Tom" 25 True

-- An example of a product (without named fields):
data Triple
  = Triple Int () String
  deriving (Generic, Show)

triple :: Triple
triple = Triple 123 () "ABC"

The HKD type constructor

The HKD type takes two parameters: your model type, and the functor in which we want to wrap all our inputs. By picking different functors for the second parameter, we can recover various behaviours:

type Partial a = HKD a  Last          -- Fields may be missing.
type Bare    a = HKD a  Identity      -- All must be present.
type Labels  a = HKD a (Const String) -- Every field holds a string.

Fresh objects

When we want to start working with the HKD interface, we have a couple of options, depending on the functor in question. The first option is to use mempty:

eg0 :: Partial User
eg0 = mempty
-- User
--   { name      = Last {getLast = Nothing}
--   , age       = Last {getLast = Nothing}
--   , likesDogs = Last {getLast = Nothing}
--   }

Other 'Alternative'-style functors lead to very different results:

eg1 :: Labels Triple
eg1 = mempty
-- Triple
--   Const ""
--   Const ""
--   Const ""

Of course, this method requires every field to be monoidal. If we try with Identity, for example, we're in trouble if all our fields aren't themselves monoids:

eg2 :: Bare Triple
eg2 = mempty
-- error:
-- • No instance for (Monoid Int) arising from a use of ‘mempty’

The other option is to deconstruct a complete object. This effectively lifts a type into the HKD structure with pure applied to each field:

eg3 :: Bare User
eg3 = deconstruct user
-- User
--   { name      = Identity "Tom"
--   , age       = Identity 25
--   , likesDogs = Identity True
--   }

This approach works with any applicative we like, so we can recover the other behaviours:

eg4 :: Partial Triple
eg4 = deconstruct @Last triple
-- Triple
--   Last {getLast = Just 123}
--   Last {getLast = Just ()}
--   Last {getLast = Just "ABC"}

There's also construct for when we want to escape our HKD wrapper, and attempt to construct our original type:

eg5 :: Last Triple
eg5 = construct eg4
-- Last {getLast = Just (Triple 123 () "ABC")}

Field Access

The field lens, when given a type-applied field name, allows us to focus on fields within a record:

eg6 :: Last Int
eg6 = eg0 ^. field @"age"
-- Last {getLast = Nothing}

As this is a true Lens, it also means that we can set values within our record (note that these set values will also need to be in our functor of choice):

eg7 :: Partial User
eg7 = eg0 & field @"name"      .~ pure "Evil Tom"
          & field @"likesDogs" .~ pure False     
-- User
--   { name      = Last {getLast = Just "Evil Tom"}
--   , age       = Last {getLast = Nothing}
--   , likesDogs = Last {getLast = Just False}
--   }

This also means, for example, we can check whether a particular value has been completed for a given partial type:

eg8 :: Bool
eg8 = anyOf (field @"name") (isJust . getLast) eg0
-- False

Finally, thanks to the fact that this library exploits some of the internals of generic-lens, we'll also get a nice type error when we mention a field that doesn't exist in our type:

eg9 :: Identity ()
eg9 = eg3 ^. field @"oops"
-- error:
-- • The type User does not contain a field named 'oops'.

Position Access

Just as with field names, we can use positions when working with non-record product types:

eg10 :: Labels Triple
eg10 = mempty & position @1 .~ Const "hello"
              & position @2 .~ Const "world"
-- Triple
--   Const "hello"
--   Const "world"
--   Const ""

Again, this is a Lens, so we can just as easily set values:

eg11 :: Partial User
eg11 = eg7 & position @2 .~ pure 25
-- User
--   { name      = Last {getLast = Just "Evil Tom"}
--   , age       = Last {getLast = Just 25}
--   , likesDogs = Last {getLast = Just False}
--   }

Similarly, the internals here come to us courtesy of generic-lens, so the type errors are a delight:

eg9 :: Identity ()
eg9 = deconstruct @Identity triple ^. position @4
-- error:
-- • The type Triple does not contain a field at position 4

Labels

One neat trick we can do - thanks to the generic representation - is get the names of the fields into the functor we're using. The label function gives us this interface:

eg10 :: Labels User
eg10 = label eg11
-- User
--   { name = Const "name"
--   , age = Const "age"
--   , likesDogs = Const "likesDogs"
--   }

By combining this with some of the Barbies interface (the entirety of which is available to any HKD-wrapped type) such as bprod and bmap, we can implement functions such as labelsWhere, which returns the names of all fields whose values satisfy some predicate:

eg13 :: [String]
eg13 = labelsWhere (isNothing . getLast) eg7
-- ["age"]