File: README.md

package info (click to toggle)
haskell-rank2classes 1.5.3.1-1
  • links: PTS
  • area: main
  • in suites: forky, sid, trixie
  • size: 180 kB
  • sloc: haskell: 1,246; makefile: 6
file content (223 lines) | stat: -rw-r--r-- 9,175 bytes parent folder | download | duplicates (2)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
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:

~~~ {.haskell}
{-# LANGUAGE RankNTypes, TemplateHaskell, TypeOperators #-}
module MyModule where
import qualified Rank2
import qualified Rank2.TH
~~~

Several more imports for the examples...

~~~ {.haskell}
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](http://hackage.haskell.org/package/rank2classes/docs/Rank2.html#t:Functor)
  * [Rank2.Apply](http://hackage.haskell.org/package/rank2classes/docs/Rank2.html#t:Apply)
  * [Rank2.Applicative](http://hackage.haskell.org/package/rank2classes/docs/Rank2.html#t:Applicative)
  * [Rank2.Foldable](http://hackage.haskell.org/package/rank2classes/docs/Rank2.html#t:Foldable)
  * [Rank2.Traversable](http://hackage.haskell.org/package/rank2classes/docs/Rank2.html#t:Traversable)
  * [Rank2.Distributive](http://hackage.haskell.org/package/rank2classes/docs/Rank2.html#t:Distributive)
  * [Rank2.Logistic](http://hackage.haskell.org/package/rank2classes/docs/Rank2.html#t: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:

~~~ {.haskell}
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

~~~ {.haskell}
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](http://hackage.haskell.org/package/base/docs/Data-Eq.html#t:Eq) and
[Show](http://hackage.haskell.org/package/base/docs/Text-Show.html#t:Show) instances for a record type like `Person`,
it's best if they refer to the
[Eq1](http://hackage.haskell.org/package/base-4.9.1.0/docs/Data-Functor-Classes.html#t:Eq1) and
[Show1](http://hackage.haskell.org/package/base-4.9.1.0/docs/Data-Functor-Classes.html#t:Show1) instances for its
parameter `f`:

~~~ {.haskell}
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:

~~~ {.haskell}
$(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:

~~~ {.haskell}
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:
 
~~~ {.haskell}
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.<*>](http://hackage.haskell.org/package/rank2classes/docs/Rank2.html#v:-60--42--62-)
method of the [Rank2.Apply](http://hackage.haskell.org/package/rank2classes/docs/Rank2.html#t:Apply) type class to a bunch
of textual fields for `Person`, and get back either errors or proper field values:

~~~ {.haskell}
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](http://hackage.haskell.org/package/rank2classes/docs/Rank2.html#v:traverse) to the result:

~~~ {.haskell}
completeVerified :: PersonWithErrors -> Either String PersonVerified
completeVerified = Rank2.traverse (Identity <$>)
~~~

or we can go in the opposite direction with
[Rank2.<$>](http://hackage.haskell.org/package/rank2classes/docs/Rank2.html#v:-60--36--62-):

~~~ {.haskell}
uncompleteVerified :: PersonVerified -> PersonWithErrors
uncompleteVerified = Rank2.fmap (Right . runIdentity)
~~~

If on the other hand there *are* errors, we can collect them using
[Rank2.foldMap](http://hackage.haskell.org/package/rank2classes/docs/Rank2.html#v:foldMap):

~~~ {.haskell}
verificationErrors :: PersonWithErrors -> [String]
verificationErrors = Rank2.foldMap (either (:[]) (const []))
~~~

Here is an example GHCi session:

~~~ {.haskell}
-- |
-- >>> :{
--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](https://hackage.haskell.org/package/hkd-lens),
[barbies](https://hackage.haskell.org/package/barbies), and [higgledy](https://hackage.haskell.org/package/higgledy).

Grammars are another use case that is almost, but not quite, entirely unlike database records. See
[grammatical-parsers](https://github.com/blamario/grampa/tree/master/grammatical-parsers) or
[construct](https://hackage.haskell.org/package/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](https://hackage.haskell.org/package/deep-transformations) instead.