miso-1.9.0.0: A tasty Haskell front-end web framework

Copyright(C) 2016-2025 David M. Johnson
LicenseBSD3-style (see the file LICENSE)
MaintainerDavid M. Johnson <code@dmj.io>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellSafe
LanguageHaskell2010

Miso.Lens

Contents

Description

This modules exposes a very simple Lens formulation that is compatible with other lens libraries.

For state management of miso applications, this module should meet all of your needs. It also ensures a smaller payload size during compilation.

data Lens record field
 = Lens
 { _get :: record -> field
 , _set :: record -> field -> record
 }

The goal is to provide users with an out-of-the box lens experience without the large dependency footprint and cognitive load. This module also aims to preserve semantics of existing lens combinators using a simple formulation (not the Van Laarhoven). It must be imported separately (import Miso.Lens) and can be used with the Effect Monad inside of a miso application (as described below).

This module is at fixity and interface parity with lens and microlens and can therefore be used interchangeably with them. Simply replace the Miso.Lens import with Control.Lens. For convenience we re-export the Lens' synonym to ease the transition into lens or microlens.

For the curious reader, if you'd like more information on lens and the Van Laarhoven formulation, we recommend the lens library https://hackage.haskell.org/package/lens.

-- Person type
data Person = Person
  { _name :: String
  , _address :: Address
  , _age  :: Int
  } deriving (Show, Eq, Generic)
-- Address type
newtype Address
  = Address
  { _zipCode :: Zip
  } deriving (Show, Eq)
-- | Zip code type synonym
type Zip = String
-- | Name Lens
name :: Lens Person String
name = lens _name $ \record x -> record { _name = x }
-- | Address Lens
address :: Lens Person Address
address = lens _address $ \record x -> record { _address = x }
-- | Zip Code Lens
zipCode :: Lens Address Zip
zipCode = lens _zipCode $ \record x -> record { _zipCode = x }
-- | Lens Composition example
personZip :: Lens Person Zip
personZip = zipCode . address
-- | Person example
person :: Person
person = Person "john" (Address "90210") 33
main :: IO ()
main = print $ john '&' address '.~' Address "10012"
Person
 { _name = "john"
 , _age = 33
 , _address = Address {_zipCode = "10012"}
 }

Example usage with miso's Effect Monad

newtype Model = Model { _value :: Int }
value :: Lens Model Int
value = lens _value $ \model v -> model { _value = v }
data Action = AddOne | SubtractOne
updateModel :: Action -> Effect Model Action ()
updateModel AddOne      = value += 1
updateModel SubtractOne = value -= 1
Synopsis

Types

data Lens record field Source #

A Lens is a generalized getter and setter.

Lenses allow both the retrieval of values from fields in a record and the assignment of values to fields in a record. The power of a Lens comes from its ability to be composed with other lenses.

In the context of building applications with miso, the model is often a deeply nested product type. This makes it highly conducive to Lens operations (as defined below).

Constructors

Lens 

Fields

  • _get :: record -> field

    Retrieves a field from a record

  • _set :: record -> field -> record

    Sets a field on a record

Instances
Category Lens Source #

Lens are Categories, and can therefore be composed.

Instance details

Defined in Miso.Lens

Methods

id :: Lens a a Source #

(.) :: Lens b c -> Lens a b -> Lens a c Source #

type Lens' record field = Lens record field Source #

Type synonym re-export for lens / microlens compatability. Note: use this if you plan on migrating to lens or microlens eventually. Just use Lens otherwise (as examples show).

Smart constructor

lens :: (record -> field) -> (record -> field -> record) -> Lens record field Source #

Smart constructor lens function. Used to easily construct a Lens

name :: Lens Person String
name = lens _name $ \p n -> p { _name = n }

Utils

(<&>) :: Functor f => f a -> (a -> b) -> f b infixl 1 Source #

Functor utility, a flipped infix fmap.

Re-exports

(&) :: a -> (a -> b) -> b infixl 1 Source #

& is a reverse application operator. This provides notational convenience. Its precedence is one higher than that of the forward application operator $, which allows & to be nested in $.

>>> 5 & (+1) & show
"6"

Since: base-4.8.0.0

Combinators

(.~) :: Lens record field -> field -> record -> record infixr 4 Source #

Set a field on a record

newtype Person = Person { _name :: String }
name :: Lens Person String
name = lens _name $ \person n -> person { _name = n }
setName :: Person -> String -> Person
setName person newName = person & name .~ newName

(?~) :: Lens record (Maybe field) -> field -> record -> record infixr 4 Source #

Set an options field on a record

newtype Person = Person { _name :: Maybe String }
name :: Lens Person (Maybe String)
name = lens _name $ \person n -> person { _name = n }
setName :: Person -> String -> Person
setName person newName = person & name ?~ newName

set :: Lens record field -> field -> record -> record Source #

Synonym for (.~)

(%~) :: Lens record field -> (field -> field) -> record -> record infixr 4 Source #

Modify a field on a record

\x -> record & field %~ f x

over :: Lens record field -> (field -> field) -> record -> record Source #

Synonym for (%~)

(^.) :: record -> Lens record field -> field infixl 8 Source #

Read a field from a record using a Lens

newtype Person = Person { _name :: String }
  deriving (Show, Eq)
name :: Lens Person String
name = lens _name $ \person n -> person { _name = n }
getName :: Person -> String
getName = person ^. name

(+~) :: Num field => Lens record field -> field -> record -> record infixr 4 Source #

Increment a Numeric field on a record using a Lens

newtype Person = Person { _age :: Int }
age :: Lens Person Int
age = lens _age $ \person a -> person { _age = a }
birthday :: Person -> Person
birthday person = person & age +~ 1

(*~) :: Num field => Lens record field -> field -> record -> record infixr 4 Source #

Multiply a Numeric field on a record using a Lens

newtype Circle = Circle { _radius :: Int }
radius :: Lens Circle Int
radius = lens _radius $ \circle r -> circle { _radius = r }
expand :: Circle -> Circle
expand circle = circle & radius *~ 10

(//~) :: Fractional field => Lens record field -> field -> record -> record infixr 4 Source #

Divide a Fractional field on a record using a Lens

newtype Circle = Circle { _radius :: Int }
radius :: Lens Circle Int
radius = lens _radius $ \circle r -> circle { _radius = r }
expand :: Circle -> Circle
expand circle = circle & radius *~ 10

(-~) :: Num field => Lens record field -> field -> record -> record infixr 4 Source #

Increment a Numeric field on a record using a Lens

newtype Person = Person { _age :: Int }
age :: Lens Person Int
age = lens _age $ \person a -> person { _age = a }
timeTravel :: Person -> Person
timeTravel person = person & age -~ 1

(%=) :: MonadState record m => Lens record field -> (field -> field) -> m () infix 4 Source #

Modify a record in MonadState monad at a field using a Lens

newtype Model = Model { _value :: Int }
data Action = AddOne | SubtractOne
value :: Lens Model Int
value = lens _value $ \p x -> p { _value = x }
update :: Action -> Effect Model Action ()
update AddOne = do
  value %= (+1)

modifying :: MonadState record m => Lens record field -> (field -> field) -> m () Source #

Synonym for (%=)

(+=) :: (MonadState record m, Num field) => Lens record field -> field -> m () infix 4 Source #

Increments the value of a Numeric field of a record using a Lens inside a State Monad.

newtype Model = Model { _value :: Int }
  deriving (Show, Eq)
data Action = IncrementBy Int
value :: Lens Model Int
value = lens _value $ \p x -> p { _value = x }
update :: Action -> Effect Model Action ()
update (IncrementBy x) = value += x

(*=) :: (MonadState record m, Num field) => Lens record field -> field -> m () infix 4 Source #

Multiplies the value of a Numeric field of a record using a Lens inside a State Monad.

newtype Model = Model { _value :: Int }
  deriving (Show, Eq)
data Action = MultiplyBy Int
value :: Lens Model Int
value = lens _value $ \p x -> p { _value = x }
update :: Action -> Effect Model Action ()
update (MultiplyBy x) = value *= x

(//=) :: (MonadState record m, Fractional field) => Lens record field -> field -> m () infix 4 Source #

Divides the value of a Fractional field of a record using a Lens inside a State Monad.

newtype Model = Model { _value :: Double }
  deriving (Show, Eq)
data Action = DivideBy Double
value :: Lens Model Double
value = lens _value $ \p x -> p { _value = x }
update :: Action -> Effect Model Action ()
update (DivideBy x) = value //= x

(-=) :: (MonadState record m, Num field) => Lens record field -> field -> m () infix 4 Source #

Subtracts the value of a Numeric field of a record using a Lens inside of a State Monad.

newtype Model = Model { _value :: Double }
  deriving (Show, Eq)
data Action = SubtractBy Double
value :: Lens Model Double
value = lens _value $ \p x -> p { _value = x }
update :: Action -> Effect Model Action ()
update (SubtractBy x) = value -= x

(.=) :: MonadState record m => Lens record field -> field -> m () infix 4 Source #

Sets the value of a field in a record using MonadState and a Lens

import Miso.String (ms)
newtype Model = Model { _value :: Int }
  deriving (Show, Eq)
data Action = SetValue Int
value :: Lens Model Int
value = lens _value $ \p x -> p { _value = x }
update' :: Action -> Effect Model Action ()
update' (SetValue v) = value .= v

(<~) :: MonadState record m => Lens record field -> m field -> m () infixr 2 Source #

Execute a monadic action in MonadState that returns a field. Sets the return value equal to the field in the record.

newtype List = List { _values :: [Int] }
values :: Lens List [Int]
values = lens _values $ \l vs -> l { _values = vs }

addElement :: List -> List
addElement list = list & values <>~ [2]

(<%=) :: MonadState record m => Lens record field -> (field -> field) -> m field infix 4 Source #

Modify the field of a record in MonadState using a Lens, then return the newly modified field from the updated record.

import Miso.String (ms)
newtype Model = Model { _value :: Int }
  deriving (Show)
data Action = AddOne
value :: Lens Model Int
value = lens _value $ \p x -> p { _value = x }
update :: Action -> Effect Model Action ()
update AddOne = do
  result <- value <%= (+1)
  io $ consoleLog (ms result)

(<.=) :: MonadState record m => Lens record field -> field -> m field infix 4 Source #

Assign the field of a record in MonadState to a value using a Lens Return the value after assignment.

import Miso.String (ms)
newtype Model = Model { _value :: Int }
data Action = Assign Int
value :: Lens Model Int
value = lens _value $ \p x -> p { _value = x }
update :: Action -> Effect Model Action ()
update (Assign x) = do
  result <- value <.= x
  io $ consoleLog (ms result) -- x

(<?=) :: MonadState record m => Lens record (Maybe field) -> field -> m field infix 4 Source #

Assign the field of a record in a MonadState to a value (wrapped in a Just) using a Lens. Return the value after assignment.

import Miso.String (ms)
newtype Model = Model { _value :: Maybe Int }
data Action = SetValue Int
value :: Lens Model (Maybe Int)
value = lens _value $ \p x -> p { _value = x }
update :: Action -> Effect Model Action ()
update (SetValue x) = do
  result <- value <?= x
  io $ consoleLog (ms result) -- Just 1

(<<.=) :: MonadState record m => Lens record field -> field -> m field infix 4 Source #

Assign the field of a record in a MonadState to a value using a Lens. Returns the previous value, before assignment.

import Miso.String (ms)
newtype Model = Model { _value :: Int }
  deriving (Show, Eq)
data Action = Assign Int
  deriving (Show, Eq)
value :: Lens Model Int
value = lens _value $ \p x -> p { _value = x }
update :: Action -> Effect Model Action ()
update (Assign x) = do
  value .= x
  previousValue <- value <<.= 1
  io $ consoleLog $ ms (show previousValue) -- prints value at x

(<<%=) :: MonadState record m => Lens record field -> (field -> field) -> m field infix 4 Source #

Modifies the field of a record in MonadState using a Lens. Returns the previous value, before modification.

import Miso.String (ms)
newtype Model = Model { _value :: Int }
  deriving (Show, Eq)
data Action = Modify (Int -> Int)
value :: Lens Model Int
value = lens _value $ \p x -> p { _value = x }
update :: Action -> Effect Model Action ()
update (Modify f) = do
  value .= 2
  result <- value <<%= f
  io $ consoleLog (ms (show result)) -- prints previous value of 2

assign :: MonadState record m => Lens record field -> field -> m () Source #

Synonym for (.=)

use :: MonadState record m => Lens record field -> m field Source #

Retrieves the value of a field in a record using a Lens inside MonadState

import Miso.String (ms)
newtype Model = Model { _value :: Int }
  deriving (Show, Eq)
data Action = SetValue Int
value :: Lens Model Int
value = lens _value $ \p x -> p { _value = x }
update :: Action -> Effect Model Action ()
update (SetValue x) = do
  value .= x
  result <- use value
  io $ consoleLog (ms (show result)) -- prints the value of 'x'

(?=) :: MonadState record m => Lens record (Maybe field) -> field -> m () infix 4 Source #

Sets the value of a field in a record using a Lens inside a MonadState The value is wrapped in a Just before being assigned.

newtype Model = Model { _value :: Maybe Int }
  deriving (Show, Eq)
data Action = AssignValue Int
value :: Lens Model (Maybe Int)
value = lens _value $ \p x -> p { _value = x }
update :: Action -> Effect Model Action ()
update (AssignValue x) = value ?= x

(<>~) :: Monoid field => Lens record field -> field -> record -> record infixr 4 Source #

Monoidally append a field in a record using a Lens

newtype List = List { _values :: [Int] }
values :: Lens List [Int]
values = lens _values $ \l vs -> l { _values = vs }
addElement :: List -> List
addElement list = list & values <>~ [2]
addElement (List [])
-- List [2]