rank2classes: a mirror image of some standard type classes, with methods of rank 2 types

This is a package candidate release! Here you can preview how this package release will appear once published to the main package index (which can be accomplished via the 'maintain' link below). Please note that once a package has been published to the main package index it cannot be undone! Please consult the package uploading documentation for more information.

[maintain] [Publish]

Warnings:

A mirror image of the standard constructor type class hierarchy rooted in Functor, except with methods of rank 2 types and class instances of kind (*->*)->*. The classes enable generic handling of heterogenously typed data structures and other neat tricks.


[Skip to Readme]

Properties

Versions 0.1, 0.1, 0.2, 0.2.1.1, 1.0, 1.0.1, 1.0.2, 1.1, 1.1.0.1, 1.2, 1.2.1, 1.3, 1.3.1, 1.3.1.1, 1.3.1.2, 1.3.2.1, 1.4, 1.4.0.1, 1.4.1, 1.4.2, 1.4.3, 1.4.4, 1.4.5, 1.4.6, 1.5, 1.5.1, 1.5.2, 1.5.3
Change log None available
Dependencies base (>=4.7 && <5), template-haskell (>=2.11 && <2.12), transformers (>=0.5 && <0.6) [details]
License BSD-3-Clause
Copyright (c) 2017 Mario Blažević
Author Mario Blažević
Maintainer Mario Blažević <blamario@protonmail.com>
Category Control, Data, Generics
Home page https://github.com/blamario/grampa/tree/master/rank2classes
Bug tracker https://github.com/blamario/grampa/issues
Source repo head: git clone https://github.com/blamario/grampa
Uploaded by MarioBlazevic at 2017-05-28T02:46:22Z

Modules

[Index]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees


Readme for rank2classes-0.1

[back to package description]

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 #-}
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:

The methods of these type classes all have rank-2 types. The class instances are data types of kind (* -> *) -> *, 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 (Rank2.Arrow (Const String) (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 ""}
-- >>> let Right bob = completeVerified $ verify [] Person{name= Const "Bob", age= Const "45", mother= Const "", father= Const ""}
-- >>> let 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 "Eve", age= Const "young", mother= Const "Lise", father= Const "Mike"}
-- >>> dave
-- Person{
--  name=Right "Eve",
--  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)})]}

Grammars are another use case that is almost, but not quite, completely unlike database records. See grammatical-parsers about that.