rank2classes
standard type constructor class hierarchy, only with methods of rank 2 types
https://github.com/blamario/grampa/tree/master/rank2classes
| LTS Haskell 24.16: | 1.5.4 | 
| Stackage Nightly 2025-10-25: | 1.5.4 | 
| Latest on Hackage: | 1.5.4 | 
rank2classes-1.5.4@sha256:6aa71842adb59172d0e55f4d3817a1b9d03c3f37f31d55ad1659e931f40f8f5a,2712Module documentation for 1.5.4
Rank 2 Classes
The standard constructor type classes in the parallel rank-2 universe
The rank2 package exports module Rank2, meant to be imported qualified like this:
{-# LANGUAGE RankNTypes, TemplateHaskell, TypeOperators #-}
module MyModule where
import qualified Rank2
import qualified Rank2.TH
Several more imports for the examples…
import Data.Functor.Classes (Show1, showsPrec1)
import Data.Functor.Identity (Identity(..))
import Data.Functor.Const (Const(..))
import Data.List (find)
The Rank2 import will make available the following type classes:
- Rank2.Functor
- Rank2.Apply
- Rank2.Applicative
- Rank2.Foldable
- Rank2.Traversable
- Rank2.Distributive
- Rank2.Logistic
The methods of these type classes all have rank-2 types. The class instances are data types of kind (k -> *) -> *,
one example of which would be a database record with different field types but all wrapped by the same type
constructor:
data Person f = Person{
   name           :: f String,
   age            :: f Int,
   mother, father :: f (Maybe PersonVerified)
   }
By wrapping each field we have declared a generalized record type. It can made to play different roles by switching the
value of the parameter f. Some examples would be
type PersonVerified = Person Identity
type PersonText = Person (Const String)
type PersonWithErrors = Person (Either String)
type PersonDatabase = [PersonVerified]
type PersonDatabaseByColumns = Person []
If you wish to have the standard Eq and
Show instances for a record type like Person,
it’s best if they refer to the
Eq1 and
Show1 instances for its
parameter f:
instance Show1 f => Show (Person f) where
   showsPrec prec person rest =
       "Person{" ++ separator ++ "name=" ++ showsPrec1 prec' (name person)
            ("," ++ separator ++ "age=" ++ showsPrec1 prec' (age person)
            ("," ++ separator ++ "mother=" ++ showsPrec1 prec' (mother person)
            ("," ++ separator ++ "father=" ++ showsPrec1 prec' (father person)
            ("}" ++ rest))))
        where prec' = succ prec
              separator = "\n" ++ replicate prec' ' '
You can create the rank-2 class instances for your data types manually, or you can generate the instances using the
templates imported from the Rank2.TH module with a single line of code per data type:
$(Rank2.TH.deriveAll ''Person)
Either way, once you have the rank-2 type class instances, you can use them to easily convert between records with
different parameters f.
Record construction and modification examples
In case of our Person record, a couple of helper functions will prove handy:
findPerson :: PersonDatabase -> String -> Maybe PersonVerified
findPerson db nameToFind = find ((nameToFind ==) . runIdentity . name) db
   
personByName :: PersonDatabase -> String -> Either String (Maybe PersonVerified)
personByName db personName
   | null personName = Right Nothing
   | p@Just{} <- findPerson db personName = Right p
   | otherwise = Left ("Nobody by name of " ++ personName)
Now we can start by constructing a Person record with rank-2 functions for fields. This record is not so much a person
as a field-by-field person verifier:
personChecker :: PersonDatabase -> Person (Const String Rank2.~> Either String)
personChecker db =
   Person{name= Rank2.Arrow (Right . getConst),
          age= Rank2.Arrow $ \(Const age)->
               case reads age
               of [(n, "")] -> Right n
                  _ -> Left (age ++ " is not an integer"),
          mother= Rank2.Arrow (personByName db . getConst),
          father= Rank2.Arrow (personByName db . getConst)}
We can apply it using the Rank2.<*>
method of the Rank2.Apply type class to a bunch
of textual fields for Person, and get back either errors or proper field values:
verify :: PersonDatabase -> PersonText -> PersonWithErrors
verify db person = personChecker db Rank2.<*> person
If there are no errors, we can get a fully verified record by applying Rank2.traverse to the result:
completeVerified :: PersonWithErrors -> Either String PersonVerified
completeVerified = Rank2.traverse (Identity <$>)
or we can go in the opposite direction with Rank2.<$>:
uncompleteVerified :: PersonVerified -> PersonWithErrors
uncompleteVerified = Rank2.fmap (Right . runIdentity)
If on the other hand there are errors, we can collect them using Rank2.foldMap:
verificationErrors :: PersonWithErrors -> [String]
verificationErrors = Rank2.foldMap (either (:[]) (const []))
Here is an example GHCi session:
-- |
-- >>> :{
--let Right alice = completeVerified $
--                  verify [] Person{name= Const "Alice", age= Const "44",
--                                   mother= Const "", father= Const ""}
--    Right bob = completeVerified $
--                verify [] Person{name= Const "Bob", age= Const "45",
--                                 mother= Const "", father= Const ""}
--    Right charlie = completeVerified $
--                    verify [alice, bob] Person{name= Const "Charlie", age= Const "19",
--                                               mother= Const "Alice", father= Const "Bob"}
-- :}
-- 
-- >>> charlie
-- Person{
--  name=Identity "Charlie",
--  age=Identity 19,
--  mother=Identity (Just Person{
--             name=(Identity "Alice"),
--             age=(Identity 44),
--             mother=(Identity Nothing),
--             father=(Identity Nothing)}),
--  father=Identity (Just Person{
--             name=(Identity "Bob"),
--             age=(Identity 45),
--             mother=(Identity Nothing),
--             father=(Identity Nothing)})}
-- >>> :{
--let dave = verify [alice, bob, charlie]
--           Person{name= Const "Dave", age= Const "young",
--                  mother= Const "Lise", father= Const "Mike"}
-- :}
--
-- >>> dave
-- Person{
--  name=Right "Dave",
--  age=Left "young is not an integer",
--  mother=Left "Nobody by name of Lise",
--  father=Left "Nobody by name of Mike"}
-- >>> completeVerified dave
-- Left "young is not an integer"
-- >>> verificationErrors  dave
-- ["young is not an integer","Nobody by name of Lise","Nobody by name of Mike"]
-- >>> Rank2.distribute [alice, bob, charlie]
-- Person{
--  name=Compose [Identity "Alice",Identity "Bob",Identity "Charlie"],
--  age=Compose [Identity 44,Identity 45,Identity 19],
--  mother=Compose [Identity Nothing,Identity Nothing,Identity (Just Person{
--             name=(Identity "Alice"),
--             age=(Identity 44),
--             mother=(Identity Nothing),
--             father=(Identity Nothing)})],
--  father=Compose [Identity Nothing,Identity Nothing,Identity (Just Person{
--             name=(Identity "Bob"),
--             age=(Identity 45),
--             mother=(Identity Nothing),
--             father=(Identity Nothing)})]}
Related works
This package is one of several implementations of a pattern that is often called Higher-Kinded Data. Other examples include hkd-lens, barbies, and higgledy.
Grammars are another use case that is almost, but not quite, entirely unlike database records. See grammatical-parsers or construct for examples.
Both database records and grammars are flat structures. If your use case involves trees of rank-2 records, this package will probably not suffice. Consider using deep-transformations instead.
Changes
Version 1.5.4
- Deriving DataandTypeablefor all declared data types.
- Bumped the upper bound of the template-haskelldependency.
Version 1.5.3.1
- Bumped the upper bound of the template-haskelldependency.
Version 1.5.3
- Fixed compilation with GHC 9.8.1 and template-haskell2.22
Version 1.5.2
- Fixed the generated TH instance contexts for GADTs.
- Fixed the generated signature of the deliverinstance method in presence ofInstanceSigs.
- Bumped the upper bound of the template-haskelldependency.
Version 1.5.1
- Fixed the Rank2.THtemplates on GHC < 9.2 with noOverloadedRecordDotsupport to revert to their 1.4.6 behaviour.
Version 1.5
- The Rank2.THtemplates have changed, are now applicable withDuplicateRecordFieldsprovided thatOverloadedRecordDotis enabled.
- Rank2.TH.deriveLogisticalso needs- ScopedTypeVariablesand- InstanceSigsextensions to generate proper record updates.
Version 1.4.6
- Added the Logistictype class,gettersandsetters
- Added Rank2.TH.deriveLogistic, included it inderiveAll
- Compiling with GHC 9.4.2
- Forward compatibility with TypeFamilies
Version 1.4.4
- Tested with GHC 9.2.1, incremented the upper template-haskelldependency bound
- Generalized the TH generation to handle PolyRec types
- Incremented the lower bound of rank2classes’ basedependency, thanks to phadej
Version 1.4.3
- Fixed links to standard rank-1 classes in Haddock documentation
- Fixed issue #23 with the traversetemplate generated for sum types with a fieldless constructor
- Incremented upper dependency bounds
Version 1.4.2
- Fixed compatibility with GHC 9 - PR by Felix Yan
Version 1.4.1
- Fixed the templates for multi-constructor records
- Made Rank2.TH.unsafeDeriveApply even more unsafe
Version 1.4
- Added Rank2.Compose :: ((* -> *) -> ) -> ( -> ) -> (( -> *) -> *)
- Matched the precedence of <$> and <*> operators with Prelude
- Relaxed the lower bound of base dependency to 4.10
Version 1.3.2.1
- Incremented the upper bound of the template-haskell dependency
Version 1.3.2
- Exported the $synonym forapply
Version 1.3.1.2
- Fixed doctest module name issue
- Incremented the lower bound of base dependency
Version 1.3.1.1
- Fixed the doctests after cabal get
Version 1.3.1
- Added missing markdown-unlit dependency
- Strictified one argument of Rank2.<$> and Rank2.<*>
Version 1.3
- Added newtype Flipto exports - PR by Jeremy List
- Generating INLINE pragmas from Rank2.TH
- Generating the proper constraints on derived instances where needed
Version 1.2.1
- Added unsafeDeriveApply
Version 1.2
- Added the class instances for Data.Functor.Const
- Fixed and optimized the Foldable/Traversable instance code generated for bare fields in Rank2.TH
Version 1.1
- Replaced own Productdata type by the one fromData.Functor.Product
- Added instances of Data.Functor.Sum
- Removed the TH generation of partial Apply and Distributive instances
- Covered more constructor cases in TH code
- Added use-template-haskell flag, true by default - PR by Dridus
Version 1.0.2
- Fixed the bounds and Semigroupto compile with GHC 8.4.1
- Added the ~> type synonym
- Fixed deriveFunctorfor record fields with concrete types - PR by Tom Smalley
Version 1.0.1
- Fixed the doctests
Version 1.0
- Swapped distributeWithwithcotraverse
- Documentation improvements
Version 0.2.1.1
- Corrected the README
Version 0.2.1
- Incremented the dependency bounds for GHC 8.2.1
Version 0.2
- Introduced DistributiveTraversableas a generalization ofDistributive
- Export “cotraverse” and “cotraverseTraversable”
- Added liftA3,liftA4,liftA5
- Added more convienence functions
- Fixed grammatical errors and overlong lines
Version 0.1.1
- Generalized the classes with {-# LANGUAGE PolyKinds" #-}
Version 0.1
- Initial release
