First-class type families
Go to file
2024-04-03 03:42:47 +02:00
.github/workflows ci: Run cabal-docspec 2024-04-02 23:22:59 +02:00
src Fix very odd failure in the docspec for Unfoldr under GHC 9.10 2024-04-03 01:04:42 +02:00
test doctest: Move to cabal-docspec 2021-03-07 20:10:22 -05:00
cabal.haskell-ci ci: Run cabal-docspec 2024-04-02 23:22:59 +02:00
CHANGELOG.md Update CHANGELOG 2024-04-03 03:41:18 +02:00
first-class-families.cabal Bump version to 0.8.1.0 2024-04-03 03:42:47 +02:00
LICENSE Update copyright years 2024-04-02 18:43:51 +02:00
README.md README: Comment about overloaded families 2020-03-08 11:10:09 -04:00
Setup.hs First class type families 2018-07-09 00:13:46 -04:00
stack.yaml ci: Switch to Github Actions 2021-01-29 14:13:28 -05:00

First-class type families Hackage Build Status

First-class type families are type-level functions that can be composed using higher-order functions.

The core of the idea is an extensible kind of "type-level expressions" and an open type family for evaluating such expressions.

type Exp (k :: Type) :: Type
type family Eval (e :: Exp k) :: k

This library provides that core foundation, and also exports basic first-class type families.

Example

For example, consider this simple type family:

type family   FromMaybe (a :: k) (m :: Maybe k) :: k
type instance FromMaybe a 'Nothing  = a
type instance FromMaybe a ('Just b) = b

With first-class-families (fcfs), it translates to a data declaration and instances for a single Eval family:

import Fcf

data FromMaybe :: k -> Maybe k -> Exp k
type instance Eval (FromMaybe a 'Nothing)  = a
type instance Eval (FromMaybe a ('Just b)) = b

That way, the FromMaybe constructor can be partially applied, and passed to higher-order fcfs such as Map:

Eval (Map (FromMaybe 0) '[ 'Just 1, 'Nothing ])  =  '[ 1, 0 ] :: [Nat]

Essential language extensions:

{-# LANGUAGE
    DataKinds,
    PolyKinds,
    TypeFamilies,
    TypeInType,
    TypeOperators,
    UndecidableInstances #-}

Overview

  • Fcf.Core: definition of Exp and Eval.
  • Fcf.Combinators: general combinators to compose first-class families.
  • Fcf.Data.*: first-class families on common data types.
  • Fcf.Class.*: overloaded first-class families.
  • Fcf.Utils: miscellaneous.

The top-level module Fcf is a prelude to get acquainted with the library. For regular use, import what you need from the specialized modules above, preferably with explicit import lists.

import Fcf                       -- Simple but fragile

import Fcf.Class.Functor (FMap)  -- Explicit and robust

Features

Overloaded type families

Value-level functions can be overloaded using type classes. Type families---type-level functions---are open by design, so overloading is as easy as just declaring them with more general types.

data Map :: (a -> Exp b) -> f a -> Exp (f b)

-- Instances for f = []
type instance Eval (Map f '[]) = '[]
type instance Eval (Map f (x ': xs)) = Eval (f x) ': Eval (Map f xs)

-- Instances for f = Maybe
type instance Eval (Map f 'Nothing) = 'Nothing
type instance Eval (Map f ('Just x)) = 'Just (Eval (f x))

See also


Contributions are welcome. Feel free to open an issue or make a PR on Github!