barlow-lens: lens via string literals

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:

Please see the README on GitHub at https://github.com/value/barlow-lens#readme


[Skip to Readme]

Properties

Versions 0.1.0.0, 0.1.0.0, 0.1.0.1, 0.1.0.2
Change log CHANGELOG.md
Dependencies base (>=4.7 && <5), first-class-families, generic-lens, lens, profunctors [details]
License BSD-3-Clause
Copyright Danila Danko
Author Danila Danko,
Maintainer Danila Danko
Category Generics, Records, Lens
Home page https://github.com/deemp/barlow-lens#readme
Bug tracker https://github.com/deemp/barlow-lens/issues
Source repo head: git clone https://github.com/deemp/barlow-lens
Uploaded by deemp at 2023-08-31T09:58:45Z

Modules

[Index] [Quick Jump]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees


Readme for barlow-lens-0.1.0.0

[back to package description]

barlow-lens

Barlow lens increases your magnification and let's you see the stars sparkles

In other words, barlow lens makes creating complex lenses such as record lenses super simple.

This package is a port of purescript-barlow-lens based on generic-lens.

tl;dr

{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE DuplicateRecordFields #-}
import Control.Lens ((%~), (&), (^.), (^..), (^?))
import Data.Char (toUpper)
import Data.Lens.Barlow
import GHC.Generics

Features

Barlow creates optics for the following types:

Records

zodiac ~ field @"zodiac"

data AlphaRecord = AlphaRecord {alpha :: String} deriving (Generic, Show)
data VirgoRecord = VirgoRecord {virgo :: AlphaRecord} deriving (Generic, Show)
data ZodiacRecord = ZodiacRecord {zodiac :: VirgoRecord} deriving (Generic, Show)

sky :: ZodiacRecord
sky = ZodiacRecord{zodiac = VirgoRecord{virgo = AlphaRecord{alpha = "Spica"}}}

spica :: String
spica = sky ^. (bw @"zodiac.virgo.alpha")

-- >>> spica
-- "Spica"

-- >>> alfa = sky ^. barlow @"zodiac.virgo.alfa"
-- The type AlphaRecord does not contain a field named 'alfa'.
-- In the second argument of `(^.)', namely
--   `barlow @"zodiac.virgo.alfa"'
-- In the expression: sky ^. barlow @"zodiac.virgo.alfa"
-- In an equation for `alfa':
--     alfa = sky ^. barlow @"zodiac.virgo.alfa"

Maybe

Use ? to zoom into a Maybe.

newtype AlphaMaybe = AlphaMaybe {alpha :: Maybe String} deriving (Generic, Show)
newtype VirgoMaybe = VirgoMaybe {virgo :: Maybe AlphaMaybe} deriving (Generic, Show)
newtype ZodiacMaybe = ZodiacMaybe {zodiac :: Maybe VirgoMaybe} deriving (Generic, Show)

skyMaybe :: ZodiacMaybe
skyMaybe = ZodiacMaybe{zodiac = Just VirgoMaybe{virgo = Just AlphaMaybe{alpha = Just "Spica"}}}

spicaMaybe :: Maybe String
spicaMaybe = skyMaybe ^? bw @"zodiac?.virgo?.alpha?"

-- >>> spicaMaybe
-- Just "Spica"

Either

Use < for Left and > for Right to zoom into an Either.

newtype AlphaLeft = AlphaLeft {alpha :: Either String ()} deriving (Generic, Show)
newtype VirgoRight = VirgoRight {virgo :: Either () AlphaLeft} deriving (Generic, Show)
newtype ZodiacEither = ZodiacEither {zodiac :: Either VirgoRight VirgoRight} deriving (Generic, Show)

skyLeft :: ZodiacEither
skyLeft = ZodiacEither{zodiac = Left VirgoRight{virgo = Right AlphaLeft{alpha = Left "Spica"}}}

starLeftRightLeft :: Maybe String
starLeftRightLeft = skyLeft ^? bw @"zodiac<virgo>alpha<"

-- >>> starLeftRightLeft
-- Just "Spica"

starLeftLeft :: Maybe VirgoRight
starLeftLeft = skyLeft ^? bw @"zodiac>"

-- >>> starLeftLeft
-- Nothing

Traversables

Use + to zoom into Traversables.

newtype AlphaLeftRight = AlphaLeftRight {alpha :: Either String String} deriving (Generic, Show)
newtype VirgoLeftRight = VirgoLeftRight {virgo :: Either AlphaLeftRight AlphaLeftRight} deriving (Generic, Show)
newtype ZodiacList = ZodiacList {zodiac :: [VirgoLeftRight]} deriving (Generic, Show)

skyList :: ZodiacList
skyList =
  ZodiacList
    { zodiac =
        [ VirgoLeftRight{virgo = Right AlphaLeftRight{alpha = Left "Spica1"}}
        , VirgoLeftRight{virgo = Right AlphaLeftRight{alpha = Right "Spica2"}}
        , VirgoLeftRight{virgo = Left AlphaLeftRight{alpha = Right "Spica3"}}
        , VirgoLeftRight{virgo = Left AlphaLeftRight{alpha = Left "Spica4"}}
        ]
    }

starList :: [String]
starList = skyList ^.. bw @"zodiac+virgo>alpha>" & bw @"++" %~ toUpper

-- >>> starList
-- ["SPICA2"]

alphaRight :: [AlphaLeftRight]
alphaRight = skyList ^.. bw @"zodiac+virgo>"

-- >>> alphaRight
-- [AlphaLeftRight {alpha = Left "Spica1"},AlphaLeftRight {alpha = Right "Spica2"}]

Newtype

Use ! to zoom into a newtype.

newtype AlphaNewtype = AlphaNewtype {alpha :: String} deriving (Generic)
newtype VirgoNewtype = VirgoNewtype {virgo :: AlphaNewtype} deriving (Generic)
newtype ZodiacNewtype = ZodiacNewtype {zodiac :: VirgoNewtype} deriving (Generic)

skyNewtype :: ZodiacNewtype
skyNewtype = ZodiacNewtype (VirgoNewtype (AlphaNewtype "Spica"))

starNewtype :: [Char]
starNewtype = skyNewtype ^. bw @"zodiac!!"

-- >>> starNewtype
-- "Spica"

Data types

Barlow supports zooming into arbitrary sum and product types as long as there is a Generic instance.

Use %<NAME> to zoom into sum types, where <NAME> is the name of your data constructor. E.g. %VirgoData for the data constructor VirgoData.

Use %<INDEX> to zoom into product types, where <INDEX> is a natural number. Note that counting for product types and tuples usually starts with 1 and not 0. So the first element of a product is %1.

It is more readable if you separate your sum lens from your product lens with a . dot.

data ZodiacData
  = CarinaData {alpha :: String}
  | VirgoData {alpha :: String, beta :: String, gamma :: String, delta :: String}
  | CanisMaiorData String
  deriving (Generic)

skyData :: ZodiacData
skyData = VirgoData{alpha = "Spica", beta = "Beta Vir", gamma = "Gamma Vir", delta = "Del Vir"}

starData :: [Char]
starData = skyData ^. bw @"%VirgoData%3"

-- >>> starData
-- "Gamma Vir"

Prerequisites

Spoiler

Quick start

  1. Install Nix - see how.

  2. In a new terminal, start a devshell, build and test the app.

    nix develop
    cabal build
    cabal test
    
  3. Write settings.json and start VSCodium.

    nix run .#writeSettings
    nix run .#codium .
    
  4. Open a Haskell file app/Main.hs and hover over a function.

  5. Wait until Haskell Language Server (HLS) starts giving you type info.

  6. Sometimes, cabal doesn't use the Nix-supplied packages (issue). In this case, use cabal v1-* - commands.

Configs