Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
This module provides linear traversals.
Traversals provides a means of accessing several a
s organized in some
structural way in an s
, and a means of changing them to b
s 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 a
s 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
- type Traversal s t a b = Optic Wandering s t a b
- type Traversal' s a = Traversal s s a a
- (.>) :: Optic_ arr s t a b -> Optic_ arr a b x y -> Optic_ arr s t x y
- traversed :: Traversable t => Traversal (t a) (t b) a b
- over :: Optic_ LinearArrow s t a b -> (a %1 -> b) -> s %1 -> t
- overU :: Optic_ (->) s t a b -> (a -> b) -> s -> t
- traverseOf :: Optic_ (Kleisli f) s t a b -> (a %1 -> f b) -> s %1 -> f t
- traverseOfU :: Optic_ (Kleisli f) s t a b -> (a -> f b) -> s -> f t
- traversal :: (forall f. Applicative f => (a %1 -> f b) -> s %1 -> f t) -> Traversal s t a b
Types
type Traversal' s a = Traversal s s a a Source #
Composing optics
Common optics
traversed :: Traversable t => Traversal (t a) (t b) a b Source #
Using optics
over :: Optic_ LinearArrow s t a b -> (a %1 -> b) -> s %1 -> 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 #