putlenses-0.1.1: Put-based lens library

Stabilityprovisional
MaintainerHugo Pacheco <hpacheco@nii.ac.jp>
Safe HaskellNone

Generics.Putlenses.Putlens

Description

General framework for put-based lenses.

A well-behaved putlens is expected to satisfy two properties: GetPut: |Just v = get l s => s = runPutM (put (Just s) v) e st| PutGet: |s' = runPutM (put s v') e st => Just v' = get s'|

Synopsis

Documentation

newtype GetPut Source

Constructors

GetPut Bool 

newtype PutGet Source

Constructors

PutGet Bool 

Instances

data LensM m s v Source

Interface for normal lenses

Constructors

LensM 

Fields

get :: s -> v
 
put :: s -> v -> m s
 
create :: v -> m s
 

type Lens s v = LensM Identity s vSource

Interface for lenses without monadic effects

simpleput :: Lens s v -> s -> v -> sSource

Non-monadic put function

simplecreate :: Lens s v -> v -> sSource

Non-monadic create function

type PutM m a = ReaderT GetPut (WriterT PutGet m) aSource

Monad for put-based lenses includes an environment, state, and boolean tags that our system will use to ensure GetPut and PutGet

type Get s v = s -> Maybe vSource

type Put m s v = Maybe s -> v -> PutM m sSource

type Create m s v = v -> PutM m sSource

data PutlensM m s v Source

Framework for put-based lenses

Constructors

PutlensM 

Fields

getputM :: s -> (Maybe v, Create m s v)
 
createM :: Create m s v
 

type PutlensMaybeM m s v = PutlensM (MaybeT m) s vSource

type PutlensReaderM m e s v = PutlensM (ReaderT e m) s vSource

type PutlensStateM m st s v = PutlensM (StateT st m) s vSource

type Putlens s v = PutlensM Identity s vSource

mapPutM :: (forall a. m a -> n a) -> PutM m a -> PutM n aSource

Changes the resulting monad of a put computation

mapPutlensM :: Monad m => (forall a. m a -> n a) -> PutlensM m s v -> PutlensM n s vSource

Changes the resulting monad of a putlens

liftPutM :: Monad m => m s -> PutM m sSource

Lifts a function on a given monad to a put computation

liftPutlensM :: (MonadTrans t, Monad m) => PutlensM m s v -> PutlensM (t m) s vSource

Function lift applied to the monadic argument of a putlens

getM :: PutlensM m s v -> Get s vSource

Forward |get| function

dom :: PutlensM m s v -> s -> BoolSource

Domain of a putlens (the domains of its get function)

putM :: PutlensM m s v -> Put m s vSource

Backward |put| function

evalPutM :: Monad m => PutM m s -> GetPut -> m sSource

Runs a putlens for a particular environment

runPutM :: Monad m => PutM m s -> GetPut -> m (s, PutGet)Source

lens2put :: Monad m => LensM m s v -> PutlensM m s vSource

Converts a normal lens to a putlens (without explicit failure)

simplelens2put :: Monad m => Lens' s v -> PutlensM m s vSource

Converts a simple lens of the Haskell lens package into a putlens

put2lens :: Eq v => Putlens s v -> Lens s vSource

Converts a putlens to a normal lens, enforcing well-behavedness

put2quicklens :: Eq v => Putlens s v -> Lens s vSource

Converts a putlens to a normal lens but without enforcing PutGet (for unsafe casts)

put2quicklensNoGetPut :: Eq v => Putlens s v -> Lens s vSource

Converts a putlens to a normal lens, without enforcing GetPut

put2lensNoGetPut :: Eq v => Putlens s v -> Lens s vSource

Converts a putlens to a normal lens, without enforcing GetPut

put2lensM :: (Monad m, Eq v) => PutlensM m s v -> LensM m s vSource

Converts a monadic putlens to a monadic lens, enforcing well-behavedness

put2quicklensM :: (Monad m, Eq v) => PutlensM m s v -> LensM m s vSource

Converts a monadic putlens to a monadic lens but without enforcing PutGet (for unsafe casts)

put2lensNoGetPutM :: (Monad m, Eq v) => PutlensM m s v -> LensM m s vSource

Converts a monadic putlens to a monadic lens, without enforcing GetPut

put2quicklensNoGetPutM :: (Monad m, Eq v) => PutlensM m s v -> LensM m s vSource

Converts a monadic putlens to a monadic lens, without enforcing GetPut

put2lensM' :: (Monad m, Eq v) => Bool -> Bool -> PutlensM m s v -> LensM m s vSource

Converts a putlens to a normal lens with a parameter telling to ensure well-behavedness or not (for unsafe casts) Initializes the environment as the original source, the state as empty, the GetPut tag as True and the PutGet tag as False

get' :: Eq v => PutlensM m s v -> s -> vSource

The get function of a putlens

put' :: (Monad m, Eq v) => Bool -> Bool -> PutlensM m s v -> s -> v -> m sSource

getput' :: (Monad m, Eq v) => Bool -> Bool -> PutlensM m s v -> s -> (v, v -> m s)Source

The tupled get/put function of a putlens (with PutGet and GetPut flags)

create' :: (Monad m, Eq v) => Bool -> PutlensM m s v -> v -> m sSource

The create function of a putlens (with PutGet flag)

put2create :: (Monad m, Eq v) => PutlensM m s v -> PutlensM m s vSource

Converts a putlens into another putlens that only uses the create function

checkGetPut :: (Monad m, Eq v) => PutlensM m s v -> PutlensM m s vSource

checkPutGet :: Monad m => PutlensM m s v -> PutlensM m s vSource

offGetPut :: Monad m => PutM m s -> PutM m sSource

onPutGet :: Monad m => PutM m s -> PutM m sSource