generic-lens-0.1.0.0: Generic data-structure operations exposed as lenses.

Copyright(C) 2017 Csongor Kiss
LicenseBSD3
MaintainerCsongor Kiss <kiss.csongor.kiss@gmail.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellSafe
LanguageHaskell2010

Data.Generics.Record.Subtype

Description

Structural subtype relationship between record types.

The running example in this module is the following two types:

  module Test where

  import GHC.Generics
  import Data.Generics.Record

  data Human = Human
    { name    :: String
    , age     :: Int
    , address :: String
    } deriving (Generic, Show)

  data Animal = Animal
    { name    :: String
    , age     :: Int
    } deriving (Generic, Show)

   human :: Human
   human = Human "Tunyasz" 50 "London"

Synopsis

Documentation

class Subtype sub sup where Source #

Structural subtype relationship

sub is a (structural) subtype of sup, if its fields are a subset of those of sup.

Minimal complete definition

upcast, smash

Methods

upcast :: sub -> sup Source #

Cast the more specific subtype to the more general supertype

>>> upcast human :: Animal
Animal {name = "Tunyasz", age = 50}

smash :: sup -> sub -> sub Source #

Plug a smaller structure into a larger one

>>> smash (Animal "dog" 10) human
Human {name = "dog", age = 10, address = "London"}

Instances

(GSmash * (Rep a) (Rep b), GUpcast (Rep a) (Rep b), Generic a, Generic b) => Subtype a b Source #

Instances are created by the compiler

Methods

upcast :: a -> b Source #

smash :: b -> a -> a Source #

subtype :: forall sup sub. Subtype sub sup => Lens' sub sup Source #

Structural subtype lens. Given a subtype relationship sub :< sup, we can focus on the sub structure of sup.

>>> human ^. subtype @Animal
Animal {name = "Tunyasz", age = 50}
>>> set (subtype @Animal) (Animal "dog" 10) human
Human {name = "dog", age = 10, address = "London"}