microlens-pro-0.2.0.1: Prisms and isomorphisms for microlens
Copyright(C) 2013-2016 Edward Kmett 2018 Monadfix
LicenseBSD-style (see the file LICENSE)
Safe HaskellSafe-Inferred
LanguageHaskell2010

Lens.Micro.Pro.Internal

Description

Definitions used internally by microlens. If you're going to use these, only define instances for your own types, and don't export an API using these!

Synopsis

Documentation

class Strict lazy strict | lazy -> strict, strict -> lazy where Source #

Methods

strict :: Iso' lazy strict Source #

lazy :: Iso' strict lazy Source #

class IsText t where Source #

Methods

packed :: Iso' String t Source #

packed lets you convert between String and Text (strict or lazy). It can be used as a replacement for pack or as a way to modify some String if you have a function like Text -> Text.

unpacked :: Iso' t String Source #

unpacked is like packed but works in the opposite direction.

Instances

Instances details
IsText Text Source # 
Instance details

Defined in Lens.Micro.Pro

IsText Text Source # 
Instance details

Defined in Lens.Micro.Pro

IsText [Char] Source # 
Instance details

Defined in Lens.Micro.Pro

data Exchange a b s t Source #

This type is used internally to provide efficient access to the two inverse functions behind an Iso.

Constructors

Exchange (s -> a) (b -> t) 

Instances

Instances details
Profunctor (Exchange a b) Source # 
Instance details

Defined in Lens.Micro.Pro.Internal

Methods

dimap :: (a0 -> b0) -> (c -> d) -> Exchange a b b0 c -> Exchange a b a0 d #

lmap :: (a0 -> b0) -> Exchange a b b0 c -> Exchange a b a0 c #

rmap :: (b0 -> c) -> Exchange a b a0 b0 -> Exchange a b a0 c #

(#.) :: forall a0 b0 c q. Coercible c b0 => q b0 c -> Exchange a b a0 b0 -> Exchange a b a0 c #

(.#) :: forall a0 b0 c q. Coercible b0 a0 => Exchange a b b0 c -> q a0 b0 -> Exchange a b a0 c #

Functor (Exchange a b s) Source # 
Instance details

Defined in Lens.Micro.Pro.Internal

Methods

fmap :: (a0 -> b0) -> Exchange a b s a0 -> Exchange a b s b0 #

(<$) :: a0 -> Exchange a b s b0 -> Exchange a b s a0 #

type Exchange' a s = Exchange a a s s Source #

data Market a b s t Source #

This type is used internally by the Prism code to provide efficient access to the two parts of a Prism, i.e. a constructor and a selector — see: prism.

Constructors

Market (b -> t) (s -> Either t a) 

Instances

Instances details
Choice (Market a b) Source # 
Instance details

Defined in Lens.Micro.Pro.Internal

Methods

left' :: Market a b a0 b0 -> Market a b (Either a0 c) (Either b0 c) #

right' :: Market a b a0 b0 -> Market a b (Either c a0) (Either c b0) #

Profunctor (Market a b) Source # 
Instance details

Defined in Lens.Micro.Pro.Internal

Methods

dimap :: (a0 -> b0) -> (c -> d) -> Market a b b0 c -> Market a b a0 d #

lmap :: (a0 -> b0) -> Market a b b0 c -> Market a b a0 c #

rmap :: (b0 -> c) -> Market a b a0 b0 -> Market a b a0 c #

(#.) :: forall a0 b0 c q. Coercible c b0 => q b0 c -> Market a b a0 b0 -> Market a b a0 c #

(.#) :: forall a0 b0 c q. Coercible b0 a0 => Market a b b0 c -> q a0 b0 -> Market a b a0 c #

Functor (Market a b s) Source # 
Instance details

Defined in Lens.Micro.Pro.Internal

Methods

fmap :: (a0 -> b0) -> Market a b s a0 -> Market a b s b0 #

(<$) :: a0 -> Market a b s b0 -> Market a b s a0 #

type Market' a s = Market a a s s Source #

type Iso s t a b = forall p f. (Profunctor p, Functor f) => p a (f b) -> p s (f t) Source #

The type signature of iso provides a nice interpretation of Iso. If you want to apply a function a -> b to a type s, you'd have to convert with s -> a, apply your function a -> b, and convert back with b -> t.

iso :: (s -> a) -> (b -> t) -> Iso s t a b
-- or, put monomorphically
iso :: (s -> a) -> (a -> s) -> Iso' s a

type Iso' s a = Iso s s a a Source #

The type of monomorphic isomorphisms, i.e. isos that change neither the outer type s nor the inner type a.

type Prism s t a b = forall p f. (Choice p, Applicative f) => p a (f b) -> p s (f t) Source #

  • s is the type of the whole structure
  • t is the type of the reconstructed structure
  • a is the type of the target
  • b is the type of the value used for reconstruction

type Prism' s a = Prism s s a a Source #

The type of monomorphic prisms, i.e. prisms that change neither the outer type s nor the inner type a.