linear-base-0.3.0: Standard library for linear types.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Control.Optics.Linear.Traversal

Description

This module provides linear traversals.

Traversals provides a means of accessing several as organized in some structural way in an s, and a means of changing them to bs to create a t. In very ordinary language, it's like walking or traversing the data structure, going across cases and inside definitions. In more imaginative language, it's like selecting some specific as by looking at each constructor of a data definition and recursing on each non-basic type (where basic types are things like Int, Bool or Char).

Example

{-# LANGUAGE LinearTypes #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE GADTs #-}

import Control.Optics.Linear.Internal
import qualified Control.Functor.Linear as Control
import Control.Functor.Linear (($), (*), pure)
import Prelude.Linear

-- We can use a traversal to append a string only to the
-- human names in a classroom struct
appendToNames :: String -> Classroom %1-> Classroom
appendToNames s = over classroomNamesTrav (name -> name ++ s)

data Classroom where
  Classroom ::
    { className :: String
    , teacherName :: String
    , classNum :: Int
    , students :: [Student]
    , textbooks :: [String]
    } %1-> Classroom

-- A Student is a name and a student id number
data Student = Student String Int

classroomNamesTrav :: Traversal' Classroom String
classroomNamesTrav = traversal traverseClassStr where
  traverseClassStr :: forall f. Control.Applicative f =>
    (String %1-> f String) -> Classroom %1-> f Classroom
  traverseClassStr onName (Classroom cname teachname x students texts) =
    Classroom $
    pure cname *
    onName teachname *
    pure x *
    traverse' ((Student s i) -> Student $ onName s * pure i) students *
    pure texts
Synopsis

Types

type Traversal s t a b = Optic Wandering s t a b Source #

type Traversal' s a = Traversal s s a a Source #

Composing optics

(.>) :: Optic_ arr s t a b -> Optic_ arr a b x y -> Optic_ arr s t x y infixr 9 Source #

Common optics

traversed :: Traversable t => Traversal (t a) (t b) a b Source #

Using optics

over :: Optic_ (FUN 'One) s t a b -> (a %1 -> b) -> s %1 -> t Source #

overU :: Optic_ (->) s t a b -> (a -> b) -> s -> t Source #

traverseOf :: Optic_ (Kleisli f) s t a b -> (a %1 -> f b) -> s %1 -> f t Source #

traverseOfU :: Optic_ (Kleisli f) s t a b -> (a -> f b) -> s -> f t Source #

Constructing optics

traversal :: (forall f. Applicative f => (a %1 -> f b) -> s %1 -> f t) -> Traversal s t a b Source #