hkd-lens: Generic lens/prism/traversal-kinded data.

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]

This library uses GHC Generics to generate lenses, prisms, and traversals for higher-kinded data types.


[Skip to Readme]

Properties

Versions 0.0.1, 0.0.1
Change log CHANGELOG.md
Dependencies base (>=4.12.0.0 && <4.13), profunctors [details]
License BSD-3-Clause
Copyright Trevor Cook
Author Trevor Cook
Maintainer trevor.j.cook@gmail.com
Category Data
Home page https://github.com/trevorcook/hkd-lens
Source repo this: git clone git://github.com/trevorcook/hkd-lens.git(tag 0.0.1)
Uploaded by trevorcook at 2019-06-04T02:38:01Z

Modules

[Index] [Quick Jump]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees


Readme for hkd-lens-0.0.1

[back to package description]

hkd-lens

A library for creating traversals for higher kinded data (HKD) following the method detailed by Sandy Maguire (http://reasonablypolymorphic.com/blog/higher-kinded-data). It expands on the methodology given there by including data with multiple constructors and by allowing type-changing traversals, Traverse s t a b.

This library currently supplies lenses, prisms, and traversals. However, the methodology only allows traversals which target a single specific location in a data structure. This is an inherent feature of the method and will not change. Consult the package "generic-lens" for generic ways of targeting multiple locations. Consult also "generic-lens" for also providing everything else in this package.

Quick Start

{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE DeriveGeneric  #-}
{-# LANGUAGE DataKinds  #-}
{-# LANGUAGE KindSignatures  #-}
{-# LANGUAGE TypeFamilies  #-}
{-# LANGUAGE UndecidableInstances  #-}
{-# LANGUAGE PolyKinds #-}

module Test where

import Generics.OneLiner --package one-liner
import Control.Lens      --package lens, used here for operators, e.g. (^.)
import HKD.Lens
import GHC.TypeLits
import GHC.Generics(Generic)

First, we define a higher kinded data. Its a data wherein every field is wrapped in some control constructof f. The selection of f controls how the data is expressed.

type Character = Character' Z
data Character' f a = Character { name :: HK f String
                                , role :: HK f a }
                    deriving Generic
data Protagonist = Hero | Sidekick deriving Show
data Antagonist = Villian | Henchman deriving Show
deriving instance (Constraints (Character' f a) Show)  --provided by one-liner
  => Show (Character' f a)

This HKD is built not only with a control parameter, but with a type family, HK, which allows reversion to a lower, or base type, for the specially defined data Z.

data Z a
type family HK (f :: ( * -> * ) ) a where
  HK Z a = a
  HK f a = f a

A lens is made via the LensesOf type family to direct exactly what lenses will be made (this includes a Nat specifying the index of the control parameter), and the makeLensesOf function which supplies a Lens Kinded Data.

lensesForCharacters :: LensesOf (Character a) (Character b) 1
lensesForCharacters = makeLensesOf

What is a lens kinded data? Well, thats the original data parameterized by a f = LensOf type (exported from HKD.Lens). So, at each data field is a lens from the whole data to that field.

For instance, the "role" lens is retrieved using the role field and unwrapping the LensOf data to reveal the lens.

roleLens :: Lens (Character a) (Character b) a b
roleLens = getLensOf $ role lensesForCharacters

Similarly, the name field reveals a lens targeting the name field of the base kinded Character a. Note that this lens does not involve a change in type parameters.

nameLens :: Lens (Character a) (Character a) String String
nameLens = getLensOf $ name lensesForCharacters

Here's an application of the role lens. It is used to turn "Villians" into "Heroes"; specifically the evil henchman "Number One" changes his ways.

redemption :: Antagonist -> Protagonist
redemption Villian = Hero
redemption Henchman = Sidekick

evilNumberOne :: Character Antagonist
evilNumberOne = Character "Number One" Henchman
goodNumberOne = evilNumberOne & roleLens %~ redemption
-- goodNumberOne = Character {name = "Number One", role = Sidekick}


To showcase traversals, a Scene data type is created.

type Scene = Scene' Z
data Scene' f a b = Meeting { inAttendence :: HK f [a]
                            , meetingPlace :: HK f Place }
                  | Confrontation { attacker :: HK f [a]
                                  , attackee :: HK f [b]
                                  , confrontationPlace :: HK f Place}
                deriving Generic
data Place = ARoom | TheMountainTop deriving Show
deriving instance (Constraints (Scene' f a b) Show) => Show (Scene' f a b)

Here the Traversal-kinded data for the Meeting constructor is made.

meetingTraversals :: TraversalsOf (Scene a b) (Scene a b) 1
meetingTraversals = makeTraversalsOf @"Meeting"

A specific inAttendence traversal is called out. Note that since the type variable a is used in more than one location, we cannot change it's type.

meetingAttendeeTraversal :: Traversal (Scene a b) (Scene a b) [a] [a]
meetingAttendeeTraversal = getTraversalOf $ inAttendence meetingTraversals

someoneWalksIn :: a -> Scene a b -> Scene a b
someoneWalksIn a = meetingAttendeeTraversal %~ (a:)

However, we could create a traversal that changes the type of b.

confrontationTraversals :: TraversalsOf (Scene a b) (Scene a b') 1
confrontationTraversals = makeTraversalsOf @"Confrontation"

We change a scene of good and evil characters to a scene of evil and evil characters through the use of a Mind Control traversal.

evilMindControl :: Protagonist -> Antagonist
evilMindControl _ = Henchman

useMindControlGun :: Scene (Character Antagonist) (Character Protagonist)
                  -> Scene (Character Antagonist) (Character Antagonist)
useMindControlGun = getTraversalOf (attackee confrontationTraversals)
                  . mapped . roleLens
                  %~ evilMindControl

poorNumberOneTrappedInARoom
  :: Scene (Character Antagonist) (Character Protagonist)
poorNumberOneTrappedInARoom = Confrontation [] [goodNumberOne] ARoom

numberOneReadyForEvilOnceAgain
  :: Scene (Character Antagonist) (Character Antagonist)
numberOneReadyForEvilOnceAgain = useMindControlGun poorNumberOneTrappedInARoom
-- Confrontation [] [Character "Number One" Henchman}] ARoom


Ok, enough of the Hero business, the library also supplies Prisms.

type AB = AB' Z
data AB' f a b = A {getA::(HK f a)} | B (HK f b) deriving Generic
deriving instance (Constraints (AB' f a b) Show) => Show (AB' f a b)
aPrism :: PrismsOf (AB a b) (AB c d) 1
aPrism = makePrismsOf @"A"

its1 = (A 1 :: AB Int ()) ^? getPrismOf (getA aPrism)


Finally, lenses/prisms/traversals may also be provided for types whose fields match their type parameters. These are the most fundamental/simplest types. This is accomplished by signaling there is no HKD parameter with a 0 for the Nat which targets the HKD parameter.

_1 :: Lens (a,b) (c,b) a c
_1 = getLensOf . fst $ (makeLensesOf :: LensesOf (a,b) (c,d) 0)