optics-core-0.4: Optics as an abstract interface: core definitions
Safe HaskellNone
LanguageHaskell2010

Optics.Generic

Description

This module provides, for data types having a Generic instance, a way to focus on:

  • their named total fields via gfield,
  • their named partial fields via gafield,
  • their constructors via gconstructor,
  • their fields at a specific position via gposition,
  • their fields of a specific type via gplate.

Note: gfield and gconstructor are supported by labelOptic and can be used with a consise syntax via OverloadedLabels.

If you're looking for optics for working with a generic representation of a data type, there's GHC.Generics.Optics.

Synopsis

Fields

class GField (name :: Symbol) s t a b | name s -> t a b, name t -> s a b where Source #

Focus on a field name of type a within a type s using its Generic instance.

>>> :{
data User a
  = User { name :: String
         , age  :: a
         }
  | LazyUser { name :: String
             , age  :: a
             , lazy :: Bool
             }
  deriving (Show, Generic)
:}
>>> let user = User "Tom" 32 :: User Int
>>> user ^. gfield @"name"
"Tom"
>>> user ^. gfield @"age"
32
>>> user ^. gfield @"salary"
...
...Data constructor ‘User’ doesn't have a field named ‘salary’
...In the...
...

Only total fields are accessible (for partial ones see gafield):

>>> user ^. gfield @"lazy"
...
...Data constructor ‘User’ doesn't have a field named ‘lazy’
...In the...
...

Type changing updates are supported:

>>> user & gfield @"age" .~ ()
User {name = "Tom", age = ()}

Types without a Generic instance are not supported:

>>> NoG 'x' ^. gfield @"any"
...
...Type ‘NoG’ doesn't have a Generic instance
...In the...
...

Note: gfield is supported by labelOptic and can be used with a concise syntax via OverloadedLabels.

>>> user ^. #name
"Tom"
>>> user & #age %~ (+1)
User {name = "Tom", age = 33}

Since: 0.4

Methods

gfield :: Lens s t a b Source #

Instances

Instances details
GFieldContext name s t a b => GField name s t a b Source # 
Instance details

Defined in Optics.Generic

Methods

gfield :: Lens s t a b Source #

class GAffineField (name :: Symbol) s t a b | name s -> t a b, name t -> s a b where Source #

Focus on a possibly partial field name of type a within a type s using its Generic instance.

>>> :{
data Fish = Herring { name :: String }
          | Tuna    { name :: String, sleeping :: Bool }
  deriving Generic
:}
>>> let herring = Herring { name = "Henry" }
>>> let tuna    = Tuna { name = "Tony", sleeping = True }
>>> herring ^? gafield @"name"
Just "Henry"
>>> herring ^? gafield @"sleeping"
Nothing
>>> tuna ^? gafield @"sleeping"
Just True

Types without a Generic instance are not supported:

>>> NoG 'x' ^? gafield @"any"
...
...Type ‘NoG’ doesn't have a Generic instance
...In the...
...

Note: trying to access a field that doesn't exist in any data constructor results in an error:

>>> tuna ^? gafield @"salary"
...
...Type ‘Fish’ doesn't have a field named ‘salary’
...In the...
...

Since: 0.4

Methods

gafield :: AffineTraversal s t a b Source #

Instances

Instances details
GAFieldContext repDefined name s t a b => GAffineField name s t a b Source # 
Instance details

Defined in Optics.Generic

Methods

gafield :: AffineTraversal s t a b Source #

Positions

class GPosition (n :: Nat) s t a b | n s -> t a b, n t -> s a b where Source #

Focus on a field at position n of type a within a type s using its Generic instance.

>>> ('a', 'b', 'c') ^. gposition @2
'b'
>>> ('a', 'b') & gposition @1 .~ "hi" & gposition @2 .~ "there"
("hi","there")
>>> ('a', 'b', 'c') ^. gposition @4
...
...Data constructor ‘(,,)’ has 3 fields, 4th requested
...In the...
...
>>> () ^. gposition @1
...
...Data constructor ‘()’ has no fields, 1st requested
...In the...
...

Types without a Generic instance are not supported:

>>> NoG 'x' ^. gposition @1
...
...Type ‘NoG’ doesn't have a Generic instance
...In the...
...

Note: Positions start from 1:

>>> ('a', 'b') ^. gposition @0
...
...There is no 0th position
...In the...
...

Since: 0.4

Methods

gposition :: Lens s t a b Source #

Instances

Instances details
GPositionContext repDefined n s t a b => GPosition n s t a b Source # 
Instance details

Defined in Optics.Generic

Methods

gposition :: Lens s t a b Source #

Constructors

class GConstructor (name :: Symbol) s t a b | name s -> t a b, name t -> s a b where Source #

Focus on a constructor name of a type s using its Generic instance.

>>> :{
data Animal = Dog { name :: String, age :: Int }
            | Cat { name :: String, purrs :: Bool }
  deriving (Show, Generic)
:}
>>> let dog = Dog "Sparky" 2
>>> let cat = Cat "Cuddly" True
>>> dog ^? gconstructor @"Dog"
Just ("Sparky",2)
>>> dog ^? gconstructor @"Cat"
Nothing
>>> cat & gconstructor @"Cat" % _2 %~ not
Cat {name = "Cuddly", purrs = False}
>>> dog & gconstructor @"Cat" % _1 .~ "Merry"
Dog {name = "Sparky", age = 2}
>>> cat ^? gconstructor @"Parrot"
...
...Type ‘Animal’ doesn't have a constructor named ‘Parrot’
...In the...
...

Types without a Generic instance are not supported:

>>> NoG 'x' ^. gconstructor @"NoG"
...
...Type ‘NoG’ doesn't have a Generic instance
...In the...
...

Note: gconstructor is supported by labelOptic and can be used with a concise syntax via OverloadedLabels.

>>> dog ^? #_Dog
Just ("Sparky",2)
>>> cat & #_Cat % _1 .~ "Merry"
Cat {name = "Merry", purrs = True}

Since: 0.4

Methods

gconstructor :: Prism s t a b Source #

Instances

Instances details
GConstructorContext repDefined name s t a b => GConstructor name s t a b Source # 
Instance details

Defined in Optics.Generic

Methods

gconstructor :: Prism s t a b Source #

Types

class GPlate a s where Source #

Traverse occurrences of a type a within a type s using its Generic instance.

>>> toListOf (gplate @Char) ('h', ((), 'e', Just 'l'), "lo")
"hello"

If a occurs recursively in its own definition, only outermost occurrences of a within s will be traversed:

>>> toListOf (gplate @String) ("one","two")
["one","two"]

Note: types without a Generic instance in scope when GPlate class constraint is resolved will not be entered during the traversal.

>>> let noG = (NoG 'n', (Just 'i', "c"), 'e')
>>> toListOf (gplate @Char) noG
"ice"
>>> deriving instance Generic NoG
>>> toListOf (gplate @Char) noG
"nice"

Since: 0.4

Methods

gplate :: Traversal' s a Source #

Instances

Instances details
GPlateContext a s => GPlate a s Source # 
Instance details

Defined in Optics.Generic

Methods

gplate :: Traversal' s a Source #