| Copyright | (c) Adam Conner-Sax 2019 |
|---|---|
| License | BSD-3-Clause |
| Maintainer | adam_conner_sax@yahoo.com |
| Stability | experimental |
| Safe Haskell | None |
| Language | Haskell2010 |
Knit.Report.Input.Visualization.Diagrams
Contents
Description
Functions to Diagrams (from the Diagrams library) to the current Pandoc document.
Synopsis
- addDiagramAsSVG :: (PandocEffects effs, Member ToPandoc effs, Member UnusedId effs) => Maybe Text -> Maybe Text -> Double -> Double -> QDiagram SVG V2 Double Any -> Sem effs Text
- (<$) :: Functor f => a -> f b -> f a
- class Functor f => Applicative (f :: Type -> Type) where
- class (Functor t, Foldable t) => Traversable (t :: Type -> Type) where
- traverse :: Applicative f => (a -> f b) -> t a -> f (t b)
- class Semigroup a where
- liftA :: Applicative f => (a -> b) -> f a -> f b
- liftA3 :: Applicative f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d
- (<$>) :: Functor f => (a -> b) -> f a -> f b
- newtype Const a (b :: k) :: forall k. Type -> k -> Type = Const {
- getConst :: a
- newtype Identity a = Identity {
- runIdentity :: a
- simulate :: Rational -> Active a -> [a]
- discrete :: [a] -> Active a
- movie :: [Active a] -> Active a
- (|>>) :: Active a -> Active a -> Active a
- (->>) :: Semigroup a => Active a -> Active a -> Active a
- after :: Active a -> Active a -> Active a
- atTime :: Time Rational -> Active a -> Active a
- setEra :: Era Rational -> Active a -> Active a
- trimAfter :: Monoid a => Active a -> Active a
- trimBefore :: Monoid a => Active a -> Active a
- trim :: Monoid a => Active a -> Active a
- clampAfter :: Active a -> Active a
- clampBefore :: Active a -> Active a
- clamp :: Active a -> Active a
- snapshot :: Time Rational -> Active a -> Active a
- backwards :: Active a -> Active a
- shift :: Duration Rational -> Active a -> Active a
- during :: Active a -> Active a -> Active a
- stretchTo :: Duration Rational -> Active a -> Active a
- stretch :: Rational -> Active a -> Active a
- interval :: Fractional a => Time Rational -> Time Rational -> Active a
- ui :: Fractional a => Active a
- isDynamic :: Active a -> Bool
- isConstant :: Active a -> Bool
- activeEra :: Active a -> Maybe (Era Rational)
- activeEnd :: Active a -> a
- activeStart :: Active a -> a
- runActive :: Active a -> Time Rational -> a
- modActive :: (a -> b) -> (Dynamic a -> Dynamic b) -> Active a -> Active b
- onActive :: (a -> b) -> (Dynamic a -> b) -> Active a -> b
- mkActive :: Time Rational -> Time Rational -> (Time Rational -> a) -> Active a
- fromDynamic :: Dynamic a -> Active a
- shiftDynamic :: Duration Rational -> Dynamic a -> Dynamic a
- onDynamic :: (Time Rational -> Time Rational -> (Time Rational -> a) -> b) -> Dynamic a -> b
- mkDynamic :: Time Rational -> Time Rational -> (Time Rational -> a) -> Dynamic a
- duration :: Num n => Era n -> Duration n
- end :: Era n -> Time n
- start :: Era n -> Time n
- mkEra :: Time n -> Time n -> Era n
- fromDuration :: Duration n -> n
- toDuration :: n -> Duration n
- data Era n
- data Dynamic a = Dynamic {}
- data Active a
- fromTime :: Time n -> n
- toTime :: n -> Time n
- data Duration n
- data Time n
- class Contravariant (f :: Type -> Type) where
- option :: b -> (a -> b) -> Option a -> b
- mtimesDefault :: (Integral b, Monoid a) => b -> a -> a
- diff :: Semigroup m => m -> Endo m
- cycle1 :: Semigroup m => m -> m
- newtype Min a = Min {
- getMin :: a
- newtype Max a = Max {
- getMax :: a
- data Arg a b = Arg a b
- type ArgMin a b = Min (Arg a b)
- type ArgMax a b = Max (Arg a b)
- newtype First a = First {
- getFirst :: a
- newtype Last a = Last {
- getLast :: a
- newtype WrappedMonoid m = WrapMonoid {
- unwrapMonoid :: m
- newtype Option a = Option {}
- class Bifunctor (p :: Type -> Type -> Type) where
- bimap :: (a -> b) -> (c -> d) -> p a c -> p b d
- stimesMonoid :: (Integral b, Monoid a) => b -> a -> a
- stimesIdempotent :: Integral b => b -> a -> a
- newtype Dual a = Dual {
- getDual :: a
- newtype Endo a = Endo {
- appEndo :: a -> a
- newtype All = All {}
- newtype Any = Any {}
- newtype Sum a = Sum {
- getSum :: a
- newtype Product a = Product {
- getProduct :: a
- (&) :: a -> (a -> b) -> b
- (<&>) :: Functor f => f a -> (a -> b) -> f b
- stimesIdempotentMonoid :: (Integral b, Monoid a) => b -> a -> a
- yellowgreen :: (Ord a, Floating a) => Colour a
- yellow :: (Ord a, Floating a) => Colour a
- whitesmoke :: (Ord a, Floating a) => Colour a
- white :: (Ord a, Floating a) => Colour a
- wheat :: (Ord a, Floating a) => Colour a
- violet :: (Ord a, Floating a) => Colour a
- turquoise :: (Ord a, Floating a) => Colour a
- tomato :: (Ord a, Floating a) => Colour a
- thistle :: (Ord a, Floating a) => Colour a
- teal :: (Ord a, Floating a) => Colour a
- steelblue :: (Ord a, Floating a) => Colour a
- springgreen :: (Ord a, Floating a) => Colour a
- snow :: (Ord a, Floating a) => Colour a
- slategrey :: (Ord a, Floating a) => Colour a
- slategray :: (Ord a, Floating a) => Colour a
- slateblue :: (Ord a, Floating a) => Colour a
- skyblue :: (Ord a, Floating a) => Colour a
- silver :: (Ord a, Floating a) => Colour a
- sienna :: (Ord a, Floating a) => Colour a
- seashell :: (Ord a, Floating a) => Colour a
- seagreen :: (Ord a, Floating a) => Colour a
- sandybrown :: (Ord a, Floating a) => Colour a
- salmon :: (Ord a, Floating a) => Colour a
- saddlebrown :: (Ord a, Floating a) => Colour a
- royalblue :: (Ord a, Floating a) => Colour a
- rosybrown :: (Ord a, Floating a) => Colour a
- red :: (Ord a, Floating a) => Colour a
- purple :: (Ord a, Floating a) => Colour a
- powderblue :: (Ord a, Floating a) => Colour a
- plum :: (Ord a, Floating a) => Colour a
- pink :: (Ord a, Floating a) => Colour a
- peru :: (Ord a, Floating a) => Colour a
- peachpuff :: (Ord a, Floating a) => Colour a
- papayawhip :: (Ord a, Floating a) => Colour a
- palevioletred :: (Ord a, Floating a) => Colour a
- paleturquoise :: (Ord a, Floating a) => Colour a
- palegreen :: (Ord a, Floating a) => Colour a
- palegoldenrod :: (Ord a, Floating a) => Colour a
- orchid :: (Ord a, Floating a) => Colour a
- orangered :: (Ord a, Floating a) => Colour a
- orange :: (Ord a, Floating a) => Colour a
- olivedrab :: (Ord a, Floating a) => Colour a
- olive :: (Ord a, Floating a) => Colour a
- oldlace :: (Ord a, Floating a) => Colour a
- navy :: (Ord a, Floating a) => Colour a
- navajowhite :: (Ord a, Floating a) => Colour a
- moccasin :: (Ord a, Floating a) => Colour a
- mistyrose :: (Ord a, Floating a) => Colour a
- mintcream :: (Ord a, Floating a) => Colour a
- midnightblue :: (Ord a, Floating a) => Colour a
- mediumvioletred :: (Ord a, Floating a) => Colour a
- mediumturquoise :: (Ord a, Floating a) => Colour a
- mediumspringgreen :: (Ord a, Floating a) => Colour a
- mediumslateblue :: (Ord a, Floating a) => Colour a
- mediumseagreen :: (Ord a, Floating a) => Colour a
- mediumpurple :: (Ord a, Floating a) => Colour a
- mediumorchid :: (Ord a, Floating a) => Colour a
- mediumblue :: (Ord a, Floating a) => Colour a
- mediumaquamarine :: (Ord a, Floating a) => Colour a
- maroon :: (Ord a, Floating a) => Colour a
- magenta :: (Ord a, Floating a) => Colour a
- linen :: (Ord a, Floating a) => Colour a
- limegreen :: (Ord a, Floating a) => Colour a
- lime :: (Ord a, Floating a) => Colour a
- lightyellow :: (Ord a, Floating a) => Colour a
- lightsteelblue :: (Ord a, Floating a) => Colour a
- lightslategrey :: (Ord a, Floating a) => Colour a
- lightslategray :: (Ord a, Floating a) => Colour a
- lightskyblue :: (Ord a, Floating a) => Colour a
- lightseagreen :: (Ord a, Floating a) => Colour a
- lightsalmon :: (Ord a, Floating a) => Colour a
- lightpink :: (Ord a, Floating a) => Colour a
- lightgrey :: (Ord a, Floating a) => Colour a
- lightgreen :: (Ord a, Floating a) => Colour a
- lightgray :: (Ord a, Floating a) => Colour a
- lightgoldenrodyellow :: (Ord a, Floating a) => Colour a
- lightcyan :: (Ord a, Floating a) => Colour a
- lightcoral :: (Ord a, Floating a) => Colour a
- lightblue :: (Ord a, Floating a) => Colour a
- lemonchiffon :: (Ord a, Floating a) => Colour a
- lawngreen :: (Ord a, Floating a) => Colour a
- lavenderblush :: (Ord a, Floating a) => Colour a
- lavender :: (Ord a, Floating a) => Colour a
- khaki :: (Ord a, Floating a) => Colour a
- ivory :: (Ord a, Floating a) => Colour a
- indigo :: (Ord a, Floating a) => Colour a
- indianred :: (Ord a, Floating a) => Colour a
- hotpink :: (Ord a, Floating a) => Colour a
- honeydew :: (Ord a, Floating a) => Colour a
- greenyellow :: (Ord a, Floating a) => Colour a
- green :: (Ord a, Floating a) => Colour a
- grey :: (Ord a, Floating a) => Colour a
- gray :: (Ord a, Floating a) => Colour a
- goldenrod :: (Ord a, Floating a) => Colour a
- gold :: (Ord a, Floating a) => Colour a
- ghostwhite :: (Ord a, Floating a) => Colour a
- gainsboro :: (Ord a, Floating a) => Colour a
- fuchsia :: (Ord a, Floating a) => Colour a
- forestgreen :: (Ord a, Floating a) => Colour a
- floralwhite :: (Ord a, Floating a) => Colour a
- firebrick :: (Ord a, Floating a) => Colour a
- dodgerblue :: (Ord a, Floating a) => Colour a
- dimgrey :: (Ord a, Floating a) => Colour a
- dimgray :: (Ord a, Floating a) => Colour a
- deepskyblue :: (Ord a, Floating a) => Colour a
- deeppink :: (Ord a, Floating a) => Colour a
- darkviolet :: (Ord a, Floating a) => Colour a
- darkturquoise :: (Ord a, Floating a) => Colour a
- darkslategrey :: (Ord a, Floating a) => Colour a
- darkslategray :: (Ord a, Floating a) => Colour a
- darkslateblue :: (Ord a, Floating a) => Colour a
- darkseagreen :: (Ord a, Floating a) => Colour a
- darksalmon :: (Ord a, Floating a) => Colour a
- darkred :: (Ord a, Floating a) => Colour a
- darkorchid :: (Ord a, Floating a) => Colour a
- darkorange :: (Ord a, Floating a) => Colour a
- darkolivegreen :: (Ord a, Floating a) => Colour a
- darkmagenta :: (Ord a, Floating a) => Colour a
- darkkhaki :: (Ord a, Floating a) => Colour a
- darkgrey :: (Ord a, Floating a) => Colour a
- darkgreen :: (Ord a, Floating a) => Colour a
- darkgray :: (Ord a, Floating a) => Colour a
- darkgoldenrod :: (Ord a, Floating a) => Colour a
- darkcyan :: (Ord a, Floating a) => Colour a
- darkblue :: (Ord a, Floating a) => Colour a
- cyan :: (Ord a, Floating a) => Colour a
- crimson :: (Ord a, Floating a) => Colour a
- cornsilk :: (Ord a, Floating a) => Colour a
- cornflowerblue :: (Ord a, Floating a) => Colour a
- coral :: (Ord a, Floating a) => Colour a
- chocolate :: (Ord a, Floating a) => Colour a
- chartreuse :: (Ord a, Floating a) => Colour a
- cadetblue :: (Ord a, Floating a) => Colour a
- burlywood :: (Ord a, Floating a) => Colour a
- brown :: (Ord a, Floating a) => Colour a
- blueviolet :: (Ord a, Floating a) => Colour a
- blue :: (Ord a, Floating a) => Colour a
- blanchedalmond :: (Ord a, Floating a) => Colour a
- bisque :: (Ord a, Floating a) => Colour a
- beige :: (Ord a, Floating a) => Colour a
- azure :: (Ord a, Floating a) => Colour a
- aquamarine :: (Ord a, Floating a) => Colour a
- aqua :: (Ord a, Floating a) => Colour a
- antiquewhite :: (Ord a, Floating a) => Colour a
- aliceblue :: (Ord a, Floating a) => Colour a
- readColourName :: (MonadFail m, Monad m, Ord a, Floating a) => String -> m (Colour a)
- sRGBSpace :: (Ord a, Floating a) => RGBSpace a
- sRGB24read :: (Ord b, Floating b) => String -> Colour b
- sRGB24reads :: (Ord b, Floating b) => ReadS (Colour b)
- sRGB24show :: (RealFrac b, Floating b) => Colour b -> String
- sRGB24shows :: (RealFrac b, Floating b) => Colour b -> ShowS
- toSRGB24 :: (RealFrac b, Floating b) => Colour b -> RGB Word8
- toSRGBBounded :: (RealFrac b, Floating b, Integral a, Bounded a) => Colour b -> RGB a
- toSRGB :: (Ord b, Floating b) => Colour b -> RGB b
- sRGB24 :: (Ord b, Floating b) => Word8 -> Word8 -> Word8 -> Colour b
- sRGBBounded :: (Ord b, Floating b, Integral a, Bounded a) => a -> a -> a -> Colour b
- sRGB :: (Ord b, Floating b) => b -> b -> b -> Colour b
- data RGB a = RGB {
- channelRed :: !a
- channelGreen :: !a
- channelBlue :: !a
- alphaChannel :: AlphaColour a -> a
- blend :: (Num a, AffineSpace f) => a -> f a -> f a -> f a
- withOpacity :: Num a => Colour a -> a -> AlphaColour a
- dissolve :: Num a => a -> AlphaColour a -> AlphaColour a
- opaque :: Num a => Colour a -> AlphaColour a
- alphaColourConvert :: (Fractional b, Real a) => AlphaColour a -> AlphaColour b
- transparent :: Num a => AlphaColour a
- black :: Num a => Colour a
- colourConvert :: (Fractional b, Real a) => Colour a -> Colour b
- data Colour a
- data AlphaColour a
- class ColourOps (f :: Type -> Type) where
- class Default a where
- def :: a
- class Functor f => Additive (f :: Type -> Type) where
- renderDia :: (Backend b v n, HasLinearMap v, Metric v, Typeable n, OrderedField n, Monoid' m) => b -> Options b v n -> QDiagram b v n m -> Result b v n
- renderDiaT :: (Backend b v n, HasLinearMap v, Metric v, Typeable n, OrderedField n, Monoid' m) => b -> Options b v n -> QDiagram b v n m -> (Transformation v n, Result b v n)
- lookupSub :: IsName nm => nm -> SubMap b v n m -> Maybe [Subdiagram b v n m]
- rememberAs :: IsName a => a -> QDiagram b v n m -> SubMap b v n m -> SubMap b v n m
- fromNames :: IsName a => [(a, Subdiagram b v n m)] -> SubMap b v n m
- rawSub :: Subdiagram b v n m -> QDiagram b v n m
- getSub :: (Metric v, OrderedField n, Semigroup m) => Subdiagram b v n m -> QDiagram b v n m
- location :: (Additive v, Num n) => Subdiagram b v n m -> Point v n
- subPoint :: (Metric v, OrderedField n) => Point v n -> Subdiagram b v n m
- mkSubdiagram :: QDiagram b v n m -> Subdiagram b v n m
- atop :: (OrderedField n, Metric v, Semigroup m) => QDiagram b v n m -> QDiagram b v n m -> QDiagram b v n m
- mkQD :: Prim b v n -> Envelope v n -> Trace v n -> SubMap b v n m -> Query v n m -> QDiagram b v n m
- query :: Monoid m => QDiagram b v n m -> Query v n m
- localize :: (Metric v, OrderedField n, Semigroup m) => QDiagram b v n m -> QDiagram b v n m
- withNames :: (IsName nm, Metric v, Semigroup m, OrderedField n) => [nm] -> ([Subdiagram b v n m] -> QDiagram b v n m -> QDiagram b v n m) -> QDiagram b v n m -> QDiagram b v n m
- withNameAll :: (IsName nm, Metric v, Semigroup m, OrderedField n) => nm -> ([Subdiagram b v n m] -> QDiagram b v n m -> QDiagram b v n m) -> QDiagram b v n m -> QDiagram b v n m
- withName :: (IsName nm, Metric v, Semigroup m, OrderedField n) => nm -> (Subdiagram b v n m -> QDiagram b v n m -> QDiagram b v n m) -> QDiagram b v n m -> QDiagram b v n m
- lookupName :: (IsName nm, Metric v, Semigroup m, OrderedField n) => nm -> QDiagram b v n m -> Maybe (Subdiagram b v n m)
- nameSub :: (IsName nm, Metric v, OrderedField n, Semigroup m) => (QDiagram b v n m -> Subdiagram b v n m) -> nm -> QDiagram b v n m -> QDiagram b v n m
- names :: (Metric v, Semigroup m, OrderedField n) => QDiagram b v n m -> [(Name, [Point v n])]
- subMap :: (Metric v, Semigroup m, OrderedField n) => Lens' (QDiagram b v n m) (SubMap b v n m)
- setTrace :: (OrderedField n, Metric v, Semigroup m) => Trace v n -> QDiagram b v n m -> QDiagram b v n m
- setEnvelope :: (OrderedField n, Metric v, Monoid' m) => Envelope v n -> QDiagram b v n m -> QDiagram b v n m
- envelope :: (OrderedField n, Metric v, Monoid' m) => Lens' (QDiagram b v n m) (Envelope v n)
- pointDiagram :: (Metric v, Fractional n) => Point v n -> QDiagram b v n m
- groupOpacity :: (Metric v, OrderedField n, Semigroup m) => Double -> QDiagram b v n m -> QDiagram b v n m
- opacityGroup :: (Metric v, OrderedField n, Semigroup m) => Double -> QDiagram b v n m -> QDiagram b v n m
- href :: (Metric v, OrderedField n, Semigroup m) => String -> QDiagram b v n m -> QDiagram b v n m
- type TypeableFloat n = (Typeable n, RealFloat n)
- data QDiagram b (v :: Type -> Type) n m
- type Diagram b = QDiagram b (V b) (N b) Any
- data Subdiagram b (v :: Type -> Type) n m = Subdiagram (QDiagram b v n m) (DownAnnots v n)
- newtype SubMap b (v :: Type -> Type) n m = SubMap (Map Name [Subdiagram b v n m])
- data Prim b (v :: Type -> Type) n where
- Prim :: forall b (v :: Type -> Type) n p. (Transformable p, Typeable p, Renderable p b) => p -> Prim b (V p) (N p)
- class Backend b (v :: Type -> Type) n where
- data Render b (v :: Type -> Type) n :: Type
- type Result b (v :: Type -> Type) n :: Type
- data Options b (v :: Type -> Type) n :: Type
- adjustDia :: (Additive v, Monoid' m, Num n) => b -> Options b v n -> QDiagram b v n m -> (Options b v n, Transformation v n, QDiagram b v n m)
- renderRTree :: b -> Options b v n -> RTree b v n Annotation -> Result b v n
- type D (v :: Type -> Type) n = QDiagram NullBackend v n Any
- data NullBackend
- class Transformable t => Renderable t b where
- juxtaposeDefault :: (Enveloped a, HasOrigin a) => Vn a -> a -> a -> a
- class Juxtaposable a where
- size :: (V a ~ v, N a ~ n, Enveloped a, HasBasis v) => a -> v n
- radius :: (V a ~ v, N a ~ n, Enveloped a) => v n -> a -> n
- diameter :: (V a ~ v, N a ~ n, Enveloped a) => v n -> a -> n
- envelopeP :: (V a ~ v, N a ~ n, Enveloped a) => v n -> a -> Point v n
- envelopePMay :: (V a ~ v, N a ~ n, Enveloped a) => v n -> a -> Maybe (Point v n)
- envelopeV :: Enveloped a => Vn a -> a -> Vn a
- envelopeVMay :: Enveloped a => Vn a -> a -> Maybe (Vn a)
- mkEnvelope :: (v n -> n) -> Envelope v n
- onEnvelope :: ((v n -> n) -> v n -> n) -> Envelope v n -> Envelope v n
- appEnvelope :: Envelope v n -> Maybe (v n -> n)
- newtype Envelope (v :: Type -> Type) n = Envelope (Option (v n -> Max n))
- type OrderedField s = (Floating s, Ord s)
- class (Metric (V a), OrderedField (N a)) => Enveloped a where
- getEnvelope :: a -> Envelope (V a) (N a)
- newtype Query (v :: Type -> Type) n m = Query {}
- maxRayTraceP :: (n ~ N a, Traced a, Num n) => Point (V a) n -> V a n -> a -> Maybe (Point (V a) n)
- maxRayTraceV :: (n ~ N a, Traced a, Num n) => Point (V a) n -> V a n -> a -> Maybe (V a n)
- rayTraceP :: (n ~ N a, Traced a, Num n) => Point (V a) n -> V a n -> a -> Maybe (Point (V a) n)
- rayTraceV :: (n ~ N a, Traced a, Num n) => Point (V a) n -> V a n -> a -> Maybe (V a n)
- maxTraceP :: (n ~ N a, Num n, Traced a) => Point (V a) n -> V a n -> a -> Maybe (Point (V a) n)
- maxTraceV :: (n ~ N a, Num n, Traced a) => Point (V a) n -> V a n -> a -> Maybe (V a n)
- traceP :: (n ~ N a, Traced a, Num n) => Point (V a) n -> V a n -> a -> Maybe (Point (V a) n)
- traceV :: (n ~ N a, Num n, Traced a) => Point (V a) n -> V a n -> a -> Maybe (V a n)
- mkTrace :: (Point v n -> v n -> SortedList n) -> Trace v n
- getSortedList :: SortedList a -> [a]
- mkSortedList :: Ord a => [a] -> SortedList a
- data SortedList a
- newtype Trace (v :: Type -> Type) n = Trace {
- appTrace :: Point v n -> v n -> SortedList n
- class (Additive (V a), Ord (N a)) => Traced a where
- (.>) :: (IsName a1, IsName a2) => a1 -> a2 -> Name
- eachName :: (Typeable a, Ord a, Show a) => Traversal' Name a
- class (Typeable a, Ord a, Show a) => IsName a where
- data AName
- data Name
- class Qualifiable q where
- applyTAttr :: (AttributeClass a, Transformable a, V a ~ V d, N a ~ N d, HasStyle d) => a -> d -> d
- applyMAttr :: (AttributeClass a, N d ~ n, HasStyle d) => Measured n a -> d -> d
- applyAttr :: (AttributeClass a, HasStyle d) => a -> d -> d
- atTAttr :: (V a ~ v, N a ~ n, AttributeClass a, Transformable a) => Lens' (Style v n) (Maybe a)
- atMAttr :: (AttributeClass a, Typeable n) => Lens' (Style v n) (Maybe (Measured n a))
- atAttr :: AttributeClass a => Lens' (Style v n) (Maybe a)
- getAttr :: AttributeClass a => Style v n -> Maybe a
- class (Typeable a, Semigroup a) => AttributeClass a
- data Attribute (v :: Type -> Type) n where
- Attribute :: forall (v :: Type -> Type) n a. AttributeClass a => a -> Attribute v n
- MAttribute :: forall (v :: Type -> Type) n a. AttributeClass a => Measured n a -> Attribute v n
- TAttribute :: forall (v :: Type -> Type) n a. (AttributeClass a, Transformable a, V a ~ v, N a ~ n) => a -> Attribute v n
- data Style (v :: Type -> Type) n
- class HasStyle a where
- applyStyle :: Style (V a) (N a) -> a -> a
- scale :: (InSpace v n a, Eq n, Fractional n, Transformable a) => n -> a -> a
- scaling :: (Additive v, Fractional n) => n -> Transformation v n
- translate :: Transformable t => Vn t -> t -> t
- translation :: v n -> Transformation v n
- avgScale :: (Additive v, Traversable v, Floating n) => Transformation v n -> n
- isReflection :: (Additive v, Traversable v, Num n, Ord n) => Transformation v n -> Bool
- determinant :: (Additive v, Traversable v, Num n) => Transformation v n -> n
- dimension :: (Additive (V a), Traversable (V a)) => a -> Int
- fromLinear :: (Additive v, Num n) => (v n :-: v n) -> (v n :-: v n) -> Transformation v n
- papply :: (Additive v, Num n) => Transformation v n -> Point v n -> Point v n
- apply :: Transformation v n -> v n -> v n
- dropTransl :: (Additive v, Num n) => Transformation v n -> Transformation v n
- transl :: Transformation v n -> v n
- transp :: Transformation v n -> v n :-: v n
- inv :: (Functor v, Num n) => Transformation v n -> Transformation v n
- eye :: (HasBasis v, Num n) => v (v n)
- lapp :: (u :-: v) -> u -> v
- linv :: (u :-: v) -> v :-: u
- (<->) :: (u -> v) -> (v -> u) -> u :-: v
- data u :-: v
- data Transformation (v :: Type -> Type) n
- type HasLinearMap (v :: Type -> Type) = (HasBasis v, Traversable v)
- type HasBasis (v :: Type -> Type) = (Additive v, Representable v, Rep v ~ E v)
- class Transformable t where
- transform :: Transformation (V t) (N t) -> t -> t
- newtype TransInv t = TransInv t
- place :: (InSpace v n t, HasOrigin t) => t -> Point v n -> t
- moveTo :: (InSpace v n t, HasOrigin t) => Point v n -> t -> t
- moveOriginBy :: (V t ~ v, N t ~ n, HasOrigin t) => v n -> t -> t
- class HasOrigin t where
- moveOriginTo :: Point (V t) (N t) -> t -> t
- atMost :: Ord n => Measure n -> Measure n -> Measure n
- atLeast :: Ord n => Measure n -> Measure n -> Measure n
- scaleLocal :: Num n => n -> Measured n a -> Measured n a
- normalized :: Num n => n -> Measure n
- global :: Num n => n -> Measure n
- local :: Num n => n -> Measure n
- output :: n -> Measure n
- fromMeasured :: Num n => n -> n -> Measured n a -> a
- data Measured n a
- type Measure n = Measured n n
- (*.) :: (Functor v, Num n) => n -> Point v n -> Point v n
- type family V a :: Type -> Type
- type family N a :: Type
- type Vn a = V a (N a)
- type InSpace (v :: Type -> Type) n a = (V a ~ v, N a ~ n, Additive v, Num n)
- type SameSpace a b = (V a ~ V b, N a ~ N b)
- type Monoid' = Monoid
- basis :: (Additive t, Traversable t, Num a) => [t a]
- newtype Point (f :: Type -> Type) a = P (f a)
- _Point :: Iso' (Point f a) (f a)
- origin :: (Additive f, Num a) => Point f a
- relative :: (Additive f, Num a) => Point f a -> Iso' (Point f a) (f a)
- newtype E (t :: Type -> Type) = E {}
- negated :: (Functor f, Num a) => f a -> f a
- sumV :: (Foldable f, Additive v, Num a) => f (v a) -> v a
- (*^) :: (Functor f, Num a) => a -> f a -> f a
- (^*) :: (Functor f, Num a) => f a -> a -> f a
- (^/) :: (Functor f, Fractional a) => f a -> a -> f a
- basisFor :: (Traversable t, Num a) => t b -> [t a]
- scaled :: (Traversable t, Num a) => t a -> t (t a)
- unit :: (Additive t, Num a) => ASetter' (t a) a -> t a
- outer :: (Functor f, Functor g, Num a) => f a -> g a -> f (g a)
- class Additive f => Metric (f :: Type -> Type) where
- normalize :: (Floating a, Metric f, Epsilon a) => f a -> f a
- class Additive (Diff p) => Affine (p :: Type -> Type) where
- qdA :: (Affine p, Foldable (Diff p), Num a) => p a -> p a -> a
- distanceA :: (Floating a, Foldable (Diff p), Affine p) => p a -> p a -> a
- (.#) :: Coercible b a => (b -> c) -> (a -> b) -> a -> c
- (#.) :: Coercible c b => (b -> c) -> (a -> b) -> a -> c
- unP :: Point f a -> f a
- data family MVector s a :: Type
- data family Vector a :: Type
- animRect' :: (InSpace V2 n t, Monoid' m, TrailLike t, Enveloped t, Transformable t, Monoid t) => Rational -> QAnimation b V2 n m -> t
- animRect :: (InSpace V2 n t, Monoid' m, TrailLike t, Enveloped t, Transformable t, Monoid t) => QAnimation b V2 n m -> t
- animEnvelope' :: (OrderedField n, Metric v, Monoid' m) => Rational -> QAnimation b v n m -> QAnimation b v n m
- animEnvelope :: (OrderedField n, Metric v, Monoid' m) => QAnimation b v n m -> QAnimation b v n m
- type QAnimation b (v :: Type -> Type) n m = Active (QDiagram b v n m)
- type Animation b (v :: Type -> Type) n = QAnimation b v n Any
- mkHeight :: Num n => n -> SizeSpec V2 n
- mkWidth :: Num n => n -> SizeSpec V2 n
- dims2D :: n -> n -> SizeSpec V2 n
- mkSizeSpec2D :: Num n => Maybe n -> Maybe n -> SizeSpec V2 n
- extentY :: (InSpace v n a, R2 v, Enveloped a) => a -> Maybe (n, n)
- extentX :: (InSpace v n a, R1 v, Enveloped a) => a -> Maybe (n, n)
- height :: (InSpace V2 n a, Enveloped a) => a -> n
- width :: (InSpace V2 n a, Enveloped a) => a -> n
- sizeAdjustment :: (Additive v, Foldable v, OrderedField n) => SizeSpec v n -> BoundingBox v n -> (v n, Transformation v n)
- sizedAs :: (InSpace v n a, SameSpace a b, HasLinearMap v, Transformable a, Enveloped a, Enveloped b) => b -> a -> a
- sized :: (InSpace v n a, HasLinearMap v, Transformable a, Enveloped a) => SizeSpec v n -> a -> a
- requiredScaling :: (Additive v, Foldable v, Fractional n, Ord n) => SizeSpec v n -> v n -> Transformation v n
- requiredScale :: (Additive v, Foldable v, Fractional n, Ord n) => SizeSpec v n -> v n -> n
- specToSize :: (Foldable v, Functor v, Num n, Ord n) => n -> SizeSpec v n -> v n
- absolute :: (Additive v, Num n) => SizeSpec v n
- dims :: v n -> SizeSpec v n
- mkSizeSpec :: (Functor v, Num n) => v (Maybe n) -> SizeSpec v n
- getSpec :: (Functor v, Num n, Ord n) => SizeSpec v n -> v (Maybe n)
- data SizeSpec (v :: Type -> Type) n
- bgFrame :: (TypeableFloat n, Renderable (Path V2 n) b) => n -> Colour Double -> QDiagram b V2 n Any -> QDiagram b V2 n Any
- bg :: (TypeableFloat n, Renderable (Path V2 n) b) => Colour Double -> QDiagram b V2 n Any -> QDiagram b V2 n Any
- boundingRect :: (InSpace V2 n a, SameSpace a t, Enveloped t, Transformable t, TrailLike t, Monoid t, Enveloped a) => a -> t
- rectEnvelope :: (OrderedField n, Monoid' m) => Point V2 n -> V2 n -> QDiagram b V2 n m -> QDiagram b V2 n m
- extrudeTop :: (OrderedField n, Monoid' m) => n -> QDiagram b V2 n m -> QDiagram b V2 n m
- extrudeBottom :: (OrderedField n, Monoid' m) => n -> QDiagram b V2 n m -> QDiagram b V2 n m
- extrudeRight :: (OrderedField n, Monoid' m) => n -> QDiagram b V2 n m -> QDiagram b V2 n m
- extrudeLeft :: (OrderedField n, Monoid' m) => n -> QDiagram b V2 n m -> QDiagram b V2 n m
- padY :: (Metric v, R2 v, Monoid' m, OrderedField n) => n -> QDiagram b v n m -> QDiagram b v n m
- padX :: (Metric v, R2 v, OrderedField n, Monoid' m) => n -> QDiagram b v n m -> QDiagram b v n m
- strutY :: (Metric v, R2 v, OrderedField n) => n -> QDiagram b v n m
- strutX :: (Metric v, R1 v, OrderedField n) => n -> QDiagram b v n m
- vsep :: (InSpace V2 n a, Floating n, Juxtaposable a, HasOrigin a, Monoid' a) => n -> [a] -> a
- vcat' :: (InSpace V2 n a, Floating n, Juxtaposable a, HasOrigin a, Monoid' a) => CatOpts n -> [a] -> a
- vcat :: (InSpace V2 n a, Floating n, Juxtaposable a, HasOrigin a, Monoid' a) => [a] -> a
- hsep :: (InSpace V2 n a, Floating n, Juxtaposable a, HasOrigin a, Monoid' a) => n -> [a] -> a
- hcat' :: (InSpace V2 n a, Floating n, Juxtaposable a, HasOrigin a, Monoid' a) => CatOpts n -> [a] -> a
- hcat :: (InSpace V2 n a, Floating n, Juxtaposable a, HasOrigin a, Monoid' a) => [a] -> a
- (|||) :: (InSpace V2 n a, Juxtaposable a, Semigroup a) => a -> a -> a
- (===) :: (InSpace V2 n a, Juxtaposable a, Semigroup a) => a -> a -> a
- boxGrid :: (Traversable v, Additive v, Num n, Enum n) => n -> BoundingBox v n -> [Point v n]
- outside' :: (Additive v, Foldable v, Ord n) => BoundingBox v n -> BoundingBox v n -> Bool
- inside' :: (Additive v, Foldable v, Ord n) => BoundingBox v n -> BoundingBox v n -> Bool
- contains' :: (Additive v, Foldable v, Ord n) => BoundingBox v n -> Point v n -> Bool
- boxFit :: (InSpace v n a, HasBasis v, Enveloped a, Transformable a, Monoid a) => BoundingBox v n -> a -> a
- boxTransform :: (Additive v, Fractional n) => BoundingBox v n -> BoundingBox v n -> Maybe (Transformation v n)
- centerPoint :: (InSpace v n a, HasBasis v, Enveloped a) => a -> Point v n
- mCenterPoint :: (InSpace v n a, HasBasis v, Enveloped a) => a -> Maybe (Point v n)
- boxCenter :: (Additive v, Fractional n) => BoundingBox v n -> Maybe (Point v n)
- boxExtents :: (Additive v, Num n) => BoundingBox v n -> v n
- getAllCorners :: (Additive v, Traversable v) => BoundingBox v n -> [Point v n]
- getCorners :: BoundingBox v n -> Maybe (Point v n, Point v n)
- isEmptyBox :: BoundingBox v n -> Bool
- boundingBox :: (InSpace v n a, HasBasis v, Enveloped a) => a -> BoundingBox v n
- fromPoints :: (Additive v, Ord n) => [Point v n] -> BoundingBox v n
- fromPoint :: Point v n -> BoundingBox v n
- fromCorners :: (Additive v, Foldable v, Ord n) => Point v n -> Point v n -> BoundingBox v n
- emptyBox :: BoundingBox v n
- data BoundingBox (v :: Type -> Type) n
- showLabels :: (TypeableFloat n, Renderable (Text n) b, Semigroup m) => QDiagram b V2 n m -> QDiagram b V2 n Any
- showTrace :: (Enum n, TypeableFloat n, Renderable (Path V2 n) b) => QDiagram b V2 n Any -> QDiagram b V2 n Any
- showTrace' :: (Enum n, TypeableFloat n, Renderable (Path V2 n) b) => TraceOpts n -> QDiagram b V2 n Any -> QDiagram b V2 n Any
- showEnvelope :: (Enum n, TypeableFloat n, Renderable (Path V2 n) b) => QDiagram b V2 n Any -> QDiagram b V2 n Any
- showEnvelope' :: (Enum n, TypeableFloat n, Renderable (Path V2 n) b) => EnvelopeOpts n -> QDiagram b V2 n Any -> QDiagram b V2 n Any
- showOrigin' :: (TypeableFloat n, Renderable (Path V2 n) b, Monoid' m) => OriginOpts n -> QDiagram b V2 n m -> QDiagram b V2 n m
- showOrigin :: (TypeableFloat n, Renderable (Path V2 n) b, Monoid' m) => QDiagram b V2 n m -> QDiagram b V2 n m
- tScale :: Lens' (TraceOpts n) n
- tPoints :: Lens' (TraceOpts n) Int
- tMinSize :: Lens' (TraceOpts n) n
- tColor :: Lens' (TraceOpts n) (Colour Double)
- ePoints :: Lens' (EnvelopeOpts n) Int
- eLineWidth :: Lens (EnvelopeOpts n1) (EnvelopeOpts n2) (Measure n1) (Measure n2)
- eColor :: Lens' (EnvelopeOpts n) (Colour Double)
- data TraceOpts n = TraceOpts {}
- oScale :: Lens' (OriginOpts n) n
- oMinSize :: Lens' (OriginOpts n) n
- oColor :: Lens' (OriginOpts n) (Colour Double)
- data EnvelopeOpts n = EnvelopeOpts {}
- data OriginOpts n = OriginOpts {}
- cubicSpline :: (V t ~ v, N t ~ n, TrailLike t, Fractional (v n)) => Bool -> [Point v n] -> t
- bspline :: (TrailLike t, V t ~ v, N t ~ n) => BSpline v n -> t
- type BSpline (v :: Type -> Type) n = [Point v n]
- facingZ :: (R3 v, Functor v, Fractional n) => Deformation v v n
- perspectiveZ1 :: (R3 v, Functor v, Fractional n) => Deformation v v n
- parallelZ0 :: (R3 v, Num n) => Deformation v v n
- facingY :: (R2 v, Functor v, Fractional n) => Deformation v v n
- facingX :: (R1 v, Functor v, Fractional n) => Deformation v v n
- perspectiveY1 :: (R2 v, Functor v, Floating n) => Deformation v v n
- parallelY0 :: (R2 v, Num n) => Deformation v v n
- perspectiveX1 :: (R1 v, Functor v, Fractional n) => Deformation v v n
- parallelX0 :: (R1 v, Num n) => Deformation v v n
- asDeformation :: (Additive v, Num n) => Transformation v n -> Deformation v v n
- newtype Deformation (v :: Type -> Type) (u :: Type -> Type) n = Deformation (Point v n -> Point u n)
- class Deformable a b where
- connectOutside' :: (TypeableFloat n, Renderable (Path V2 n) b, IsName n1, IsName n2) => ArrowOpts n -> n1 -> n2 -> QDiagram b V2 n Any -> QDiagram b V2 n Any
- connectOutside :: (TypeableFloat n, Renderable (Path V2 n) b, IsName n1, IsName n2) => n1 -> n2 -> QDiagram b V2 n Any -> QDiagram b V2 n Any
- connectPerim' :: (TypeableFloat n, Renderable (Path V2 n) b, IsName n1, IsName n2) => ArrowOpts n -> n1 -> n2 -> Angle n -> Angle n -> QDiagram b V2 n Any -> QDiagram b V2 n Any
- connectPerim :: (TypeableFloat n, Renderable (Path V2 n) b, IsName n1, IsName n2) => n1 -> n2 -> Angle n -> Angle n -> QDiagram b V2 n Any -> QDiagram b V2 n Any
- connect' :: (TypeableFloat n, Renderable (Path V2 n) b, IsName n1, IsName n2) => ArrowOpts n -> n1 -> n2 -> QDiagram b V2 n Any -> QDiagram b V2 n Any
- connect :: (TypeableFloat n, Renderable (Path V2 n) b, IsName n1, IsName n2) => n1 -> n2 -> QDiagram b V2 n Any -> QDiagram b V2 n Any
- arrowV' :: (TypeableFloat n, Renderable (Path V2 n) b) => ArrowOpts n -> V2 n -> QDiagram b V2 n Any
- arrowV :: (TypeableFloat n, Renderable (Path V2 n) b) => V2 n -> QDiagram b V2 n Any
- arrowAt' :: (TypeableFloat n, Renderable (Path V2 n) b) => ArrowOpts n -> Point V2 n -> V2 n -> QDiagram b V2 n Any
- arrowAt :: (TypeableFloat n, Renderable (Path V2 n) b) => Point V2 n -> V2 n -> QDiagram b V2 n Any
- arrowBetween' :: (TypeableFloat n, Renderable (Path V2 n) b) => ArrowOpts n -> Point V2 n -> Point V2 n -> QDiagram b V2 n Any
- arrowBetween :: (TypeableFloat n, Renderable (Path V2 n) b) => Point V2 n -> Point V2 n -> QDiagram b V2 n Any
- arrow' :: (TypeableFloat n, Renderable (Path V2 n) b) => ArrowOpts n -> n -> QDiagram b V2 n Any
- arrow :: (TypeableFloat n, Renderable (Path V2 n) b) => n -> QDiagram b V2 n Any
- shaftTexture :: TypeableFloat n => Lens' (ArrowOpts n) (Texture n)
- tailTexture :: TypeableFloat n => Lens' (ArrowOpts n) (Texture n)
- headTexture :: TypeableFloat n => Lens' (ArrowOpts n) (Texture n)
- lengths :: Traversal' (ArrowOpts n) (Measure n)
- gap :: Traversal' (ArrowOpts n) (Measure n)
- gaps :: Traversal' (ArrowOpts n) (Measure n)
- tailStyle :: Lens' (ArrowOpts n) (Style V2 n)
- tailLength :: Lens' (ArrowOpts n) (Measure n)
- tailGap :: Lens' (ArrowOpts n) (Measure n)
- shaftStyle :: Lens' (ArrowOpts n) (Style V2 n)
- headStyle :: Lens' (ArrowOpts n) (Style V2 n)
- headLength :: Lens' (ArrowOpts n) (Measure n)
- headGap :: Lens' (ArrowOpts n) (Measure n)
- arrowTail :: Lens' (ArrowOpts n) (ArrowHT n)
- arrowShaft :: Lens' (ArrowOpts n) (Trail V2 n)
- arrowHead :: Lens' (ArrowOpts n) (ArrowHT n)
- straightShaft :: OrderedField n => Trail V2 n
- data ArrowOpts n = ArrowOpts {
- _arrowHead :: ArrowHT n
- _arrowTail :: ArrowHT n
- _arrowShaft :: Trail V2 n
- _headGap :: Measure n
- _tailGap :: Measure n
- _headStyle :: Style V2 n
- _headLength :: Measure n
- _tailStyle :: Style V2 n
- _tailLength :: Measure n
- _shaftStyle :: Style V2 n
- block :: RealFloat n => ArrowHT n
- quill :: (Floating n, Ord n) => ArrowHT n
- halfDart' :: RealFloat n => ArrowHT n
- dart' :: RealFloat n => ArrowHT n
- thorn' :: RealFloat n => ArrowHT n
- spike' :: RealFloat n => ArrowHT n
- tri' :: RealFloat n => ArrowHT n
- noTail :: ArrowHT n
- lineTail :: RealFloat n => ArrowHT n
- arrowtailQuill :: OrderedField n => Angle n -> ArrowHT n
- arrowtailBlock :: RealFloat n => Angle n -> ArrowHT n
- halfDart :: RealFloat n => ArrowHT n
- dart :: RealFloat n => ArrowHT n
- thorn :: RealFloat n => ArrowHT n
- spike :: RealFloat n => ArrowHT n
- tri :: RealFloat n => ArrowHT n
- noHead :: ArrowHT n
- lineHead :: RealFloat n => ArrowHT n
- arrowheadThorn :: RealFloat n => Angle n -> ArrowHT n
- arrowheadSpike :: RealFloat n => Angle n -> ArrowHT n
- arrowheadHalfDart :: RealFloat n => Angle n -> ArrowHT n
- arrowheadDart :: RealFloat n => Angle n -> ArrowHT n
- arrowheadTriangle :: RealFloat n => Angle n -> ArrowHT n
- type ArrowHT n = n -> n -> (Path V2 n, Path V2 n)
- lighter :: HasStyle a => a -> a
- bolder :: HasStyle a => a -> a
- heavy :: HasStyle a => a -> a
- ultraBold :: HasStyle a => a -> a
- semiBold :: HasStyle a => a -> a
- mediumWeight :: HasStyle a => a -> a
- light :: HasStyle a => a -> a
- ultraLight :: HasStyle a => a -> a
- thinWeight :: HasStyle a => a -> a
- bold :: HasStyle a => a -> a
- oblique :: HasStyle a => a -> a
- italic :: HasStyle a => a -> a
- _fontSize :: (Typeable n, OrderedField n) => Lens' (Style v n) (Measure n)
- _fontSizeR :: (Typeable n, OrderedField n) => Lens' (Style v n) (Measured n (Recommend n))
- fontSizeL :: (N a ~ n, Typeable n, Num n, HasStyle a) => n -> a -> a
- fontSizeO :: (N a ~ n, Typeable n, HasStyle a) => n -> a -> a
- fontSizeN :: (N a ~ n, Typeable n, Num n, HasStyle a) => n -> a -> a
- fontSizeG :: (N a ~ n, Typeable n, Num n, HasStyle a) => n -> a -> a
- fontSize :: (N a ~ n, Typeable n, HasStyle a) => Measure n -> a -> a
- _font :: Lens' (Style v n) (Maybe String)
- font :: HasStyle a => String -> a -> a
- baselineText :: (TypeableFloat n, Renderable (Text n) b) => String -> QDiagram b V2 n Any
- alignedText :: (TypeableFloat n, Renderable (Text n) b) => n -> n -> String -> QDiagram b V2 n Any
- topLeftText :: (TypeableFloat n, Renderable (Text n) b) => String -> QDiagram b V2 n Any
- text :: (TypeableFloat n, Renderable (Text n) b) => String -> QDiagram b V2 n Any
- fcA :: (InSpace V2 n a, Floating n, Typeable n, HasStyle a) => AlphaColour Double -> a -> a
- fc :: (InSpace V2 n a, Floating n, Typeable n, HasStyle a) => Colour Double -> a -> a
- recommendFillColor :: (InSpace V2 n a, Color c, Typeable n, Floating n, HasStyle a) => c -> a -> a
- fillColor :: (InSpace V2 n a, Color c, Typeable n, Floating n, HasStyle a) => c -> a -> a
- _fillTexture :: (Typeable n, Floating n) => Lens' (Style V2 n) (Texture n)
- fillTexture :: (InSpace V2 n a, Typeable n, Floating n, HasStyle a) => Texture n -> a -> a
- getFillTexture :: FillTexture n -> Texture n
- _FillTexture :: Iso' (FillTexture n) (Recommend (Texture n))
- lcA :: (InSpace V2 n a, Typeable n, Floating n, HasStyle a) => AlphaColour Double -> a -> a
- lc :: (InSpace V2 n a, Typeable n, Floating n, HasStyle a) => Colour Double -> a -> a
- lineColor :: (InSpace V2 n a, Color c, Typeable n, Floating n, HasStyle a) => c -> a -> a
- _lineTexture :: (Floating n, Typeable n) => Lens' (Style V2 n) (Texture n)
- lineTextureA :: (InSpace V2 n a, Typeable n, Floating n, HasStyle a) => LineTexture n -> a -> a
- lineTexture :: (InSpace V2 n a, Typeable n, Floating n, HasStyle a) => Texture n -> a -> a
- getLineTexture :: LineTexture n -> Texture n
- _LineTexture :: Iso (LineTexture n) (LineTexture n') (Texture n) (Texture n')
- mkRadialGradient :: Num n => [GradientStop n] -> Point V2 n -> n -> Point V2 n -> n -> SpreadMethod -> Texture n
- mkLinearGradient :: Num n => [GradientStop n] -> Point V2 n -> Point V2 n -> SpreadMethod -> Texture n
- mkStops :: [(Colour Double, d, Double)] -> [GradientStop d]
- defaultRG :: Fractional n => Texture n
- defaultLG :: Fractional n => Texture n
- solid :: Color a => a -> Texture n
- _AC :: Prism' (Texture n) (AlphaColour Double)
- _RG :: Prism' (Texture n) (RGradient n)
- _LG :: Prism' (Texture n) (LGradient n)
- _SC :: Prism' (Texture n) SomeColor
- rGradTrans :: Lens' (RGradient n) (Transformation V2 n)
- rGradStops :: Lens' (RGradient n) [GradientStop n]
- rGradSpreadMethod :: Lens' (RGradient n) SpreadMethod
- rGradRadius1 :: Lens' (RGradient n) n
- rGradRadius0 :: Lens' (RGradient n) n
- rGradCenter1 :: Lens' (RGradient n) (Point V2 n)
- rGradCenter0 :: Lens' (RGradient n) (Point V2 n)
- data Texture n
- lGradTrans :: Lens' (LGradient n) (Transformation V2 n)
- lGradStops :: Lens' (LGradient n) [GradientStop n]
- lGradStart :: Lens' (LGradient n) (Point V2 n)
- lGradSpreadMethod :: Lens' (LGradient n) SpreadMethod
- lGradEnd :: Lens' (LGradient n) (Point V2 n)
- data RGradient n = RGradient {
- _rGradStops :: [GradientStop n]
- _rGradCenter0 :: Point V2 n
- _rGradRadius0 :: n
- _rGradCenter1 :: Point V2 n
- _rGradRadius1 :: n
- _rGradTrans :: Transformation V2 n
- _rGradSpreadMethod :: SpreadMethod
- stopFraction :: Lens' (GradientStop n) n
- stopColor :: Lens' (GradientStop n) SomeColor
- data SpreadMethod
- data LGradient n = LGradient {
- _lGradStops :: [GradientStop n]
- _lGradStart :: Point V2 n
- _lGradEnd :: Point V2 n
- _lGradTrans :: Transformation V2 n
- _lGradSpreadMethod :: SpreadMethod
- data GradientStop d = GradientStop {
- _stopColor :: SomeColor
- _stopFraction :: d
- raster :: Num n => (Int -> Int -> AlphaColour Double) -> Int -> Int -> DImage n Embedded
- rasterDia :: (TypeableFloat n, Renderable (DImage n Embedded) b) => (Int -> Int -> AlphaColour Double) -> Int -> Int -> QDiagram b V2 n Any
- uncheckedImageRef :: Num n => FilePath -> Int -> Int -> DImage n External
- loadImageExt :: Num n => FilePath -> IO (Either String (DImage n External))
- loadImageEmb :: Num n => FilePath -> IO (Either String (DImage n Embedded))
- image :: (TypeableFloat n, Typeable a, Renderable (DImage n a) b) => DImage n a -> QDiagram b V2 n Any
- data Embedded
- data External
- data Native t
- data ImageData a where
- ImageRaster :: forall a. DynamicImage -> ImageData Embedded
- ImageRef :: forall a. FilePath -> ImageData External
- ImageNative :: forall a t. t -> ImageData (Native t)
- data DImage a b = DImage (ImageData b) Int Int (Transformation V2 a)
- intersectPointsT' :: OrderedField n => n -> Located (Trail V2 n) -> Located (Trail V2 n) -> [P2 n]
- intersectPointsT :: OrderedField n => Located (Trail V2 n) -> Located (Trail V2 n) -> [P2 n]
- intersectPointsP' :: OrderedField n => n -> Path V2 n -> Path V2 n -> [P2 n]
- intersectPointsP :: OrderedField n => Path V2 n -> Path V2 n -> [P2 n]
- intersectPoints' :: (InSpace V2 n t, SameSpace t s, ToPath t, ToPath s, OrderedField n) => n -> t -> s -> [P2 n]
- intersectPoints :: (InSpace V2 n t, SameSpace t s, ToPath t, ToPath s, OrderedField n) => t -> s -> [P2 n]
- clipped :: TypeableFloat n => Path V2 n -> QDiagram b V2 n Any -> QDiagram b V2 n Any
- clipTo :: TypeableFloat n => Path V2 n -> QDiagram b V2 n Any -> QDiagram b V2 n Any
- clipBy :: (HasStyle a, V a ~ V2, N a ~ n, TypeableFloat n) => Path V2 n -> a -> a
- _clip :: (Typeable n, OrderedField n) => Lens' (Style V2 n) [Path V2 n]
- _Clip :: Iso (Clip n) (Clip n') [Path V2 n] [Path V2 n']
- _fillRule :: Lens' (Style V2 n) FillRule
- fillRule :: HasStyle a => FillRule -> a -> a
- strokeLocLoop :: (TypeableFloat n, Renderable (Path V2 n) b) => Located (Trail' Loop V2 n) -> QDiagram b V2 n Any
- strokeLocLine :: (TypeableFloat n, Renderable (Path V2 n) b) => Located (Trail' Line V2 n) -> QDiagram b V2 n Any
- strokeLocT :: (TypeableFloat n, Renderable (Path V2 n) b) => Located (Trail V2 n) -> QDiagram b V2 n Any
- strokeLocTrail :: (TypeableFloat n, Renderable (Path V2 n) b) => Located (Trail V2 n) -> QDiagram b V2 n Any
- strokeLoop :: (TypeableFloat n, Renderable (Path V2 n) b) => Trail' Loop V2 n -> QDiagram b V2 n Any
- strokeLine :: (TypeableFloat n, Renderable (Path V2 n) b) => Trail' Line V2 n -> QDiagram b V2 n Any
- strokeT' :: (TypeableFloat n, Renderable (Path V2 n) b, IsName a) => StrokeOpts a -> Trail V2 n -> QDiagram b V2 n Any
- strokeTrail' :: (TypeableFloat n, Renderable (Path V2 n) b, IsName a) => StrokeOpts a -> Trail V2 n -> QDiagram b V2 n Any
- strokeT :: (TypeableFloat n, Renderable (Path V2 n) b) => Trail V2 n -> QDiagram b V2 n Any
- strokeTrail :: (TypeableFloat n, Renderable (Path V2 n) b) => Trail V2 n -> QDiagram b V2 n Any
- strokePath' :: (TypeableFloat n, Renderable (Path V2 n) b, IsName a) => StrokeOpts a -> Path V2 n -> QDiagram b V2 n Any
- strokeP' :: (TypeableFloat n, Renderable (Path V2 n) b, IsName a) => StrokeOpts a -> Path V2 n -> QDiagram b V2 n Any
- strokePath :: (TypeableFloat n, Renderable (Path V2 n) b) => Path V2 n -> QDiagram b V2 n Any
- strokeP :: (TypeableFloat n, Renderable (Path V2 n) b) => Path V2 n -> QDiagram b V2 n Any
- stroke' :: (InSpace V2 n t, ToPath t, TypeableFloat n, Renderable (Path V2 n) b, IsName a) => StrokeOpts a -> t -> QDiagram b V2 n Any
- stroke :: (InSpace V2 n t, ToPath t, TypeableFloat n, Renderable (Path V2 n) b) => t -> QDiagram b V2 n Any
- vertexNames :: Lens (StrokeOpts a) (StrokeOpts a') [[a]] [[a']]
- queryFillRule :: Lens' (StrokeOpts a) FillRule
- data FillRule
- data StrokeOpts a = StrokeOpts {
- _vertexNames :: [[a]]
- _queryFillRule :: FillRule
- roundedRect' :: (InSpace V2 n t, TrailLike t, RealFloat n) => n -> n -> RoundedRectOpts n -> t
- roundedRect :: (InSpace V2 n t, TrailLike t, RealFloat n) => n -> n -> n -> t
- radiusTR :: Lens' (RoundedRectOpts d) d
- radiusTL :: Lens' (RoundedRectOpts d) d
- radiusBR :: Lens' (RoundedRectOpts d) d
- radiusBL :: Lens' (RoundedRectOpts d) d
- dodecagon :: (InSpace V2 n t, TrailLike t) => n -> t
- hendecagon :: (InSpace V2 n t, TrailLike t) => n -> t
- decagon :: (InSpace V2 n t, TrailLike t) => n -> t
- nonagon :: (InSpace V2 n t, TrailLike t) => n -> t
- octagon :: (InSpace V2 n t, TrailLike t) => n -> t
- septagon :: (InSpace V2 n t, TrailLike t) => n -> t
- heptagon :: (InSpace V2 n t, TrailLike t) => n -> t
- hexagon :: (InSpace V2 n t, TrailLike t) => n -> t
- pentagon :: (InSpace V2 n t, TrailLike t) => n -> t
- triangle :: (InSpace V2 n t, TrailLike t) => n -> t
- eqTriangle :: (InSpace V2 n t, TrailLike t) => n -> t
- regPoly :: (InSpace V2 n t, TrailLike t) => Int -> n -> t
- rect :: (InSpace V2 n t, TrailLike t) => n -> n -> t
- square :: (InSpace V2 n t, TrailLike t) => n -> t
- unitSquare :: (InSpace V2 n t, TrailLike t) => t
- vrule :: (InSpace V2 n t, TrailLike t) => n -> t
- hrule :: (InSpace V2 n t, TrailLike t) => n -> t
- data RoundedRectOpts d = RoundedRectOpts {}
- star :: OrderedField n => StarOpts -> [Point V2 n] -> Path V2 n
- polygon :: (InSpace V2 n t, TrailLike t) => PolygonOpts n -> t
- polyTrail :: OrderedField n => PolygonOpts n -> Located (Trail V2 n)
- polyType :: Lens' (PolygonOpts n) (PolyType n)
- polyOrient :: Lens' (PolygonOpts n) (PolyOrientation n)
- polyCenter :: Lens' (PolygonOpts n) (Point V2 n)
- data StarOpts
- data PolyType n
- data PolyOrientation n
- data PolygonOpts n = PolygonOpts {
- _polyType :: PolyType n
- _polyOrient :: PolyOrientation n
- _polyCenter :: Point V2 n
- reversePath :: (Metric v, OrderedField n) => Path v n -> Path v n
- scalePath :: (HasLinearMap v, Metric v, OrderedField n) => n -> Path v n -> Path v n
- partitionPath :: (Located (Trail v n) -> Bool) -> Path v n -> (Path v n, Path v n)
- explodePath :: (V t ~ v, N t ~ n, TrailLike t) => Path v n -> [[t]]
- fixPath :: (Metric v, OrderedField n) => Path v n -> [[FixedSegment v n]]
- pathLocSegments :: (Metric v, OrderedField n) => Path v n -> [[Located (Segment Closed v n)]]
- pathCentroid :: (Metric v, OrderedField n) => Path v n -> Point v n
- pathOffsets :: (Metric v, OrderedField n) => Path v n -> [v n]
- pathVertices :: (Metric v, OrderedField n) => Path v n -> [[Point v n]]
- pathVertices' :: (Metric v, OrderedField n) => n -> Path v n -> [[Point v n]]
- pathFromLocTrail :: (Metric v, OrderedField n) => Located (Trail v n) -> Path v n
- pathFromTrailAt :: (Metric v, OrderedField n) => Trail v n -> Point v n -> Path v n
- pathFromTrail :: (Metric v, OrderedField n) => Trail v n -> Path v n
- pathTrails :: Path v n -> [Located (Trail v n)]
- newtype Path (v :: Type -> Type) n = Path [Located (Trail v n)]
- class ToPath t where
- boundaryFromMay :: (Metric v, OrderedField n, Semigroup m) => Subdiagram b v n m -> v n -> Maybe (Point v n)
- boundaryFrom :: (OrderedField n, Metric v, Semigroup m) => Subdiagram b v n m -> v n -> Point v n
- composeAligned :: (Monoid' m, Floating n, Ord n, Metric v) => (QDiagram b v n m -> QDiagram b v n m) -> ([QDiagram b v n m] -> QDiagram b v n m) -> [QDiagram b v n m] -> QDiagram b v n m
- cat' :: (InSpace v n a, Metric v, Floating n, Juxtaposable a, Monoid' a, HasOrigin a) => v n -> CatOpts n -> [a] -> a
- cat :: (InSpace v n a, Metric v, Floating n, Juxtaposable a, Monoid' a, HasOrigin a) => v n -> [a] -> a
- sep :: Lens' (CatOpts n) n
- catMethod :: Lens' (CatOpts n) CatMethod
- atPoints :: (InSpace v n a, HasOrigin a, Monoid' a) => [Point v n] -> [a] -> a
- position :: (InSpace v n a, HasOrigin a, Monoid' a) => [(Point v n, a)] -> a
- appends :: (Juxtaposable a, Monoid' a) => a -> [(Vn a, a)] -> a
- atDirection :: (InSpace v n a, Metric v, Floating n, Juxtaposable a, Semigroup a) => Direction v n -> a -> a -> a
- beside :: (Juxtaposable a, Semigroup a) => Vn a -> a -> a -> a
- beneath :: (Metric v, OrderedField n, Monoid' m) => QDiagram b v n m -> QDiagram b v n m -> QDiagram b v n m
- intrudeEnvelope :: (Metric v, OrderedField n, Monoid' m) => v n -> QDiagram b v n m -> QDiagram b v n m
- extrudeEnvelope :: (Metric v, OrderedField n, Monoid' m) => v n -> QDiagram b v n m -> QDiagram b v n m
- strut :: (Metric v, OrderedField n) => v n -> QDiagram b v n m
- frame :: (Metric v, OrderedField n, Monoid' m) => n -> QDiagram b v n m -> QDiagram b v n m
- pad :: (Metric v, OrderedField n, Monoid' m) => n -> QDiagram b v n m -> QDiagram b v n m
- phantom :: (InSpace v n a, Monoid' m, Enveloped a, Traced a) => a -> QDiagram b v n m
- withTrace :: (InSpace v n a, Metric v, OrderedField n, Monoid' m, Traced a) => a -> QDiagram b v n m -> QDiagram b v n m
- withEnvelope :: (InSpace v n a, Monoid' m, Enveloped a) => a -> QDiagram b v n m -> QDiagram b v n m
- data CatMethod
- data CatOpts n
- ellipseXY :: (TrailLike t, V t ~ V2, N t ~ n, Transformable t) => n -> n -> t
- ellipse :: (TrailLike t, V t ~ V2, N t ~ n, Transformable t) => n -> t
- circle :: (TrailLike t, V t ~ V2, N t ~ n, Transformable t) => n -> t
- unitCircle :: (TrailLike t, V t ~ V2, N t ~ n) => t
- annularWedge :: (TrailLike t, V t ~ V2, N t ~ n, RealFloat n) => n -> n -> Direction V2 n -> Angle n -> t
- arcBetween :: (TrailLike t, V t ~ V2, N t ~ n, RealFloat n) => Point V2 n -> Point V2 n -> n -> t
- wedge :: (InSpace V2 n t, OrderedField n, TrailLike t) => n -> Direction V2 n -> Angle n -> t
- arcCW :: (InSpace V2 n t, RealFloat n, TrailLike t) => Direction V2 n -> Direction V2 n -> t
- arcCCW :: (InSpace V2 n t, RealFloat n, TrailLike t) => Direction V2 n -> Direction V2 n -> t
- arc' :: (InSpace V2 n t, OrderedField n, TrailLike t) => n -> Direction V2 n -> Angle n -> t
- arc :: (InSpace V2 n t, OrderedField n, TrailLike t) => Direction V2 n -> Angle n -> t
- explodeTrail :: (V t ~ v, N t ~ n, TrailLike t) => Located (Trail v n) -> [t]
- (~~) :: (V t ~ v, N t ~ n, TrailLike t) => Point v n -> Point v n -> t
- fromVertices :: TrailLike t => [Point (V t) (N t)] -> t
- fromLocOffsets :: (V t ~ v, N t ~ n, V (v n) ~ v, N (v n) ~ n, TrailLike t) => Located [v n] -> t
- fromOffsets :: TrailLike t => [Vn t] -> t
- fromLocSegments :: TrailLike t => Located [Segment Closed (V t) (N t)] -> t
- fromSegments :: TrailLike t => [Segment Closed (V t) (N t)] -> t
- class (Metric (V t), OrderedField (N t)) => TrailLike t where
- reverseLocLoop :: (Metric v, OrderedField n) => Located (Trail' Loop v n) -> Located (Trail' Loop v n)
- reverseLoop :: (Metric v, OrderedField n) => Trail' Loop v n -> Trail' Loop v n
- reverseLocLine :: (Metric v, OrderedField n) => Located (Trail' Line v n) -> Located (Trail' Line v n)
- reverseLine :: (Metric v, OrderedField n) => Trail' Line v n -> Trail' Line v n
- reverseLocTrail :: (Metric v, OrderedField n) => Located (Trail v n) -> Located (Trail v n)
- reverseTrail :: (Metric v, OrderedField n) => Trail v n -> Trail v n
- trailLocSegments :: (Metric v, OrderedField n) => Located (Trail v n) -> [Located (Segment Closed v n)]
- unfixTrail :: (Metric v, Ord n, Floating n) => [FixedSegment v n] -> Located (Trail v n)
- fixTrail :: (Metric v, OrderedField n) => Located (Trail v n) -> [FixedSegment v n]
- loopVertices :: (Metric v, OrderedField n) => Located (Trail' Loop v n) -> [Point v n]
- loopVertices' :: (Metric v, OrderedField n) => n -> Located (Trail' Loop v n) -> [Point v n]
- lineVertices :: (Metric v, OrderedField n) => Located (Trail' Line v n) -> [Point v n]
- lineVertices' :: (Metric v, OrderedField n) => n -> Located (Trail' Line v n) -> [Point v n]
- trailVertices :: (Metric v, OrderedField n) => Located (Trail v n) -> [Point v n]
- trailVertices' :: (Metric v, OrderedField n) => n -> Located (Trail v n) -> [Point v n]
- lineOffset :: (Metric v, OrderedField n) => Trail' Line v n -> v n
- loopOffsets :: (Metric v, OrderedField n) => Trail' Loop v n -> [v n]
- lineOffsets :: Trail' Line v n -> [v n]
- trailOffset :: (Metric v, OrderedField n) => Trail v n -> v n
- trailOffsets :: (Metric v, OrderedField n) => Trail v n -> [v n]
- trailSegments :: (Metric v, OrderedField n) => Trail v n -> [Segment Closed v n]
- loopSegments :: Trail' Loop v n -> ([Segment Closed v n], Segment Open v n)
- onLineSegments :: (Metric v, OrderedField n) => ([Segment Closed v n] -> [Segment Closed v n]) -> Trail' Line v n -> Trail' Line v n
- lineSegments :: Trail' Line v n -> [Segment Closed v n]
- isLoop :: Trail v n -> Bool
- isLine :: Trail v n -> Bool
- isTrailEmpty :: (Metric v, OrderedField n) => Trail v n -> Bool
- isLineEmpty :: (Metric v, OrderedField n) => Trail' Line v n -> Bool
- cutTrail :: (Metric v, OrderedField n) => Trail v n -> Trail v n
- cutLoop :: (Metric v, OrderedField n) => Trail' Loop v n -> Trail' Line v n
- closeTrail :: Trail v n -> Trail v n
- closeLine :: Trail' Line v n -> Trail' Loop v n
- glueTrail :: (Metric v, OrderedField n) => Trail v n -> Trail v n
- glueLine :: (Metric v, OrderedField n) => Trail' Line v n -> Trail' Loop v n
- trailFromVertices :: (Metric v, OrderedField n) => [Point v n] -> Trail v n
- lineFromVertices :: (Metric v, OrderedField n) => [Point v n] -> Trail' Line v n
- trailFromOffsets :: (Metric v, OrderedField n) => [v n] -> Trail v n
- lineFromOffsets :: (Metric v, OrderedField n) => [v n] -> Trail' Line v n
- trailFromSegments :: (Metric v, OrderedField n) => [Segment Closed v n] -> Trail v n
- loopFromSegments :: (Metric v, OrderedField n) => [Segment Closed v n] -> Segment Open v n -> Trail' Loop v n
- lineFromSegments :: (Metric v, OrderedField n) => [Segment Closed v n] -> Trail' Line v n
- emptyTrail :: (Metric v, OrderedField n) => Trail v n
- emptyLine :: (Metric v, OrderedField n) => Trail' Line v n
- wrapLoop :: Trail' Loop v n -> Trail v n
- wrapLine :: Trail' Line v n -> Trail v n
- wrapTrail :: Trail' l v n -> Trail v n
- onLine :: (Metric v, OrderedField n) => (Trail' Line v n -> Trail' Line v n) -> Trail v n -> Trail v n
- withLine :: (Metric v, OrderedField n) => (Trail' Line v n -> r) -> Trail v n -> r
- onTrail :: (Trail' Line v n -> Trail' l1 v n) -> (Trail' Loop v n -> Trail' l2 v n) -> Trail v n -> Trail v n
- withTrail :: (Trail' Line v n -> r) -> (Trail' Loop v n -> r) -> Trail v n -> r
- _LocLoop :: Prism' (Located (Trail v n)) (Located (Trail' Loop v n))
- _LocLine :: Prism' (Located (Trail v n)) (Located (Trail' Line v n))
- _Loop :: Prism' (Trail v n) (Trail' Loop v n)
- _Line :: Prism' (Trail v n) (Trail' Line v n)
- getSegment :: t -> GetSegment t
- withTrail' :: (Trail' Line v n -> r) -> (Trail' Loop v n -> r) -> Trail' l v n -> r
- offset :: (OrderedField n, Metric v, Measured (SegMeasure v n) t) => t -> v n
- numSegs :: (Num c, Measured (SegMeasure v n) a) => a -> c
- trailMeasure :: (SegMeasure v n :>: m, Measured (SegMeasure v n) t) => a -> (m -> a) -> t -> a
- newtype SegTree (v :: Type -> Type) n = SegTree (FingerTree (SegMeasure v n) (Segment Closed v n))
- data Line
- data Loop
- data Trail' l (v :: Type -> Type) n where
- newtype GetSegment t = GetSegment t
- newtype GetSegmentCodomain (v :: Type -> Type) n = GetSegmentCodomain (Maybe (v n, Segment Closed v n, AnIso' n n))
- data Trail (v :: Type -> Type) n where
- normalAtEnd :: (InSpace V2 n t, EndValues (Tangent t), Floating n) => t -> V2 n
- normalAtStart :: (InSpace V2 n t, EndValues (Tangent t), Floating n) => t -> V2 n
- normalAtParam :: (InSpace V2 n t, Parametric (Tangent t), Floating n) => t -> n -> V2 n
- tangentAtEnd :: EndValues (Tangent t) => t -> Vn t
- tangentAtStart :: EndValues (Tangent t) => t -> Vn t
- tangentAtParam :: Parametric (Tangent t) => t -> N t -> Vn t
- newtype Tangent t = Tangent t
- oeOffset :: Lens' (OffsetEnvelope v n) (TotalOffset v n)
- oeEnvelope :: Lens' (OffsetEnvelope v n) (Envelope v n)
- type SegMeasure (v :: Type -> Type) n = SegCount ::: (ArcLength n ::: (OffsetEnvelope v n ::: ()))
- getArcLengthBounded :: (Num n, Ord n) => n -> ArcLength n -> Interval n
- getArcLengthFun :: ArcLength n -> n -> Interval n
- getArcLengthCached :: ArcLength n -> Interval n
- fixedSegIso :: (Num n, Additive v) => Iso' (FixedSegment v n) (Located (Segment Closed v n))
- fromFixedSeg :: (Num n, Additive v) => FixedSegment v n -> Located (Segment Closed v n)
- mkFixedSeg :: (Num n, Additive v) => Located (Segment Closed v n) -> FixedSegment v n
- reverseSegment :: (Num n, Additive v) => Segment Closed v n -> Segment Closed v n
- openCubic :: v n -> v n -> Segment Open v n
- openLinear :: Segment Open v n
- segOffset :: Segment Closed v n -> v n
- bézier3 :: v n -> v n -> v n -> Segment Closed v n
- bezier3 :: v n -> v n -> v n -> Segment Closed v n
- straight :: v n -> Segment Closed v n
- mapSegmentVectors :: (v n -> v' n') -> Segment c v n -> Segment c v' n'
- data Open
- data Closed
- data Offset c (v :: Type -> Type) n where
- OffsetOpen :: forall c (v :: Type -> Type) n. Offset Open v n
- OffsetClosed :: forall c (v :: Type -> Type) n. v n -> Offset Closed v n
- data Segment c (v :: Type -> Type) n
- data FixedSegment (v :: Type -> Type) n
- newtype SegCount = SegCount (Sum Int)
- newtype ArcLength n = ArcLength (Sum (Interval n), n -> Sum (Interval n))
- newtype TotalOffset (v :: Type -> Type) n = TotalOffset (v n)
- data OffsetEnvelope (v :: Type -> Type) n = OffsetEnvelope {
- _oeOffset :: !(TotalOffset v n)
- _oeEnvelope :: Envelope v n
- _loc :: Lens' (Located a) (Point (V a) (N a))
- located :: SameSpace a b => Lens (Located a) (Located b) a b
- mapLoc :: SameSpace a b => (a -> b) -> Located a -> Located b
- viewLoc :: Located a -> (Point (V a) (N a), a)
- at :: a -> Point (V a) (N a) -> Located a
- data Located a = Loc {}
- snugCenterXYZ :: (InSpace v n a, R3 v, Fractional n, Alignable a, HasOrigin a, Traced a) => a -> a
- centerXYZ :: (InSpace v n a, R3 v, Fractional n, Alignable a, HasOrigin a) => a -> a
- snugCenterYZ :: (InSpace v n a, R3 v, Fractional n, Alignable a, HasOrigin a, Traced a) => a -> a
- centerYZ :: (InSpace v n a, R3 v, Fractional n, Alignable a, HasOrigin a) => a -> a
- snugCenterXZ :: (InSpace v n a, R3 v, Fractional n, Alignable a, HasOrigin a, Traced a) => a -> a
- centerXZ :: (InSpace v n a, R3 v, Fractional n, Alignable a, HasOrigin a) => a -> a
- snugCenterZ :: (InSpace v n a, R3 v, Fractional n, Alignable a, HasOrigin a, Traced a) => a -> a
- centerZ :: (InSpace v n a, R3 v, Fractional n, Alignable a, HasOrigin a) => a -> a
- snugZ :: (V a ~ v, N a ~ n, Alignable a, Traced a, HasOrigin a, R3 v, Fractional n) => n -> a -> a
- alignZ :: (InSpace v n a, R3 v, Fractional n, Alignable a, HasOrigin a) => n -> a -> a
- snugZMax :: (InSpace v n a, R3 v, Fractional n, Alignable a, HasOrigin a, Traced a) => a -> a
- alignZMax :: (InSpace v n a, R3 v, Fractional n, Alignable a, HasOrigin a) => a -> a
- snugZMin :: (InSpace v n a, R3 v, Fractional n, Alignable a, HasOrigin a, Traced a) => a -> a
- alignZMin :: (InSpace v n a, R3 v, Fractional n, Alignable a, HasOrigin a) => a -> a
- snugYMax :: (InSpace v n a, R2 v, Fractional n, Alignable a, HasOrigin a, Traced a) => a -> a
- alignYMax :: (InSpace v n a, R2 v, Fractional n, Alignable a, HasOrigin a) => a -> a
- snugYMin :: (InSpace v n a, R2 v, Fractional n, Alignable a, HasOrigin a, Traced a) => a -> a
- alignYMin :: (InSpace v n a, R2 v, Fractional n, Alignable a, HasOrigin a) => a -> a
- snugXMax :: (InSpace v n a, R1 v, Fractional n, Alignable a, HasOrigin a, Traced a) => a -> a
- alignXMax :: (InSpace v n a, R1 v, Fractional n, Alignable a, HasOrigin a) => a -> a
- snugXMin :: (InSpace v n a, R1 v, Fractional n, Alignable a, HasOrigin a, Traced a) => a -> a
- alignXMin :: (InSpace v n a, R1 v, Fractional n, Alignable a, HasOrigin a) => a -> a
- snugCenterXY :: (InSpace v n a, R2 v, Fractional n, Alignable a, Traced a, HasOrigin a) => a -> a
- centerXY :: (InSpace v n a, R2 v, Fractional n, Alignable a, HasOrigin a) => a -> a
- snugCenterY :: (InSpace v n a, R2 v, Fractional n, Alignable a, Traced a, HasOrigin a) => a -> a
- centerY :: (InSpace v n a, R2 v, Fractional n, Alignable a, HasOrigin a) => a -> a
- snugCenterX :: (InSpace v n a, R1 v, Fractional n, Alignable a, Traced a, HasOrigin a) => a -> a
- centerX :: (InSpace v n a, R1 v, Fractional n, Alignable a, HasOrigin a) => a -> a
- snugY :: (InSpace v n a, R2 v, Fractional n, Alignable a, Traced a, HasOrigin a) => n -> a -> a
- alignY :: (InSpace v n a, R2 v, Fractional n, Alignable a, HasOrigin a) => n -> a -> a
- snugX :: (InSpace v n a, R1 v, Fractional n, Alignable a, Traced a, HasOrigin a) => n -> a -> a
- alignX :: (InSpace v n a, R1 v, Fractional n, Alignable a, HasOrigin a) => n -> a -> a
- alignBR :: (InSpace V2 n a, Fractional n, Alignable a, HasOrigin a) => a -> a
- alignBL :: (InSpace V2 n a, Fractional n, Alignable a, HasOrigin a) => a -> a
- alignTR :: (InSpace V2 n a, Fractional n, Alignable a, HasOrigin a) => a -> a
- alignTL :: (InSpace V2 n a, Fractional n, Alignable a, HasOrigin a) => a -> a
- snugB :: (InSpace V2 n a, Fractional n, Alignable a, Traced a, HasOrigin a) => a -> a
- alignB :: (InSpace V2 n a, Fractional n, Alignable a, HasOrigin a) => a -> a
- snugT :: (InSpace V2 n a, Fractional n, Alignable a, Traced a, HasOrigin a) => a -> a
- alignT :: (InSpace V2 n a, Fractional n, Alignable a, HasOrigin a) => a -> a
- snugR :: (InSpace V2 n a, Fractional n, Alignable a, Traced a, HasOrigin a) => a -> a
- alignR :: (InSpace V2 n a, Fractional n, Alignable a, HasOrigin a) => a -> a
- snugL :: (InSpace V2 n a, Fractional n, Alignable a, Traced a, HasOrigin a) => a -> a
- alignL :: (InSpace V2 n a, Fractional n, Alignable a, HasOrigin a) => a -> a
- snugCenter :: (InSpace v n a, Traversable v, Fractional n, Alignable a, HasOrigin a, Traced a) => a -> a
- snugCenterV :: (InSpace v n a, Fractional n, Alignable a, Traced a, HasOrigin a) => v n -> a -> a
- center :: (InSpace v n a, Fractional n, Traversable v, Alignable a, HasOrigin a) => a -> a
- centerV :: (InSpace v n a, Fractional n, Alignable a, HasOrigin a) => v n -> a -> a
- snug :: (InSpace v n a, Fractional n, Alignable a, Traced a, HasOrigin a) => v n -> a -> a
- snugBy :: (InSpace v n a, Fractional n, Alignable a, Traced a, HasOrigin a) => v n -> n -> a -> a
- align :: (InSpace v n a, Fractional n, Alignable a, HasOrigin a) => v n -> a -> a
- traceBoundary :: (V a ~ v, N a ~ n, Num n, Traced a) => v n -> a -> Point v n
- envelopeBoundary :: (V a ~ v, N a ~ n, Enveloped a) => v n -> a -> Point v n
- alignBy'Default :: (InSpace v n a, Fractional n, HasOrigin a) => (v n -> a -> Point v n) -> v n -> n -> a -> a
- class Alignable a where
- alignBy' :: (InSpace v n a, Fractional n, HasOrigin a) => (v n -> a -> Point v n) -> v n -> n -> a -> a
- defaultBoundary :: (V a ~ v, N a ~ n) => v n -> a -> Point v n
- alignBy :: (InSpace v n a, Fractional n, HasOrigin a) => v n -> n -> a -> a
- globalPackage :: IO FilePath
- findSandbox :: [FilePath] -> IO (Maybe FilePath)
- findHsFile :: FilePath -> IO (Maybe FilePath)
- foldB :: (a -> a -> a) -> a -> [a] -> a
- tau :: Floating a => a
- iterateN :: Int -> (a -> a) -> a -> [a]
- (##) :: AReview t b -> b -> t
- (#) :: a -> (a -> b) -> b
- applyAll :: [a -> a] -> a -> a
- with :: Default d => d
- camAspect :: (Floating n, CameraLens l) => Camera l n -> n
- camLens :: Camera l n -> l n
- camRight :: Fractional n => Camera l n -> Direction V3 n
- camUp :: Camera l n -> Direction V3 n
- camForward :: Camera l n -> Direction V3 n
- mm50Narrow :: Floating n => PerspectiveLens n
- mm50Wide :: Floating n => PerspectiveLens n
- mm50 :: Floating n => PerspectiveLens n
- facing_ZCamera :: (Floating n, Ord n, Typeable n, CameraLens l, Renderable (Camera l n) b) => l n -> QDiagram b V3 n Any
- mm50Camera :: (Typeable n, Floating n, Ord n, Renderable (Camera PerspectiveLens n) b) => QDiagram b V3 n Any
- orthoWidth :: Lens' (OrthoLens n) n
- orthoHeight :: Lens' (OrthoLens n) n
- verticalFieldOfView :: Lens' (PerspectiveLens n) (Angle n)
- horizontalFieldOfView :: Lens' (PerspectiveLens n) (Angle n)
- data OrthoLens n = OrthoLens {
- _orthoWidth :: n
- _orthoHeight :: n
- data Camera (l :: Type -> Type) n
- data PerspectiveLens n = PerspectiveLens {}
- difference :: (CsgPrim a, CsgPrim b) => a n -> b n -> CSG n
- intersection :: (CsgPrim a, CsgPrim b) => a n -> b n -> CSG n
- union :: (CsgPrim a, CsgPrim b) => a n -> b n -> CSG n
- cylinder :: Num n => Frustum n
- cone :: Num n => Frustum n
- frustum :: Num n => n -> n -> Frustum n
- cube :: Num n => Box n
- sphere :: Num n => Ellipsoid n
- data Ellipsoid n = Ellipsoid (Transformation V3 n)
- data Box n = Box (Transformation V3 n)
- data Frustum n = Frustum n n (Transformation V3 n)
- class Skinned t where
- skin :: (Renderable t b, N t ~ n, TypeableFloat n) => t -> QDiagram b V3 n Any
- data CSG n
- = CsgEllipsoid (Ellipsoid n)
- | CsgBox (Box n)
- | CsgFrustum (Frustum n)
- | CsgUnion [CSG n]
- | CsgIntersection [CSG n]
- | CsgDifference (CSG n) (CSG n)
- zDir :: (R3 v, Additive v, Num n) => Direction v n
- unit_Z :: (R3 v, Additive v, Num n) => v n
- unitZ :: (R3 v, Additive v, Num n) => v n
- reflectAcross :: (InSpace v n t, Metric v, Fractional n, Transformable t) => Point v n -> v n -> t -> t
- reflectionAcross :: (Metric v, Fractional n) => Point v n -> v n -> Transformation v n
- reflectZ :: (InSpace v n t, R3 v, Transformable t) => t -> t
- reflectionZ :: (Additive v, R3 v, Num n) => Transformation v n
- translateZ :: (InSpace v n t, R3 v, Transformable t) => n -> t -> t
- translationZ :: (Additive v, R3 v, Num n) => n -> Transformation v n
- scaleZ :: (InSpace v n t, R3 v, Fractional n, Transformable t) => n -> t -> t
- scalingZ :: (Additive v, R3 v, Fractional n) => n -> Transformation v n
- pointAt' :: (Floating n, Ord n) => V3 n -> V3 n -> V3 n -> Transformation V3 n
- pointAt :: (Floating n, Ord n) => Direction V3 n -> Direction V3 n -> Direction V3 n -> Transformation V3 n
- rotateAbout :: (InSpace V3 n t, Floating n, Transformable t) => Point V3 n -> Direction V3 n -> Angle n -> t -> t
- rotationAbout :: Floating n => Point V3 n -> Direction V3 n -> Angle n -> Transformation V3 n
- aboutY :: Floating n => Angle n -> Transformation V3 n
- aboutX :: Floating n => Angle n -> Transformation V3 n
- aboutZ :: Floating n => Angle n -> Transformation V3 n
- shearY :: (InSpace V2 n t, Transformable t) => n -> t -> t
- shearingY :: Num n => n -> T2 n
- shearX :: (InSpace V2 n t, Transformable t) => n -> t -> t
- shearingX :: Num n => n -> T2 n
- reflectAbout :: (InSpace V2 n t, OrderedField n, Transformable t) => P2 n -> Direction V2 n -> t -> t
- reflectionAbout :: OrderedField n => P2 n -> Direction V2 n -> T2 n
- reflectXY :: (InSpace v n t, R2 v, Transformable t) => t -> t
- reflectionXY :: (Additive v, R2 v, Num n) => Transformation v n
- reflectY :: (InSpace v n t, R2 v, Transformable t) => t -> t
- reflectionY :: (Additive v, R2 v, Num n) => Transformation v n
- reflectX :: (InSpace v n t, R1 v, Transformable t) => t -> t
- reflectionX :: (Additive v, R1 v, Num n) => Transformation v n
- scaleRotateTo :: (InSpace V2 n t, Transformable t, Floating n) => V2 n -> t -> t
- scalingRotationTo :: Floating n => V2 n -> T2 n
- translateY :: (InSpace v n t, R2 v, Transformable t) => n -> t -> t
- translationY :: (Additive v, R2 v, Num n) => n -> Transformation v n
- translateX :: (InSpace v n t, R1 v, Transformable t) => n -> t -> t
- translationX :: (Additive v, R1 v, Num n) => n -> Transformation v n
- scaleUToY :: (InSpace v n t, R2 v, Enveloped t, Transformable t) => n -> t -> t
- scaleUToX :: (InSpace v n t, R1 v, Enveloped t, Transformable t) => n -> t -> t
- scaleToY :: (InSpace v n t, R2 v, Enveloped t, Transformable t) => n -> t -> t
- scaleToX :: (InSpace v n t, R2 v, Enveloped t, Transformable t) => n -> t -> t
- scaleY :: (InSpace v n t, R2 v, Fractional n, Transformable t) => n -> t -> t
- scalingY :: (Additive v, R2 v, Fractional n) => n -> Transformation v n
- scaleX :: (InSpace v n t, R2 v, Fractional n, Transformable t) => n -> t -> t
- scalingX :: (Additive v, R1 v, Fractional n) => n -> Transformation v n
- rotateTo :: (InSpace V2 n t, OrderedField n, Transformable t) => Direction V2 n -> t -> t
- rotationTo :: OrderedField n => Direction V2 n -> T2 n
- rotateAround :: (InSpace V2 n t, Transformable t, Floating n) => P2 n -> Angle n -> t -> t
- rotationAround :: Floating n => P2 n -> Angle n -> T2 n
- rotated :: (InSpace V2 n a, Floating n, SameSpace a b, Transformable a, Transformable b) => Angle n -> Iso a b a b
- rotateBy :: (InSpace V2 n t, Transformable t, Floating n) => n -> t -> t
- signedAngleBetweenDirs :: RealFloat n => Direction V2 n -> Direction V2 n -> Angle n
- signedAngleBetween :: RealFloat n => V2 n -> V2 n -> Angle n
- leftTurn :: (Num n, Ord n) => V2 n -> V2 n -> Bool
- angleV :: Floating n => Angle n -> V2 n
- angleDir :: Floating n => Angle n -> Direction V2 n
- yDir :: (R2 v, Additive v, Num n) => Direction v n
- xDir :: (R1 v, Additive v, Num n) => Direction v n
- unit_Y :: (R2 v, Additive v, Num n) => v n
- unitY :: (R2 v, Additive v, Num n) => v n
- unit_X :: (R1 v, Additive v, Num n) => v n
- unitX :: (R1 v, Additive v, Num n) => v n
- parallelLight :: (Typeable n, OrderedField n, Renderable (ParallelLight n) b) => Direction V3 n -> Colour Double -> QDiagram b V3 n Any
- pointLight :: (Typeable n, Num n, Ord n, Renderable (PointLight n) b) => Colour Double -> QDiagram b V3 n Any
- data PointLight n = PointLight (Point V3 n) (Colour Double)
- data ParallelLight n = ParallelLight (V3 n) (Colour Double)
- r3CylindricalIso :: RealFloat n => Iso' (V3 n) (n, Angle n, n)
- r3SphericalIso :: RealFloat n => Iso' (V3 n) (n, Angle n, Angle n)
- mkP3 :: n -> n -> n -> P3 n
- p3Iso :: Iso' (P3 n) (n, n, n)
- unp3 :: P3 n -> (n, n, n)
- p3 :: (n, n, n) -> P3 n
- unr3 :: V3 n -> (n, n, n)
- mkR3 :: n -> n -> n -> V3 n
- r3 :: (n, n, n) -> V3 n
- r3Iso :: Iso' (V3 n) (n, n, n)
- type P3 = Point V3
- type T3 = Transformation V3
- r2PolarIso :: RealFloat n => Iso' (V2 n) (n, Angle n)
- mkP2 :: n -> n -> P2 n
- unp2 :: P2 n -> (n, n)
- p2 :: (n, n) -> P2 n
- mkR2 :: n -> n -> V2 n
- unr2 :: V2 n -> (n, n)
- r2 :: (n, n) -> V2 n
- type P2 = Point V2
- type T2 = Transformation V2
- class HasR (t :: Type -> Type) where
- translated :: (InSpace v n a, SameSpace a b, Transformable a, Transformable b) => v n -> Iso a b a b
- movedFrom :: (InSpace v n a, SameSpace a b, HasOrigin a, HasOrigin b) => Point v n -> Iso a b a b
- movedTo :: (InSpace v n a, SameSpace a b, HasOrigin a, HasOrigin b) => Point v n -> Iso a b a b
- transformed :: (InSpace v n a, SameSpace a b, Transformable a, Transformable b) => Transformation v n -> Iso a b a b
- underT :: (InSpace v n a, SameSpace a b, Transformable a, Transformable b) => (a -> b) -> Transformation v n -> a -> b
- conjugate :: (Additive v, Num n) => Transformation v n -> Transformation v n -> Transformation v n
- highlightSize :: Traversal' (Style v n) Double
- highlightIntensity :: Traversal' (Style v n) Double
- _highlight :: Lens' (Style v n) (Maybe Specular)
- highlight :: HasStyle d => Specular -> d -> d
- _Highlight :: Iso' Highlight Specular
- specularSize :: Lens' Specular Double
- specularIntensity :: Lens' Specular Double
- newtype Highlight = Highlight (Last Specular)
- _ambient :: Lens' (Style v n) (Maybe Double)
- ambient :: HasStyle d => Double -> d -> d
- _Ambient :: Iso' Ambient Double
- _diffuse :: Lens' (Style v n) (Maybe Double)
- diffuse :: HasStyle d => Double -> d -> d
- _Diffuse :: Iso' Diffuse Double
- _sc :: Lens' (Style v n) (Maybe (Colour Double))
- sc :: HasStyle d => Colour Double -> d -> d
- _SurfaceColor :: Iso' SurfaceColor (Colour Double)
- newtype SurfaceColor = SurfaceColor (Last (Colour Double))
- newtype Diffuse = Diffuse (Last Double)
- newtype Ambient = Ambient (Last Double)
- data Specular = Specular {}
- clearValue :: QDiagram b v n m -> QDiagram b v n Any
- resetValue :: (Eq m, Monoid m) => QDiagram b v n m -> QDiagram b v n Any
- value :: Monoid m => m -> QDiagram b v n Any -> QDiagram b v n m
- sample :: HasQuery t m => t -> Point (V t) (N t) -> m
- inquire :: HasQuery t Any => t -> Point (V t) (N t) -> Bool
- class HasQuery t m | t -> m where
- dirBetween :: (Additive v, Num n) => Point v n -> Point v n -> Direction v n
- angleBetweenDirs :: (Metric v, Floating n, Ord n) => Direction v n -> Direction v n -> Angle n
- fromDir :: (Metric v, Floating n) => Direction v n -> v n
- fromDirection :: (Metric v, Floating n) => Direction v n -> v n
- direction :: v n -> Direction v n
- _Dir :: Iso' (Direction v n) (v n)
- data Direction (v :: Type -> Type) n
- rotate :: (InSpace V2 n t, Transformable t, Floating n) => Angle n -> t -> t
- rotation :: Floating n => Angle n -> Transformation V2 n
- normalizeAngle :: (Floating n, Real n) => Angle n -> Angle n
- angleBetween :: (Metric v, Floating n, Ord n) => v n -> v n -> Angle n
- (@@) :: b -> AReview a b -> a
- atan2A' :: OrderedField n => n -> n -> Angle n
- atan2A :: RealFloat n => n -> n -> Angle n
- atanA :: Floating n => n -> Angle n
- acosA :: Floating n => n -> Angle n
- asinA :: Floating n => n -> Angle n
- tanA :: Floating n => Angle n -> n
- cosA :: Floating n => Angle n -> n
- sinA :: Floating n => Angle n -> n
- angleRatio :: Floating n => Angle n -> Angle n -> n
- quarterTurn :: Floating v => Angle v
- halfTurn :: Floating v => Angle v
- fullTurn :: Floating v => Angle v
- deg :: Floating n => Iso' (Angle n) n
- turn :: Floating n => Iso' (Angle n) n
- rad :: Iso' (Angle n) n
- data Angle n
- class HasTheta (t :: Type -> Type) where
- class HasTheta t => HasPhi (t :: Type -> Type) where
- class Coordinates c where
- type FinalCoord c :: Type
- type PrevDim c :: Type
- type Decomposition c :: Type
- (^&) :: PrevDim c -> FinalCoord c -> c
- pr :: PrevDim c -> FinalCoord c -> c
- coords :: c -> Decomposition c
- data a :& b = a :& b
- centroid :: (Additive v, Fractional n) => [Point v n] -> Point v n
- adjust :: (N t ~ n, Sectionable t, HasArcLength t, Fractional n) => t -> AdjustOpts n -> t
- adjSide :: Lens' (AdjustOpts n) AdjustSide
- adjMethod :: Lens' (AdjustOpts n) (AdjustMethod n)
- adjEps :: Lens' (AdjustOpts n) n
- data AdjustMethod n
- = ByParam n
- | ByAbsolute n
- | ToAbsolute n
- data AdjustSide
- data AdjustOpts n
- stdTolerance :: Fractional a => a
- domainBounds :: DomainBounds p => p -> (N p, N p)
- type family Codomain p :: Type -> Type
- class Parametric p where
- class DomainBounds p where
- domainLower :: p -> N p
- domainUpper :: p -> N p
- class (Parametric p, DomainBounds p) => EndValues p where
- class DomainBounds p => Sectionable p where
- splitAtParam :: p -> N p -> (p, p)
- section :: p -> N p -> N p -> p
- reverseDomain :: p -> p
- class Parametric p => HasArcLength p where
- arcLengthBounded :: N p -> p -> Interval (N p)
- arcLength :: N p -> p -> N p
- stdArcLength :: p -> N p
- arcLengthToParam :: N p -> p -> N p -> N p
- stdArcLengthToParam :: p -> N p -> N p
- namePoint :: (IsName nm, Metric v, OrderedField n, Semigroup m) => (QDiagram b v n m -> Point v n) -> nm -> QDiagram b v n m -> QDiagram b v n m
- named :: (IsName nm, Metric v, OrderedField n, Semigroup m) => nm -> QDiagram b v n m -> QDiagram b v n m
- committed :: Iso (Recommend a) (Recommend b) a b
- isCommitted :: Lens' (Recommend a) Bool
- _recommend :: Lens (Recommend a) (Recommend b) a b
- _Commit :: Prism' (Recommend a) a
- _Recommend :: Prism' (Recommend a) a
- _lineMiterLimit :: Lens' (Style v n) Double
- lineMiterLimitA :: HasStyle a => LineMiterLimit -> a -> a
- lineMiterLimit :: HasStyle a => Double -> a -> a
- getLineMiterLimit :: LineMiterLimit -> Double
- _LineMiterLimit :: Iso' LineMiterLimit Double
- _lineJoin :: Lens' (Style v n) LineJoin
- lineJoin :: HasStyle a => LineJoin -> a -> a
- getLineJoin :: LineJoin -> LineJoin
- _lineCap :: Lens' (Style v n) LineCap
- lineCap :: HasStyle a => LineCap -> a -> a
- getLineCap :: LineCap -> LineCap
- _strokeOpacity :: Lens' (Style v n) Double
- strokeOpacity :: HasStyle a => Double -> a -> a
- getStrokeOpacity :: StrokeOpacity -> Double
- _StrokeOpacity :: Iso' StrokeOpacity Double
- _fillOpacity :: Lens' (Style v n) Double
- fillOpacity :: HasStyle a => Double -> a -> a
- getFillOpacity :: FillOpacity -> Double
- _FillOpacity :: Iso' FillOpacity Double
- _opacity :: Lens' (Style v n) Double
- opacity :: HasStyle a => Double -> a -> a
- getOpacity :: Opacity -> Double
- _Opacity :: Iso' Opacity Double
- colorToRGBA :: Color c => c -> (Double, Double, Double, Double)
- colorToSRGBA :: Color c => c -> (Double, Double, Double, Double)
- someToAlpha :: SomeColor -> AlphaColour Double
- _SomeColor :: Iso' SomeColor (AlphaColour Double)
- _dashingU :: Typeable n => Lens' (Style v n) (Maybe (Dashing n))
- _dashing :: Typeable n => Lens' (Style v n) (Maybe (Measured n (Dashing n)))
- dashingL :: (N a ~ n, HasStyle a, Typeable n, Num n) => [n] -> n -> a -> a
- dashingO :: (N a ~ n, HasStyle a, Typeable n) => [n] -> n -> a -> a
- dashingN :: (N a ~ n, HasStyle a, Typeable n, Num n) => [n] -> n -> a -> a
- dashingG :: (N a ~ n, HasStyle a, Typeable n, Num n) => [n] -> n -> a -> a
- dashing :: (N a ~ n, HasStyle a, Typeable n) => [Measure n] -> Measure n -> a -> a
- getDashing :: Dashing n -> Dashing n
- _lineWidthU :: Typeable n => Lens' (Style v n) (Maybe n)
- _lw :: (Typeable n, OrderedField n) => Lens' (Style v n) (Measure n)
- _lineWidth :: (Typeable n, OrderedField n) => Lens' (Style v n) (Measure n)
- lwL :: (N a ~ n, HasStyle a, Typeable n, Num n) => n -> a -> a
- lwO :: (N a ~ n, HasStyle a, Typeable n) => n -> a -> a
- lwN :: (N a ~ n, HasStyle a, Typeable n, Num n) => n -> a -> a
- lwG :: (N a ~ n, HasStyle a, Typeable n, Num n) => n -> a -> a
- lw :: (N a ~ n, HasStyle a, Typeable n) => Measure n -> a -> a
- lineWidthM :: (N a ~ n, HasStyle a, Typeable n) => LineWidthM n -> a -> a
- lineWidth :: (N a ~ n, HasStyle a, Typeable n) => Measure n -> a -> a
- getLineWidth :: LineWidth n -> n
- _LineWidthM :: Iso' (LineWidthM n) (Measure n)
- _LineWidth :: Iso' (LineWidth n) n
- huge :: OrderedField n => Measure n
- veryLarge :: OrderedField n => Measure n
- large :: OrderedField n => Measure n
- normal :: OrderedField n => Measure n
- small :: OrderedField n => Measure n
- verySmall :: OrderedField n => Measure n
- tiny :: OrderedField n => Measure n
- ultraThick :: OrderedField n => Measure n
- veryThick :: OrderedField n => Measure n
- thick :: OrderedField n => Measure n
- medium :: OrderedField n => Measure n
- thin :: OrderedField n => Measure n
- veryThin :: OrderedField n => Measure n
- ultraThin :: OrderedField n => Measure n
- none :: OrderedField n => Measure n
- data LineWidth n
- data Dashing n = Dashing [n] n
- class Color c where
- toAlphaColour :: c -> AlphaColour Double
- fromAlphaColour :: AlphaColour Double -> c
- data SomeColor where
- data Opacity
- data FillOpacity
- data StrokeOpacity
- data LineCap
- data LineJoin
- newtype LineMiterLimit = LineMiterLimit (Last Double)
- project :: (Metric v, Fractional a) => v a -> v a -> v a
- class R1 (t :: Type -> Type) where
- class R1 t => R2 (t :: Type -> Type) where
- data V2 a = V2 !a !a
- perp :: Num a => V2 a -> V2 a
- class R2 t => R3 (t :: Type -> Type) where
- data V3 a = V3 !a !a !a
- lensP :: Lens' (Point g a) (g a)
- class Profunctor p => Choice (p :: Type -> Type -> Type) where
- sequenceBy :: Traversable t => (forall x. x -> f x) -> (forall x y. f (x -> y) -> f x -> f y) -> t (f a) -> f (t a)
- traverseBy :: Traversable t => (forall x. x -> f x) -> (forall x y. f (x -> y) -> f x -> f y) -> (a -> f b) -> t a -> f (t b)
- foldMapBy :: Foldable t => (r -> r -> r) -> r -> (a -> r) -> t a -> r
- foldBy :: Foldable t => (a -> a -> a) -> a -> t a -> a
- class (Foldable1 t, Traversable t) => Traversable1 (t :: Type -> Type) where
- data Rightmost a
- data Leftmost a
- data Sequenced a (m :: Type -> Type)
- data Traversed a (f :: Type -> Type)
- newtype Indexed i a b = Indexed {
- runIndexed :: i -> a -> b
- class Conjoined p => Indexable i (p :: Type -> Type -> Type)
- class (Choice p, Corepresentable p, Comonad (Corep p), Traversable (Corep p), Strong p, Representable p, Monad (Rep p), MonadFix (Rep p), Distributive (Rep p), Costrong p, ArrowLoop p, ArrowApply p, ArrowChoice p, Closed p) => Conjoined (p :: Type -> Type -> Type) where
- indexing :: Indexable Int p => ((a -> Indexing f b) -> s -> Indexing f t) -> p a (f b) -> s -> f t
- indexing64 :: Indexable Int64 p => ((a -> Indexing64 f b) -> s -> Indexing64 f t) -> p a (f b) -> s -> f t
- withIndex :: (Indexable i p, Functor f) => p (i, s) (f (j, t)) -> Indexed i s (f t)
- asIndex :: (Indexable i p, Contravariant f, Functor f) => p i (f i) -> Indexed i s (f s)
- type Context' a = Context a a
- data Context a b t = Context (b -> t) a
- type Bazaar1' (p :: Type -> Type -> Type) a = Bazaar1 p a a
- newtype Bazaar1 (p :: Type -> Type -> Type) a b t = Bazaar1 {
- runBazaar1 :: forall (f :: Type -> Type). Apply f => p a (f b) -> f t
- type Bazaar' (p :: Type -> Type -> Type) a = Bazaar p a a
- newtype Bazaar (p :: Type -> Type -> Type) a b t = Bazaar {
- runBazaar :: forall (f :: Type -> Type). Applicative f => p a (f b) -> f t
- class Reversing t where
- reversing :: t -> t
- data Level i a
- data Magma i t b a
- class (Profunctor p, Bifunctor p) => Reviewable (p :: Type -> Type -> Type)
- retagged :: (Profunctor p, Bifunctor p) => p a b -> p s b
- class (Applicative f, Distributive f, Traversable f) => Settable (f :: Type -> Type)
- type Over' (p :: Type -> Type -> Type) (f :: Type -> Type) s a = Over p f s s a a
- type Over (p :: k -> Type -> Type) (f :: k1 -> Type) s (t :: k1) (a :: k) (b :: k1) = p a (f b) -> s -> f t
- type IndexedLensLike' i (f :: Type -> Type) s a = IndexedLensLike i f s s a a
- type IndexedLensLike i (f :: k -> Type) s (t :: k) a (b :: k) = forall (p :: Type -> Type -> Type). Indexable i p => p a (f b) -> s -> f t
- type LensLike' (f :: Type -> Type) s a = LensLike f s s a a
- type LensLike (f :: k -> Type) s (t :: k) a (b :: k) = (a -> f b) -> s -> f t
- type Optical' (p :: k1 -> k -> Type) (q :: k1 -> k -> Type) (f :: k1 -> k) (s :: k1) (a :: k1) = Optical p q f s s a a
- type Optical (p :: k2 -> k -> Type) (q :: k1 -> k -> Type) (f :: k3 -> k) (s :: k1) (t :: k3) (a :: k2) (b :: k3) = p a (f b) -> q s (f t)
- type Optic' (p :: k1 -> k -> Type) (f :: k1 -> k) (s :: k1) (a :: k1) = Optic p f s s a a
- type Optic (p :: k1 -> k -> Type) (f :: k2 -> k) (s :: k1) (t :: k2) (a :: k1) (b :: k2) = p a (f b) -> p s (f t)
- type Simple (f :: k -> k -> k1 -> k1 -> k2) (s :: k) (a :: k1) = f s s a a
- type IndexPreservingFold1 s a = forall (p :: Type -> Type -> Type) (f :: Type -> Type). (Conjoined p, Contravariant f, Apply f) => p a (f a) -> p s (f s)
- type IndexedFold1 i s a = forall (p :: Type -> Type -> Type) (f :: Type -> Type). (Indexable i p, Contravariant f, Apply f) => p a (f a) -> s -> f s
- type Fold1 s a = forall (f :: Type -> Type). (Contravariant f, Apply f) => (a -> f a) -> s -> f s
- type IndexPreservingFold s a = forall (p :: Type -> Type -> Type) (f :: Type -> Type). (Conjoined p, Contravariant f, Applicative f) => p a (f a) -> p s (f s)
- type IndexedFold i s a = forall (p :: Type -> Type -> Type) (f :: Type -> Type). (Indexable i p, Contravariant f, Applicative f) => p a (f a) -> s -> f s
- type Fold s a = forall (f :: Type -> Type). (Contravariant f, Applicative f) => (a -> f a) -> s -> f s
- type IndexPreservingGetter s a = forall (p :: Type -> Type -> Type) (f :: Type -> Type). (Conjoined p, Contravariant f, Functor f) => p a (f a) -> p s (f s)
- type IndexedGetter i s a = forall (p :: Type -> Type -> Type) (f :: Type -> Type). (Indexable i p, Contravariant f, Functor f) => p a (f a) -> s -> f s
- type Getter s a = forall (f :: Type -> Type). (Contravariant f, Functor f) => (a -> f a) -> s -> f s
- type As (a :: k2) = Equality' a a
- type Equality' (s :: k2) (a :: k2) = Equality s s a a
- type Equality (s :: k1) (t :: k2) (a :: k1) (b :: k2) = forall k3 (p :: k1 -> k3 -> Type) (f :: k2 -> k3). p a (f b) -> p s (f t)
- type Prism' s a = Prism s s a a
- type Prism s t a b = forall (p :: Type -> Type -> Type) (f :: Type -> Type). (Choice p, Applicative f) => p a (f b) -> p s (f t)
- type AReview t b = Optic' (Tagged :: Type -> Type -> Type) Identity t b
- type Review t b = forall (p :: Type -> Type -> Type) (f :: Type -> Type). (Choice p, Bifunctor p, Settable f) => Optic' p f t b
- type Iso' s a = Iso s s a a
- type Iso s t a b = forall (p :: Type -> Type -> Type) (f :: Type -> Type). (Profunctor p, Functor f) => p a (f b) -> p s (f t)
- type IndexPreservingSetter' s a = IndexPreservingSetter s s a a
- type IndexPreservingSetter s t a b = forall (p :: Type -> Type -> Type) (f :: Type -> Type). (Conjoined p, Settable f) => p a (f b) -> p s (f t)
- type IndexedSetter' i s a = IndexedSetter i s s a a
- type IndexedSetter i s t a b = forall (f :: Type -> Type) (p :: Type -> Type -> Type). (Indexable i p, Settable f) => p a (f b) -> s -> f t
- type Setter' s a = Setter s s a a
- type Setter s t a b = forall (f :: Type -> Type). Settable f => (a -> f b) -> s -> f t
- type IndexPreservingTraversal1' s a = IndexPreservingTraversal1 s s a a
- type IndexPreservingTraversal1 s t a b = forall (p :: Type -> Type -> Type) (f :: Type -> Type). (Conjoined p, Apply f) => p a (f b) -> p s (f t)
- type IndexPreservingTraversal' s a = IndexPreservingTraversal s s a a
- type IndexPreservingTraversal s t a b = forall (p :: Type -> Type -> Type) (f :: Type -> Type). (Conjoined p, Applicative f) => p a (f b) -> p s (f t)
- type IndexedTraversal1' i s a = IndexedTraversal1 i s s a a
- type IndexedTraversal1 i s t a b = forall (p :: Type -> Type -> Type) (f :: Type -> Type). (Indexable i p, Apply f) => p a (f b) -> s -> f t
- type IndexedTraversal' i s a = IndexedTraversal i s s a a
- type IndexedTraversal i s t a b = forall (p :: Type -> Type -> Type) (f :: Type -> Type). (Indexable i p, Applicative f) => p a (f b) -> s -> f t
- type Traversal1' s a = Traversal1 s s a a
- type Traversal1 s t a b = forall (f :: Type -> Type). Apply f => (a -> f b) -> s -> f t
- type Traversal' s a = Traversal s s a a
- type Traversal s t a b = forall (f :: Type -> Type). Applicative f => (a -> f b) -> s -> f t
- type IndexPreservingLens' s a = IndexPreservingLens s s a a
- type IndexPreservingLens s t a b = forall (p :: Type -> Type -> Type) (f :: Type -> Type). (Conjoined p, Functor f) => p a (f b) -> p s (f t)
- type IndexedLens' i s a = IndexedLens i s s a a
- type IndexedLens i s t a b = forall (f :: Type -> Type) (p :: Type -> Type -> Type). (Indexable i p, Functor f) => p a (f b) -> s -> f t
- type Lens' s a = Lens s s a a
- type Lens s t a b = forall (f :: Type -> Type). Functor f => (a -> f b) -> s -> f t
- type Setting' (p :: Type -> Type -> Type) s a = Setting p s s a a
- type Setting (p :: Type -> Type -> Type) s t a b = p a (Identity b) -> s -> Identity t
- type AnIndexedSetter' i s a = AnIndexedSetter i s s a a
- type AnIndexedSetter i s t a b = Indexed i a (Identity b) -> s -> Identity t
- type ASetter' s a = ASetter s s a a
- type ASetter s t a b = (a -> Identity b) -> s -> Identity t
- mapped :: Functor f => Setter (f a) (f b) a b
- lifted :: Monad m => Setter (m a) (m b) a b
- contramapped :: Contravariant f => Setter (f b) (f a) a b
- setting :: ((a -> b) -> s -> t) -> IndexPreservingSetter s t a b
- sets :: (Profunctor p, Profunctor q, Settable f) => (p a b -> q s t) -> Optical p q f s t a b
- cloneSetter :: ASetter s t a b -> Setter s t a b
- cloneIndexPreservingSetter :: ASetter s t a b -> IndexPreservingSetter s t a b
- cloneIndexedSetter :: AnIndexedSetter i s t a b -> IndexedSetter i s t a b
- over :: ASetter s t a b -> (a -> b) -> s -> t
- set :: ASetter s t a b -> b -> s -> t
- set' :: ASetter' s a -> a -> s -> s
- (%~) :: ASetter s t a b -> (a -> b) -> s -> t
- (.~) :: ASetter s t a b -> b -> s -> t
- (?~) :: ASetter s t a (Maybe b) -> b -> s -> t
- (<.~) :: ASetter s t a b -> b -> s -> (b, t)
- (<?~) :: ASetter s t a (Maybe b) -> b -> s -> (b, t)
- (+~) :: Num a => ASetter s t a a -> a -> s -> t
- (*~) :: Num a => ASetter s t a a -> a -> s -> t
- (-~) :: Num a => ASetter s t a a -> a -> s -> t
- (//~) :: Fractional a => ASetter s t a a -> a -> s -> t
- (^~) :: (Num a, Integral e) => ASetter s t a a -> e -> s -> t
- (^^~) :: (Fractional a, Integral e) => ASetter s t a a -> e -> s -> t
- (**~) :: Floating a => ASetter s t a a -> a -> s -> t
- (||~) :: ASetter s t Bool Bool -> Bool -> s -> t
- (&&~) :: ASetter s t Bool Bool -> Bool -> s -> t
- assign :: MonadState s m => ASetter s s a b -> b -> m ()
- (.=) :: MonadState s m => ASetter s s a b -> b -> m ()
- (%=) :: MonadState s m => ASetter s s a b -> (a -> b) -> m ()
- modifying :: MonadState s m => ASetter s s a b -> (a -> b) -> m ()
- (?=) :: MonadState s m => ASetter s s a (Maybe b) -> b -> m ()
- (+=) :: (MonadState s m, Num a) => ASetter' s a -> a -> m ()
- (-=) :: (MonadState s m, Num a) => ASetter' s a -> a -> m ()
- (*=) :: (MonadState s m, Num a) => ASetter' s a -> a -> m ()
- (//=) :: (MonadState s m, Fractional a) => ASetter' s a -> a -> m ()
- (^=) :: (MonadState s m, Num a, Integral e) => ASetter' s a -> e -> m ()
- (^^=) :: (MonadState s m, Fractional a, Integral e) => ASetter' s a -> e -> m ()
- (**=) :: (MonadState s m, Floating a) => ASetter' s a -> a -> m ()
- (&&=) :: MonadState s m => ASetter' s Bool -> Bool -> m ()
- (||=) :: MonadState s m => ASetter' s Bool -> Bool -> m ()
- (<~) :: MonadState s m => ASetter s s a b -> m b -> m ()
- (<.=) :: MonadState s m => ASetter s s a b -> b -> m b
- (<?=) :: MonadState s m => ASetter s s a (Maybe b) -> b -> m b
- (<>~) :: Monoid a => ASetter s t a a -> a -> s -> t
- (<>=) :: (MonadState s m, Monoid a) => ASetter' s a -> a -> m ()
- scribe :: (MonadWriter t m, Monoid s) => ASetter s t a b -> b -> m ()
- passing :: MonadWriter w m => Setter w w u v -> m (a, u -> v) -> m a
- ipassing :: MonadWriter w m => IndexedSetter i w w u v -> m (a, i -> u -> v) -> m a
- censoring :: MonadWriter w m => Setter w w u v -> (u -> v) -> m a -> m a
- icensoring :: MonadWriter w m => IndexedSetter i w w u v -> (i -> u -> v) -> m a -> m a
- locally :: MonadReader s m => ASetter s s a b -> (a -> b) -> m r -> m r
- ilocally :: MonadReader s m => AnIndexedSetter i s s a b -> (i -> a -> b) -> m r -> m r
- iover :: AnIndexedSetter i s t a b -> (i -> a -> b) -> s -> t
- iset :: AnIndexedSetter i s t a b -> (i -> b) -> s -> t
- isets :: ((i -> a -> b) -> s -> t) -> IndexedSetter i s t a b
- (%@~) :: AnIndexedSetter i s t a b -> (i -> a -> b) -> s -> t
- (.@~) :: AnIndexedSetter i s t a b -> (i -> b) -> s -> t
- (%@=) :: MonadState s m => AnIndexedSetter i s s a b -> (i -> a -> b) -> m ()
- imodifying :: MonadState s m => AnIndexedSetter i s s a b -> (i -> a -> b) -> m ()
- (.@=) :: MonadState s m => AnIndexedSetter i s s a b -> (i -> b) -> m ()
- assignA :: Arrow p => ASetter s t a b -> p s b -> p s t
- mapOf :: ASetter s t a b -> (a -> b) -> s -> t
- imapOf :: AnIndexedSetter i s t a b -> (i -> a -> b) -> s -> t
- type AnIndexedLens' i s a = AnIndexedLens i s s a a
- type AnIndexedLens i s t a b = Optical (Indexed i) ((->) :: Type -> Type -> Type) (Pretext (Indexed i) a b) s t a b
- type ALens' s a = ALens s s a a
- type ALens s t a b = LensLike (Pretext ((->) :: Type -> Type -> Type) a b) s t a b
- lens :: (s -> a) -> (s -> b -> t) -> Lens s t a b
- iplens :: (s -> a) -> (s -> b -> t) -> IndexPreservingLens s t a b
- ilens :: (s -> (i, a)) -> (s -> b -> t) -> IndexedLens i s t a b
- (&~) :: s -> State s a -> s
- (%%~) :: LensLike f s t a b -> (a -> f b) -> s -> f t
- (%%=) :: MonadState s m => Over p ((,) r) s s a b -> p a (r, b) -> m r
- (??) :: Functor f => f (a -> b) -> a -> f b
- choosing :: Functor f => LensLike f s t a b -> LensLike f s' t' a b -> LensLike f (Either s s') (Either t t') a b
- chosen :: IndexPreservingLens (Either a a) (Either b b) a b
- alongside :: LensLike (AlongsideLeft f b') s t a b -> LensLike (AlongsideRight f t) s' t' a' b' -> LensLike f (s, s') (t, t') (a, a') (b, b')
- locus :: IndexedComonadStore p => Lens (p a c s) (p b c s) a b
- cloneLens :: ALens s t a b -> Lens s t a b
- cloneIndexPreservingLens :: ALens s t a b -> IndexPreservingLens s t a b
- cloneIndexedLens :: AnIndexedLens i s t a b -> IndexedLens i s t a b
- (<%~) :: LensLike ((,) b) s t a b -> (a -> b) -> s -> (b, t)
- (<+~) :: Num a => LensLike ((,) a) s t a a -> a -> s -> (a, t)
- (<-~) :: Num a => LensLike ((,) a) s t a a -> a -> s -> (a, t)
- (<*~) :: Num a => LensLike ((,) a) s t a a -> a -> s -> (a, t)
- (<//~) :: Fractional a => LensLike ((,) a) s t a a -> a -> s -> (a, t)
- (<^~) :: (Num a, Integral e) => LensLike ((,) a) s t a a -> e -> s -> (a, t)
- (<^^~) :: (Fractional a, Integral e) => LensLike ((,) a) s t a a -> e -> s -> (a, t)
- (<**~) :: Floating a => LensLike ((,) a) s t a a -> a -> s -> (a, t)
- (<||~) :: LensLike ((,) Bool) s t Bool Bool -> Bool -> s -> (Bool, t)
- (<&&~) :: LensLike ((,) Bool) s t Bool Bool -> Bool -> s -> (Bool, t)
- (<<%~) :: LensLike ((,) a) s t a b -> (a -> b) -> s -> (a, t)
- (<<.~) :: LensLike ((,) a) s t a b -> b -> s -> (a, t)
- (<<?~) :: LensLike ((,) a) s t a (Maybe b) -> b -> s -> (a, t)
- (<<+~) :: Num a => LensLike' ((,) a) s a -> a -> s -> (a, s)
- (<<-~) :: Num a => LensLike' ((,) a) s a -> a -> s -> (a, s)
- (<<*~) :: Num a => LensLike' ((,) a) s a -> a -> s -> (a, s)
- (<<//~) :: Fractional a => LensLike' ((,) a) s a -> a -> s -> (a, s)
- (<<^~) :: (Num a, Integral e) => LensLike' ((,) a) s a -> e -> s -> (a, s)
- (<<^^~) :: (Fractional a, Integral e) => LensLike' ((,) a) s a -> e -> s -> (a, s)
- (<<**~) :: Floating a => LensLike' ((,) a) s a -> a -> s -> (a, s)
- (<<||~) :: LensLike' ((,) Bool) s Bool -> Bool -> s -> (Bool, s)
- (<<&&~) :: LensLike' ((,) Bool) s Bool -> Bool -> s -> (Bool, s)
- (<<<>~) :: Monoid r => LensLike' ((,) r) s r -> r -> s -> (r, s)
- (<%=) :: MonadState s m => LensLike ((,) b) s s a b -> (a -> b) -> m b
- (<+=) :: (MonadState s m, Num a) => LensLike' ((,) a) s a -> a -> m a
- (<-=) :: (MonadState s m, Num a) => LensLike' ((,) a) s a -> a -> m a
- (<*=) :: (MonadState s m, Num a) => LensLike' ((,) a) s a -> a -> m a
- (<//=) :: (MonadState s m, Fractional a) => LensLike' ((,) a) s a -> a -> m a
- (<^=) :: (MonadState s m, Num a, Integral e) => LensLike' ((,) a) s a -> e -> m a
- (<^^=) :: (MonadState s m, Fractional a, Integral e) => LensLike' ((,) a) s a -> e -> m a
- (<**=) :: (MonadState s m, Floating a) => LensLike' ((,) a) s a -> a -> m a
- (<||=) :: MonadState s m => LensLike' ((,) Bool) s Bool -> Bool -> m Bool
- (<&&=) :: MonadState s m => LensLike' ((,) Bool) s Bool -> Bool -> m Bool
- (<<%=) :: (Strong p, MonadState s m) => Over p ((,) a) s s a b -> p a b -> m a
- (<<.=) :: MonadState s m => LensLike ((,) a) s s a b -> b -> m a
- (<<?=) :: MonadState s m => LensLike ((,) a) s s a (Maybe b) -> b -> m a
- (<<+=) :: (MonadState s m, Num a) => LensLike' ((,) a) s a -> a -> m a
- (<<-=) :: (MonadState s m, Num a) => LensLike' ((,) a) s a -> a -> m a
- (<<*=) :: (MonadState s m, Num a) => LensLike' ((,) a) s a -> a -> m a
- (<<//=) :: (MonadState s m, Fractional a) => LensLike' ((,) a) s a -> a -> m a
- (<<^=) :: (MonadState s m, Num a, Integral e) => LensLike' ((,) a) s a -> e -> m a
- (<<^^=) :: (MonadState s m, Fractional a, Integral e) => LensLike' ((,) a) s a -> e -> m a
- (<<**=) :: (MonadState s m, Floating a) => LensLike' ((,) a) s a -> a -> m a
- (<<||=) :: MonadState s m => LensLike' ((,) Bool) s Bool -> Bool -> m Bool
- (<<&&=) :: MonadState s m => LensLike' ((,) Bool) s Bool -> Bool -> m Bool
- (<<<>=) :: (MonadState s m, Monoid r) => LensLike' ((,) r) s r -> r -> m r
- (<<~) :: MonadState s m => ALens s s a b -> m b -> m b
- (<<>~) :: Monoid m => LensLike ((,) m) s t m m -> m -> s -> (m, t)
- (<<>=) :: (MonadState s m, Monoid r) => LensLike' ((,) r) s r -> r -> m r
- overA :: Arrow ar => LensLike (Context a b) s t a b -> ar a b -> ar s t
- (<%@~) :: Over (Indexed i) ((,) b) s t a b -> (i -> a -> b) -> s -> (b, t)
- (<<%@~) :: Over (Indexed i) ((,) a) s t a b -> (i -> a -> b) -> s -> (a, t)
- (%%@~) :: Over (Indexed i) f s t a b -> (i -> a -> f b) -> s -> f t
- (%%@=) :: MonadState s m => Over (Indexed i) ((,) r) s s a b -> (i -> a -> (r, b)) -> m r
- (<%@=) :: MonadState s m => Over (Indexed i) ((,) b) s s a b -> (i -> a -> b) -> m b
- (<<%@=) :: MonadState s m => Over (Indexed i) ((,) a) s s a b -> (i -> a -> b) -> m a
- (^#) :: s -> ALens s t a b -> a
- storing :: ALens s t a b -> b -> s -> t
- (#~) :: ALens s t a b -> b -> s -> t
- (#%~) :: ALens s t a b -> (a -> b) -> s -> t
- (#%%~) :: Functor f => ALens s t a b -> (a -> f b) -> s -> f t
- (#=) :: MonadState s m => ALens s s a b -> b -> m ()
- (#%=) :: MonadState s m => ALens s s a b -> (a -> b) -> m ()
- (<#%~) :: ALens s t a b -> (a -> b) -> s -> (b, t)
- (<#%=) :: MonadState s m => ALens s s a b -> (a -> b) -> m b
- (#%%=) :: MonadState s m => ALens s s a b -> (a -> (r, b)) -> m r
- (<#~) :: ALens s t a b -> b -> s -> (b, t)
- (<#=) :: MonadState s m => ALens s s a b -> b -> m b
- devoid :: Over p f Void Void a b
- united :: Lens' a ()
- fusing :: Functor f => LensLike (Yoneda f) s t a b -> LensLike f s t a b
- class Field19 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field18 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field17 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field16 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field15 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field14 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field13 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field12 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field11 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field10 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field9 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field8 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field7 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field6 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field5 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field4 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field3 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field2 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field1 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- _1' :: Field1 s t a b => Lens s t a b
- _2' :: Field2 s t a b => Lens s t a b
- _3' :: Field3 s t a b => Lens s t a b
- _4' :: Field4 s t a b => Lens s t a b
- _5' :: Field5 s t a b => Lens s t a b
- _6' :: Field6 s t a b => Lens s t a b
- _7' :: Field7 s t a b => Lens s t a b
- _8' :: Field8 s t a b => Lens s t a b
- _9' :: Field9 s t a b => Lens s t a b
- _10' :: Field10 s t a b => Lens s t a b
- _11' :: Field11 s t a b => Lens s t a b
- _12' :: Field12 s t a b => Lens s t a b
- _13' :: Field13 s t a b => Lens s t a b
- _14' :: Field14 s t a b => Lens s t a b
- _15' :: Field15 s t a b => Lens s t a b
- _16' :: Field16 s t a b => Lens s t a b
- _17' :: Field17 s t a b => Lens s t a b
- _18' :: Field18 s t a b => Lens s t a b
- _19' :: Field19 s t a b => Lens s t a b
- type Accessing (p :: Type -> Type -> Type) m s a = p a (Const m a) -> s -> Const m s
- type IndexedGetting i m s a = Indexed i a (Const m a) -> s -> Const m s
- type Getting r s a = (a -> Const r a) -> s -> Const r s
- to :: (Profunctor p, Contravariant f) => (s -> a) -> Optic' p f s a
- ito :: (Indexable i p, Contravariant f) => (s -> (i, a)) -> Over' p f s a
- like :: (Profunctor p, Contravariant f, Functor f) => a -> Optic' p f s a
- ilike :: (Indexable i p, Contravariant f, Functor f) => i -> a -> Over' p f s a
- view :: MonadReader s m => Getting a s a -> m a
- views :: MonadReader s m => LensLike' (Const r :: Type -> Type) s a -> (a -> r) -> m r
- (^.) :: s -> Getting a s a -> a
- use :: MonadState s m => Getting a s a -> m a
- uses :: MonadState s m => LensLike' (Const r :: Type -> Type) s a -> (a -> r) -> m r
- listening :: MonadWriter w m => Getting u w u -> m a -> m (a, u)
- ilistening :: MonadWriter w m => IndexedGetting i (i, u) w u -> m a -> m (a, (i, u))
- listenings :: MonadWriter w m => Getting v w u -> (u -> v) -> m a -> m (a, v)
- ilistenings :: MonadWriter w m => IndexedGetting i v w u -> (i -> u -> v) -> m a -> m (a, v)
- iview :: MonadReader s m => IndexedGetting i (i, a) s a -> m (i, a)
- iviews :: MonadReader s m => IndexedGetting i r s a -> (i -> a -> r) -> m r
- iuse :: MonadState s m => IndexedGetting i (i, a) s a -> m (i, a)
- iuses :: MonadState s m => IndexedGetting i r s a -> (i -> a -> r) -> m r
- (^@.) :: s -> IndexedGetting i (i, a) s a -> (i, a)
- getting :: (Profunctor p, Profunctor q, Functor f, Contravariant f) => Optical p q f s t a b -> Optical' p q f s a
- unto :: (Profunctor p, Bifunctor p, Functor f) => (b -> t) -> Optic p f s t a b
- un :: (Profunctor p, Bifunctor p, Functor f) => Getting a s a -> Optic' p f a s
- re :: AReview t b -> Getter b t
- review :: MonadReader b m => AReview t b -> m t
- reviews :: MonadReader b m => AReview t b -> (t -> r) -> m r
- reuse :: MonadState b m => AReview t b -> m t
- reuses :: MonadState b m => AReview t b -> (t -> r) -> m r
- type APrism' s a = APrism s s a a
- type APrism s t a b = Market a b a (Identity b) -> Market a b s (Identity t)
- withPrism :: APrism s t a b -> ((b -> t) -> (s -> Either t a) -> r) -> r
- clonePrism :: APrism s t a b -> Prism s t a b
- prism :: (b -> t) -> (s -> Either t a) -> Prism s t a b
- prism' :: (b -> s) -> (s -> Maybe a) -> Prism s s a b
- without :: APrism s t a b -> APrism u v c d -> Prism (Either s u) (Either t v) (Either a c) (Either b d)
- aside :: APrism s t a b -> Prism (e, s) (e, t) (e, a) (e, b)
- below :: Traversable f => APrism' s a -> Prism' (f s) (f a)
- isn't :: APrism s t a b -> s -> Bool
- matching :: APrism s t a b -> s -> Either t a
- _Left :: Prism (Either a c) (Either b c) a b
- _Right :: Prism (Either c a) (Either c b) a b
- _Just :: Prism (Maybe a) (Maybe b) a b
- _Nothing :: Prism' (Maybe a) ()
- _Void :: Prism s s a Void
- only :: Eq a => a -> Prism' a ()
- nearly :: a -> (a -> Bool) -> Prism' a ()
- _Show :: (Read a, Show a) => Prism' String a
- folding :: Foldable f => (s -> f a) -> Fold s a
- ifolding :: (Foldable f, Indexable i p, Contravariant g, Applicative g) => (s -> f (i, a)) -> Over p g s t a b
- foldring :: (Contravariant f, Applicative f) => ((a -> f a -> f a) -> f a -> s -> f a) -> LensLike f s t a b
- ifoldring :: (Indexable i p, Contravariant f, Applicative f) => ((i -> a -> f a -> f a) -> f a -> s -> f a) -> Over p f s t a b
- folded :: Foldable f => IndexedFold Int (f a) a
- folded64 :: Foldable f => IndexedFold Int64 (f a) a
- repeated :: Apply f => LensLike' f a a
- replicated :: Int -> Fold a a
- cycled :: Apply f => LensLike f s t a b -> LensLike f s t a b
- unfolded :: (b -> Maybe (a, b)) -> Fold b a
- iterated :: Apply f => (a -> a) -> LensLike' f a a
- filtered :: (Choice p, Applicative f) => (a -> Bool) -> Optic' p f a a
- takingWhile :: (Conjoined p, Applicative f) => (a -> Bool) -> Over p (TakingWhile p f a a) s t a a -> Over p f s t a a
- droppingWhile :: (Conjoined p, Profunctor q, Applicative f) => (a -> Bool) -> Optical p q (Compose (State Bool) f) s t a a -> Optical p q f s t a a
- worded :: Applicative f => IndexedLensLike' Int f String String
- lined :: Applicative f => IndexedLensLike' Int f String String
- foldMapOf :: Getting r s a -> (a -> r) -> s -> r
- foldOf :: Getting a s a -> s -> a
- foldrOf :: Getting (Endo r) s a -> (a -> r -> r) -> r -> s -> r
- foldlOf :: Getting (Dual (Endo r)) s a -> (r -> a -> r) -> r -> s -> r
- toListOf :: Getting (Endo [a]) s a -> s -> [a]
- toNonEmptyOf :: Getting (NonEmptyDList a) s a -> s -> NonEmpty a
- (^..) :: s -> Getting (Endo [a]) s a -> [a]
- andOf :: Getting All s Bool -> s -> Bool
- orOf :: Getting Any s Bool -> s -> Bool
- anyOf :: Getting Any s a -> (a -> Bool) -> s -> Bool
- allOf :: Getting All s a -> (a -> Bool) -> s -> Bool
- noneOf :: Getting Any s a -> (a -> Bool) -> s -> Bool
- productOf :: Num a => Getting (Endo (Endo a)) s a -> s -> a
- sumOf :: Num a => Getting (Endo (Endo a)) s a -> s -> a
- traverseOf_ :: Functor f => Getting (Traversed r f) s a -> (a -> f r) -> s -> f ()
- forOf_ :: Functor f => Getting (Traversed r f) s a -> s -> (a -> f r) -> f ()
- sequenceAOf_ :: Functor f => Getting (Traversed a f) s (f a) -> s -> f ()
- traverse1Of_ :: Functor f => Getting (TraversedF r f) s a -> (a -> f r) -> s -> f ()
- for1Of_ :: Functor f => Getting (TraversedF r f) s a -> s -> (a -> f r) -> f ()
- sequence1Of_ :: Functor f => Getting (TraversedF a f) s (f a) -> s -> f ()
- mapMOf_ :: Monad m => Getting (Sequenced r m) s a -> (a -> m r) -> s -> m ()
- forMOf_ :: Monad m => Getting (Sequenced r m) s a -> s -> (a -> m r) -> m ()
- sequenceOf_ :: Monad m => Getting (Sequenced a m) s (m a) -> s -> m ()
- asumOf :: Alternative f => Getting (Endo (f a)) s (f a) -> s -> f a
- msumOf :: MonadPlus m => Getting (Endo (m a)) s (m a) -> s -> m a
- elemOf :: Eq a => Getting Any s a -> a -> s -> Bool
- notElemOf :: Eq a => Getting All s a -> a -> s -> Bool
- concatMapOf :: Getting [r] s a -> (a -> [r]) -> s -> [r]
- concatOf :: Getting [r] s [r] -> s -> [r]
- lengthOf :: Getting (Endo (Endo Int)) s a -> s -> Int
- (^?) :: s -> Getting (First a) s a -> Maybe a
- (^?!) :: HasCallStack => s -> Getting (Endo a) s a -> a
- firstOf :: Getting (Leftmost a) s a -> s -> Maybe a
- first1Of :: Getting (First a) s a -> s -> a
- lastOf :: Getting (Rightmost a) s a -> s -> Maybe a
- last1Of :: Getting (Last a) s a -> s -> a
- nullOf :: Getting All s a -> s -> Bool
- notNullOf :: Getting Any s a -> s -> Bool
- maximumOf :: Ord a => Getting (Endo (Endo (Maybe a))) s a -> s -> Maybe a
- maximum1Of :: Ord a => Getting (Max a) s a -> s -> a
- minimumOf :: Ord a => Getting (Endo (Endo (Maybe a))) s a -> s -> Maybe a
- minimum1Of :: Ord a => Getting (Min a) s a -> s -> a
- maximumByOf :: Getting (Endo (Endo (Maybe a))) s a -> (a -> a -> Ordering) -> s -> Maybe a
- minimumByOf :: Getting (Endo (Endo (Maybe a))) s a -> (a -> a -> Ordering) -> s -> Maybe a
- findOf :: Getting (Endo (Maybe a)) s a -> (a -> Bool) -> s -> Maybe a
- findMOf :: Monad m => Getting (Endo (m (Maybe a))) s a -> (a -> m Bool) -> s -> m (Maybe a)
- lookupOf :: Eq k => Getting (Endo (Maybe v)) s (k, v) -> k -> s -> Maybe v
- foldr1Of :: HasCallStack => Getting (Endo (Maybe a)) s a -> (a -> a -> a) -> s -> a
- foldl1Of :: HasCallStack => Getting (Dual (Endo (Maybe a))) s a -> (a -> a -> a) -> s -> a
- foldrOf' :: Getting (Dual (Endo (Endo r))) s a -> (a -> r -> r) -> r -> s -> r
- foldlOf' :: Getting (Endo (Endo r)) s a -> (r -> a -> r) -> r -> s -> r
- foldr1Of' :: HasCallStack => Getting (Dual (Endo (Endo (Maybe a)))) s a -> (a -> a -> a) -> s -> a
- foldl1Of' :: HasCallStack => Getting (Endo (Endo (Maybe a))) s a -> (a -> a -> a) -> s -> a
- foldrMOf :: Monad m => Getting (Dual (Endo (r -> m r))) s a -> (a -> r -> m r) -> r -> s -> m r
- foldlMOf :: Monad m => Getting (Endo (r -> m r)) s a -> (r -> a -> m r) -> r -> s -> m r
- has :: Getting Any s a -> s -> Bool
- hasn't :: Getting All s a -> s -> Bool
- pre :: Getting (First a) s a -> IndexPreservingGetter s (Maybe a)
- ipre :: IndexedGetting i (First (i, a)) s a -> IndexPreservingGetter s (Maybe (i, a))
- preview :: MonadReader s m => Getting (First a) s a -> m (Maybe a)
- ipreview :: MonadReader s m => IndexedGetting i (First (i, a)) s a -> m (Maybe (i, a))
- previews :: MonadReader s m => Getting (First r) s a -> (a -> r) -> m (Maybe r)
- ipreviews :: MonadReader s m => IndexedGetting i (First r) s a -> (i -> a -> r) -> m (Maybe r)
- preuse :: MonadState s m => Getting (First a) s a -> m (Maybe a)
- ipreuse :: MonadState s m => IndexedGetting i (First (i, a)) s a -> m (Maybe (i, a))
- preuses :: MonadState s m => Getting (First r) s a -> (a -> r) -> m (Maybe r)
- ipreuses :: MonadState s m => IndexedGetting i (First r) s a -> (i -> a -> r) -> m (Maybe r)
- ifoldMapOf :: IndexedGetting i m s a -> (i -> a -> m) -> s -> m
- ifoldrOf :: IndexedGetting i (Endo r) s a -> (i -> a -> r -> r) -> r -> s -> r
- ifoldlOf :: IndexedGetting i (Dual (Endo r)) s a -> (i -> r -> a -> r) -> r -> s -> r
- ianyOf :: IndexedGetting i Any s a -> (i -> a -> Bool) -> s -> Bool
- iallOf :: IndexedGetting i All s a -> (i -> a -> Bool) -> s -> Bool
- inoneOf :: IndexedGetting i Any s a -> (i -> a -> Bool) -> s -> Bool
- itraverseOf_ :: Functor f => IndexedGetting i (Traversed r f) s a -> (i -> a -> f r) -> s -> f ()
- iforOf_ :: Functor f => IndexedGetting i (Traversed r f) s a -> s -> (i -> a -> f r) -> f ()
- imapMOf_ :: Monad m => IndexedGetting i (Sequenced r m) s a -> (i -> a -> m r) -> s -> m ()
- iforMOf_ :: Monad m => IndexedGetting i (Sequenced r m) s a -> s -> (i -> a -> m r) -> m ()
- iconcatMapOf :: IndexedGetting i [r] s a -> (i -> a -> [r]) -> s -> [r]
- ifindOf :: IndexedGetting i (Endo (Maybe a)) s a -> (i -> a -> Bool) -> s -> Maybe a
- ifindMOf :: Monad m => IndexedGetting i (Endo (m (Maybe a))) s a -> (i -> a -> m Bool) -> s -> m (Maybe a)
- ifoldrOf' :: IndexedGetting i (Dual (Endo (r -> r))) s a -> (i -> a -> r -> r) -> r -> s -> r
- ifoldlOf' :: IndexedGetting i (Endo (r -> r)) s a -> (i -> r -> a -> r) -> r -> s -> r
- ifoldrMOf :: Monad m => IndexedGetting i (Dual (Endo (r -> m r))) s a -> (i -> a -> r -> m r) -> r -> s -> m r
- ifoldlMOf :: Monad m => IndexedGetting i (Endo (r -> m r)) s a -> (i -> r -> a -> m r) -> r -> s -> m r
- itoListOf :: IndexedGetting i (Endo [(i, a)]) s a -> s -> [(i, a)]
- (^@..) :: s -> IndexedGetting i (Endo [(i, a)]) s a -> [(i, a)]
- (^@?) :: s -> IndexedGetting i (Endo (Maybe (i, a))) s a -> Maybe (i, a)
- (^@?!) :: HasCallStack => s -> IndexedGetting i (Endo (i, a)) s a -> (i, a)
- elemIndexOf :: Eq a => IndexedGetting i (First i) s a -> a -> s -> Maybe i
- elemIndicesOf :: Eq a => IndexedGetting i (Endo [i]) s a -> a -> s -> [i]
- findIndexOf :: IndexedGetting i (First i) s a -> (a -> Bool) -> s -> Maybe i
- findIndicesOf :: IndexedGetting i (Endo [i]) s a -> (a -> Bool) -> s -> [i]
- ifiltered :: (Indexable i p, Applicative f) => (i -> a -> Bool) -> Optical' p (Indexed i) f a a
- itakingWhile :: (Indexable i p, Profunctor q, Contravariant f, Applicative f) => (i -> a -> Bool) -> Optical' (Indexed i) q (Const (Endo (f s)) :: Type -> Type) s a -> Optical' p q f s a
- idroppingWhile :: (Indexable i p, Profunctor q, Applicative f) => (i -> a -> Bool) -> Optical (Indexed i) q (Compose (State Bool) f) s t a a -> Optical p q f s t a a
- foldByOf :: Fold s a -> (a -> a -> a) -> a -> s -> a
- foldMapByOf :: Fold s a -> (r -> r -> r) -> r -> (a -> r) -> s -> r
- class Ord k => TraverseMax k (m :: Type -> Type) | m -> k where
- traverseMax :: IndexedTraversal' k (m v) v
- class Ord k => TraverseMin k (m :: Type -> Type) | m -> k where
- traverseMin :: IndexedTraversal' k (m v) v
- type Traversing1' (p :: Type -> Type -> Type) (f :: Type -> Type) s a = Traversing1 p f s s a a
- type Traversing' (p :: Type -> Type -> Type) (f :: Type -> Type) s a = Traversing p f s s a a
- type Traversing1 (p :: Type -> Type -> Type) (f :: Type -> Type) s t a b = Over p (BazaarT1 p f a b) s t a b
- type Traversing (p :: Type -> Type -> Type) (f :: Type -> Type) s t a b = Over p (BazaarT p f a b) s t a b
- type AnIndexedTraversal1' i s a = AnIndexedTraversal1 i s s a a
- type AnIndexedTraversal' i s a = AnIndexedTraversal i s s a a
- type AnIndexedTraversal1 i s t a b = Over (Indexed i) (Bazaar1 (Indexed i) a b) s t a b
- type AnIndexedTraversal i s t a b = Over (Indexed i) (Bazaar (Indexed i) a b) s t a b
- type ATraversal1' s a = ATraversal1 s s a a
- type ATraversal1 s t a b = LensLike (Bazaar1 ((->) :: Type -> Type -> Type) a b) s t a b
- type ATraversal' s a = ATraversal s s a a
- type ATraversal s t a b = LensLike (Bazaar ((->) :: Type -> Type -> Type) a b) s t a b
- traverseOf :: LensLike f s t a b -> (a -> f b) -> s -> f t
- forOf :: LensLike f s t a b -> s -> (a -> f b) -> f t
- sequenceAOf :: LensLike f s t (f b) b -> s -> f t
- mapMOf :: LensLike (WrappedMonad m) s t a b -> (a -> m b) -> s -> m t
- forMOf :: LensLike (WrappedMonad m) s t a b -> s -> (a -> m b) -> m t
- sequenceOf :: LensLike (WrappedMonad m) s t (m b) b -> s -> m t
- transposeOf :: LensLike ZipList s t [a] a -> s -> [t]
- mapAccumROf :: LensLike (Backwards (State acc)) s t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t)
- mapAccumLOf :: LensLike (State acc) s t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t)
- scanr1Of :: LensLike (Backwards (State (Maybe a))) s t a a -> (a -> a -> a) -> s -> t
- scanl1Of :: LensLike (State (Maybe a)) s t a a -> (a -> a -> a) -> s -> t
- loci :: Traversal (Bazaar ((->) :: Type -> Type -> Type) a c s) (Bazaar ((->) :: Type -> Type -> Type) b c s) a b
- iloci :: IndexedTraversal i (Bazaar (Indexed i) a c s) (Bazaar (Indexed i) b c s) a b
- partsOf :: Functor f => Traversing ((->) :: Type -> Type -> Type) f s t a a -> LensLike f s t [a] [a]
- ipartsOf :: (Indexable [i] p, Functor f) => Traversing (Indexed i) f s t a a -> Over p f s t [a] [a]
- partsOf' :: ATraversal s t a a -> Lens s t [a] [a]
- ipartsOf' :: (Indexable [i] p, Functor f) => Over (Indexed i) (Bazaar' (Indexed i) a) s t a a -> Over p f s t [a] [a]
- unsafePartsOf :: Functor f => Traversing ((->) :: Type -> Type -> Type) f s t a b -> LensLike f s t [a] [b]
- iunsafePartsOf :: (Indexable [i] p, Functor f) => Traversing (Indexed i) f s t a b -> Over p f s t [a] [b]
- unsafePartsOf' :: ATraversal s t a b -> Lens s t [a] [b]
- iunsafePartsOf' :: Over (Indexed i) (Bazaar (Indexed i) a b) s t a b -> IndexedLens [i] s t [a] [b]
- unsafeSingular :: (HasCallStack, Conjoined p, Functor f) => Traversing p f s t a b -> Over p f s t a b
- holesOf :: Conjoined p => Over p (Bazaar p a a) s t a a -> s -> [Pretext p a a t]
- holes1Of :: Conjoined p => Over p (Bazaar1 p a a) s t a a -> s -> NonEmpty (Pretext p a a t)
- both :: Bitraversable r => Traversal (r a a) (r b b) a b
- both1 :: Bitraversable1 r => Traversal1 (r a a) (r b b) a b
- taking :: (Conjoined p, Applicative f) => Int -> Traversing p f s t a a -> Over p f s t a a
- dropping :: (Conjoined p, Applicative f) => Int -> Over p (Indexing f) s t a a -> Over p f s t a a
- cloneTraversal :: ATraversal s t a b -> Traversal s t a b
- cloneIndexPreservingTraversal :: ATraversal s t a b -> IndexPreservingTraversal s t a b
- cloneIndexedTraversal :: AnIndexedTraversal i s t a b -> IndexedTraversal i s t a b
- cloneTraversal1 :: ATraversal1 s t a b -> Traversal1 s t a b
- cloneIndexPreservingTraversal1 :: ATraversal1 s t a b -> IndexPreservingTraversal1 s t a b
- cloneIndexedTraversal1 :: AnIndexedTraversal1 i s t a b -> IndexedTraversal1 i s t a b
- itraverseOf :: (Indexed i a (f b) -> s -> f t) -> (i -> a -> f b) -> s -> f t
- iforOf :: (Indexed i a (f b) -> s -> f t) -> s -> (i -> a -> f b) -> f t
- imapMOf :: Over (Indexed i) (WrappedMonad m) s t a b -> (i -> a -> m b) -> s -> m t
- iforMOf :: (Indexed i a (WrappedMonad m b) -> s -> WrappedMonad m t) -> s -> (i -> a -> m b) -> m t
- imapAccumROf :: Over (Indexed i) (Backwards (State acc)) s t a b -> (i -> acc -> a -> (acc, b)) -> acc -> s -> (acc, t)
- imapAccumLOf :: Over (Indexed i) (State acc) s t a b -> (i -> acc -> a -> (acc, b)) -> acc -> s -> (acc, t)
- traversed :: Traversable f => IndexedTraversal Int (f a) (f b) a b
- traversed1 :: Traversable1 f => IndexedTraversal1 Int (f a) (f b) a b
- traversed64 :: Traversable f => IndexedTraversal Int64 (f a) (f b) a b
- ignored :: Applicative f => pafb -> s -> f s
- elementOf :: Applicative f => LensLike (Indexing f) s t a a -> Int -> IndexedLensLike Int f s t a a
- element :: Traversable t => Int -> IndexedTraversal' Int (t a) a
- elementsOf :: Applicative f => LensLike (Indexing f) s t a a -> (Int -> Bool) -> IndexedLensLike Int f s t a a
- elements :: Traversable t => (Int -> Bool) -> IndexedTraversal' Int (t a) a
- failover :: Alternative m => LensLike ((,) Any) s t a b -> (a -> b) -> s -> m t
- ifailover :: Alternative m => Over (Indexed i) ((,) Any) s t a b -> (i -> a -> b) -> s -> m t
- failing :: (Conjoined p, Applicative f) => Traversing p f s t a b -> Over p f s t a b -> Over p f s t a b
- deepOf :: (Conjoined p, Applicative f) => LensLike f s t s t -> Traversing p f s t a b -> Over p f s t a b
- confusing :: Applicative f => LensLike (Curried (Yoneda f) (Yoneda f)) s t a b -> LensLike f s t a b
- traverseByOf :: Traversal s t a b -> (forall x. x -> f x) -> (forall x y. f (x -> y) -> f x -> f y) -> (a -> f b) -> s -> f t
- sequenceByOf :: Traversal s t (f b) b -> (forall x. x -> f x) -> (forall x y. f (x -> y) -> f x -> f y) -> s -> f t
- ilevels :: Applicative f => Traversing (Indexed i) f s t a b -> IndexedLensLike Int f s t (Level i a) (Level j b)
- type ReifiedPrism' s a = ReifiedPrism s s a a
- newtype ReifiedPrism s t a b = Prism {}
- type ReifiedIso' s a = ReifiedIso s s a a
- newtype ReifiedIso s t a b = Iso {}
- type ReifiedIndexedSetter' i s a = ReifiedIndexedSetter i s s a a
- newtype ReifiedIndexedSetter i s t a b = IndexedSetter {
- runIndexedSetter :: IndexedSetter i s t a b
- type ReifiedSetter' s a = ReifiedSetter s s a a
- newtype ReifiedSetter s t a b = Setter {}
- newtype ReifiedIndexedFold i s a = IndexedFold {
- runIndexedFold :: IndexedFold i s a
- newtype ReifiedFold s a = Fold {}
- newtype ReifiedIndexedGetter i s a = IndexedGetter {
- runIndexedGetter :: IndexedGetter i s a
- newtype ReifiedGetter s a = Getter {}
- type ReifiedTraversal' s a = ReifiedTraversal s s a a
- newtype ReifiedTraversal s t a b = Traversal {
- runTraversal :: Traversal s t a b
- type ReifiedIndexedTraversal' i s a = ReifiedIndexedTraversal i s s a a
- newtype ReifiedIndexedTraversal i s t a b = IndexedTraversal {
- runIndexedTraversal :: IndexedTraversal i s t a b
- type ReifiedIndexedLens' i s a = ReifiedIndexedLens i s s a a
- newtype ReifiedIndexedLens i s t a b = IndexedLens {
- runIndexedLens :: IndexedLens i s t a b
- type ReifiedLens' s a = ReifiedLens s s a a
- newtype ReifiedLens s t a b = Lens {}
- class (FunctorWithIndex i t, FoldableWithIndex i t, Traversable t) => TraversableWithIndex i (t :: Type -> Type) | t -> i where
- itraverse :: Applicative f => (i -> a -> f b) -> t a -> f (t b)
- itraversed :: IndexedTraversal i (t a) (t b) a b
- class Foldable f => FoldableWithIndex i (f :: Type -> Type) | f -> i where
- class Functor f => FunctorWithIndex i (f :: Type -> Type) | f -> i where
- imap :: (i -> a -> b) -> f a -> f b
- imapped :: IndexedSetter i (f a) (f b) a b
- (<.) :: Indexable i p => (Indexed i s t -> r) -> ((a -> b) -> s -> t) -> p a b -> r
- selfIndex :: Indexable a p => p a fb -> a -> fb
- reindexed :: Indexable j p => (i -> j) -> (Indexed i a b -> r) -> p a b -> r
- icompose :: Indexable p c => (i -> j -> p) -> (Indexed i s t -> r) -> (Indexed j a b -> s -> t) -> c a b -> r
- index :: (Indexable i p, Eq i, Applicative f) => i -> Optical' p (Indexed i) f a a
- iany :: FoldableWithIndex i f => (i -> a -> Bool) -> f a -> Bool
- iall :: FoldableWithIndex i f => (i -> a -> Bool) -> f a -> Bool
- inone :: FoldableWithIndex i f => (i -> a -> Bool) -> f a -> Bool
- itraverse_ :: (FoldableWithIndex i t, Applicative f) => (i -> a -> f b) -> t a -> f ()
- ifor_ :: (FoldableWithIndex i t, Applicative f) => t a -> (i -> a -> f b) -> f ()
- imapM_ :: (FoldableWithIndex i t, Monad m) => (i -> a -> m b) -> t a -> m ()
- iforM_ :: (FoldableWithIndex i t, Monad m) => t a -> (i -> a -> m b) -> m ()
- iconcatMap :: FoldableWithIndex i f => (i -> a -> [b]) -> f a -> [b]
- ifind :: FoldableWithIndex i f => (i -> a -> Bool) -> f a -> Maybe (i, a)
- ifoldrM :: (FoldableWithIndex i f, Monad m) => (i -> a -> b -> m b) -> b -> f a -> m b
- ifoldlM :: (FoldableWithIndex i f, Monad m) => (i -> b -> a -> m b) -> b -> f a -> m b
- itoList :: FoldableWithIndex i f => f a -> [(i, a)]
- ifor :: (TraversableWithIndex i t, Applicative f) => t a -> (i -> a -> f b) -> f (t b)
- imapM :: (TraversableWithIndex i t, Monad m) => (i -> a -> m b) -> t a -> m (t b)
- iforM :: (TraversableWithIndex i t, Monad m) => t a -> (i -> a -> m b) -> m (t b)
- imapAccumR :: TraversableWithIndex i t => (i -> s -> a -> (s, b)) -> s -> t a -> (s, t b)
- imapAccumL :: TraversableWithIndex i t => (i -> s -> a -> (s, b)) -> s -> t a -> (s, t b)
- ifoldMapBy :: FoldableWithIndex i t => (r -> r -> r) -> r -> (i -> a -> r) -> t a -> r
- ifoldMapByOf :: IndexedFold i t a -> (r -> r -> r) -> r -> (i -> a -> r) -> t -> r
- itraverseBy :: TraversableWithIndex i t => (forall x. x -> f x) -> (forall x y. f (x -> y) -> f x -> f y) -> (i -> a -> f b) -> t a -> f (t b)
- itraverseByOf :: IndexedTraversal i s t a b -> (forall x. x -> f x) -> (forall x y. f (x -> y) -> f x -> f y) -> (i -> a -> f b) -> s -> f t
- type AnEquality' (s :: k2) (a :: k2) = AnEquality s s a a
- type AnEquality (s :: k1) (t :: k2) (a :: k1) (b :: k2) = Identical a (Proxy b) a (Proxy b) -> Identical a (Proxy b) s (Proxy t)
- data Identical (a :: k) (b :: k1) (s :: k) (t :: k1) :: forall k k1. k -> k1 -> k -> k1 -> Type where
- runEq :: AnEquality s t a b -> Identical s t a b
- substEq :: AnEquality s t a b -> ((s ~ a) -> (t ~ b) -> r) -> r
- mapEq :: AnEquality s t a b -> f s -> f a
- fromEq :: AnEquality s t a b -> Equality b a t s
- simply :: (Optic' p f s a -> r) -> Optic' p f s a -> r
- simple :: Equality' a a
- class Strict lazy strict | lazy -> strict, strict -> lazy where
- class Bifunctor p => Swapped (p :: Type -> Type -> Type) where
- type AnIso' s a = AnIso s s a a
- type AnIso s t a b = Exchange a b a (Identity b) -> Exchange a b s (Identity t)
- pattern List :: forall l. IsList l => [Item l] -> l
- pattern Reversed :: forall t. Reversing t => t -> t
- pattern Swapped :: forall (p :: Type -> Type -> Type) c d. Swapped p => p d c -> p c d
- pattern Lazy :: forall t s. Strict t s => t -> s
- pattern Strict :: forall s t. Strict s t => t -> s
- iso :: (s -> a) -> (b -> t) -> Iso s t a b
- from :: AnIso s t a b -> Iso b a t s
- withIso :: AnIso s t a b -> ((s -> a) -> (b -> t) -> r) -> r
- cloneIso :: AnIso s t a b -> Iso s t a b
- au :: Functor f => AnIso s t a b -> ((b -> t) -> f s) -> f a
- auf :: Optic (Costar f) g s t a b -> (f a -> g b) -> f s -> g t
- under :: AnIso s t a b -> (t -> s) -> b -> a
- enum :: Enum a => Iso' Int a
- mapping :: (Functor f, Functor g) => AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
- non :: Eq a => a -> Iso' (Maybe a) a
- non' :: APrism' a () -> Iso' (Maybe a) a
- anon :: a -> (a -> Bool) -> Iso' (Maybe a) a
- curried :: Iso ((a, b) -> c) ((d, e) -> f) (a -> b -> c) (d -> e -> f)
- uncurried :: Iso (a -> b -> c) (d -> e -> f) ((a, b) -> c) ((d, e) -> f)
- flipped :: Iso (a -> b -> c) (a' -> b' -> c') (b -> a -> c) (b' -> a' -> c')
- lazy :: Strict lazy strict => Iso' strict lazy
- reversed :: Reversing a => Iso' a a
- involuted :: (a -> a) -> Iso' a a
- magma :: LensLike (Mafic a b) s t a b -> Iso s u (Magma Int t b a) (Magma j u c c)
- imagma :: Over (Indexed i) (Molten i a b) s t a b -> Iso s t' (Magma i t b a) (Magma j t' c c)
- contramapping :: Contravariant f => AnIso s t a b -> Iso (f a) (f b) (f s) (f t)
- dimapping :: (Profunctor p, Profunctor q) => AnIso s t a b -> AnIso s' t' a' b' -> Iso (p a s') (q b t') (p s a') (q t b')
- lmapping :: (Profunctor p, Profunctor q) => AnIso s t a b -> Iso (p a x) (q b y) (p s x) (q t y)
- rmapping :: (Profunctor p, Profunctor q) => AnIso s t a b -> Iso (p x s) (q y t) (p x a) (q y b)
- bimapping :: (Bifunctor f, Bifunctor g) => AnIso s t a b -> AnIso s' t' a' b' -> Iso (f s s') (g t t') (f a a') (g b b')
- firsting :: (Bifunctor f, Bifunctor g) => AnIso s t a b -> Iso (f s x) (g t y) (f a x) (g b y)
- seconding :: (Bifunctor f, Bifunctor g) => AnIso s t a b -> Iso (f x s) (g y t) (f x a) (g y b)
- coerced :: (Coercible s a, Coercible t b) => Iso s t a b
- class AsEmpty a where
- pattern Empty :: forall s. AsEmpty s => s
- class Snoc s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Cons s t a b | s -> a, t -> b, s b -> t, t a -> s where
- pattern (:>) :: forall a b. Snoc a a b b => a -> b -> a
- pattern (:<) :: forall b a. Cons b b a a => a -> b -> b
- (<|) :: Cons s s a a => a -> s -> s
- cons :: Cons s s a a => a -> s -> s
- uncons :: Cons s s a a => s -> Maybe (a, s)
- _head :: Cons s s a a => Traversal' s a
- _tail :: Cons s s a a => Traversal' s s
- _init :: Snoc s s a a => Traversal' s s
- _last :: Snoc s s a a => Traversal' s a
- (|>) :: Snoc s s a a => s -> a -> s
- snoc :: Snoc s s a a => s -> a -> s
- unsnoc :: Snoc s s a a => s -> Maybe (s, a)
- class (Rewrapped s t, Rewrapped t s) => Rewrapping s t
- class Wrapped s => Rewrapped s t
- class Wrapped s where
- pattern Unwrapped :: forall t. Rewrapped t t => t -> Unwrapped t
- pattern Wrapped :: forall s. Rewrapped s s => Unwrapped s -> s
- _GWrapped' :: (Generic s, D1 d (C1 c (S1 s' (Rec0 a))) ~ Rep s, Unwrapped s ~ GUnwrapped (Rep s)) => Iso' s (Unwrapped s)
- _Unwrapped' :: Wrapped s => Iso' (Unwrapped s) s
- _Wrapped :: Rewrapping s t => Iso s t (Unwrapped s) (Unwrapped t)
- _Unwrapped :: Rewrapping s t => Iso (Unwrapped t) (Unwrapped s) t s
- op :: Wrapped s => (Unwrapped s -> s) -> s -> Unwrapped s
- _Wrapping' :: Wrapped s => (Unwrapped s -> s) -> Iso' s (Unwrapped s)
- _Unwrapping' :: Wrapped s => (Unwrapped s -> s) -> Iso' (Unwrapped s) s
- _Wrapping :: Rewrapping s t => (Unwrapped s -> s) -> Iso s t (Unwrapped s) (Unwrapped t)
- _Unwrapping :: Rewrapping s t => (Unwrapped s -> s) -> Iso (Unwrapped t) (Unwrapped s) t s
- ala :: (Functor f, Rewrapping s t) => (Unwrapped s -> s) -> ((Unwrapped t -> t) -> f s) -> f (Unwrapped s)
- alaf :: (Functor f, Functor g, Rewrapping s t) => (Unwrapped s -> s) -> (f t -> g s) -> f (Unwrapped t) -> g (Unwrapped s)
- class (Magnified m ~ Magnified n, MonadReader b m, MonadReader a n) => Magnify (m :: Type -> Type) (n :: Type -> Type) b a | m -> b, n -> a, m a -> n, n b -> m where
- class (MonadState s m, MonadState t n) => Zoom (m :: Type -> Type) (n :: Type -> Type) s t | m -> s, n -> t, m t -> n, n s -> m where
- type family Magnified (m :: Type -> Type) :: Type -> Type -> Type
- type family Zoomed (m :: Type -> Type) :: Type -> Type -> Type
- class GPlated1 (f :: k -> Type) (g :: k -> Type)
- class GPlated a (g :: k -> Type)
- class Plated a where
- plate :: Traversal' a a
- deep :: (Conjoined p, Applicative f, Plated s) => Traversing p f s s a b -> Over p f s s a b
- rewrite :: Plated a => (a -> Maybe a) -> a -> a
- rewriteOf :: ASetter a b a b -> (b -> Maybe a) -> a -> b
- rewriteOn :: Plated a => ASetter s t a a -> (a -> Maybe a) -> s -> t
- rewriteOnOf :: ASetter s t a b -> ASetter a b a b -> (b -> Maybe a) -> s -> t
- rewriteM :: (Monad m, Plated a) => (a -> m (Maybe a)) -> a -> m a
- rewriteMOf :: Monad m => LensLike (WrappedMonad m) a b a b -> (b -> m (Maybe a)) -> a -> m b
- rewriteMOn :: (Monad m, Plated a) => LensLike (WrappedMonad m) s t a a -> (a -> m (Maybe a)) -> s -> m t
- rewriteMOnOf :: Monad m => LensLike (WrappedMonad m) s t a b -> LensLike (WrappedMonad m) a b a b -> (b -> m (Maybe a)) -> s -> m t
- universe :: Plated a => a -> [a]
- universeOf :: Getting [a] a a -> a -> [a]
- universeOn :: Plated a => Getting [a] s a -> s -> [a]
- universeOnOf :: Getting [a] s a -> Getting [a] a a -> s -> [a]
- cosmos :: Plated a => Fold a a
- cosmosOf :: (Applicative f, Contravariant f) => LensLike' f a a -> LensLike' f a a
- cosmosOn :: (Applicative f, Contravariant f, Plated a) => LensLike' f s a -> LensLike' f s a
- cosmosOnOf :: (Applicative f, Contravariant f) => LensLike' f s a -> LensLike' f a a -> LensLike' f s a
- transformOn :: Plated a => ASetter s t a a -> (a -> a) -> s -> t
- transformOf :: ASetter a b a b -> (b -> b) -> a -> b
- transformOnOf :: ASetter s t a b -> ASetter a b a b -> (b -> b) -> s -> t
- transformM :: (Monad m, Plated a) => (a -> m a) -> a -> m a
- transformMOn :: (Monad m, Plated a) => LensLike (WrappedMonad m) s t a a -> (a -> m a) -> s -> m t
- transformMOf :: Monad m => LensLike (WrappedMonad m) a b a b -> (b -> m b) -> a -> m b
- transformMOnOf :: Monad m => LensLike (WrappedMonad m) s t a b -> LensLike (WrappedMonad m) a b a b -> (b -> m b) -> s -> m t
- contexts :: Plated a => a -> [Context a a a]
- contextsOf :: ATraversal' a a -> a -> [Context a a a]
- contextsOn :: Plated a => ATraversal s t a a -> s -> [Context a a t]
- contextsOnOf :: ATraversal s t a a -> ATraversal' a a -> s -> [Context a a t]
- holes :: Plated a => a -> [Pretext ((->) :: Type -> Type -> Type) a a a]
- holesOn :: Conjoined p => Over p (Bazaar p a a) s t a a -> s -> [Pretext p a a t]
- holesOnOf :: Conjoined p => LensLike (Bazaar p r r) s t a b -> Over p (Bazaar p r r) a b r r -> s -> [Pretext p r r t]
- paraOf :: Getting (Endo [a]) a a -> (a -> [r] -> r) -> a -> r
- para :: Plated a => (a -> [r] -> r) -> a -> r
- composOpFold :: Plated a => b -> (b -> b -> b) -> (a -> b) -> a -> b
- parts :: Plated a => Lens' a [a]
- gplate :: (Generic a, GPlated a (Rep a)) => Traversal' a a
- gplate1 :: (Generic1 f, GPlated1 f (Rep1 f)) => Traversal' (f a) (f a)
- class Each s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Ixed m => At m
- class Ixed m where
- ix :: Index m -> Traversal' m (IxValue m)
- type family IxValue m :: Type
- class Contains m
- type family Index s :: Type
- icontains :: Contains m => Index m -> IndexedLens' (Index m) m Bool
- iix :: Ixed m => Index m -> IndexedTraversal' (Index m) m (IxValue m)
- ixAt :: At m => Index m -> Traversal' m (IxValue m)
- sans :: At m => Index m -> m -> m
- iat :: At m => Index m -> IndexedLens' (Index m) m (Maybe (IxValue m))
- makePrisms :: Name -> DecsQ
- makeClassyPrisms :: Name -> DecsQ
- type ClassyNamer = Name -> Maybe (Name, Name)
- data DefName
- type FieldNamer = Name -> [Name] -> Name -> [DefName]
- data LensRules
- simpleLenses :: Lens' LensRules Bool
- generateSignatures :: Lens' LensRules Bool
- generateUpdateableOptics :: Lens' LensRules Bool
- generateLazyPatterns :: Lens' LensRules Bool
- createClass :: Lens' LensRules Bool
- lensField :: Lens' LensRules FieldNamer
- lensClass :: Lens' LensRules ClassyNamer
- lensRules :: LensRules
- underscoreNoPrefixNamer :: FieldNamer
- lensRulesFor :: [(String, String)] -> LensRules
- lookingupNamer :: [(String, String)] -> FieldNamer
- mappingNamer :: (String -> [String]) -> FieldNamer
- classyRules :: LensRules
- classyRules_ :: LensRules
- makeLenses :: Name -> DecsQ
- makeClassy :: Name -> DecsQ
- makeClassy_ :: Name -> DecsQ
- makeLensesFor :: [(String, String)] -> Name -> DecsQ
- makeClassyFor :: String -> String -> [(String, String)] -> Name -> DecsQ
- makeLensesWith :: LensRules -> Name -> DecsQ
- declareLenses :: DecsQ -> DecsQ
- declareLensesFor :: [(String, String)] -> DecsQ -> DecsQ
- declareClassy :: DecsQ -> DecsQ
- declareClassyFor :: [(String, (String, String))] -> [(String, String)] -> DecsQ -> DecsQ
- declarePrisms :: DecsQ -> DecsQ
- declareWrapped :: DecsQ -> DecsQ
- declareFields :: DecsQ -> DecsQ
- declareLensesWith :: LensRules -> DecsQ -> DecsQ
- makeWrapped :: Name -> DecsQ
- underscoreFields :: LensRules
- underscoreNamer :: FieldNamer
- camelCaseFields :: LensRules
- camelCaseNamer :: FieldNamer
- classUnderscoreNoPrefixFields :: LensRules
- classUnderscoreNoPrefixNamer :: FieldNamer
- abbreviatedFields :: LensRules
- abbreviatedNamer :: FieldNamer
- makeFields :: Name -> DecsQ
- makeFieldsNoPrefix :: Name -> DecsQ
- defaultFieldRules :: LensRules
- class Profunctor (p :: Type -> Type -> Type) where
- aspect :: (CameraLens l, Floating n) => l n -> n
- module Diagrams.Backend.SVG
- module Diagrams.Backend.SVG
Add Diagrams Inputs
Arguments
| :: (PandocEffects effs, Member ToPandoc effs, Member UnusedId effs) | |
| => Maybe Text | id attribute for figure. Will use next unused "figure" id if Nothing |
| -> Maybe Text | caption for figure |
| -> Double | width in pixels (?) |
| -> Double | height in pixels (?) |
| -> QDiagram SVG V2 Double Any | diagram |
| -> Sem effs Text |
Add diagram (via svg inserted as html).
re-exports
class Functor f => Applicative (f :: Type -> Type) where #
A functor with application, providing operations to
A minimal complete definition must include implementations of pure
and of either <*> or liftA2. If it defines both, then they must behave
the same as their default definitions:
(<*>) =liftA2id
liftA2f x y = f<$>x<*>y
Further, any definition must satisfy the following:
- identity
pureid<*>v = v- composition
pure(.)<*>u<*>v<*>w = u<*>(v<*>w)- homomorphism
puref<*>purex =pure(f x)- interchange
u
<*>purey =pure($y)<*>u
The other methods have the following default definitions, which may be overridden with equivalent specialized implementations:
As a consequence of these laws, the Functor instance for f will satisfy
It may be useful to note that supposing
forall x y. p (q x y) = f x . g y
it follows from the above that
liftA2p (liftA2q u v) =liftA2f u .liftA2g v
If f is also a Monad, it should satisfy
(which implies that pure and <*> satisfy the applicative functor laws).
Methods
Lift a value.
(<*>) :: f (a -> b) -> f a -> f b infixl 4 #
Sequential application.
A few functors support an implementation of <*> that is more
efficient than the default one.
liftA2 :: (a -> b -> c) -> f a -> f b -> f c #
Lift a binary function to actions.
Some functors support an implementation of liftA2 that is more
efficient than the default one. In particular, if fmap is an
expensive operation, it is likely better to use liftA2 than to
fmap over the structure and then use <*>.
(*>) :: f a -> f b -> f b infixl 4 #
Sequence actions, discarding the value of the first argument.
(<*) :: f a -> f b -> f a infixl 4 #
Sequence actions, discarding the value of the second argument.
Instances
| Applicative [] | Since: base-2.1 |
| Applicative Maybe | Since: base-2.1 |
| Applicative IO | Since: base-2.1 |
| Applicative Par1 | Since: base-4.9.0.0 |
| Applicative Q | |
| Applicative Identity | Since: base-4.8.0.0 |
| Applicative ZipList | f '<$>' 'ZipList' xs1 '<*>' ... '<*>' 'ZipList' xsN
= 'ZipList' (zipWithN f xs1 ... xsN)where (\a b c -> stimes c [a, b]) <$> ZipList "abcd" <*> ZipList "567" <*> ZipList [1..]
= ZipList (zipWith3 (\a b c -> stimes c [a, b]) "abcd" "567" [1..])
= ZipList {getZipList = ["a5","b6b6","c7c7c7"]}Since: base-2.1 |
| Applicative Active | |
| Applicative Duration | |
| Applicative IResult | |
| Applicative Result | |
| Applicative Parser | |
| Applicative Complex | Since: base-4.9.0.0 |
| Applicative Min | Since: base-4.9.0.0 |
| Applicative Max | Since: base-4.9.0.0 |
| Applicative First | Since: base-4.9.0.0 |
| Applicative Last | Since: base-4.9.0.0 |
| Applicative Option | Since: base-4.9.0.0 |
| Applicative STM | Since: base-4.8.0.0 |
| Applicative First | Since: base-4.8.0.0 |
| Applicative Last | Since: base-4.8.0.0 |
| Applicative Dual | Since: base-4.8.0.0 |
| Applicative Sum | Since: base-4.8.0.0 |
| Applicative Product | Since: base-4.8.0.0 |
| Applicative Down | Since: base-4.11.0.0 |
| Applicative ReadP | Since: base-4.6.0.0 |
| Applicative NonEmpty | Since: base-4.9.0.0 |
| Applicative MarkupM | |
| Applicative Vector | |
| Applicative Headed | |
| Applicative Headless | |
| Applicative RGB | |
| Applicative Tree | |
| Applicative Seq | Since: containers-0.5.4 |
| Applicative CryptoFailable | |
Defined in Crypto.Error.Types Methods pure :: a -> CryptoFailable a # (<*>) :: CryptoFailable (a -> b) -> CryptoFailable a -> CryptoFailable b # liftA2 :: (a -> b -> c) -> CryptoFailable a -> CryptoFailable b -> CryptoFailable c # (*>) :: CryptoFailable a -> CryptoFailable b -> CryptoFailable b # (<*) :: CryptoFailable a -> CryptoFailable b -> CryptoFailable a # | |
| Applicative Angle | |
| Applicative V2 | |
| Applicative V3 | |
| Applicative DList | |
| Applicative Lua | |
| Applicative Interval | |
| Applicative Plucker | |
| Applicative Quaternion | |
Defined in Linear.Quaternion Methods pure :: a -> Quaternion a # (<*>) :: Quaternion (a -> b) -> Quaternion a -> Quaternion b # liftA2 :: (a -> b -> c) -> Quaternion a -> Quaternion b -> Quaternion c # (*>) :: Quaternion a -> Quaternion b -> Quaternion b # (<*) :: Quaternion a -> Quaternion b -> Quaternion a # | |
| Applicative V0 | |
| Applicative V4 | |
| Applicative V1 | |
| Applicative PandocIO | |
| Applicative PandocPure | |
Defined in Text.Pandoc.Class Methods pure :: a -> PandocPure a # (<*>) :: PandocPure (a -> b) -> PandocPure a -> PandocPure b # liftA2 :: (a -> b -> c) -> PandocPure a -> PandocPure b -> PandocPure c # (*>) :: PandocPure a -> PandocPure b -> PandocPure b # (<*) :: PandocPure a -> PandocPure b -> PandocPure a # | |
| Applicative SmallArray | |
Defined in Data.Primitive.SmallArray Methods pure :: a -> SmallArray a # (<*>) :: SmallArray (a -> b) -> SmallArray a -> SmallArray b # liftA2 :: (a -> b -> c) -> SmallArray a -> SmallArray b -> SmallArray c # (*>) :: SmallArray a -> SmallArray b -> SmallArray b # (<*) :: SmallArray a -> SmallArray b -> SmallArray a # | |
| Applicative Array | |
| Applicative Stream | |
| Applicative P | Since: base-4.5.0.0 |
| Applicative (Either e) | Since: base-3.0 |
| Applicative (U1 :: Type -> Type) | Since: base-4.9.0.0 |
| Monoid a => Applicative ((,) a) | For tuples, the ("hello ", (+15)) <*> ("world!", 2002)
("hello world!",2017)Since: base-2.1 |
| Monad m => Applicative (WrappedMonad m) | Since: base-2.1 |
Defined in Control.Applicative Methods pure :: a -> WrappedMonad m a # (<*>) :: WrappedMonad m (a -> b) -> WrappedMonad m a -> WrappedMonad m b # liftA2 :: (a -> b -> c) -> WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m c # (*>) :: WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m b # (<*) :: WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m a # | |
| Applicative (Prompt p) | |
| Applicative (RecPrompt p) | |
Defined in Control.Monad.Prompt | |
| Representable f => Applicative (Co f) | |
| Applicative (Parser i) | |
| Arrow a => Applicative (ArrowMonad a) | Since: base-4.6.0.0 |
Defined in Control.Arrow Methods pure :: a0 -> ArrowMonad a a0 # (<*>) :: ArrowMonad a (a0 -> b) -> ArrowMonad a a0 -> ArrowMonad a b # liftA2 :: (a0 -> b -> c) -> ArrowMonad a a0 -> ArrowMonad a b -> ArrowMonad a c # (*>) :: ArrowMonad a a0 -> ArrowMonad a b -> ArrowMonad a b # (<*) :: ArrowMonad a a0 -> ArrowMonad a b -> ArrowMonad a a0 # | |
| Applicative (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
| Applicative (Measured n) | |
Defined in Diagrams.Core.Measure | |
| Applicative f => Applicative (Point f) | |
| (Functor m, Monad m) => Applicative (MaybeT m) | |
| Applicative (ReifiedFold s) | |
Defined in Control.Lens.Reified Methods pure :: a -> ReifiedFold s a # (<*>) :: ReifiedFold s (a -> b) -> ReifiedFold s a -> ReifiedFold s b # liftA2 :: (a -> b -> c) -> ReifiedFold s a -> ReifiedFold s b -> ReifiedFold s c # (*>) :: ReifiedFold s a -> ReifiedFold s b -> ReifiedFold s b # (<*) :: ReifiedFold s a -> ReifiedFold s b -> ReifiedFold s a # | |
| Applicative (ReifiedGetter s) | |
Defined in Control.Lens.Reified Methods pure :: a -> ReifiedGetter s a # (<*>) :: ReifiedGetter s (a -> b) -> ReifiedGetter s a -> ReifiedGetter s b # liftA2 :: (a -> b -> c) -> ReifiedGetter s a -> ReifiedGetter s b -> ReifiedGetter s c # (*>) :: ReifiedGetter s a -> ReifiedGetter s b -> ReifiedGetter s b # (<*) :: ReifiedGetter s a -> ReifiedGetter s b -> ReifiedGetter s a # | |
| Alternative f => Applicative (Cofree f) | |
| Functor f => Applicative (Free f) | |
| Applicative f => Applicative (Yoneda f) | |
| Applicative f => Applicative (Indexing f) | |
Defined in Control.Lens.Internal.Indexed | |
| Applicative f => Applicative (Indexing64 f) | |
Defined in Control.Lens.Internal.Indexed Methods pure :: a -> Indexing64 f a # (<*>) :: Indexing64 f (a -> b) -> Indexing64 f a -> Indexing64 f b # liftA2 :: (a -> b -> c) -> Indexing64 f a -> Indexing64 f b -> Indexing64 f c # (*>) :: Indexing64 f a -> Indexing64 f b -> Indexing64 f b # (<*) :: Indexing64 f a -> Indexing64 f b -> Indexing64 f a # | |
| Applicative m => Applicative (HtmlT m) | Based on the monad instance. |
| Applicative m => Applicative (ListT m) | |
| Applicative (Sem f) | |
| (Applicative (Rep p), Representable p) => Applicative (Prep p) | |
| Applicative (RVarT n) | |
| Applicative f => Applicative (WrappedApplicative f) | |
Defined in Data.Functor.Bind.Class Methods pure :: a -> WrappedApplicative f a # (<*>) :: WrappedApplicative f (a -> b) -> WrappedApplicative f a -> WrappedApplicative f b # liftA2 :: (a -> b -> c) -> WrappedApplicative f a -> WrappedApplicative f b -> WrappedApplicative f c # (*>) :: WrappedApplicative f a -> WrappedApplicative f b -> WrappedApplicative f b # (<*) :: WrappedApplicative f a -> WrappedApplicative f b -> WrappedApplicative f a # | |
| Apply f => Applicative (MaybeApply f) | |
Defined in Data.Functor.Bind.Class Methods pure :: a -> MaybeApply f a # (<*>) :: MaybeApply f (a -> b) -> MaybeApply f a -> MaybeApply f b # liftA2 :: (a -> b -> c) -> MaybeApply f a -> MaybeApply f b -> MaybeApply f c # (*>) :: MaybeApply f a -> MaybeApply f b -> MaybeApply f b # (<*) :: MaybeApply f a -> MaybeApply f b -> MaybeApply f a # | |
| Applicative f => Applicative (Rec1 f) | Since: base-4.9.0.0 |
| Applicative m => Applicative (IdentityT m) | |
Defined in Control.Monad.Trans.Identity | |
| Monoid m => Applicative (Const m :: Type -> Type) | Since: base-2.0.1 |
| Arrow a => Applicative (WrappedArrow a b) | Since: base-2.1 |
Defined in Control.Applicative Methods pure :: a0 -> WrappedArrow a b a0 # (<*>) :: WrappedArrow a b (a0 -> b0) -> WrappedArrow a b a0 -> WrappedArrow a b b0 # liftA2 :: (a0 -> b0 -> c) -> WrappedArrow a b a0 -> WrappedArrow a b b0 -> WrappedArrow a b c # (*>) :: WrappedArrow a b a0 -> WrappedArrow a b b0 -> WrappedArrow a b b0 # (<*) :: WrappedArrow a b a0 -> WrappedArrow a b b0 -> WrappedArrow a b a0 # | |
| Applicative (PromptT p m) | |
Defined in Control.Monad.Prompt | |
| Applicative (RecPromptT p m) | |
Defined in Control.Monad.Prompt Methods pure :: a -> RecPromptT p m a # (<*>) :: RecPromptT p m (a -> b) -> RecPromptT p m a -> RecPromptT p m b # liftA2 :: (a -> b -> c) -> RecPromptT p m a -> RecPromptT p m b -> RecPromptT p m c # (*>) :: RecPromptT p m a -> RecPromptT p m b -> RecPromptT p m b # (<*) :: RecPromptT p m a -> RecPromptT p m b -> RecPromptT p m a # | |
| Applicative f => Applicative (Ap f) | Since: base-4.12.0.0 |
| Applicative f => Applicative (Alt f) | Since: base-4.8.0.0 |
| Biapplicative p => Applicative (Join p) | |
| Biapplicative p => Applicative (Fix p) | |
| Applicative w => Applicative (TracedT m w) | |
Defined in Control.Comonad.Trans.Traced | |
| (Applicative f, Monad f) => Applicative (WhenMissing f x) | Equivalent to Since: containers-0.5.9 |
Defined in Data.IntMap.Internal Methods pure :: a -> WhenMissing f x a # (<*>) :: WhenMissing f x (a -> b) -> WhenMissing f x a -> WhenMissing f x b # liftA2 :: (a -> b -> c) -> WhenMissing f x a -> WhenMissing f x b -> WhenMissing f x c # (*>) :: WhenMissing f x a -> WhenMissing f x b -> WhenMissing f x b # (<*) :: WhenMissing f x a -> WhenMissing f x b -> WhenMissing f x a # | |
| Applicative (Query v n) | |
| Applicative (Indexed i a) | |
Defined in Control.Lens.Internal.Indexed | |
| (Functor m, Monad m) => Applicative (ExceptT e m) | |
Defined in Control.Monad.Trans.Except | |
| (Functor f, Monad m) => Applicative (FreeT f m) | |
Defined in Control.Monad.Trans.Free | |
| (Alternative f, Applicative w) => Applicative (CofreeT f w) | |
Defined in Control.Comonad.Trans.Cofree | |
| (Functor g, g ~ h) => Applicative (Curried g h) | |
Defined in Data.Functor.Day.Curried | |
| (Applicative f, Applicative g) => Applicative (Day f g) | |
| (Functor m, Monad m) => Applicative (ErrorT e m) | |
Defined in Control.Monad.Trans.Error | |
| (Functor m, Monad m) => Applicative (StateT s m) | |
Defined in Control.Monad.Trans.State.Strict | |
| Applicative f => Applicative (Backwards f) | Apply |
Defined in Control.Applicative.Backwards | |
| Applicative (Mafic a b) | |
Defined in Control.Lens.Internal.Magma | |
| Applicative (Flows i b) | This is an illegal |
Defined in Control.Lens.Internal.Level | |
| Dim n => Applicative (V n) | |
| Applicative m => Applicative (LoggingT message m) | |
Defined in Control.Monad.Log Methods pure :: a -> LoggingT message m a # (<*>) :: LoggingT message m (a -> b) -> LoggingT message m a -> LoggingT message m b # liftA2 :: (a -> b -> c) -> LoggingT message m a -> LoggingT message m b -> LoggingT message m c # (*>) :: LoggingT message m a -> LoggingT message m b -> LoggingT message m b # (<*) :: LoggingT message m a -> LoggingT message m b -> LoggingT message m a # | |
| Monad m => Applicative (PureLoggingT log m) | |
Defined in Control.Monad.Log Methods pure :: a -> PureLoggingT log m a # (<*>) :: PureLoggingT log m (a -> b) -> PureLoggingT log m a -> PureLoggingT log m b # liftA2 :: (a -> b -> c) -> PureLoggingT log m a -> PureLoggingT log m b -> PureLoggingT log m c # (*>) :: PureLoggingT log m a -> PureLoggingT log m b -> PureLoggingT log m b # (<*) :: PureLoggingT log m a -> PureLoggingT log m b -> PureLoggingT log m a # | |
| Applicative m => Applicative (DiscardLoggingT message m) | |
Defined in Control.Monad.Log Methods pure :: a -> DiscardLoggingT message m a # (<*>) :: DiscardLoggingT message m (a -> b) -> DiscardLoggingT message m a -> DiscardLoggingT message m b # liftA2 :: (a -> b -> c) -> DiscardLoggingT message m a -> DiscardLoggingT message m b -> DiscardLoggingT message m c # (*>) :: DiscardLoggingT message m a -> DiscardLoggingT message m b -> DiscardLoggingT message m b # (<*) :: DiscardLoggingT message m a -> DiscardLoggingT message m b -> DiscardLoggingT message m a # | |
| (Monoid w, Applicative m) => Applicative (WriterT w m) | |
Defined in Control.Monad.Trans.Writer.Lazy | |
| (Functor m, Monad m) => Applicative (StateT s m) | |
Defined in Control.Monad.Trans.State.Lazy | |
| (Monoid w, Applicative m) => Applicative (WriterT w m) | |
Defined in Control.Monad.Trans.Writer.Strict | |
| (Profunctor p, Arrow p) => Applicative (Tambara p a) | |
Defined in Data.Profunctor.Strong | |
| Applicative f => Applicative (Star f a) | |
| Applicative (Costar f a) | |
Defined in Data.Profunctor.Types | |
| Applicative (Tagged s) | |
| Applicative f => Applicative (Reverse f) | Derived instance. |
| Applicative (Mag a b) | |
| Monoid m => Applicative (Holes t m) | |
| Applicative ((->) a :: Type -> Type) | Since: base-2.1 |
| Monoid c => Applicative (K1 i c :: Type -> Type) | Since: base-4.12.0.0 |
| (Applicative f, Applicative g) => Applicative (f :*: g) | Since: base-4.9.0.0 |
| (Applicative f, Applicative g) => Applicative (Product f g) | Since: base-4.9.0.0 |
Defined in Data.Functor.Product | |
| (Monad f, Applicative f) => Applicative (WhenMatched f x y) | Equivalent to Since: containers-0.5.9 |
Defined in Data.IntMap.Internal Methods pure :: a -> WhenMatched f x y a # (<*>) :: WhenMatched f x y (a -> b) -> WhenMatched f x y a -> WhenMatched f x y b # liftA2 :: (a -> b -> c) -> WhenMatched f x y a -> WhenMatched f x y b -> WhenMatched f x y c # (*>) :: WhenMatched f x y a -> WhenMatched f x y b -> WhenMatched f x y b # (<*) :: WhenMatched f x y a -> WhenMatched f x y b -> WhenMatched f x y a # | |
| (Applicative f, Monad f) => Applicative (WhenMissing f k x) | Equivalent to Since: containers-0.5.9 |
Defined in Data.Map.Internal Methods pure :: a -> WhenMissing f k x a # (<*>) :: WhenMissing f k x (a -> b) -> WhenMissing f k x a -> WhenMissing f k x b # liftA2 :: (a -> b -> c) -> WhenMissing f k x a -> WhenMissing f k x b -> WhenMissing f k x c # (*>) :: WhenMissing f k x a -> WhenMissing f k x b -> WhenMissing f k x b # (<*) :: WhenMissing f k x a -> WhenMissing f k x b -> WhenMissing f k x a # | |
| Applicative (Bazaar p a b) | |
Defined in Control.Lens.Internal.Bazaar Methods pure :: a0 -> Bazaar p a b a0 # (<*>) :: Bazaar p a b (a0 -> b0) -> Bazaar p a b a0 -> Bazaar p a b b0 # liftA2 :: (a0 -> b0 -> c) -> Bazaar p a b a0 -> Bazaar p a b b0 -> Bazaar p a b c # (*>) :: Bazaar p a b a0 -> Bazaar p a b b0 -> Bazaar p a b b0 # (<*) :: Bazaar p a b a0 -> Bazaar p a b b0 -> Bazaar p a b a0 # | |
| Applicative (Molten i a b) | |
Defined in Control.Lens.Internal.Magma Methods pure :: a0 -> Molten i a b a0 # (<*>) :: Molten i a b (a0 -> b0) -> Molten i a b a0 -> Molten i a b b0 # liftA2 :: (a0 -> b0 -> c) -> Molten i a b a0 -> Molten i a b b0 -> Molten i a b c # (*>) :: Molten i a b a0 -> Molten i a b b0 -> Molten i a b b0 # (<*) :: Molten i a b a0 -> Molten i a b b0 -> Molten i a b a0 # | |
| Applicative m => Applicative (ReaderT r m) | |
Defined in Control.Monad.Trans.Reader | |
| Applicative (ContT r m) | |
Defined in Control.Monad.Trans.Cont | |
| Applicative (ParsecT s u m) | |
Defined in Text.Parsec.Prim Methods pure :: a -> ParsecT s u m a # (<*>) :: ParsecT s u m (a -> b) -> ParsecT s u m a -> ParsecT s u m b # liftA2 :: (a -> b -> c) -> ParsecT s u m a -> ParsecT s u m b -> ParsecT s u m c # (*>) :: ParsecT s u m a -> ParsecT s u m b -> ParsecT s u m b # (<*) :: ParsecT s u m a -> ParsecT s u m b -> ParsecT s u m a # | |
| Applicative f => Applicative (M1 i c f) | Since: base-4.9.0.0 |
| (Applicative f, Applicative g) => Applicative (f :.: g) | Since: base-4.9.0.0 |
| (Applicative f, Applicative g) => Applicative (Compose f g) | Since: base-4.9.0.0 |
Defined in Data.Functor.Compose | |
| (Monad f, Applicative f) => Applicative (WhenMatched f k x y) | Equivalent to Since: containers-0.5.9 |
Defined in Data.Map.Internal Methods pure :: a -> WhenMatched f k x y a # (<*>) :: WhenMatched f k x y (a -> b) -> WhenMatched f k x y a -> WhenMatched f k x y b # liftA2 :: (a -> b -> c) -> WhenMatched f k x y a -> WhenMatched f k x y b -> WhenMatched f k x y c # (*>) :: WhenMatched f k x y a -> WhenMatched f k x y b -> WhenMatched f k x y b # (<*) :: WhenMatched f k x y a -> WhenMatched f k x y b -> WhenMatched f k x y a # | |
| (Monoid w, Functor m, Monad m) => Applicative (RWST r w s m) | |
Defined in Control.Monad.Trans.RWS.Strict | |
| Applicative (TakingWhile p f a b) | |
Defined in Control.Lens.Internal.Magma Methods pure :: a0 -> TakingWhile p f a b a0 # (<*>) :: TakingWhile p f a b (a0 -> b0) -> TakingWhile p f a b a0 -> TakingWhile p f a b b0 # liftA2 :: (a0 -> b0 -> c) -> TakingWhile p f a b a0 -> TakingWhile p f a b b0 -> TakingWhile p f a b c # (*>) :: TakingWhile p f a b a0 -> TakingWhile p f a b b0 -> TakingWhile p f a b b0 # (<*) :: TakingWhile p f a b a0 -> TakingWhile p f a b b0 -> TakingWhile p f a b a0 # | |
| Applicative (BazaarT p g a b) | |
Defined in Control.Lens.Internal.Bazaar Methods pure :: a0 -> BazaarT p g a b a0 # (<*>) :: BazaarT p g a b (a0 -> b0) -> BazaarT p g a b a0 -> BazaarT p g a b b0 # liftA2 :: (a0 -> b0 -> c) -> BazaarT p g a b a0 -> BazaarT p g a b b0 -> BazaarT p g a b c # (*>) :: BazaarT p g a b a0 -> BazaarT p g a b b0 -> BazaarT p g a b b0 # (<*) :: BazaarT p g a b a0 -> BazaarT p g a b b0 -> BazaarT p g a b a0 # | |
| (Monoid w, Functor m, Monad m) => Applicative (RWST r w s m) | |
Defined in Control.Monad.Trans.RWS.Lazy | |
| Reifies s (ReifiedApplicative f) => Applicative (ReflectedApplicative f s) | |
Defined in Data.Reflection Methods pure :: a -> ReflectedApplicative f s a # (<*>) :: ReflectedApplicative f s (a -> b) -> ReflectedApplicative f s a -> ReflectedApplicative f s b # liftA2 :: (a -> b -> c) -> ReflectedApplicative f s a -> ReflectedApplicative f s b -> ReflectedApplicative f s c # (*>) :: ReflectedApplicative f s a -> ReflectedApplicative f s b -> ReflectedApplicative f s b # (<*) :: ReflectedApplicative f s a -> ReflectedApplicative f s b -> ReflectedApplicative f s a # | |
| Monad state => Applicative (Builder collection mutCollection step state err) | |
Defined in Basement.MutableBuilder Methods pure :: a -> Builder collection mutCollection step state err a # (<*>) :: Builder collection mutCollection step state err (a -> b) -> Builder collection mutCollection step state err a -> Builder collection mutCollection step state err b # liftA2 :: (a -> b -> c) -> Builder collection mutCollection step state err a -> Builder collection mutCollection step state err b -> Builder collection mutCollection step state err c # (*>) :: Builder collection mutCollection step state err a -> Builder collection mutCollection step state err b -> Builder collection mutCollection step state err b # (<*) :: Builder collection mutCollection step state err a -> Builder collection mutCollection step state err b -> Builder collection mutCollection step state err a # | |
class (Functor t, Foldable t) => Traversable (t :: Type -> Type) where #
Functors representing data structures that can be traversed from left to right.
A definition of traverse must satisfy the following laws:
- naturality
t .for every applicative transformationtraversef =traverse(t . f)t- identity
traverseIdentity = Identity- composition
traverse(Compose .fmapg . f) = Compose .fmap(traverseg) .traversef
A definition of sequenceA must satisfy the following laws:
- naturality
t .for every applicative transformationsequenceA=sequenceA.fmaptt- identity
sequenceA.fmapIdentity = Identity- composition
sequenceA.fmapCompose = Compose .fmapsequenceA.sequenceA
where an applicative transformation is a function
t :: (Applicative f, Applicative g) => f a -> g a
preserving the Applicative operations, i.e.
and the identity functor Identity and composition of functors Compose
are defined as
newtype Identity a = Identity a
instance Functor Identity where
fmap f (Identity x) = Identity (f x)
instance Applicative Identity where
pure x = Identity x
Identity f <*> Identity x = Identity (f x)
newtype Compose f g a = Compose (f (g a))
instance (Functor f, Functor g) => Functor (Compose f g) where
fmap f (Compose x) = Compose (fmap (fmap f) x)
instance (Applicative f, Applicative g) => Applicative (Compose f g) where
pure x = Compose (pure (pure x))
Compose f <*> Compose x = Compose ((<*>) <$> f <*> x)(The naturality law is implied by parametricity.)
Instances are similar to Functor, e.g. given a data type
data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a)
a suitable instance would be
instance Traversable Tree where traverse f Empty = pure Empty traverse f (Leaf x) = Leaf <$> f x traverse f (Node l k r) = Node <$> traverse f l <*> f k <*> traverse f r
This is suitable even for abstract types, as the laws for <*>
imply a form of associativity.
The superclass instances should satisfy the following:
- In the
Functorinstance,fmapshould be equivalent to traversal with the identity applicative functor (fmapDefault). - In the
Foldableinstance,foldMapshould be equivalent to traversal with a constant applicative functor (foldMapDefault).
Methods
traverse :: Applicative f => (a -> f b) -> t a -> f (t b) #
Map each element of a structure to an action, evaluate these actions
from left to right, and collect the results. For a version that ignores
the results see traverse_.
Instances
The class of semigroups (types with an associative binary operation).
Instances should satisfy the associativity law:
Since: base-4.9.0.0
Minimal complete definition
Methods
(<>) :: a -> a -> a infixr 6 #
An associative operation.
Reduce a non-empty list with <>
The default definition should be sufficient, but this can be overridden for efficiency.
stimes :: Integral b => b -> a -> a #
Repeat a value n times.
Given that this works on a Semigroup it is allowed to fail if
you request 0 or fewer repetitions, and the default definition
will do so.
By making this a member of the class, idempotent semigroups
and monoids can upgrade this to execute in O(1) by
picking stimes = or stimesIdempotentstimes =
respectively.stimesIdempotentMonoid
Instances
liftA :: Applicative f => (a -> b) -> f a -> f b #
liftA3 :: Applicative f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d #
Lift a ternary function to actions.
(<$>) :: Functor f => (a -> b) -> f a -> f b infixl 4 #
An infix synonym for fmap.
The name of this operator is an allusion to $.
Note the similarities between their types:
($) :: (a -> b) -> a -> b (<$>) :: Functor f => (a -> b) -> f a -> f b
Whereas $ is function application, <$> is function
application lifted over a Functor.
Examples
Convert from a to a Maybe Int using Maybe Stringshow:
>>>show <$> NothingNothing>>>show <$> Just 3Just "3"
Convert from an to an Either Int IntEither IntString using show:
>>>show <$> Left 17Left 17>>>show <$> Right 17Right "17"
Double each element of a list:
>>>(*2) <$> [1,2,3][2,4,6]
Apply even to the second element of a pair:
>>>even <$> (2,2)(2,True)
newtype Const a (b :: k) :: forall k. Type -> k -> Type #
The Const functor.
Instances
| Generic1 (Const a :: k -> Type) | |
| ToJSON2 (Const :: Type -> Type -> Type) | |
Defined in Data.Aeson.Types.ToJSON Methods liftToJSON2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> Const a b -> Value # liftToJSONList2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> [Const a b] -> Value # liftToEncoding2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> Const a b -> Encoding # liftToEncodingList2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> [Const a b] -> Encoding # | |
| Bitraversable (Const :: Type -> Type -> Type) | Since: base-4.10.0.0 |
Defined in Data.Bitraversable Methods bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Const a b -> f (Const c d) # | |
| Bifoldable (Const :: Type -> Type -> Type) | Since: base-4.10.0.0 |
| Bifunctor (Const :: Type -> Type -> Type) | Since: base-4.8.0.0 |
| Biapplicative (Const :: Type -> Type -> Type) | |
Defined in Data.Biapplicative | |
| Bitraversable1 (Const :: Type -> Type -> Type) | |
Defined in Data.Semigroup.Traversable.Class Methods bitraverse1 :: Apply f => (a -> f b) -> (c -> f d) -> Const a c -> f (Const b d) # bisequence1 :: Apply f => Const (f a) (f b) -> f (Const a b) # | |
| Biapply (Const :: Type -> Type -> Type) | |
| Functor (Const m :: Type -> Type) | Since: base-2.1 |
| Monoid m => Applicative (Const m :: Type -> Type) | Since: base-2.0.1 |
| Foldable (Const m :: Type -> Type) | Since: base-4.7.0.0 |
Defined in Data.Functor.Const Methods fold :: Monoid m0 => Const m m0 -> m0 # foldMap :: Monoid m0 => (a -> m0) -> Const m a -> m0 # foldr :: (a -> b -> b) -> b -> Const m a -> b # foldr' :: (a -> b -> b) -> b -> Const m a -> b # foldl :: (b -> a -> b) -> b -> Const m a -> b # foldl' :: (b -> a -> b) -> b -> Const m a -> b # foldr1 :: (a -> a -> a) -> Const m a -> a # foldl1 :: (a -> a -> a) -> Const m a -> a # elem :: Eq a => a -> Const m a -> Bool # maximum :: Ord a => Const m a -> a # minimum :: Ord a => Const m a -> a # | |
| Traversable (Const m :: Type -> Type) | Since: base-4.7.0.0 |
| Semigroup m => Apply (Const m :: Type -> Type) | |
| Contravariant (Const a :: Type -> Type) | |
| ToJSON a => ToJSON1 (Const a :: Type -> Type) | |
Defined in Data.Aeson.Types.ToJSON Methods liftToJSON :: (a0 -> Value) -> ([a0] -> Value) -> Const a a0 -> Value # liftToJSONList :: (a0 -> Value) -> ([a0] -> Value) -> [Const a a0] -> Value # liftToEncoding :: (a0 -> Encoding) -> ([a0] -> Encoding) -> Const a a0 -> Encoding # liftToEncodingList :: (a0 -> Encoding) -> ([a0] -> Encoding) -> [Const a a0] -> Encoding # | |
| Bounded a => Bounded (Const a b) | Since: base-4.9.0.0 |
| Enum a => Enum (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const Methods succ :: Const a b -> Const a b # pred :: Const a b -> Const a b # fromEnum :: Const a b -> Int # enumFrom :: Const a b -> [Const a b] # enumFromThen :: Const a b -> Const a b -> [Const a b] # enumFromTo :: Const a b -> Const a b -> [Const a b] # enumFromThenTo :: Const a b -> Const a b -> Const a b -> [Const a b] # | |
| Eq a => Eq (Const a b) | Since: base-4.9.0.0 |
| Floating a => Floating (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const Methods exp :: Const a b -> Const a b # log :: Const a b -> Const a b # sqrt :: Const a b -> Const a b # (**) :: Const a b -> Const a b -> Const a b # logBase :: Const a b -> Const a b -> Const a b # sin :: Const a b -> Const a b # cos :: Const a b -> Const a b # tan :: Const a b -> Const a b # asin :: Const a b -> Const a b # acos :: Const a b -> Const a b # atan :: Const a b -> Const a b # sinh :: Const a b -> Const a b # cosh :: Const a b -> Const a b # tanh :: Const a b -> Const a b # asinh :: Const a b -> Const a b # acosh :: Const a b -> Const a b # atanh :: Const a b -> Const a b # log1p :: Const a b -> Const a b # expm1 :: Const a b -> Const a b # | |
| Fractional a => Fractional (Const a b) | Since: base-4.9.0.0 |
| Integral a => Integral (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const Methods quot :: Const a b -> Const a b -> Const a b # rem :: Const a b -> Const a b -> Const a b # div :: Const a b -> Const a b -> Const a b # mod :: Const a b -> Const a b -> Const a b # quotRem :: Const a b -> Const a b -> (Const a b, Const a b) # divMod :: Const a b -> Const a b -> (Const a b, Const a b) # | |
| Num a => Num (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const | |
| Ord a => Ord (Const a b) | Since: base-4.9.0.0 |
| Read a => Read (Const a b) | This instance would be equivalent to the derived instances of the
Since: base-4.8.0.0 |
| Real a => Real (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const Methods toRational :: Const a b -> Rational # | |
| RealFloat a => RealFloat (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const Methods floatRadix :: Const a b -> Integer # floatDigits :: Const a b -> Int # floatRange :: Const a b -> (Int, Int) # decodeFloat :: Const a b -> (Integer, Int) # encodeFloat :: Integer -> Int -> Const a b # exponent :: Const a b -> Int # significand :: Const a b -> Const a b # scaleFloat :: Int -> Const a b -> Const a b # isInfinite :: Const a b -> Bool # isDenormalized :: Const a b -> Bool # isNegativeZero :: Const a b -> Bool # | |
| RealFrac a => RealFrac (Const a b) | Since: base-4.9.0.0 |
| Show a => Show (Const a b) | This instance would be equivalent to the derived instances of the
Since: base-4.8.0.0 |
| Ix a => Ix (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const Methods range :: (Const a b, Const a b) -> [Const a b] # index :: (Const a b, Const a b) -> Const a b -> Int # unsafeIndex :: (Const a b, Const a b) -> Const a b -> Int inRange :: (Const a b, Const a b) -> Const a b -> Bool # rangeSize :: (Const a b, Const a b) -> Int # unsafeRangeSize :: (Const a b, Const a b) -> Int | |
| IsString a => IsString (Const a b) | Since: base-4.9.0.0 |
Defined in Data.String Methods fromString :: String -> Const a b # | |
| Generic (Const a b) | |
| Semigroup a => Semigroup (Const a b) | Since: base-4.9.0.0 |
| Monoid a => Monoid (Const a b) | Since: base-4.9.0.0 |
| ToJSON a => ToJSON (Const a b) | |
Defined in Data.Aeson.Types.ToJSON | |
| Storable a => Storable (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const | |
| Bits a => Bits (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const Methods (.&.) :: Const a b -> Const a b -> Const a b # (.|.) :: Const a b -> Const a b -> Const a b # xor :: Const a b -> Const a b -> Const a b # complement :: Const a b -> Const a b # shift :: Const a b -> Int -> Const a b # rotate :: Const a b -> Int -> Const a b # setBit :: Const a b -> Int -> Const a b # clearBit :: Const a b -> Int -> Const a b # complementBit :: Const a b -> Int -> Const a b # testBit :: Const a b -> Int -> Bool # bitSizeMaybe :: Const a b -> Maybe Int # isSigned :: Const a b -> Bool # shiftL :: Const a b -> Int -> Const a b # unsafeShiftL :: Const a b -> Int -> Const a b # shiftR :: Const a b -> Int -> Const a b # unsafeShiftR :: Const a b -> Int -> Const a b # rotateL :: Const a b -> Int -> Const a b # | |
| FiniteBits a => FiniteBits (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const Methods finiteBitSize :: Const a b -> Int # countLeadingZeros :: Const a b -> Int # countTrailingZeros :: Const a b -> Int # | |
| Wrapped (Const a x) | |
| Newtype (Const a x) | |
| Pretty a => Pretty (Const a b) | |
Defined in Data.Text.Prettyprint.Doc.Internal | |
| t ~ Const a' x' => Rewrapped (Const a x) t | |
Defined in Control.Lens.Wrapped | |
| type Rep1 (Const a :: k -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const | |
| type Rep (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const | |
| type Unwrapped (Const a x) | |
Defined in Control.Lens.Wrapped | |
| type O (Const a x) | |
Defined in Control.Newtype.Generics | |
Identity functor and monad. (a non-strict monad)
Since: base-4.8.0.0
Constructors
| Identity | |
Fields
| |
Instances
simulate :: Rational -> Active a -> [a] #
simulate r act simulates the Active value act, returning a
list of "snapshots" taken at regular intervals from the start
time to the end time. The interval used is determined by the
rate r, which denotes the "frame rate", that is, the number
of snapshots per unit time.
If the Active value is constant (and thus has no start or end
times), a list of length 1 is returned, containing the constant
value.
Create an Active which takes on each value in the given list in
turn during the time [0,1], with each value getting an equal
amount of time. In other words, discrete creates a "slide
show" that starts at time 0 and ends at time 1. The first
element is used prior to time 0, and the last element is used
after time 1.
It is an error to call discrete on the empty list.
movie :: [Active a] -> Active a #
Splice together a list of active values using |>>. The list
must be nonempty.
after :: Active a -> Active a -> Active a #
a1 `after` a2 produces an active that behaves like a1 but is
shifted to start at the end time of a2. If either a1 or a2
are constant, a1 is returned unchanged.
atTime :: Time Rational -> Active a -> Active a #
atTime t a is an active value with the same behavior as a,
shifted so that it starts at time t. If a is constant it is
returned unchanged.
trimBefore :: Monoid a => Active a -> Active a #
trim :: Monoid a => Active a -> Active a #
"Trim" an active value so that it is empty outside its era.
trim has no effect on constant values.
For example, trim can be visualized asui
Actually, trim ui is not well-typed, since it is not guaranteed
that ui's values will be monoidal (and usually they won't be)!
But the above image still provides a good intuitive idea of what
trim is doing. To make this precise we could consider something
like trim (First . Just $ ui).
See also trimBefore and trimActive, which trim only before or
after the era, respectively.
clampAfter :: Active a -> Active a #
clampBefore :: Active a -> Active a #
clamp :: Active a -> Active a #
"Clamp" an active value so that it is constant before and after
its era. Before the era, clamp a takes on the value of a at
the start of the era. Likewise, after the era, clamp a takes
on the value of a at the end of the era. clamp has no effect
on constant values.
For example, clamp can be visualized asui
See also clampBefore and clampAfter, which clamp only before
or after the era, respectively.
snapshot :: Time Rational -> Active a -> Active a #
Take a "snapshot" of an active value at a particular time, resulting in a constant value.
backwards :: Active a -> Active a #
Reverse an active value so the start of its era gets mapped to
the end and vice versa. For example, backwards can be
visualized asui
shift :: Duration Rational -> Active a -> Active a #
shift d act shifts the start time of act by duration d.
Has no effect on constant values.
stretch :: Rational -> Active a -> Active a #
stretch s act "stretches" the active act so that it takes
s times as long (retaining the same start time).
interval :: Fractional a => Time Rational -> Time Rational -> Active a #
interval a b is an active value starting at time a, ending at
time b, and taking the value t at time t.
ui :: Fractional a => Active a #
ui represents the unit interval, which takes on the value t
at time t, and has as its era [0,1]. It is equivalent to
, and can be visualized as follows:interval 0 1
On the x-axis is time, and the value that ui takes on is on the
y-axis. The shaded portion represents the era. Note that the
value of ui (as with any active) is still defined outside its
era, and this can make a difference when it is combined with
other active values with different eras. Applying a function
with fmap affects all values, both inside and outside the era.
To manipulate values outside the era specifically, see clamp
and trim.
To alter the values that ui takes on without altering its
era, use its Functor and Applicative instances. For example,
(*2) <$> ui varies from 0 to 2 over the era [0,1]. To
alter the era, you can use stretch or shift.
isConstant :: Active a -> Bool #
Test whether an Active value is constant.
activeStart :: Active a -> a #
Get the value of an Active a at the beginning of its era.
modActive :: (a -> b) -> (Dynamic a -> Dynamic b) -> Active a -> Active b #
Modify an Active value using a case analysis to see whether it
is constant or dynamic.
mkActive :: Time Rational -> Time Rational -> (Time Rational -> a) -> Active a #
Create a dynamic Active from a start time, an end time, and a
time-varying value.
shiftDynamic :: Duration Rational -> Dynamic a -> Dynamic a #
Shift a Dynamic value by a certain duration.
onDynamic :: (Time Rational -> Time Rational -> (Time Rational -> a) -> b) -> Dynamic a -> b #
Fold for Dynamic.
mkDynamic :: Time Rational -> Time Rational -> (Time Rational -> a) -> Dynamic a #
Create a Dynamic from a start time, an end time, and a
time-varying value.
fromDuration :: Duration n -> n #
A convenient unwrapper function to turn a duration into a numeric value.
toDuration :: n -> Duration n #
A convenient wrapper function to convert a numeric value into a duration.
An Era is a concrete span of time, that is, a pair of times
representing the start and end of the era. Eras form a
semigroup: the combination of two Eras is the smallest Era
which contains both. They do not form a Monoid, since there is
no Era which acts as the identity with respect to this
combining operation.
Era is abstract. To construct Era values, use mkEra; to
deconstruct, use start and end.
A Dynamic a can be thought of as an a value that changes over
the course of a particular Era. It's envisioned that Dynamic
will be mostly an internal implementation detail and that
Active will be most commonly used. But you never know what
uses people might find for things.
Instances
| Functor Dynamic | |
| Apply Dynamic |
|
| Semigroup a => Semigroup (Dynamic a) |
|
There are two types of Active values:
- An
Activecan simply be aDynamic, that is, a time-varying value with start and end times. - An
Activevalue can also be a constant: a single value, constant across time, with no start and end times.
The addition of constant values enable Monoid and Applicative
instances for Active.
Instances
| Functor Active | |
| Applicative Active | |
| Apply Active | |
| Semigroup a => Semigroup (Active a) | Active values over a type with a |
| (Monoid a, Semigroup a) => Monoid (Active a) | |
| Wrapped (Active a) | |
| Active a1 ~ t => Rewrapped (Active a2) t | |
Defined in Data.Active | |
| type V (Active a) | |
Defined in Diagrams.Animation.Active | |
| type N (Active a) | |
Defined in Diagrams.Animation.Active | |
| type Unwrapped (Active a) | |
Defined in Data.Active | |
An abstract type representing elapsed time between two points
in time. Note that durations can be negative. Literal numeric
values may be used as Durations thanks to the Num and
Fractional instances.
Instances
An abstract type for representing points in time. Note that
literal numeric values may be used as Times, thanks to the the
Num and Fractional instances.
Instances
| Functor Time | |
| Affine Time | |
| Enum n => Enum (Time n) | |
Defined in Data.Active | |
| Eq n => Eq (Time n) | |
| Fractional n => Fractional (Time n) | |
| Num n => Num (Time n) | |
| Ord n => Ord (Time n) | |
| Read n => Read (Time n) | |
| Real n => Real (Time n) | |
Defined in Data.Active Methods toRational :: Time n -> Rational # | |
| RealFrac n => RealFrac (Time n) | |
| Show n => Show (Time n) | |
| Wrapped (Time n) | |
| Time n1 ~ t => Rewrapped (Time n2) t | |
Defined in Data.Active | |
| type Diff Time | |
Defined in Data.Active | |
| type Unwrapped (Time n) | |
Defined in Data.Active | |
class Contravariant (f :: Type -> Type) where #
The class of contravariant functors.
Whereas in Haskell, one can think of a Functor as containing or producing
values, a contravariant functor is a functor that can be thought of as
consuming values.
As an example, consider the type of predicate functions a -> Bool. One
such predicate might be negative x = x < 0, which
classifies integers as to whether they are negative. However, given this
predicate, we can re-use it in other situations, providing we have a way to
map values to integers. For instance, we can use the negative predicate
on a person's bank balance to work out if they are currently overdrawn:
newtype Predicate a = Predicate { getPredicate :: a -> Bool }
instance Contravariant Predicate where
contramap f (Predicate p) = Predicate (p . f)
| `- First, map the input...
`----- then apply the predicate.
overdrawn :: Predicate Person
overdrawn = contramap personBankBalance negative
Any instance should be subject to the following laws:
contramap id = id contramap f . contramap g = contramap (g . f)
Note, that the second law follows from the free theorem of the type of
contramap and the first law, so you need only check that the former
condition holds.
Minimal complete definition
Instances
mtimesDefault :: (Integral b, Monoid a) => b -> a -> a #
Instances
| Monad Min | Since: base-4.9.0.0 |
| Functor Min | Since: base-4.9.0.0 |
| MonadFix Min | Since: base-4.9.0.0 |
Defined in Data.Semigroup | |
| Applicative Min | Since: base-4.9.0.0 |
| Foldable Min | Since: base-4.9.0.0 |
Defined in Data.Semigroup Methods fold :: Monoid m => Min m -> m # foldMap :: Monoid m => (a -> m) -> Min a -> m # foldr :: (a -> b -> b) -> b -> Min a -> b # foldr' :: (a -> b -> b) -> b -> Min a -> b # foldl :: (b -> a -> b) -> b -> Min a -> b # foldl' :: (b -> a -> b) -> b -> Min a -> b # foldr1 :: (a -> a -> a) -> Min a -> a # foldl1 :: (a -> a -> a) -> Min a -> a # elem :: Eq a => a -> Min a -> Bool # maximum :: Ord a => Min a -> a # | |
| Traversable Min | Since: base-4.9.0.0 |
| Apply Min | |
| ToJSON1 Min | |
Defined in Data.Aeson.Types.ToJSON Methods liftToJSON :: (a -> Value) -> ([a] -> Value) -> Min a -> Value # liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Min a] -> Value # liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Min a -> Encoding # liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Min a] -> Encoding # | |
| Traversable1 Min | |
| Bind Min | |
| Bounded a => Bounded (Min a) | Since: base-4.9.0.0 |
| Enum a => Enum (Min a) | Since: base-4.9.0.0 |
| Eq a => Eq (Min a) | Since: base-4.9.0.0 |
| Data a => Data (Min a) | Since: base-4.9.0.0 |
Defined in Data.Semigroup Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Min a -> c (Min a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Min a) # dataTypeOf :: Min a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Min a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Min a)) # gmapT :: (forall b. Data b => b -> b) -> Min a -> Min a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Min a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Min a -> r # gmapQ :: (forall d. Data d => d -> u) -> Min a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Min a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Min a -> m (Min a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Min a -> m (Min a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Min a -> m (Min a) # | |
| Num a => Num (Min a) | Since: base-4.9.0.0 |
| Ord a => Ord (Min a) | Since: base-4.9.0.0 |
| Read a => Read (Min a) | Since: base-4.9.0.0 |
| Show a => Show (Min a) | Since: base-4.9.0.0 |
| Generic (Min a) | |
| Ord a => Semigroup (Min a) | Since: base-4.9.0.0 |
| (Ord a, Bounded a) => Monoid (Min a) | Since: base-4.9.0.0 |
| ToJSON a => ToJSON (Min a) | |
Defined in Data.Aeson.Types.ToJSON | |
| Wrapped (Min a) | |
| Newtype (Min a) | Since: newtype-generics-0.5.1 |
| Generic1 Min | |
| t ~ Min b => Rewrapped (Min a) t | |
Defined in Control.Lens.Wrapped | |
| type Rep (Min a) | Since: base-4.9.0.0 |
Defined in Data.Semigroup | |
| type Unwrapped (Min a) | |
Defined in Control.Lens.Wrapped | |
| type O (Min a) | |
Defined in Control.Newtype.Generics | |
| type Rep1 Min | Since: base-4.9.0.0 |
Defined in Data.Semigroup | |
Instances
| Monad Max | Since: base-4.9.0.0 |
| Functor Max | Since: base-4.9.0.0 |
| MonadFix Max | Since: base-4.9.0.0 |
Defined in Data.Semigroup | |
| Applicative Max | Since: base-4.9.0.0 |
| Foldable Max | Since: base-4.9.0.0 |
Defined in Data.Semigroup Methods fold :: Monoid m => Max m -> m # foldMap :: Monoid m => (a -> m) -> Max a -> m # foldr :: (a -> b -> b) -> b -> Max a -> b # foldr' :: (a -> b -> b) -> b -> Max a -> b # foldl :: (b -> a -> b) -> b -> Max a -> b # foldl' :: (b -> a -> b) -> b -> Max a -> b # foldr1 :: (a -> a -> a) -> Max a -> a # foldl1 :: (a -> a -> a) -> Max a -> a # elem :: Eq a => a -> Max a -> Bool # maximum :: Ord a => Max a -> a # | |
| Traversable Max | Since: base-4.9.0.0 |
| Apply Max | |
| ToJSON1 Max | |
Defined in Data.Aeson.Types.ToJSON Methods liftToJSON :: (a -> Value) -> ([a] -> Value) -> Max a -> Value # liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Max a] -> Value # liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Max a -> Encoding # liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Max a] -> Encoding # | |
| Traversable1 Max | |
| Bind Max | |
| Bounded a => Bounded (Max a) | Since: base-4.9.0.0 |
| Enum a => Enum (Max a) | Since: base-4.9.0.0 |
| Eq a => Eq (Max a) | Since: base-4.9.0.0 |
| Data a => Data (Max a) | Since: base-4.9.0.0 |
Defined in Data.Semigroup Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Max a -> c (Max a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Max a) # dataTypeOf :: Max a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Max a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Max a)) # gmapT :: (forall b. Data b => b -> b) -> Max a -> Max a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Max a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Max a -> r # gmapQ :: (forall d. Data d => d -> u) -> Max a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Max a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Max a -> m (Max a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Max a -> m (Max a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Max a -> m (Max a) # | |
| Num a => Num (Max a) | Since: base-4.9.0.0 |
| Ord a => Ord (Max a) | Since: base-4.9.0.0 |
| Read a => Read (Max a) | Since: base-4.9.0.0 |
| Show a => Show (Max a) | Since: base-4.9.0.0 |
| Generic (Max a) | |
| Ord a => Semigroup (Max a) | Since: base-4.9.0.0 |
| (Ord a, Bounded a) => Monoid (Max a) | Since: base-4.9.0.0 |
| ToJSON a => ToJSON (Max a) | |
Defined in Data.Aeson.Types.ToJSON | |
| Wrapped (Max a) | |
| Newtype (Max a) | Since: newtype-generics-0.5.1 |
| Generic1 Max | |
| t ~ Max b => Rewrapped (Max a) t | |
Defined in Control.Lens.Wrapped | |
| type Rep (Max a) | Since: base-4.9.0.0 |
Defined in Data.Semigroup | |
| type Unwrapped (Max a) | |
Defined in Control.Lens.Wrapped | |
| type O (Max a) | |
Defined in Control.Newtype.Generics | |
| type Rep1 Max | Since: base-4.9.0.0 |
Defined in Data.Semigroup | |
Arg isn't itself a Semigroup in its own right, but it can be
placed inside Min and Max to compute an arg min or arg max.
Constructors
| Arg a b |
Instances
| Bitraversable Arg | Since: base-4.10.0.0 |
Defined in Data.Semigroup Methods bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Arg a b -> f (Arg c d) # | |
| Bifoldable Arg | Since: base-4.10.0.0 |
| Bifunctor Arg | Since: base-4.9.0.0 |
| Biapplicative Arg | |
| Bitraversable1 Arg | |
Defined in Data.Semigroup.Traversable.Class Methods bitraverse1 :: Apply f => (a -> f b) -> (c -> f d) -> Arg a c -> f (Arg b d) # bisequence1 :: Apply f => Arg (f a) (f b) -> f (Arg a b) # | |
| Biapply Arg | |
| Functor (Arg a) | Since: base-4.9.0.0 |
| Foldable (Arg a) | Since: base-4.9.0.0 |
Defined in Data.Semigroup Methods fold :: Monoid m => Arg a m -> m # foldMap :: Monoid m => (a0 -> m) -> Arg a a0 -> m # foldr :: (a0 -> b -> b) -> b -> Arg a a0 -> b # foldr' :: (a0 -> b -> b) -> b -> Arg a a0 -> b # foldl :: (b -> a0 -> b) -> b -> Arg a a0 -> b # foldl' :: (b -> a0 -> b) -> b -> Arg a a0 -> b # foldr1 :: (a0 -> a0 -> a0) -> Arg a a0 -> a0 # foldl1 :: (a0 -> a0 -> a0) -> Arg a a0 -> a0 # elem :: Eq a0 => a0 -> Arg a a0 -> Bool # maximum :: Ord a0 => Arg a a0 -> a0 # minimum :: Ord a0 => Arg a a0 -> a0 # | |
| Traversable (Arg a) | Since: base-4.9.0.0 |
| Generic1 (Arg a :: Type -> Type) | |
| Eq a => Eq (Arg a b) | Since: base-4.9.0.0 |
| (Data a, Data b) => Data (Arg a b) | Since: base-4.9.0.0 |
Defined in Data.Semigroup Methods gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> Arg a b -> c (Arg a b) # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Arg a b) # toConstr :: Arg a b -> Constr # dataTypeOf :: Arg a b -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Arg a b)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Arg a b)) # gmapT :: (forall b0. Data b0 => b0 -> b0) -> Arg a b -> Arg a b # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Arg a b -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Arg a b -> r # gmapQ :: (forall d. Data d => d -> u) -> Arg a b -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Arg a b -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Arg a b -> m (Arg a b) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Arg a b -> m (Arg a b) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Arg a b -> m (Arg a b) # | |
| Ord a => Ord (Arg a b) | Since: base-4.9.0.0 |
| (Read a, Read b) => Read (Arg a b) | Since: base-4.9.0.0 |
| (Show a, Show b) => Show (Arg a b) | Since: base-4.9.0.0 |
| Generic (Arg a b) | |
| type Rep1 (Arg a :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Semigroup type Rep1 (Arg a :: Type -> Type) = D1 (MetaData "Arg" "Data.Semigroup" "base" False) (C1 (MetaCons "Arg" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1)) | |
| type Rep (Arg a b) | Since: base-4.9.0.0 |
Defined in Data.Semigroup type Rep (Arg a b) = D1 (MetaData "Arg" "Data.Semigroup" "base" False) (C1 (MetaCons "Arg" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 b))) | |
Use to get the behavior of
Option (First a)First from Data.Monoid.
Instances
| Monad First | Since: base-4.9.0.0 |
| Functor First | Since: base-4.9.0.0 |
| MonadFix First | Since: base-4.9.0.0 |
Defined in Data.Semigroup | |
| Applicative First | Since: base-4.9.0.0 |
| Foldable First | Since: base-4.9.0.0 |
Defined in Data.Semigroup Methods fold :: Monoid m => First m -> m # foldMap :: Monoid m => (a -> m) -> First a -> m # foldr :: (a -> b -> b) -> b -> First a -> b # foldr' :: (a -> b -> b) -> b -> First a -> b # foldl :: (b -> a -> b) -> b -> First a -> b # foldl' :: (b -> a -> b) -> b -> First a -> b # foldr1 :: (a -> a -> a) -> First a -> a # foldl1 :: (a -> a -> a) -> First a -> a # elem :: Eq a => a -> First a -> Bool # maximum :: Ord a => First a -> a # minimum :: Ord a => First a -> a # | |
| Traversable First | Since: base-4.9.0.0 |
| Apply First | |
| ToJSON1 First | |
Defined in Data.Aeson.Types.ToJSON Methods liftToJSON :: (a -> Value) -> ([a] -> Value) -> First a -> Value # liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [First a] -> Value # liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> First a -> Encoding # liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [First a] -> Encoding # | |
| Traversable1 First | |
| Bind First | |
| Bounded a => Bounded (First a) | Since: base-4.9.0.0 |
| Enum a => Enum (First a) | Since: base-4.9.0.0 |
| Eq a => Eq (First a) | Since: base-4.9.0.0 |
| Data a => Data (First a) | Since: base-4.9.0.0 |
Defined in Data.Semigroup Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> First a -> c (First a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (First a) # toConstr :: First a -> Constr # dataTypeOf :: First a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (First a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (First a)) # gmapT :: (forall b. Data b => b -> b) -> First a -> First a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> First a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> First a -> r # gmapQ :: (forall d. Data d => d -> u) -> First a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> First a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> First a -> m (First a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> First a -> m (First a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> First a -> m (First a) # | |
| Ord a => Ord (First a) | Since: base-4.9.0.0 |
| Read a => Read (First a) | Since: base-4.9.0.0 |
| Show a => Show (First a) | Since: base-4.9.0.0 |
| Generic (First a) | |
| Semigroup (First a) | Since: base-4.9.0.0 |
| ToJSON a => ToJSON (First a) | |
Defined in Data.Aeson.Types.ToJSON | |
| Wrapped (First a) | |
| Newtype (First a) | Since: newtype-generics-0.5.1 |
| Generic1 First | |
| t ~ First b => Rewrapped (First a) t | |
Defined in Control.Lens.Wrapped | |
| type Rep (First a) | Since: base-4.9.0.0 |
Defined in Data.Semigroup | |
| type Unwrapped (First a) | |
Defined in Control.Lens.Wrapped | |
| type O (First a) | |
Defined in Control.Newtype.Generics | |
| type Rep1 First | Since: base-4.9.0.0 |
Defined in Data.Semigroup | |
Use to get the behavior of
Option (Last a)Last from Data.Monoid
Instances
| Monad Last | Since: base-4.9.0.0 |
| Functor Last | Since: base-4.9.0.0 |
| MonadFix Last | Since: base-4.9.0.0 |
Defined in Data.Semigroup | |
| Applicative Last | Since: base-4.9.0.0 |
| Foldable Last | Since: base-4.9.0.0 |
Defined in Data.Semigroup Methods fold :: Monoid m => Last m -> m # foldMap :: Monoid m => (a -> m) -> Last a -> m # foldr :: (a -> b -> b) -> b -> Last a -> b # foldr' :: (a -> b -> b) -> b -> Last a -> b # foldl :: (b -> a -> b) -> b -> Last a -> b # foldl' :: (b -> a -> b) -> b -> Last a -> b # foldr1 :: (a -> a -> a) -> Last a -> a # foldl1 :: (a -> a -> a) -> Last a -> a # elem :: Eq a => a -> Last a -> Bool # maximum :: Ord a => Last a -> a # | |
| Traversable Last | Since: base-4.9.0.0 |
| Apply Last | |
| ToJSON1 Last | |
Defined in Data.Aeson.Types.ToJSON Methods liftToJSON :: (a -> Value) -> ([a] -> Value) -> Last a -> Value # liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Last a] -> Value # liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Last a -> Encoding # liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Last a] -> Encoding # | |
| Traversable1 Last | |
| Bind Last | |
| Bounded a => Bounded (Last a) | Since: base-4.9.0.0 |
| Enum a => Enum (Last a) | Since: base-4.9.0.0 |
Defined in Data.Semigroup | |
| Eq a => Eq (Last a) | Since: base-4.9.0.0 |
| Data a => Data (Last a) | Since: base-4.9.0.0 |
Defined in Data.Semigroup Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Last a -> c (Last a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Last a) # toConstr :: Last a -> Constr # dataTypeOf :: Last a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Last a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Last a)) # gmapT :: (forall b. Data b => b -> b) -> Last a -> Last a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Last a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Last a -> r # gmapQ :: (forall d. Data d => d -> u) -> Last a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Last a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Last a -> m (Last a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Last a -> m (Last a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Last a -> m (Last a) # | |
| Ord a => Ord (Last a) | Since: base-4.9.0.0 |
| Read a => Read (Last a) | Since: base-4.9.0.0 |
| Show a => Show (Last a) | Since: base-4.9.0.0 |
| Generic (Last a) | |
| Semigroup (Last a) | Since: base-4.9.0.0 |
| ToJSON a => ToJSON (Last a) | |
Defined in Data.Aeson.Types.ToJSON | |
| Wrapped (Last a) | |
| Newtype (Last a) | Since: newtype-generics-0.5.1 |
| Generic1 Last | |
| t ~ Last b => Rewrapped (Last a) t | |
Defined in Control.Lens.Wrapped | |
| type Rep (Last a) | Since: base-4.9.0.0 |
Defined in Data.Semigroup | |
| type Unwrapped (Last a) | |
Defined in Control.Lens.Wrapped | |
| type O (Last a) | |
Defined in Control.Newtype.Generics | |
| type Rep1 Last | Since: base-4.9.0.0 |
Defined in Data.Semigroup | |
newtype WrappedMonoid m #
Provide a Semigroup for an arbitrary Monoid.
NOTE: This is not needed anymore since Semigroup became a superclass of
Monoid in base-4.11 and this newtype be deprecated at some point in the future.
Constructors
| WrapMonoid | |
Fields
| |
Instances
Option is effectively Maybe with a better instance of
Monoid, built off of an underlying Semigroup instead of an
underlying Monoid.
Ideally, this type would not exist at all and we would just fix the
Monoid instance of Maybe.
In GHC 8.4 and higher, the Monoid instance for Maybe has been
corrected to lift a Semigroup instance instead of a Monoid
instance. Consequently, this type is no longer useful. It will be
marked deprecated in GHC 8.8 and removed in GHC 8.10.
Instances
| Monad Option | Since: base-4.9.0.0 |
| Functor Option | Since: base-4.9.0.0 |
| MonadFix Option | Since: base-4.9.0.0 |
Defined in Data.Semigroup | |
| Applicative Option | Since: base-4.9.0.0 |
| Foldable Option | Since: base-4.9.0.0 |
Defined in Data.Semigroup Methods fold :: Monoid m => Option m -> m # foldMap :: Monoid m => (a -> m) -> Option a -> m # foldr :: (a -> b -> b) -> b -> Option a -> b # foldr' :: (a -> b -> b) -> b -> Option a -> b # foldl :: (b -> a -> b) -> b -> Option a -> b # foldl' :: (b -> a -> b) -> b -> Option a -> b # foldr1 :: (a -> a -> a) -> Option a -> a # foldl1 :: (a -> a -> a) -> Option a -> a # elem :: Eq a => a -> Option a -> Bool # maximum :: Ord a => Option a -> a # minimum :: Ord a => Option a -> a # | |
| Traversable Option | Since: base-4.9.0.0 |
| MonadPlus Option | Since: base-4.9.0.0 |
| Alternative Option | Since: base-4.9.0.0 |
| Apply Option | |
| ToJSON1 Option | |
Defined in Data.Aeson.Types.ToJSON Methods liftToJSON :: (a -> Value) -> ([a] -> Value) -> Option a -> Value # liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Option a] -> Value # liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Option a -> Encoding # liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Option a] -> Encoding # | |
| Bind Option | |
| (Selector s, GToJSON enc arity (K1 i (Maybe a) :: Type -> Type), KeyValuePair enc pairs, Monoid pairs) => RecordToPairs enc pairs arity (S1 s (K1 i (Option a) :: Type -> Type)) | |
Defined in Data.Aeson.Types.ToJSON | |
| Eq a => Eq (Option a) | Since: base-4.9.0.0 |
| Data a => Data (Option a) | Since: base-4.9.0.0 |
Defined in Data.Semigroup Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Option a -> c (Option a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Option a) # toConstr :: Option a -> Constr # dataTypeOf :: Option a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Option a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Option a)) # gmapT :: (forall b. Data b => b -> b) -> Option a -> Option a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Option a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Option a -> r # gmapQ :: (forall d. Data d => d -> u) -> Option a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Option a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Option a -> m (Option a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Option a -> m (Option a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Option a -> m (Option a) # | |
| Ord a => Ord (Option a) | Since: base-4.9.0.0 |
Defined in Data.Semigroup | |
| Read a => Read (Option a) | Since: base-4.9.0.0 |
| Show a => Show (Option a) | Since: base-4.9.0.0 |
| Generic (Option a) | |
| Semigroup a => Semigroup (Option a) | Since: base-4.9.0.0 |
| Semigroup a => Monoid (Option a) | Since: base-4.9.0.0 |
| ToJSON a => ToJSON (Option a) | |
Defined in Data.Aeson.Types.ToJSON | |
| Wrapped (Option a) | |
| Newtype (Option a) | Since: newtype-generics-0.5.1 |
| Generic1 Option | |
| t ~ Option b => Rewrapped (Option a) t | |
Defined in Control.Lens.Wrapped | |
| (Action a a', Action (SM a) l) => Action (SM a) (Option a', l) | |
| MList l => MList (a ::: l) | |
Defined in Data.Monoid.MList | |
| MList t => (a ::: t) :>: a | |
| t :>: a => (b ::: t) :>: a | |
| (Metric v, OrderedField n) => Measured (SegMeasure v n) (SegMeasure v n) | |
Defined in Diagrams.Segment Methods measure :: SegMeasure v n -> SegMeasure v n # | |
| (Floating n, Ord n, Metric v) => Measured (SegMeasure v n) (SegTree v n) | |
Defined in Diagrams.Trail Methods measure :: SegTree v n -> SegMeasure v n # | |
| (OrderedField n, Metric v) => Measured (SegMeasure v n) (Segment Closed v n) | |
Defined in Diagrams.Segment Methods measure :: Segment Closed v n -> SegMeasure v n # | |
| type Rep (Option a) | Since: base-4.9.0.0 |
Defined in Data.Semigroup | |
| type V (Option a) | |
Defined in Diagrams.Core.V | |
| type N (Option a) | |
Defined in Diagrams.Core.V | |
| type Unwrapped (Option a) | |
Defined in Control.Lens.Wrapped | |
| type O (Option a) | |
Defined in Control.Newtype.Generics | |
| type Rep1 Option | Since: base-4.9.0.0 |
Defined in Data.Semigroup | |
class Bifunctor (p :: Type -> Type -> Type) where #
A bifunctor is a type constructor that takes
two type arguments and is a functor in both arguments. That
is, unlike with Functor, a type constructor such as Either
does not need to be partially applied for a Bifunctor
instance, and the methods in this class permit mapping
functions over the Left value or the Right value,
or both at the same time.
Formally, the class Bifunctor represents a bifunctor
from Hask -> Hask.
Intuitively it is a bifunctor where both the first and second arguments are covariant.
You can define a Bifunctor by either defining bimap or by
defining both first and second.
If you supply bimap, you should ensure that:
bimapidid≡id
If you supply first and second, ensure:
firstid≡idsecondid≡id
If you supply both, you should also ensure:
bimapf g ≡firstf.secondg
These ensure by parametricity:
bimap(f.g) (h.i) ≡bimapf h.bimapg ifirst(f.g) ≡firstf.firstgsecond(f.g) ≡secondf.secondg
Since: base-4.8.0.0
Methods
Instances
stimesMonoid :: (Integral b, Monoid a) => b -> a -> a #
stimesIdempotent :: Integral b => b -> a -> a #
The dual of a Monoid, obtained by swapping the arguments of mappend.
>>>getDual (mappend (Dual "Hello") (Dual "World"))"WorldHello"
Instances
| Monad Dual | Since: base-4.8.0.0 |
| Functor Dual | Since: base-4.8.0.0 |
| Applicative Dual | Since: base-4.8.0.0 |
| Foldable Dual | Since: base-4.8.0.0 |
Defined in Data.Foldable Methods fold :: Monoid m => Dual m -> m # foldMap :: Monoid m => (a -> m) -> Dual a -> m # foldr :: (a -> b -> b) -> b -> Dual a -> b # foldr' :: (a -> b -> b) -> b -> Dual a -> b # foldl :: (b -> a -> b) -> b -> Dual a -> b # foldl' :: (b -> a -> b) -> b -> Dual a -> b # foldr1 :: (a -> a -> a) -> Dual a -> a # foldl1 :: (a -> a -> a) -> Dual a -> a # elem :: Eq a => a -> Dual a -> Bool # maximum :: Ord a => Dual a -> a # | |
| Traversable Dual | Since: base-4.8.0.0 |
| Apply Dual | |
| Representable Dual | |
| ToJSON1 Dual | |
Defined in Data.Aeson.Types.ToJSON Methods liftToJSON :: (a -> Value) -> ([a] -> Value) -> Dual a -> Value # liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Dual a] -> Value # liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Dual a -> Encoding # liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Dual a] -> Encoding # | |
| Traversable1 Dual | |
| Bind Dual | |
| Bounded a => Bounded (Dual a) | Since: base-2.1 |
| Eq a => Eq (Dual a) | Since: base-2.1 |
| Ord a => Ord (Dual a) | Since: base-2.1 |
| Read a => Read (Dual a) | Since: base-2.1 |
| Show a => Show (Dual a) | Since: base-2.1 |
| Generic (Dual a) | |
| Semigroup a => Semigroup (Dual a) | Since: base-4.9.0.0 |
| Monoid a => Monoid (Dual a) | Since: base-2.1 |
| ToJSON a => ToJSON (Dual a) | |
Defined in Data.Aeson.Types.ToJSON | |
| Default a => Default (Dual a) | |
Defined in Data.Default.Class | |
| AsEmpty a => AsEmpty (Dual a) | |
Defined in Control.Lens.Empty | |
| Wrapped (Dual a) | |
| Newtype (Dual a) | Since: newtype-generics-0.5.1 |
| Generic1 Dual | |
| t ~ Dual b => Rewrapped (Dual a) t | |
Defined in Control.Lens.Wrapped | |
| type Rep Dual | |
Defined in Data.Functor.Rep | |
| type Rep (Dual a) | Since: base-4.7.0.0 |
Defined in Data.Semigroup.Internal | |
| type Unwrapped (Dual a) | |
Defined in Control.Lens.Wrapped | |
| type O (Dual a) | |
Defined in Control.Newtype.Generics | |
| type Rep1 Dual | Since: base-4.7.0.0 |
Defined in Data.Semigroup.Internal | |
The monoid of endomorphisms under composition.
>>>let computation = Endo ("Hello, " ++) <> Endo (++ "!")>>>appEndo computation "Haskell""Hello, Haskell!"
Instances
| Generic (Endo a) | |
| Semigroup (Endo a) | Since: base-4.9.0.0 |
| Monoid (Endo a) | Since: base-2.1 |
| Default (Endo a) | |
Defined in Data.Default.Class | |
| Wrapped (Endo a) | |
| Newtype (Endo a) | |
| t ~ Endo b => Rewrapped (Endo a) t | |
Defined in Control.Lens.Wrapped | |
| type Rep (Endo a) | Since: base-4.7.0.0 |
Defined in Data.Semigroup.Internal | |
| type Unwrapped (Endo a) | |
Defined in Control.Lens.Wrapped | |
| type O (Endo a) | |
Defined in Control.Newtype.Generics | |
Boolean monoid under conjunction (&&).
>>>getAll (All True <> mempty <> All False)False
>>>getAll (mconcat (map (\x -> All (even x)) [2,4,6,7,8]))False
Instances
| Bounded All | Since: base-2.1 |
| Eq All | Since: base-2.1 |
| Ord All | Since: base-2.1 |
| Read All | Since: base-2.1 |
| Show All | Since: base-2.1 |
| Generic All | |
| Semigroup All | Since: base-4.9.0.0 |
| Monoid All | Since: base-2.1 |
| Default All | |
Defined in Data.Default.Class | |
| AsEmpty All | |
Defined in Control.Lens.Empty | |
| Wrapped All | |
| Newtype All | |
| t ~ All => Rewrapped All t | |
Defined in Control.Lens.Wrapped | |
| RealFloat n => HasQuery (Clip n) All | A point inside a clip if the point is in |
| type Rep All | Since: base-4.7.0.0 |
Defined in Data.Semigroup.Internal | |
| type Unwrapped All | |
Defined in Control.Lens.Wrapped | |
| type O All | |
Defined in Control.Newtype.Generics | |
Boolean monoid under disjunction (||).
>>>getAny (Any True <> mempty <> Any False)True
>>>getAny (mconcat (map (\x -> Any (even x)) [2,4,6,7,8]))True
Instances
| Bounded Any | Since: base-2.1 |
| Eq Any | Since: base-2.1 |
| Ord Any | Since: base-2.1 |
| Read Any | Since: base-2.1 |
| Show Any | Since: base-2.1 |
| Generic Any | |
| Semigroup Any | Since: base-4.9.0.0 |
| Monoid Any | Since: base-2.1 |
| Default Any | |
Defined in Data.Default.Class | |
| AsEmpty Any | |
Defined in Control.Lens.Empty | |
| Wrapped Any | |
| Newtype Any | |
| t ~ Any => Rewrapped Any t | |
Defined in Control.Lens.Wrapped | |
| (Num n, Ord n) => HasQuery (Ellipsoid n) Any | |
| (Num n, Ord n) => HasQuery (Box n) Any | |
| OrderedField n => HasQuery (Frustum n) Any | |
| (Floating n, Ord n) => HasQuery (CSG n) Any | |
| (Additive v, Foldable v, Ord n) => HasQuery (BoundingBox v n) Any | |
Defined in Diagrams.BoundingBox Methods getQuery :: BoundingBox v n -> Query (V (BoundingBox v n)) (N (BoundingBox v n)) Any # | |
| RealFloat n => HasQuery (DImage n a) Any | |
| type Rep Any | Since: base-4.7.0.0 |
Defined in Data.Semigroup.Internal | |
| type Unwrapped Any | |
Defined in Control.Lens.Wrapped | |
| type O Any | |
Defined in Control.Newtype.Generics | |
Monoid under addition.
>>>getSum (Sum 1 <> Sum 2 <> mempty)3
Instances
| Monad Sum | Since: base-4.8.0.0 |
| Functor Sum | Since: base-4.8.0.0 |
| Applicative Sum | Since: base-4.8.0.0 |
| Foldable Sum | Since: base-4.8.0.0 |
Defined in Data.Foldable Methods fold :: Monoid m => Sum m -> m # foldMap :: Monoid m => (a -> m) -> Sum a -> m # foldr :: (a -> b -> b) -> b -> Sum a -> b # foldr' :: (a -> b -> b) -> b -> Sum a -> b # foldl :: (b -> a -> b) -> b -> Sum a -> b # foldl' :: (b -> a -> b) -> b -> Sum a -> b # foldr1 :: (a -> a -> a) -> Sum a -> a # foldl1 :: (a -> a -> a) -> Sum a -> a # elem :: Eq a => a -> Sum a -> Bool # maximum :: Ord a => Sum a -> a # | |
| Traversable Sum | Since: base-4.8.0.0 |
| Apply Sum | |
| Representable Sum | |
| Traversable1 Sum | |
| Bind Sum | |
| Bounded a => Bounded (Sum a) | Since: base-2.1 |
| Eq a => Eq (Sum a) | Since: base-2.1 |
| Num a => Num (Sum a) | Since: base-4.7.0.0 |
| Ord a => Ord (Sum a) | Since: base-2.1 |
| Read a => Read (Sum a) | Since: base-2.1 |
| Show a => Show (Sum a) | Since: base-2.1 |
| Generic (Sum a) | |
| Num a => Semigroup (Sum a) | Since: base-4.9.0.0 |
| Num a => Monoid (Sum a) | Since: base-2.1 |
| Num a => Default (Sum a) | |
Defined in Data.Default.Class | |
| (Eq a, Num a) => AsEmpty (Sum a) | |
Defined in Control.Lens.Empty | |
| Wrapped (Sum a) | |
| Newtype (Sum a) | |
| Generic1 Sum | |
| t ~ Sum b => Rewrapped (Sum a) t | |
Defined in Control.Lens.Wrapped | |
| type Rep Sum | |
Defined in Data.Functor.Rep | |
| type Rep (Sum a) | Since: base-4.7.0.0 |
Defined in Data.Semigroup.Internal | |
| type Unwrapped (Sum a) | |
Defined in Control.Lens.Wrapped | |
| type O (Sum a) | |
Defined in Control.Newtype.Generics | |
| type Rep1 Sum | Since: base-4.7.0.0 |
Defined in Data.Semigroup.Internal | |
Monoid under multiplication.
>>>getProduct (Product 3 <> Product 4 <> mempty)12
Constructors
| Product | |
Fields
| |
Instances
| Monad Product | Since: base-4.8.0.0 |
| Functor Product | Since: base-4.8.0.0 |
| Applicative Product | Since: base-4.8.0.0 |
| Foldable Product | Since: base-4.8.0.0 |
Defined in Data.Foldable Methods fold :: Monoid m => Product m -> m # foldMap :: Monoid m => (a -> m) -> Product a -> m # foldr :: (a -> b -> b) -> b -> Product a -> b # foldr' :: (a -> b -> b) -> b -> Product a -> b # foldl :: (b -> a -> b) -> b -> Product a -> b # foldl' :: (b -> a -> b) -> b -> Product a -> b # foldr1 :: (a -> a -> a) -> Product a -> a # foldl1 :: (a -> a -> a) -> Product a -> a # elem :: Eq a => a -> Product a -> Bool # maximum :: Ord a => Product a -> a # minimum :: Ord a => Product a -> a # | |
| Traversable Product | Since: base-4.8.0.0 |
| Apply Product | |
| Representable Product | |
| Traversable1 Product | |
| Bind Product | |
| Bounded a => Bounded (Product a) | Since: base-2.1 |
| Eq a => Eq (Product a) | Since: base-2.1 |
| Num a => Num (Product a) | Since: base-4.7.0.0 |
Defined in Data.Semigroup.Internal | |
| Ord a => Ord (Product a) | Since: base-2.1 |
| Read a => Read (Product a) | Since: base-2.1 |
| Show a => Show (Product a) | Since: base-2.1 |
| Generic (Product a) | |
| Num a => Semigroup (Product a) | Since: base-4.9.0.0 |
| Num a => Monoid (Product a) | Since: base-2.1 |
| Num a => Default (Product a) | |
Defined in Data.Default.Class | |
| (Eq a, Num a) => AsEmpty (Product a) | |
Defined in Control.Lens.Empty | |
| Wrapped (Product a) | |
| Newtype (Product a) | |
| Generic1 Product | |
| t ~ Product b => Rewrapped (Product a) t | |
Defined in Control.Lens.Wrapped | |
| type Rep Product | |
Defined in Data.Functor.Rep | |
| type Rep (Product a) | Since: base-4.7.0.0 |
Defined in Data.Semigroup.Internal | |
| type Unwrapped (Product a) | |
Defined in Control.Lens.Wrapped | |
| type O (Product a) | |
Defined in Control.Newtype.Generics | |
| type Rep1 Product | Since: base-4.7.0.0 |
Defined in Data.Semigroup.Internal | |
stimesIdempotentMonoid :: (Integral b, Monoid a) => b -> a -> a #
yellowgreen :: (Ord a, Floating a) => Colour a #
whitesmoke :: (Ord a, Floating a) => Colour a #
springgreen :: (Ord a, Floating a) => Colour a #
sandybrown :: (Ord a, Floating a) => Colour a #
saddlebrown :: (Ord a, Floating a) => Colour a #
powderblue :: (Ord a, Floating a) => Colour a #
papayawhip :: (Ord a, Floating a) => Colour a #
palevioletred :: (Ord a, Floating a) => Colour a #
paleturquoise :: (Ord a, Floating a) => Colour a #
palegoldenrod :: (Ord a, Floating a) => Colour a #
navajowhite :: (Ord a, Floating a) => Colour a #
midnightblue :: (Ord a, Floating a) => Colour a #
mediumvioletred :: (Ord a, Floating a) => Colour a #
mediumturquoise :: (Ord a, Floating a) => Colour a #
mediumspringgreen :: (Ord a, Floating a) => Colour a #
mediumslateblue :: (Ord a, Floating a) => Colour a #
mediumseagreen :: (Ord a, Floating a) => Colour a #
mediumpurple :: (Ord a, Floating a) => Colour a #
mediumorchid :: (Ord a, Floating a) => Colour a #
mediumblue :: (Ord a, Floating a) => Colour a #
mediumaquamarine :: (Ord a, Floating a) => Colour a #
lightyellow :: (Ord a, Floating a) => Colour a #
lightsteelblue :: (Ord a, Floating a) => Colour a #
lightslategrey :: (Ord a, Floating a) => Colour a #
lightslategray :: (Ord a, Floating a) => Colour a #
lightskyblue :: (Ord a, Floating a) => Colour a #
lightseagreen :: (Ord a, Floating a) => Colour a #
lightsalmon :: (Ord a, Floating a) => Colour a #
lightgreen :: (Ord a, Floating a) => Colour a #
lightgoldenrodyellow :: (Ord a, Floating a) => Colour a #
lightcoral :: (Ord a, Floating a) => Colour a #
lemonchiffon :: (Ord a, Floating a) => Colour a #
lavenderblush :: (Ord a, Floating a) => Colour a #
greenyellow :: (Ord a, Floating a) => Colour a #
ghostwhite :: (Ord a, Floating a) => Colour a #
forestgreen :: (Ord a, Floating a) => Colour a #
floralwhite :: (Ord a, Floating a) => Colour a #
dodgerblue :: (Ord a, Floating a) => Colour a #
deepskyblue :: (Ord a, Floating a) => Colour a #
darkviolet :: (Ord a, Floating a) => Colour a #
darkturquoise :: (Ord a, Floating a) => Colour a #
darkslategrey :: (Ord a, Floating a) => Colour a #
darkslategray :: (Ord a, Floating a) => Colour a #
darkslateblue :: (Ord a, Floating a) => Colour a #
darkseagreen :: (Ord a, Floating a) => Colour a #
darksalmon :: (Ord a, Floating a) => Colour a #
darkorchid :: (Ord a, Floating a) => Colour a #
darkorange :: (Ord a, Floating a) => Colour a #
darkolivegreen :: (Ord a, Floating a) => Colour a #
darkmagenta :: (Ord a, Floating a) => Colour a #
darkgoldenrod :: (Ord a, Floating a) => Colour a #
cornflowerblue :: (Ord a, Floating a) => Colour a #
chartreuse :: (Ord a, Floating a) => Colour a #
blueviolet :: (Ord a, Floating a) => Colour a #
blanchedalmond :: (Ord a, Floating a) => Colour a #
aquamarine :: (Ord a, Floating a) => Colour a #
antiquewhite :: (Ord a, Floating a) => Colour a #
sRGB24read :: (Ord b, Floating b) => String -> Colour b #
Read a colour in hexadecimal form, e.g. "#00aaff" or "00aaff"
sRGB24reads :: (Ord b, Floating b) => ReadS (Colour b) #
Read a colour in hexadecimal form, e.g. "#00aaff" or "00aaff"
sRGB24show :: (RealFrac b, Floating b) => Colour b -> String #
Show a colour in hexadecimal form, e.g. "#00aaff"
sRGB24shows :: (RealFrac b, Floating b) => Colour b -> ShowS #
Show a colour in hexadecimal form, e.g. "#00aaff"
toSRGB24 :: (RealFrac b, Floating b) => Colour b -> RGB Word8 #
Return the approximate 24-bit sRGB colour components as three 8-bit components. Out of range values are clamped.
toSRGBBounded :: (RealFrac b, Floating b, Integral a, Bounded a) => Colour b -> RGB a #
Return the approximate sRGB colour components in the range
[0..maxBound].
Out of range values are clamped.
toSRGB :: (Ord b, Floating b) => Colour b -> RGB b #
Return the sRGB colour components in the range [0..1].
sRGB24 :: (Ord b, Floating b) => Word8 -> Word8 -> Word8 -> Colour b #
Construct a colour from a 24-bit (three 8-bit words) sRGB specification.
sRGBBounded :: (Ord b, Floating b, Integral a, Bounded a) => a -> a -> a -> Colour b #
Construct a colour from an sRGB specification.
Input components are expected to be in the range [0..maxBound].
sRGB :: (Ord b, Floating b) => b -> b -> b -> Colour b #
Construct a colour from an sRGB specification. Input components are expected to be in the range [0..1].
An RGB triple for an unspecified colour space.
Constructors
| RGB | |
Fields
| |
alphaChannel :: AlphaColour a -> a #
Returns the opacity of an AlphaColour.
blend :: (Num a, AffineSpace f) => a -> f a -> f a -> f a #
Compute the weighted average of two points. e.g.
blend 0.4 a b = 0.4*a + 0.6*b
The weight can be negative, or greater than 1.0; however, be aware that non-convex combinations may lead to out of gamut colours.
withOpacity :: Num a => Colour a -> a -> AlphaColour a #
Creates an AlphaColour from a Colour with a given opacity.
c `withOpacity` o == dissolve o (opaque c)
dissolve :: Num a => a -> AlphaColour a -> AlphaColour a #
Returns an AlphaColour more transparent by a factor of o.
opaque :: Num a => Colour a -> AlphaColour a #
Creates an opaque AlphaColour from a Colour.
alphaColourConvert :: (Fractional b, Real a) => AlphaColour a -> AlphaColour b #
Change the type used to represent the colour coordinates.
transparent :: Num a => AlphaColour a #
This AlphaColour is entirely transparent and has no associated
colour channel.
colourConvert :: (Fractional b, Real a) => Colour a -> Colour b #
Change the type used to represent the colour coordinates.
This type represents the human preception of colour.
The a parameter is a numeric type used internally for the
representation.
The Monoid instance allows one to add colours, but beware that adding
colours can take you out of gamut. Consider using blend whenever
possible.
Instances
| AffineSpace Colour | |
Defined in Data.Colour.Internal | |
| ColourOps Colour | |
| Eq a => Eq (Colour a) | |
| Num a => Semigroup (Colour a) | |
| Num a => Monoid (Colour a) | |
| a ~ Double => Color (Colour a) | |
Defined in Diagrams.Attributes Methods toAlphaColour :: Colour a -> AlphaColour Double # fromAlphaColour :: AlphaColour Double -> Colour a # | |
| (Ord a, Floating a) => FromColor (Colour a) | |
Defined in Skylighting.Types | |
| (RealFrac a, Floating a) => ToColor (Colour a) | |
data AlphaColour a #
This type represents a Colour that may be semi-transparent.
The Monoid instance allows you to composite colours.
x `mappend` y == x `over` y
To get the (pre-multiplied) colour channel of an AlphaColour c,
simply composite c over black.
c `over` black
Instances
class ColourOps (f :: Type -> Type) where #
Methods
darken :: Num a => a -> f a -> f a #
darken s c blends a colour with black without changing it's opacity.
For Colour, darken s c = blend s c mempty
Instances
| ColourOps Colour | |
| ColourOps AlphaColour | |
Defined in Data.Colour.Internal Methods over :: Num a => AlphaColour a -> AlphaColour a -> AlphaColour a # darken :: Num a => a -> AlphaColour a -> AlphaColour a # | |
A class for types with a default value.
Minimal complete definition
Nothing
Instances
class Functor f => Additive (f :: Type -> Type) where #
A vector is an additive group with additional structure.
Minimal complete definition
Nothing
Methods
The zero vector
(^+^) :: Num a => f a -> f a -> f a infixl 6 #
Compute the sum of two vectors
>>>V2 1 2 ^+^ V2 3 4V2 4 6
(^-^) :: Num a => f a -> f a -> f a infixl 6 #
Compute the difference between two vectors
>>>V2 4 5 ^-^ V2 3 1V2 1 4
lerp :: Num a => a -> f a -> f a -> f a #
Linearly interpolate between two vectors.
liftU2 :: (a -> a -> a) -> f a -> f a -> f a #
Apply a function to merge the 'non-zero' components of two vectors, unioning the rest of the values.
liftI2 :: (a -> b -> c) -> f a -> f b -> f c #
Apply a function to the components of two vectors.
- For a dense vector this is equivalent to
liftA2. - For a sparse vector this is equivalent to
intersectionWith.
Instances
renderDia :: (Backend b v n, HasLinearMap v, Metric v, Typeable n, OrderedField n, Monoid' m) => b -> Options b v n -> QDiagram b v n m -> Result b v n #
Render a diagram.
renderDiaT :: (Backend b v n, HasLinearMap v, Metric v, Typeable n, OrderedField n, Monoid' m) => b -> Options b v n -> QDiagram b v n m -> (Transformation v n, Result b v n) #
Render a diagram, returning also the transformation which was
used to convert the diagram from its ("global") coordinate
system into the output coordinate system. The inverse of this
transformation can be used, for example, to convert output/screen
coordinates back into diagram coordinates. See also adjustDia.
lookupSub :: IsName nm => nm -> SubMap b v n m -> Maybe [Subdiagram b v n m] #
Look for the given name in a name map, returning a list of subdiagrams associated with that name. If no names match the given name exactly, return all the subdiagrams associated with names of which the given name is a suffix.
rememberAs :: IsName a => a -> QDiagram b v n m -> SubMap b v n m -> SubMap b v n m #
Add a name/diagram association to a submap.
fromNames :: IsName a => [(a, Subdiagram b v n m)] -> SubMap b v n m #
Construct a SubMap from a list of associations between names
and subdiagrams.
rawSub :: Subdiagram b v n m -> QDiagram b v n m #
Extract the "raw" content of a subdiagram, by throwing away the context.
getSub :: (Metric v, OrderedField n, Semigroup m) => Subdiagram b v n m -> QDiagram b v n m #
Turn a subdiagram into a normal diagram, including the enclosing
context. Concretely, a subdiagram is a pair of (1) a diagram and
(2) a "context" consisting of an extra transformation and
attributes. getSub simply applies the transformation and
attributes to the diagram to get the corresponding "top-level"
diagram.
location :: (Additive v, Num n) => Subdiagram b v n m -> Point v n #
Get the location of a subdiagram; that is, the location of its local origin with respect to the vector space of its parent diagram. In other words, the point where its local origin "ended up".
subPoint :: (Metric v, OrderedField n) => Point v n -> Subdiagram b v n m #
Create a "point subdiagram", that is, a pointDiagram (with no
content and a point envelope) treated as a subdiagram with local
origin at the given point. Note this is not the same as
mkSubdiagram . pointDiagram, which would result in a subdiagram
with local origin at the parent origin, rather than at the given
point.
mkSubdiagram :: QDiagram b v n m -> Subdiagram b v n m #
Turn a diagram into a subdiagram with no accumulated context.
atop :: (OrderedField n, Metric v, Semigroup m) => QDiagram b v n m -> QDiagram b v n m -> QDiagram b v n m infixl 6 #
A convenient synonym for mappend on diagrams, designed to be
used infix (to help remember which diagram goes on top of which
when combining them, namely, the first on top of the second).
mkQD :: Prim b v n -> Envelope v n -> Trace v n -> SubMap b v n m -> Query v n m -> QDiagram b v n m #
Create a diagram from a single primitive, along with an envelope, trace, subdiagram map, and query function.
query :: Monoid m => QDiagram b v n m -> Query v n m #
Get the query function associated with a diagram.
localize :: (Metric v, OrderedField n, Semigroup m) => QDiagram b v n m -> QDiagram b v n m #
"Localize" a diagram by hiding all the names, so they are no longer visible to the outside.
withNames :: (IsName nm, Metric v, Semigroup m, OrderedField n) => [nm] -> ([Subdiagram b v n m] -> QDiagram b v n m -> QDiagram b v n m) -> QDiagram b v n m -> QDiagram b v n m #
Given a list of names and a diagram transformation indexed by a list of subdiagrams, perform the transformation using the list of most recent subdiagrams associated with (some qualification of) each name. Do nothing (the identity transformation) if any of the names do not exist.
withNameAll :: (IsName nm, Metric v, Semigroup m, OrderedField n) => nm -> ([Subdiagram b v n m] -> QDiagram b v n m -> QDiagram b v n m) -> QDiagram b v n m -> QDiagram b v n m #
Given a name and a diagram transformation indexed by a list of subdiagrams, perform the transformation using the collection of all such subdiagrams associated with (some qualification of) the given name.
withName :: (IsName nm, Metric v, Semigroup m, OrderedField n) => nm -> (Subdiagram b v n m -> QDiagram b v n m -> QDiagram b v n m) -> QDiagram b v n m -> QDiagram b v n m #
Given a name and a diagram transformation indexed by a subdiagram, perform the transformation using the most recent subdiagram associated with (some qualification of) the name, or perform the identity transformation if the name does not exist.
lookupName :: (IsName nm, Metric v, Semigroup m, OrderedField n) => nm -> QDiagram b v n m -> Maybe (Subdiagram b v n m) #
Lookup the most recent diagram associated with (some qualification of) the given name.
nameSub :: (IsName nm, Metric v, OrderedField n, Semigroup m) => (QDiagram b v n m -> Subdiagram b v n m) -> nm -> QDiagram b v n m -> QDiagram b v n m #
Attach an atomic name to a certain subdiagram, computed from the
given diagram /with the mapping from name to subdiagram
included/. The upshot of this knot-tying is that if d' = d #
named x, then lookupName x d' == Just d' (instead of Just
d).
names :: (Metric v, Semigroup m, OrderedField n) => QDiagram b v n m -> [(Name, [Point v n])] #
Get a list of names of subdiagrams and their locations.
setTrace :: (OrderedField n, Metric v, Semigroup m) => Trace v n -> QDiagram b v n m -> QDiagram b v n m #
Replace the trace of a diagram.
setEnvelope :: (OrderedField n, Metric v, Monoid' m) => Envelope v n -> QDiagram b v n m -> QDiagram b v n m #
Replace the envelope of a diagram.
pointDiagram :: (Metric v, Fractional n) => Point v n -> QDiagram b v n m #
Create a "point diagram", which has no content, no trace, an empty query, and a point envelope.
groupOpacity :: (Metric v, OrderedField n, Semigroup m) => Double -> QDiagram b v n m -> QDiagram b v n m #
Change the transparency of a Diagram as a group.
opacityGroup :: (Metric v, OrderedField n, Semigroup m) => Double -> QDiagram b v n m -> QDiagram b v n m #
Change the transparency of a Diagram as a group.
href :: (Metric v, OrderedField n, Semigroup m) => String -> QDiagram b v n m -> QDiagram b v n m #
Make a diagram into a hyperlink. Note that only some backends will honor hyperlink annotations.
type TypeableFloat n = (Typeable n, RealFloat n) #
data QDiagram b (v :: Type -> Type) n m #
The fundamental diagram type. The type variables are as follows:
brepresents the backend, such asSVGorCairo. Note that each backend also exports a type synonymBfor itself, so the type variablebmay also typically be instantiated byB, meaning "use whatever backend is in scope".vrepresents the vector space of the diagram. Typical instantiations includeV2(for a two-dimensional diagram) orV3(for a three-dimensional diagram).nrepresents the numerical field the diagram uses. Typically this will be a concrete numeric type likeDouble.mis the monoidal type of "query annotations": each point in the diagram has a value of typemassociated to it, and these values are combined according to theMonoidinstance form. Most often,mis simply instantiated toAny, associating a simpleBoolvalue to each point indicating whether the point is inside the diagram;Diagramis a synonym forQDiagramwithmthus instantiated toAny.
Diagrams can be combined via their Monoid instance, transformed
via their Transformable instance, and assigned attributes via
their HasStyle instance.
Note that the Q in QDiagram stands for "Queriable", as
distinguished from Diagram, where m is fixed to Any. This
is not really a very good name, but it's probably not worth
changing it at this point.
Instances
| Functor (QDiagram b v n) | |
| (Metric v, OrderedField n, Semigroup m) => Semigroup (QDiagram b v n m) | |
| (Metric v, OrderedField n, Semigroup m) => Monoid (QDiagram b v n m) | Diagrams form a monoid since each of their components do: the empty diagram has no primitives, an empty envelope, an empty trace, no named subdiagrams, and a constantly empty query function. Diagrams compose by aligning their respective local origins. The new diagram has all the primitives and all the names from the two diagrams combined, and query functions are combined pointwise. The first diagram goes on top of the second. "On top of" probably only makes sense in vector spaces of dimension lower than 3, but in theory it could make sense for, say, 3-dimensional diagrams when viewed by 4-dimensional beings. |
| (Metric v, OrderedField n, Monoid' m) => Juxtaposable (QDiagram b v n m) | |
| (Metric v, OrderedField n, Monoid' m) => Enveloped (QDiagram b v n m) | |
Defined in Diagrams.Core.Types | |
| (Metric v, OrderedField n, Semigroup m) => Traced (QDiagram b v n m) | |
| (Metric v, OrderedField n, Semigroup m) => Qualifiable (QDiagram b v n m) | Diagrams can be qualified so that all their named points can now be referred to using the qualification prefix. |
| (Metric v, OrderedField n, Semigroup m) => HasStyle (QDiagram b v n m) | |
Defined in Diagrams.Core.Types | |
| (OrderedField n, Metric v, Semigroup m) => Transformable (QDiagram b v n m) | Diagrams can be transformed by transforming each of their components appropriately. |
Defined in Diagrams.Core.Types | |
| (Metric v, OrderedField n, Semigroup m) => HasOrigin (QDiagram b v n m) | Every diagram has an intrinsic "local origin" which is the basis for all combining operations. |
Defined in Diagrams.Core.Types | |
| (Metric v, OrderedField n, Monoid' m) => Alignable (QDiagram b v n m) | |
Defined in Diagrams.Align Methods alignBy' :: (InSpace v0 n0 (QDiagram b v n m), Fractional n0, HasOrigin (QDiagram b v n m)) => (v0 n0 -> QDiagram b v n m -> Point v0 n0) -> v0 n0 -> n0 -> QDiagram b v n m -> QDiagram b v n m # defaultBoundary :: (V (QDiagram b v n m) ~ v0, N (QDiagram b v n m) ~ n0) => v0 n0 -> QDiagram b v n m -> Point v0 n0 # alignBy :: (InSpace v0 n0 (QDiagram b v n m), Fractional n0, HasOrigin (QDiagram b v n m)) => v0 n0 -> n0 -> QDiagram b v n m -> QDiagram b v n m # | |
| Wrapped (QDiagram b v n m) | |
| Monoid m => HasQuery (QDiagram b v n m) m | |
| Rewrapped (QDiagram b v n m) (QDiagram b' v' n' m') | |
Defined in Diagrams.Core.Types | |
| type V (QDiagram b v n m) | |
Defined in Diagrams.Core.Types | |
| type N (QDiagram b v n m) | |
Defined in Diagrams.Core.Types | |
| type Unwrapped (QDiagram b v n m) | |
Defined in Diagrams.Core.Types type Unwrapped (QDiagram b v n m) = DUALTree (DownAnnots v n) (UpAnnots b v n m) Annotation (QDiaLeaf b v n m) | |
type Diagram b = QDiagram b (V b) (N b) Any #
Diagram b is a synonym for . That is,
the default sort of diagram is one where querying at a point
simply tells you whether the diagram contains that point or not.
Transforming a default diagram into one with a more interesting
query can be done via the QDiagram b (V b) (N b) AnyFunctor instance of or
the QDiagram b v nvalue function.
data Subdiagram b (v :: Type -> Type) n m #
A Subdiagram represents a diagram embedded within the context
of a larger diagram. Essentially, it consists of a diagram
paired with any accumulated information from the larger context
(transformations, attributes, etc.).
Constructors
| Subdiagram (QDiagram b v n m) (DownAnnots v n) |
Instances
newtype SubMap b (v :: Type -> Type) n m #
A SubMap is a map associating names to subdiagrams. There can
be multiple associations for any given name.
Constructors
| SubMap (Map Name [Subdiagram b v n m]) |
Instances
| Action Name (SubMap b v n m) | A name acts on a name map by qualifying every name in it. |
| Functor (SubMap b v n) | |
| Semigroup (SubMap b v n m) | |
| Monoid (SubMap b v n m) |
|
| Qualifiable (SubMap b v n m) |
|
| Transformable (SubMap b v n m) | |
Defined in Diagrams.Core.Types | |
| (OrderedField n, Metric v) => HasOrigin (SubMap b v n m) | |
Defined in Diagrams.Core.Types | |
| Wrapped (SubMap b v n m) | |
| Rewrapped (SubMap b v n m) (SubMap b' v' n' m') | |
Defined in Diagrams.Core.Types | |
| type V (SubMap b v n m) | |
Defined in Diagrams.Core.Types | |
| type N (SubMap b v n m) | |
Defined in Diagrams.Core.Types | |
| type Unwrapped (SubMap b v n m) | |
Defined in Diagrams.Core.Types | |
data Prim b (v :: Type -> Type) n where #
A value of type Prim b v n is an opaque (existentially quantified)
primitive which backend b knows how to render in vector space v.
Constructors
| Prim :: forall b (v :: Type -> Type) n p. (Transformable p, Typeable p, Renderable p b) => p -> Prim b (V p) (N p) |
Instances
| Transformable (Prim b v n) | The |
Defined in Diagrams.Core.Types | |
| Renderable (Prim b v n) b | The |
| type V (Prim b v n) | |
Defined in Diagrams.Core.Types | |
| type N (Prim b v n) | |
Defined in Diagrams.Core.Types | |
class Backend b (v :: Type -> Type) n where #
Abstract diagrams are rendered to particular formats by
backends. Each backend/vector space combination must be an
instance of the Backend class.
A minimal complete definition consists of Render, Result,
Options, and renderRTree. However, most backends will want to
implement adjustDia as well; the default definition does
nothing. Some useful standard definitions are provided in the
Diagrams.TwoD.Adjust module from the diagrams-lib package.
Minimal complete definition
Associated Types
data Render b (v :: Type -> Type) n :: Type #
An intermediate representation used for rendering primitives.
(Typically, this will be some sort of monad, but it need not
be.) The Renderable class guarantees that a backend will be
able to convert primitives into this type; how these rendered
primitives are combined into an ultimate Result is completely
up to the backend.
type Result b (v :: Type -> Type) n :: Type #
The result of running/interpreting a rendering operation.
data Options b (v :: Type -> Type) n :: Type #
Backend-specific rendering options.
Methods
adjustDia :: (Additive v, Monoid' m, Num n) => b -> Options b v n -> QDiagram b v n m -> (Options b v n, Transformation v n, QDiagram b v n m) #
adjustDia allows the backend to make adjustments to the final
diagram (e.g. to adjust the size based on the options) before
rendering it. It returns a modified options record, the
transformation applied to the diagram (which can be used to
convert attributes whose value is Measure, or transform
e.g. screen coordinates back into local diagram coordinates),
and the adjusted diagram itself.
See the diagrams-lib package (particularly the
Diagrams.TwoD.Adjust module) for some useful implementations.
renderRTree :: b -> Options b v n -> RTree b v n Annotation -> Result b v n #
Given some options, take a representation of a diagram as a
tree and render it. The RTree has already been simplified
and has all measurements converted to Output units.
Instances
| Backend NullBackend v n | |
Defined in Diagrams.Core.Types Associated Types data Render NullBackend v n :: Type # type Result NullBackend v n :: Type # data Options NullBackend v n :: Type # Methods adjustDia :: (Additive v, Monoid' m, Num n) => NullBackend -> Options NullBackend v n -> QDiagram NullBackend v n m -> (Options NullBackend v n, Transformation v n, QDiagram NullBackend v n m) # renderRTree :: NullBackend -> Options NullBackend v n -> RTree NullBackend v n Annotation -> Result NullBackend v n # | |
| SVGFloat n => Backend SVG V2 n | |
type D (v :: Type -> Type) n = QDiagram NullBackend v n Any #
The D type is provided for convenience in situations where you
must give a diagram a concrete, monomorphic type, but don't care
which one. Such situations arise when you pass a diagram to a
function which is polymorphic in its input but monomorphic in its
output, such as width, height, phantom, or names. Such
functions compute some property of the diagram, or use it to
accomplish some other purpose, but do not result in the diagram
being rendered. If the diagram does not have a monomorphic type,
GHC complains that it cannot determine the diagram's type.
For example, here is the error we get if we try to compute the
width of an image (this example requires diagrams-lib):
ghci> width (image (uncheckedImageRef "foo.png" 200 200))
<interactive>:11:8:
No instance for (Renderable (DImage n0 External) b0)
arising from a use of image
The type variables n0, b0 are ambiguous
Possible fix: add a type signature that fixes these type variable(s)
Note: there is a potential instance available:
instance Fractional n => Renderable (DImage n a) NullBackend
-- Defined in Image
Possible fix:
add an instance declaration for
(Renderable (DImage n0 External) b0)
In the first argument of width, namely
`(image (uncheckedImageRef "foo.png" 200 200))'
In the expression:
width (image (uncheckedImageRef "foo.png" 200 200))
In an equation for it:
it = width (image (uncheckedImageRef "foo.png" 200 200))
GHC complains that there is no instance for Renderable (DImage n0
External) b0; what is really going on is that it does not have enough
information to decide what backend to use (hence the
uninstantiated n0 and b0). This is annoying because we know that the
choice of backend cannot possibly affect the width of the image
(it's 200! it's right there in the code!); but there is no way
for GHC to know that.
The solution is to annotate the call to image with the type
, like so:D V2 Double
ghci> width (image (uncheckedImageRef "foo.png" 200 200) :: D V2 Double) 200.00000000000006
(It turns out the width wasn't 200 after all...)
As another example, here is the error we get if we try to compute the width of a radius-1 circle:
ghci> width (circle 1)
<interactive>:12:1:
Couldn't match expected type V2 with actual type `V a0'
The type variable a0 is ambiguous
Possible fix: add a type signature that fixes these type variable(s)
In the expression: width (circle 1)
In an equation for it: it = width (circle 1)
There's even more ambiguity here. Whereas image always returns
a Diagram, the circle function can produce any TrailLike
type, and the width function can consume any Enveloped type,
so GHC has no idea what type to pick to go in the middle.
However, the solution is the same:
ghci> width (circle 1 :: D V2 Double) 1.9999999999999998
data NullBackend #
A null backend which does no actual rendering. It is provided
mainly for convenience in situations where you must give a
diagram a concrete, monomorphic type, but don't actually care
which one. See D for more explanation and examples.
It is courteous, when defining a new primitive P, to make an instance
instance Renderable P NullBackend where render _ _ = mempty
This ensures that the trick with D annotations can be used for
diagrams containing your primitive.
Instances
class Transformable t => Renderable t b where #
The Renderable type class connects backends to primitives which they know how to render.
Methods
render :: b -> t -> Render b (V t) (N t) #
Given a token representing the backend and a transformable object, render it in the appropriate rendering context.
Instances
juxtaposeDefault :: (Enveloped a, HasOrigin a) => Vn a -> a -> a -> a #
class Juxtaposable a where #
Class of things which can be placed "next to" other things, for some appropriate notion of "next to".
Methods
juxtapose :: Vn a -> a -> a -> a #
juxtapose v a1 a2 positions a2 next to a1 in the
direction of v. In particular, place a2 so that v points
from the local origin of a1 towards the old local origin of
a2; a1's local origin becomes a2's new local origin. The
result is just a translated version of a2. (In particular,
this operation does not combine a1 and a2 in any way.)
Instances
| (Enveloped b, HasOrigin b) => Juxtaposable [b] | |
Defined in Diagrams.Core.Juxtapose | |
| (Enveloped b, HasOrigin b, Ord b) => Juxtaposable (Set b) | |
| Enveloped a => Juxtaposable (Located a) | |
| Juxtaposable a => Juxtaposable (b -> a) | |
Defined in Diagrams.Core.Juxtapose | |
| (Enveloped a, HasOrigin a, Enveloped b, HasOrigin b, V a ~ V b, N a ~ N b) => Juxtaposable (a, b) | |
Defined in Diagrams.Core.Juxtapose | |
| (Enveloped b, HasOrigin b) => Juxtaposable (Map k b) | |
| (Metric v, OrderedField n) => Juxtaposable (Envelope v n) | |
| Juxtaposable a => Juxtaposable (Measured n a) | |
| (Metric v, OrderedField n) => Juxtaposable (Path v n) | |
| (Metric v, OrderedField n, Monoid' m) => Juxtaposable (QDiagram b v n m) | |
size :: (V a ~ v, N a ~ n, Enveloped a, HasBasis v) => a -> v n #
The smallest positive axis-parallel vector that bounds the envelope of an object.
radius :: (V a ~ v, N a ~ n, Enveloped a) => v n -> a -> n #
Compute the "radius" (1/2 the diameter) of an enveloped object along a particular vector.
diameter :: (V a ~ v, N a ~ n, Enveloped a) => v n -> a -> n #
Compute the diameter of a enveloped object along a particular vector. Returns zero for the empty envelope.
envelopeP :: (V a ~ v, N a ~ n, Enveloped a) => v n -> a -> Point v n #
Compute the point on a separating hyperplane in the given direction. Returns the origin for the empty envelope.
envelopePMay :: (V a ~ v, N a ~ n, Enveloped a) => v n -> a -> Maybe (Point v n) #
Compute the point on a separating hyperplane in the given
direction, or Nothing for the empty envelope.
envelopeV :: Enveloped a => Vn a -> a -> Vn a #
Compute the vector from the local origin to a separating hyperplane in the given direction. Returns the zero vector for the empty envelope.
envelopeVMay :: Enveloped a => Vn a -> a -> Maybe (Vn a) #
Compute the vector from the local origin to a separating
hyperplane in the given direction, or Nothing for the empty
envelope.
mkEnvelope :: (v n -> n) -> Envelope v n #
Create an envelope from a v n -> n function.
onEnvelope :: ((v n -> n) -> v n -> n) -> Envelope v n -> Envelope v n #
A convenient way to transform an envelope, by specifying a
transformation on the underlying v n -> n function. The empty
envelope is unaffected.
appEnvelope :: Envelope v n -> Maybe (v n -> n) #
"Apply" an envelope by turning it into a function. Nothing
is returned iff the envelope is empty.
newtype Envelope (v :: Type -> Type) n #
Every diagram comes equipped with an envelope. What is an envelope?
Consider first the idea of a bounding box. A bounding box expresses the distance to a bounding plane in every direction parallel to an axis. That is, a bounding box can be thought of as the intersection of a collection of half-planes, two perpendicular to each axis.
More generally, the intersection of half-planes in every direction would give a tight "bounding region", or convex hull. However, representing such a thing intensionally would be impossible; hence bounding boxes are often used as an approximation.
An envelope is an extensional representation of such a "bounding region". Instead of storing some sort of direct representation, we store a function which takes a direction as input and gives a distance to a bounding half-plane as output. The important point is that envelopes can be composed, and transformed by any affine transformation.
Formally, given a vector v, the envelope computes a scalar s such
that
- for every point
uinside the diagram, if the projection of(u - origin)ontoviss' *^ v, thens' <= s. sis the smallest such scalar.
There is also a special "empty envelope".
The idea for envelopes came from Sebastian Setzer; see http://byorgey.wordpress.com/2009/10/28/collecting-attributes/#comment-2030. See also Brent Yorgey, Monoids: Theme and Variations, published in the 2012 Haskell Symposium: http://ozark.hendrix.edu/~yorgey/pub/monoid-pearl.pdf; video: http://www.youtube.com/watch?v=X-8NCkD2vOw.
Instances
| Show (Envelope v n) | |
| Ord n => Semigroup (Envelope v n) | Envelopes form a semigroup with pointwise maximum as composition.
Hence, if |
| Ord n => Monoid (Envelope v n) | The special empty envelope is the identity for the
|
| (Metric v, OrderedField n) => Juxtaposable (Envelope v n) | |
| (Metric v, OrderedField n) => Enveloped (Envelope v n) | |
Defined in Diagrams.Core.Envelope | |
| (Metric v, Floating n) => Transformable (Envelope v n) | |
Defined in Diagrams.Core.Envelope | |
| (Metric v, Fractional n) => HasOrigin (Envelope v n) | The local origin of an envelope is the point with respect to which bounding queries are made, i.e. the point from which the input vectors are taken to originate. |
Defined in Diagrams.Core.Envelope | |
| (Metric v, OrderedField n) => Alignable (Envelope v n) | |
Defined in Diagrams.Align Methods alignBy' :: (InSpace v0 n0 (Envelope v n), Fractional n0, HasOrigin (Envelope v n)) => (v0 n0 -> Envelope v n -> Point v0 n0) -> v0 n0 -> n0 -> Envelope v n -> Envelope v n # defaultBoundary :: (V (Envelope v n) ~ v0, N (Envelope v n) ~ n0) => v0 n0 -> Envelope v n -> Point v0 n0 # alignBy :: (InSpace v0 n0 (Envelope v n), Fractional n0, HasOrigin (Envelope v n)) => v0 n0 -> n0 -> Envelope v n -> Envelope v n # | |
| Wrapped (Envelope v n) | |
| Rewrapped (Envelope v n) (Envelope v' n') | |
Defined in Diagrams.Core.Envelope | |
| type V (Envelope v n) | |
Defined in Diagrams.Core.Envelope | |
| type N (Envelope v n) | |
Defined in Diagrams.Core.Envelope | |
| type Unwrapped (Envelope v n) | |
Defined in Diagrams.Core.Envelope | |
type OrderedField s = (Floating s, Ord s) #
When dealing with envelopes we often want scalars to be an ordered field (i.e. support all four arithmetic operations and be totally ordered) so we introduce this constraint as a convenient shorthand.
class (Metric (V a), OrderedField (N a)) => Enveloped a where #
Enveloped abstracts over things which have an envelope.
Methods
getEnvelope :: a -> Envelope (V a) (N a) #
Compute the envelope of an object. For types with an intrinsic
notion of "local origin", the envelope will be based there.
Other types (e.g. Trail) may have some other default
reference point at which the envelope will be based; their
instances should document what it is.
Instances
newtype Query (v :: Type -> Type) n m #
A query is a function that maps points in a vector space to values in some monoid. Queries naturally form a monoid, with two queries being combined pointwise.
The idea for annotating diagrams with monoidal queries came from the graphics-drawingcombinators package, http://hackage.haskell.org/package/graphics-drawingcombinators.
Instances
maxRayTraceP :: (n ~ N a, Traced a, Num n) => Point (V a) n -> V a n -> a -> Maybe (Point (V a) n) #
Like rayTraceP, but computes the "largest" boundary point
instead of the smallest. Considers only positive boundary
points.
maxRayTraceV :: (n ~ N a, Traced a, Num n) => Point (V a) n -> V a n -> a -> Maybe (V a n) #
Like rayTraceV, but computes a vector to the "largest"
boundary point instead of the smallest. Considers only
positive boundary points.
rayTraceP :: (n ~ N a, Traced a, Num n) => Point (V a) n -> V a n -> a -> Maybe (Point (V a) n) #
Compute the boundary point on an object which is closest to the
given base point in the given direction, or Nothing if there is
no such boundary point. Note that unlike traceP, only positive
boundary points are considered, i.e. boundary points
corresponding to a positive scalar multiple of the direction
vector. This is intuitively the "usual" behavior of a raytracer,
which only considers intersection points "in front of" the
camera.
rayTraceV :: (n ~ N a, Traced a, Num n) => Point (V a) n -> V a n -> a -> Maybe (V a n) #
Compute the vector from the given point to the closest boundary
point of the given object in the given direction, or Nothing if
there is no such boundary point (as in the third example
below). Note that unlike traceV, only positive boundary
points are considered, i.e. boundary points corresponding to a
positive scalar multiple of the direction vector. This is
intuitively the "usual" behavior of a raytracer, which only
considers intersections "in front of" the camera. Compare the
second example diagram below with the second example shown for
traceV.
maxTraceP :: (n ~ N a, Num n, Traced a) => Point (V a) n -> V a n -> a -> Maybe (Point (V a) n) #
Like traceP, but computes the "largest" boundary point
instead of the smallest. (Note, however, the "largest" boundary
point may still be in the opposite direction from the given
vector, if all the boundary points are.)
maxTraceV :: (n ~ N a, Num n, Traced a) => Point (V a) n -> V a n -> a -> Maybe (V a n) #
Like traceV, but computes a vector to the "largest" boundary
point instead of the smallest. (Note, however, the "largest"
boundary point may still be in the opposite direction from the
given vector, if all the boundary points are, as in the third
example shown below.)
traceP :: (n ~ N a, Traced a, Num n) => Point (V a) n -> V a n -> a -> Maybe (Point (V a) n) #
Compute the "smallest" boundary point along the line determined
by the given point p and vector v. The "smallest" boundary
point is defined as the one given by p .+^ (s *^ v) for
the smallest (most negative) value of s. Return Nothing if
there is no such boundary point. See also traceV.
See also rayTraceP which uses the smallest positive
intersection, which is often more intuitive behavior.
traceV :: (n ~ N a, Num n, Traced a) => Point (V a) n -> V a n -> a -> Maybe (V a n) #
Compute the vector from the given point p to the "smallest"
boundary intersection along the given vector v. The
"smallest" boundary intersection is defined as the one given by
p .+^ (s *^ v) for the smallest (most negative) value of
s. Return Nothing if there is no intersection. See also
traceP.
See also rayTraceV which uses the smallest positive
intersection, which is often more intuitive behavior.
mkTrace :: (Point v n -> v n -> SortedList n) -> Trace v n #
getSortedList :: SortedList a -> [a] #
Project the (guaranteed sorted) list out of a SortedList
wrapper.
mkSortedList :: Ord a => [a] -> SortedList a #
A smart constructor for the SortedList type, which sorts the
input to ensure the SortedList invariant.
data SortedList a #
A newtype wrapper around a list which maintains the invariant
that the list is sorted. The constructor is not exported; use
the smart constructor mkSortedList (which sorts the given list)
instead.
Instances
| Ord a => Semigroup (SortedList a) |
|
Defined in Diagrams.Core.Trace Methods (<>) :: SortedList a -> SortedList a -> SortedList a # sconcat :: NonEmpty (SortedList a) -> SortedList a # stimes :: Integral b => b -> SortedList a -> SortedList a # | |
| Ord a => Monoid (SortedList a) |
|
Defined in Diagrams.Core.Trace Methods mempty :: SortedList a # mappend :: SortedList a -> SortedList a -> SortedList a # mconcat :: [SortedList a] -> SortedList a # | |
newtype Trace (v :: Type -> Type) n #
Every diagram comes equipped with a trace. Intuitively, the trace for a diagram is like a raytracer: given a line (represented as a base point and a direction vector), the trace computes a sorted list of signed distances from the base point to all intersections of the line with the boundary of the diagram.
Note that the outputs are not absolute distances, but multipliers
relative to the input vector. That is, if the base point is p
and direction vector is v, and one of the output scalars is
s, then there is an intersection at the point p .+^ (s *^ v).
Constructors
| Trace | |
Fields
| |
Instances
| Show (Trace v n) | |
| Ord n => Semigroup (Trace v n) | Traces form a semigroup with pointwise minimum as composition.
Hence, if |
| Ord n => Monoid (Trace v n) | |
| (Additive v, Ord n) => Traced (Trace v n) | |
| (Additive v, Num n) => Transformable (Trace v n) | |
Defined in Diagrams.Core.Trace | |
| (Additive v, Num n) => HasOrigin (Trace v n) | |
Defined in Diagrams.Core.Trace | |
| (Metric v, OrderedField n) => Alignable (Trace v n) | |
Defined in Diagrams.Align Methods alignBy' :: (InSpace v0 n0 (Trace v n), Fractional n0, HasOrigin (Trace v n)) => (v0 n0 -> Trace v n -> Point v0 n0) -> v0 n0 -> n0 -> Trace v n -> Trace v n # defaultBoundary :: (V (Trace v n) ~ v0, N (Trace v n) ~ n0) => v0 n0 -> Trace v n -> Point v0 n0 # alignBy :: (InSpace v0 n0 (Trace v n), Fractional n0, HasOrigin (Trace v n)) => v0 n0 -> n0 -> Trace v n -> Trace v n # | |
| Wrapped (Trace v n) | |
| Rewrapped (Trace v n) (Trace v' n') | |
Defined in Diagrams.Core.Trace | |
| type V (Trace v n) | |
Defined in Diagrams.Core.Trace | |
| type N (Trace v n) | |
Defined in Diagrams.Core.Trace | |
| type Unwrapped (Trace v n) | |
Defined in Diagrams.Core.Trace | |
class (Additive (V a), Ord (N a)) => Traced a where #
Traced abstracts over things which have a trace.
Instances
| Traced b => Traced [b] | |
| Traced b => Traced (Set b) | |
| Traced t => Traced (TransInv t) | |
| (Traced a, Num (N a)) => Traced (Located a) | The trace of a |
| OrderedField n => Traced (Ellipsoid n) | |
| (Fractional n, Ord n) => Traced (Box n) | |
| (RealFloat n, Ord n) => Traced (Frustum n) | |
| (RealFloat n, Ord n) => Traced (CSG n) | |
| (Traced a, Traced b, SameSpace a b) => Traced (a, b) | |
| Traced b => Traced (Map k b) | |
| (Additive v, Ord n) => Traced (Trace v n) | |
| (Additive v, Ord n) => Traced (Point v n) | The trace of a single point is the empty trace, i.e. the one which returns no intersection points for every query. Arguably it should return a single finite distance for vectors aimed directly at the given point, but due to floating-point inaccuracy this is problematic. Note that the envelope for a single point is not the empty envelope (see Diagrams.Core.Envelope). |
| RealFloat n => Traced (BoundingBox V2 n) | |
Defined in Diagrams.BoundingBox Methods getTrace :: BoundingBox V2 n -> Trace (V (BoundingBox V2 n)) (N (BoundingBox V2 n)) # | |
| TypeableFloat n => Traced (BoundingBox V3 n) | |
Defined in Diagrams.BoundingBox Methods getTrace :: BoundingBox V3 n -> Trace (V (BoundingBox V3 n)) (N (BoundingBox V3 n)) # | |
| (Metric v, OrderedField n, Semigroup m) => Traced (QDiagram b v n m) | |
| (OrderedField n, Metric v, Semigroup m) => Traced (Subdiagram b v n m) | |
Defined in Diagrams.Core.Types Methods getTrace :: Subdiagram b v n m -> Trace (V (Subdiagram b v n m)) (N (Subdiagram b v n m)) # | |
(.>) :: (IsName a1, IsName a2) => a1 -> a2 -> Name infixr 5 #
Convenient operator for writing qualified names with atomic
components of different types. Instead of writing toName a1 <>
toName a2 <> toName a3 you can just write a1 .> a2 .> a3.
eachName :: (Typeable a, Ord a, Show a) => Traversal' Name a #
Traversal over each name in a Name that matches the target type.
>>> toListOf eachName (a.> False .>b) :: String "ab" >>>a.> True .>b& eachName %~ nota.> False .>b
Note that the type of the name is very important.
>>> sumOf eachName ((1::Int) .> (2 :: Integer) .> (3 :: Int)) :: Int 4 >>> sumOf eachName ((1::Int) .> (2 :: Integer) .> (3 :: Int)) :: Integer 2
class (Typeable a, Ord a, Show a) => IsName a where #
Class for those types which can be used as names. They must
support Typeable (to facilitate extracting them from
existential wrappers), Ord (for comparison and efficient
storage) and Show.
To make an instance of IsName, you need not define any methods,
just declare it.
WARNING: it is not recommended to use
GeneralizedNewtypeDeriving in conjunction with IsName, since
in that case the underlying type and the newtype will be
considered equivalent when comparing names. For example:
newtype WordN = WordN Int deriving (Show, Ord, Eq, Typeable, IsName)
is unlikely to work as intended, since (1 :: Int) and (WordN 1)
will be considered equal as names. Instead, use
newtype WordN = WordN Int deriving (Show, Ord, Eq, Typeable, IsName)
instance IsName WordN
Minimal complete definition
Nothing
Instances
| IsName Bool | |
Defined in Diagrams.Core.Names | |
| IsName Char | |
Defined in Diagrams.Core.Names | |
| IsName Double | |
Defined in Diagrams.Core.Names | |
| IsName Float | |
Defined in Diagrams.Core.Names | |
| IsName Int | |
Defined in Diagrams.Core.Names | |
| IsName Integer | |
Defined in Diagrams.Core.Names | |
| IsName () | |
Defined in Diagrams.Core.Names | |
| IsName AName | |
Defined in Diagrams.Core.Names | |
| IsName Name | |
Defined in Diagrams.Core.Names | |
| IsName a => IsName [a] | |
Defined in Diagrams.Core.Names | |
| IsName a => IsName (Maybe a) | |
Defined in Diagrams.Core.Names | |
| (IsName a, IsName b) => IsName (a, b) | |
Defined in Diagrams.Core.Names | |
| (IsName a, IsName b, IsName c) => IsName (a, b, c) | |
Defined in Diagrams.Core.Names | |
A (qualified) name is a (possibly empty) sequence of atomic names.
Instances
| Eq Name | |
| Ord Name | |
| Show Name | |
| Semigroup Name | |
| Monoid Name | |
| IsName Name | |
Defined in Diagrams.Core.Names | |
| Qualifiable Name | Of course, names can be qualified using |
| Wrapped Name | |
| Rewrapped Name Name | |
Defined in Diagrams.Core.Names | |
| Each Name Name AName AName | |
| Action Name (SubMap b v n m) | A name acts on a name map by qualifying every name in it. |
| type Unwrapped Name | |
Defined in Diagrams.Core.Names | |
class Qualifiable q where #
Instances of Qualifiable are things which can be qualified by
prefixing them with a name.
Instances
| Qualifiable Name | Of course, names can be qualified using |
| Qualifiable a => Qualifiable [a] | |
Defined in Diagrams.Core.Names | |
| (Ord a, Qualifiable a) => Qualifiable (Set a) | |
| Qualifiable a => Qualifiable (TransInv a) | |
| Qualifiable a => Qualifiable (Located a) | |
| Qualifiable a => Qualifiable (b -> a) | |
Defined in Diagrams.Core.Names | |
| (Qualifiable a, Qualifiable b) => Qualifiable (a, b) | |
Defined in Diagrams.Core.Names | |
| Qualifiable a => Qualifiable (Map k a) | |
| Qualifiable a => Qualifiable (Measured n a) | |
| (Qualifiable a, Qualifiable b, Qualifiable c) => Qualifiable (a, b, c) | |
Defined in Diagrams.Core.Names | |
| (Metric v, OrderedField n, Semigroup m) => Qualifiable (QDiagram b v n m) | Diagrams can be qualified so that all their named points can now be referred to using the qualification prefix. |
| Qualifiable (SubMap b v n m) |
|
applyTAttr :: (AttributeClass a, Transformable a, V a ~ V d, N a ~ N d, HasStyle d) => a -> d -> d #
Apply a transformable attribute to an instance of HasStyle
(such as a diagram or a style). If the object already has an
attribute of the same type, the new attribute is combined on the
left with the existing attribute, according to their semigroup
structure.
applyMAttr :: (AttributeClass a, N d ~ n, HasStyle d) => Measured n a -> d -> d #
Apply a measured attribute to an instance of HasStyle (such as a
diagram or a style). If the object already has an attribute of
the same type, the new attribute is combined on the left with the
existing attribute, according to their semigroup structure.
applyAttr :: (AttributeClass a, HasStyle d) => a -> d -> d #
Apply an attribute to an instance of HasStyle (such as a
diagram or a style). If the object already has an attribute of
the same type, the new attribute is combined on the left with the
existing attribute, according to their semigroup structure.
atTAttr :: (V a ~ v, N a ~ n, AttributeClass a, Transformable a) => Lens' (Style v n) (Maybe a) #
Lens onto a transformable attribute of a style.
atMAttr :: (AttributeClass a, Typeable n) => Lens' (Style v n) (Maybe (Measured n a)) #
Lens onto a measured attribute of a style.
getAttr :: AttributeClass a => Style v n -> Maybe a #
Extract an attribute from a style of a particular type. If the
style contains an attribute of the requested type, it will be
returned wrapped in Just; otherwise, Nothing is returned.
Trying to extract a measured attibute will fail. It either has to
be unmeasured with unmeasureAttrs or use the atMAttr lens.
class (Typeable a, Semigroup a) => AttributeClass a #
Every attribute must be an instance of AttributeClass, which
simply guarantees Typeable and Semigroup constraints. The
Semigroup instance for an attribute determines how it will combine
with other attributes of the same type.
Instances
data Attribute (v :: Type -> Type) n where #
An existential wrapper type to hold attributes. Some attributes are simply inert/static; some are affected by transformations; and some are affected by transformations and can be modified generically.
Constructors
| Attribute :: forall (v :: Type -> Type) n a. AttributeClass a => a -> Attribute v n | |
| MAttribute :: forall (v :: Type -> Type) n a. AttributeClass a => Measured n a -> Attribute v n | |
| TAttribute :: forall (v :: Type -> Type) n a. (AttributeClass a, Transformable a, V a ~ v, N a ~ n) => a -> Attribute v n |
Instances
| Show (Attribute v n) | Shows the kind of attribute and the type contained in the attribute. |
| Typeable n => Semigroup (Attribute v n) | Attributes form a semigroup, where the semigroup operation simply returns the right-hand attribute when the types do not match, and otherwise uses the semigroup operation specific to the (matching) types. |
| (Additive v, Traversable v, Floating n) => Transformable (Attribute v n) |
|
Defined in Diagrams.Core.Style | |
| Each (Style v n) (Style v' n') (Attribute v n) (Attribute v' n') | |
| type V (Attribute v n) | |
Defined in Diagrams.Core.Style | |
| type N (Attribute v n) | |
Defined in Diagrams.Core.Style | |
data Style (v :: Type -> Type) n #
A Style is a heterogeneous collection of attributes, containing
at most one attribute of any given type.
Instances
| Show (Style v n) | Show the attributes in the style. |
| Typeable n => Semigroup (Style v n) | Combine a style by combining the attributes; if the two styles have attributes of the same type they are combined according to their semigroup structure. |
| Typeable n => Monoid (Style v n) | The empty style contains no attributes. |
| Typeable n => HasStyle (Style v n) | |
Defined in Diagrams.Core.Style | |
| (Additive v, Traversable v, Floating n) => Transformable (Style v n) | |
Defined in Diagrams.Core.Style | |
| Wrapped (Style v n) | |
| At (Style v n) | |
| Ixed (Style v n) | |
Defined in Diagrams.Core.Style | |
| Action (Style v n) m | Styles have no action on other monoids. |
Defined in Diagrams.Core.Style | |
| Rewrapped (Style v n) (Style v' n') | |
Defined in Diagrams.Core.Style | |
| Each (Style v n) (Style v' n') (Attribute v n) (Attribute v' n') | |
| type V (Style v n) | |
Defined in Diagrams.Core.Style | |
| type N (Style v n) | |
Defined in Diagrams.Core.Style | |
| type Unwrapped (Style v n) | |
| type IxValue (Style v n) | |
Defined in Diagrams.Core.Style | |
| type Index (Style v n) | |
Defined in Diagrams.Core.Style | |
Type class for things which have a style.
Methods
applyStyle :: Style (V a) (N a) -> a -> a #
Apply a style by combining it (on the left) with the existing style.
Instances
| HasStyle a => HasStyle [a] | |
Defined in Diagrams.Core.Style Methods applyStyle :: Style (V [a]) (N [a]) -> [a] -> [a] # | |
| (HasStyle a, Ord a) => HasStyle (Set a) | |
Defined in Diagrams.Core.Style | |
| HasStyle b => HasStyle (a -> b) | |
Defined in Diagrams.Core.Style Methods applyStyle :: Style (V (a -> b)) (N (a -> b)) -> (a -> b) -> a -> b # | |
| (HasStyle a, HasStyle b, V a ~ V b, N a ~ N b) => HasStyle (a, b) | |
Defined in Diagrams.Core.Style Methods applyStyle :: Style (V (a, b)) (N (a, b)) -> (a, b) -> (a, b) # | |
| HasStyle a => HasStyle (Map k a) | |
Defined in Diagrams.Core.Style | |
| Typeable n => HasStyle (Style v n) | |
Defined in Diagrams.Core.Style | |
| HasStyle b => HasStyle (Measured n b) | |
Defined in Diagrams.Core.Style | |
| (Metric v, OrderedField n, Semigroup m) => HasStyle (QDiagram b v n m) | |
Defined in Diagrams.Core.Types | |
scale :: (InSpace v n a, Eq n, Fractional n, Transformable a) => n -> a -> a #
Scale uniformly in every dimension by the given scalar.
scaling :: (Additive v, Fractional n) => n -> Transformation v n #
Create a uniform scaling transformation.
translate :: Transformable t => Vn t -> t -> t #
Translate by a vector.
translation :: v n -> Transformation v n #
Create a translation.
avgScale :: (Additive v, Traversable v, Floating n) => Transformation v n -> n #
Compute the "average" amount of scaling performed by a transformation. Satisfies the properties
avgScale (scaling k) == k avgScale (t1 <> t2) == avgScale t1 * avgScale t2
isReflection :: (Additive v, Traversable v, Num n, Ord n) => Transformation v n -> Bool #
Determine whether a Transformation includes a reflection
component, that is, whether it reverses orientation.
determinant :: (Additive v, Traversable v, Num n) => Transformation v n -> n #
The determinant of (the linear part of) a Transformation.
dimension :: (Additive (V a), Traversable (V a)) => a -> Int #
Get the dimension of an object whose vector space is an instance of
HasLinearMap, e.g. transformations, paths, diagrams, etc.
fromLinear :: (Additive v, Num n) => (v n :-: v n) -> (v n :-: v n) -> Transformation v n #
Create a general affine transformation from an invertible linear transformation and its transpose. The translational component is assumed to be zero.
papply :: (Additive v, Num n) => Transformation v n -> Point v n -> Point v n #
Apply a transformation to a point.
apply :: Transformation v n -> v n -> v n #
Apply a transformation to a vector. Note that any translational component of the transformation will not affect the vector, since vectors are invariant under translation.
dropTransl :: (Additive v, Num n) => Transformation v n -> Transformation v n #
Drop the translational component of a transformation, leaving only the linear part.
transl :: Transformation v n -> v n #
Get the translational component of a transformation.
transp :: Transformation v n -> v n :-: v n #
Get the transpose of a transformation (ignoring the translation component).
inv :: (Functor v, Num n) => Transformation v n -> Transformation v n #
Invert a transformation.
(<->) :: (u -> v) -> (v -> u) -> u :-: v #
Create an invertible linear map from two functions which are assumed to be linear inverses.
(v1 :-: v2) is a linear map paired with its inverse.
data Transformation (v :: Type -> Type) n #
General (affine) transformations, represented by an invertible linear map, its transpose, and a vector representing a translation component.
By the transpose of a linear map we mean simply the linear map corresponding to the transpose of the map's matrix representation. For example, any scale is its own transpose, since scales are represented by matrices with zeros everywhere except the diagonal. The transpose of a rotation is the same as its inverse.
The reason we need to keep track of transposes is because it turns out that when transforming a shape according to some linear map L, the shape's normal vectors transform according to L's inverse transpose. (For a more detailed explanation and proof, see https://wiki.haskell.org/Diagrams/Dev/Transformations.) This is exactly what we need when transforming bounding functions, which are defined in terms of perpendicular (i.e. normal) hyperplanes.
For more general, non-invertible transformations, see
Diagrams.Deform (in diagrams-lib).
Instances
type HasLinearMap (v :: Type -> Type) = (HasBasis v, Traversable v) #
HasLinearMap is a constraint synonym, just to
help shorten some of the ridiculously long constraint sets.
type HasBasis (v :: Type -> Type) = (Additive v, Representable v, Rep v ~ E v) #
An Additive vector space whose representation is made up of basis elements.
class Transformable t where #
Type class for things t which can be transformed.
Instances
TransInv is a wrapper which makes a transformable type
translationally invariant; the translational component of
transformations will no longer affect things wrapped in
TransInv.
Constructors
| TransInv t |
Instances
| Eq t => Eq (TransInv t) | |
| Ord t => Ord (TransInv t) | |
Defined in Diagrams.Core.Transform | |
| Show t => Show (TransInv t) | |
| Semigroup t => Semigroup (TransInv t) | |
| Monoid t => Monoid (TransInv t) | |
| Enveloped t => Enveloped (TransInv t) | |
Defined in Diagrams.Core.Envelope | |
| Traced t => Traced (TransInv t) | |
| Qualifiable a => Qualifiable (TransInv a) | |
| (Num (N t), Additive (V t), Transformable t) => Transformable (TransInv t) | |
Defined in Diagrams.Core.Transform | |
| HasOrigin (TransInv t) | |
Defined in Diagrams.Core.Transform | |
| TrailLike t => TrailLike (TransInv t) | Translationally invariant things are trail-like as long as the underlying type is. |
| Wrapped (TransInv t) | |
| Rewrapped (TransInv t) (TransInv t') | |
Defined in Diagrams.Core.Transform | |
| type V (TransInv t) | |
Defined in Diagrams.Core.Transform | |
| type N (TransInv t) | |
Defined in Diagrams.Core.Transform | |
| type Unwrapped (TransInv t) | |
Defined in Diagrams.Core.Transform | |
place :: (InSpace v n t, HasOrigin t) => t -> Point v n -> t #
A flipped variant of moveTo, provided for convenience. Useful
when writing a function which takes a point as an argument, such
as when using withName and friends.
moveTo :: (InSpace v n t, HasOrigin t) => Point v n -> t -> t #
Translate the object by the translation that sends the origin to
the given point. Note that this is dual to moveOriginTo, i.e. we
should have
moveTo (origin .^+ v) === moveOriginTo (origin .^- v)
For types which are also Transformable, this is essentially the
same as translate, i.e.
moveTo (origin .^+ v) === translate v
moveOriginBy :: (V t ~ v, N t ~ n, HasOrigin t) => v n -> t -> t #
Move the local origin by a relative vector.
Class of types which have an intrinsic notion of a "local origin", i.e. things which are not invariant under translation, and which allow the origin to be moved.
One might wonder why not just use Transformable instead of
having a separate class for HasOrigin; indeed, for types which
are instances of both we should have the identity
moveOriginTo (origin .^+ v) === translate (negated v)
The reason is that some things (e.g. vectors, Trails) are
transformable but are translationally invariant, i.e. have no
origin.
Methods
moveOriginTo :: Point (V t) (N t) -> t -> t #
Move the local origin to another point.
Note that this function is in some sense dual to translate
(for types which are also Transformable); moving the origin
itself while leaving the object "fixed" is dual to fixing the
origin and translating the diagram.
Instances
| HasOrigin t => HasOrigin [t] | |
Defined in Diagrams.Core.HasOrigin Methods moveOriginTo :: Point (V [t]) (N [t]) -> [t] -> [t] # | |
| (HasOrigin t, Ord t) => HasOrigin (Set t) | |
Defined in Diagrams.Core.HasOrigin | |
| HasOrigin (TransInv t) | |
Defined in Diagrams.Core.Transform | |
| Floating n => HasOrigin (Text n) | |
Defined in Diagrams.TwoD.Text | |
| (Num (N a), Additive (V a)) => HasOrigin (Located a) |
|
Defined in Diagrams.Located | |
| (HasOrigin t, HasOrigin s, SameSpace s t) => HasOrigin (s, t) | |
Defined in Diagrams.Core.HasOrigin Methods moveOriginTo :: Point (V (s, t)) (N (s, t)) -> (s, t) -> (s, t) # | |
| HasOrigin t => HasOrigin (Map k t) | |
Defined in Diagrams.Core.HasOrigin | |
| (Metric v, Fractional n) => HasOrigin (Envelope v n) | The local origin of an envelope is the point with respect to which bounding queries are made, i.e. the point from which the input vectors are taken to originate. |
Defined in Diagrams.Core.Envelope | |
| (Additive v, Num n) => HasOrigin (Trace v n) | |
Defined in Diagrams.Core.Trace | |
| (Additive v, Num n) => HasOrigin (Transformation v n) | |
Defined in Diagrams.Core.Transform Methods moveOriginTo :: Point (V (Transformation v n)) (N (Transformation v n)) -> Transformation v n -> Transformation v n # | |
| HasOrigin t => HasOrigin (Measured n t) | |
Defined in Diagrams.Core.HasOrigin | |
| (Additive v, Num n) => HasOrigin (Point v n) | |
Defined in Diagrams.Core.HasOrigin | |
| (Additive v, Num n) => HasOrigin (BoundingBox v n) | |
Defined in Diagrams.BoundingBox Methods moveOriginTo :: Point (V (BoundingBox v n)) (N (BoundingBox v n)) -> BoundingBox v n -> BoundingBox v n # | |
| Fractional n => HasOrigin (DImage n a) | |
Defined in Diagrams.TwoD.Image | |
| (Additive v, Num n) => HasOrigin (Path v n) | |
Defined in Diagrams.Path | |
| (Additive v, Num n) => HasOrigin (FixedSegment v n) | |
Defined in Diagrams.Segment Methods moveOriginTo :: Point (V (FixedSegment v n)) (N (FixedSegment v n)) -> FixedSegment v n -> FixedSegment v n # | |
| (Additive v, Num n) => HasOrigin (Query v n m) | |
Defined in Diagrams.Core.Query | |
| (Metric v, OrderedField n, Semigroup m) => HasOrigin (QDiagram b v n m) | Every diagram has an intrinsic "local origin" which is the basis for all combining operations. |
Defined in Diagrams.Core.Types | |
| (Metric v, OrderedField n) => HasOrigin (Subdiagram b v n m) | |
Defined in Diagrams.Core.Types Methods moveOriginTo :: Point (V (Subdiagram b v n m)) (N (Subdiagram b v n m)) -> Subdiagram b v n m -> Subdiagram b v n m # | |
| (OrderedField n, Metric v) => HasOrigin (SubMap b v n m) | |
Defined in Diagrams.Core.Types | |
scaleLocal :: Num n => n -> Measured n a -> Measured n a #
Scale the local units of a Measured thing.
normalized :: Num n => n -> Measure n #
Normalized units get scaled so that one normalized unit is the size of the final diagram.
global :: Num n => n -> Measure n #
Global units are scaled so that they are interpreted relative to the size of the final rendered diagram.
fromMeasured :: Num n => n -> n -> Measured n a -> a #
fromMeasured globalScale normalizedScale measure -> a
'Measured n a' is an object that depends on local, normalized
and global scales. The normalized and global scales are
calculated when rendering a diagram.
For attributes, the local scale gets multiplied by the average
scale of the transform.
Instances
(*.) :: (Functor v, Num n) => n -> Point v n -> Point v n #
Scale a point by a scalar. Specialized version of '(*^)'.
type family V a :: Type -> Type #
Many sorts of objects have an associated vector space in which
they "live". The type function V maps from object types to
the associated vector space. The resulting vector space has kind * -> *
which means it takes another value (a number) and returns a concrete
vector. For example V2 has kind * -> * and V2 Double is a vector.
Instances
The numerical field for the object, the number type used for calculations.
Instances
Conveient type alias to retrieve the vector type associated with an
object's vector space. This is usually used as Vn a ~ v n where v is
the vector space and n is the numerical field.
type SameSpace a b = (V a ~ V b, N a ~ N b) #
SameSpace a b means the types a and b belong to the same
vector space v n.
basis :: (Additive t, Traversable t, Num a) => [t a] #
Produce a default basis for a vector space. If the dimensionality
of the vector space is not statically known, see basisFor.
newtype Point (f :: Type -> Type) a #
A handy wrapper to help distinguish points from vectors at the type level
Constructors
| P (f a) |
Instances
| Unbox (f a) => Vector Vector (Point f a) | |
Defined in Linear.Affine Methods basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (Point f a) -> m (Vector (Point f a)) # basicUnsafeThaw :: PrimMonad m => Vector (Point f a) -> m (Mutable Vector (PrimState m) (Point f a)) # basicLength :: Vector (Point f a) -> Int # basicUnsafeSlice :: Int -> Int -> Vector (Point f a) -> Vector (Point f a) # basicUnsafeIndexM :: Monad m => Vector (Point f a) -> Int -> m (Point f a) # basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (Point f a) -> Vector (Point f a) -> m () # | |
| Unbox (f a) => MVector MVector (Point f a) | |
Defined in Linear.Affine Methods basicLength :: MVector s (Point f a) -> Int # basicUnsafeSlice :: Int -> Int -> MVector s (Point f a) -> MVector s (Point f a) # basicOverlaps :: MVector s (Point f a) -> MVector s (Point f a) -> Bool # basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (Point f a)) # basicInitialize :: PrimMonad m => MVector (PrimState m) (Point f a) -> m () # basicUnsafeReplicate :: PrimMonad m => Int -> Point f a -> m (MVector (PrimState m) (Point f a)) # basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (Point f a) -> Int -> m (Point f a) # basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (Point f a) -> Int -> Point f a -> m () # basicClear :: PrimMonad m => MVector (PrimState m) (Point f a) -> m () # basicSet :: PrimMonad m => MVector (PrimState m) (Point f a) -> Point f a -> m () # basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (Point f a) -> MVector (PrimState m) (Point f a) -> m () # basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (Point f a) -> MVector (PrimState m) (Point f a) -> m () # basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (Point f a) -> Int -> m (MVector (PrimState m) (Point f a)) # | |
| Monad f => Monad (Point f) | |
| Functor f => Functor (Point f) | |
| Applicative f => Applicative (Point f) | |
| Foldable f => Foldable (Point f) | |
Defined in Linear.Affine Methods fold :: Monoid m => Point f m -> m # foldMap :: Monoid m => (a -> m) -> Point f a -> m # foldr :: (a -> b -> b) -> b -> Point f a -> b # foldr' :: (a -> b -> b) -> b -> Point f a -> b # foldl :: (b -> a -> b) -> b -> Point f a -> b # foldl' :: (b -> a -> b) -> b -> Point f a -> b # foldr1 :: (a -> a -> a) -> Point f a -> a # foldl1 :: (a -> a -> a) -> Point f a -> a # elem :: Eq a => a -> Point f a -> Bool # maximum :: Ord a => Point f a -> a # minimum :: Ord a => Point f a -> a # | |
| Traversable f => Traversable (Point f) | |
| Apply f => Apply (Point f) | |
| Distributive f => Distributive (Point f) | |
| Representable f => Representable (Point f) | |
| Eq1 f => Eq1 (Point f) | |
| Ord1 f => Ord1 (Point f) | |
Defined in Linear.Affine | |
| Read1 f => Read1 (Point f) | |
Defined in Linear.Affine | |
| Show1 f => Show1 (Point f) | |
| Serial1 f => Serial1 (Point f) | |
Defined in Linear.Affine Methods serializeWith :: MonadPut m => (a -> m ()) -> Point f a -> m () # deserializeWith :: MonadGet m => m a -> m (Point f a) # | |
| Additive f => Additive (Point f) | |
Defined in Linear.Affine Methods (^+^) :: Num a => Point f a -> Point f a -> Point f a # (^-^) :: Num a => Point f a -> Point f a -> Point f a # lerp :: Num a => a -> Point f a -> Point f a -> Point f a # liftU2 :: (a -> a -> a) -> Point f a -> Point f a -> Point f a # liftI2 :: (a -> b -> c) -> Point f a -> Point f b -> Point f c # | |
| Metric f => Metric (Point f) | |
Defined in Linear.Affine | |
| Additive f => Affine (Point f) | |
| (Metric v, OrderedField n) => TrailLike [Point v n] | A list of points is trail-like; this instance simply
computes the vertices of the trail, using |
| HasR v => HasR (Point v) | |
| HasTheta v => HasTheta (Point v) | |
| HasPhi v => HasPhi (Point v) | |
| R1 f => R1 (Point f) | |
Defined in Linear.Affine | |
| R2 f => R2 (Point f) | |
| R3 f => R3 (Point f) | |
| Hashable1 f => Hashable1 (Point f) | |
Defined in Linear.Affine | |
| R4 f => R4 (Point f) | |
| Finite f => Finite (Point f) | |
| Bind f => Bind (Point f) | |
| Generic1 (Point f :: Type -> Type) | |
| Functor v => Cosieve (Query v) (Point v) | |
Defined in Diagrams.Core.Query | |
| Eq (f a) => Eq (Point f a) | |
| Fractional (f a) => Fractional (Point f a) | |
| (Typeable f, Typeable a, Data (f a)) => Data (Point f a) | |
Defined in Linear.Affine Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Point f a -> c (Point f a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Point f a) # toConstr :: Point f a -> Constr # dataTypeOf :: Point f a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Point f a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Point f a)) # gmapT :: (forall b. Data b => b -> b) -> Point f a -> Point f a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Point f a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Point f a -> r # gmapQ :: (forall d. Data d => d -> u) -> Point f a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Point f a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Point f a -> m (Point f a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Point f a -> m (Point f a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Point f a -> m (Point f a) # | |
| Num (f a) => Num (Point f a) | |
Defined in Linear.Affine | |
| Ord (f a) => Ord (Point f a) | |
| Read (f a) => Read (Point f a) | |
| Show (f a) => Show (Point f a) | |
| Ix (f a) => Ix (Point f a) | |
Defined in Linear.Affine Methods range :: (Point f a, Point f a) -> [Point f a] # index :: (Point f a, Point f a) -> Point f a -> Int # unsafeIndex :: (Point f a, Point f a) -> Point f a -> Int inRange :: (Point f a, Point f a) -> Point f a -> Bool # rangeSize :: (Point f a, Point f a) -> Int # unsafeRangeSize :: (Point f a, Point f a) -> Int | |
| Generic (Point f a) | |
| Hashable (f a) => Hashable (Point f a) | |
Defined in Linear.Affine | |
| Storable (f a) => Storable (Point f a) | |
Defined in Linear.Affine | |
| Binary (f a) => Binary (Point f a) | |
| Serial (f a) => Serial (Point f a) | |
Defined in Linear.Affine | |
| Serialize (f a) => Serialize (Point f a) | |
| NFData (f a) => NFData (Point f a) | |
Defined in Linear.Affine | |
| (OrderedField n, Metric v) => Enveloped (Point v n) | |
Defined in Diagrams.Core.Envelope | |
| (Additive v, Ord n) => Traced (Point v n) | The trace of a single point is the empty trace, i.e. the one which returns no intersection points for every query. Arguably it should return a single finite distance for vectors aimed directly at the given point, but due to floating-point inaccuracy this is problematic. Note that the envelope for a single point is not the empty envelope (see Diagrams.Core.Envelope). |
| (Additive v, Num n) => Transformable (Point v n) | |
Defined in Diagrams.Core.Transform | |
| (Additive v, Num n) => HasOrigin (Point v n) | |
Defined in Diagrams.Core.HasOrigin | |
| Coordinates (v n) => Coordinates (Point v n) | |
Defined in Diagrams.Coordinates | |
| Wrapped (Point f a) | |
| Ixed (f a) => Ixed (Point f a) | |
Defined in Linear.Affine | |
| Unbox (f a) => Unbox (Point f a) | |
Defined in Linear.Affine | |
| Epsilon (f a) => Epsilon (Point f a) | |
Defined in Linear.Affine | |
| r ~ Point u n => Deformable (Point v n) r | |
| t ~ Point g b => Rewrapped (Point f a) t | |
Defined in Linear.Affine | |
| Traversable f => Each (Point f a) (Point f b) a b | |
| (Additive v', Foldable v', Ord n') => Each (BoundingBox v n) (BoundingBox v' n') (Point v n) (Point v' n') | Only valid if the second point is not smaller than the first. |
Defined in Diagrams.BoundingBox Methods each :: Traversal (BoundingBox v n) (BoundingBox v' n') (Point v n) (Point v' n') # | |
| Each (FixedSegment v n) (FixedSegment v' n') (Point v n) (Point v' n') | |
Defined in Diagrams.Segment Methods each :: Traversal (FixedSegment v n) (FixedSegment v' n') (Point v n) (Point v' n') # | |
| newtype MVector s (Point f a) | |
Defined in Linear.Affine | |
| type Rep (Point f) | |
Defined in Linear.Affine | |
| type Diff (Point f) | |
Defined in Linear.Affine | |
| type Size (Point f) | |
Defined in Linear.Affine | |
| type Rep1 (Point f :: Type -> Type) | |
| type Rep (Point f a) | |
Defined in Linear.Affine | |
| type V (Point v n) | |
Defined in Diagrams.Core.Points | |
| type N (Point v n) | |
Defined in Diagrams.Core.Points | |
| newtype Vector (Point f a) | |
Defined in Linear.Affine | |
| type Decomposition (Point v n) | |
Defined in Diagrams.Coordinates | |
| type PrevDim (Point v n) | |
Defined in Diagrams.Coordinates | |
| type FinalCoord (Point v n) | |
Defined in Diagrams.Coordinates | |
| type Unwrapped (Point f a) | |
Defined in Linear.Affine | |
| type IxValue (Point f a) | |
Defined in Linear.Affine | |
| type Index (Point f a) | |
Defined in Linear.Affine | |
relative :: (Additive f, Num a) => Point f a -> Iso' (Point f a) (f a) #
An isomorphism between points and vectors, given a reference point.
newtype E (t :: Type -> Type) #
Basis element
Instances
negated :: (Functor f, Num a) => f a -> f a #
Compute the negation of a vector
>>>negated (V2 2 4)V2 (-2) (-4)
sumV :: (Foldable f, Additive v, Num a) => f (v a) -> v a #
Sum over multiple vectors
>>>sumV [V2 1 1, V2 3 4]V2 4 5
(*^) :: (Functor f, Num a) => a -> f a -> f a infixl 7 #
Compute the left scalar product
>>>2 *^ V2 3 4V2 6 8
(^*) :: (Functor f, Num a) => f a -> a -> f a infixl 7 #
Compute the right scalar product
>>>V2 3 4 ^* 2V2 6 8
(^/) :: (Functor f, Fractional a) => f a -> a -> f a infixl 7 #
Compute division by a scalar on the right.
basisFor :: (Traversable t, Num a) => t b -> [t a] #
Produce a default basis for a vector space from which the argument is drawn.
scaled :: (Traversable t, Num a) => t a -> t (t a) #
Produce a diagonal (scale) matrix from a vector.
>>>scaled (V2 2 3)V2 (V2 2 0) (V2 0 3)
unit :: (Additive t, Num a) => ASetter' (t a) a -> t a #
Create a unit vector.
>>>unit _x :: V2 IntV2 1 0
outer :: (Functor f, Functor g, Num a) => f a -> g a -> f (g a) #
Outer (tensor) product of two vectors
class Additive f => Metric (f :: Type -> Type) where #
Free and sparse inner product/metric spaces.
Minimal complete definition
Nothing
Methods
dot :: Num a => f a -> f a -> a #
Compute the inner product of two vectors or (equivalently)
convert a vector f a into a covector f a -> a.
>>>V2 1 2 `dot` V2 3 411
quadrance :: Num a => f a -> a #
Compute the squared norm. The name quadrance arises from Norman J. Wildberger's rational trigonometry.
qd :: Num a => f a -> f a -> a #
Compute the quadrance of the difference
distance :: Floating a => f a -> f a -> a #
Compute the distance between two vectors in a metric space
norm :: Floating a => f a -> a #
Compute the norm of a vector in a metric space
signorm :: Floating a => f a -> f a #
Convert a non-zero vector to unit vector.
Instances
| Metric [] | |
| Metric Maybe | |
| Metric Identity | |
Defined in Linear.Metric | |
| Metric ZipList | |
Defined in Linear.Metric | |
| Metric Vector | |
| Metric IntMap | |
| Metric V2 | |
| Metric V3 | |
| Metric Plucker | |
Defined in Linear.Plucker | |
| Metric Quaternion | |
Defined in Linear.Quaternion Methods dot :: Num a => Quaternion a -> Quaternion a -> a # quadrance :: Num a => Quaternion a -> a # qd :: Num a => Quaternion a -> Quaternion a -> a # distance :: Floating a => Quaternion a -> Quaternion a -> a # norm :: Floating a => Quaternion a -> a # signorm :: Floating a => Quaternion a -> Quaternion a # | |
| Metric V0 | |
| Metric V4 | |
| Metric V1 | |
| Ord k => Metric (Map k) | |
| (Hashable k, Eq k) => Metric (HashMap k) | |
Defined in Linear.Metric | |
| Metric f => Metric (Point f) | |
Defined in Linear.Affine | |
| Dim n => Metric (V n) | |
class Additive (Diff p) => Affine (p :: Type -> Type) where #
An affine space is roughly a vector space in which we have forgotten or at least pretend to have forgotten the origin.
a .+^ (b .-. a) = b@ (a .+^ u) .+^ v = a .+^ (u ^+^ v)@ (a .-. b) ^+^ v = (a .+^ v) .-. q@
Methods
(.-.) :: Num a => p a -> p a -> Diff p a infixl 6 #
Get the difference between two points as a vector offset.
(.+^) :: Num a => p a -> Diff p a -> p a infixl 6 #
Add a vector offset to a point.
(.-^) :: Num a => p a -> Diff p a -> p a infixl 6 #
Subtract a vector offset from a point.
Instances
| Affine [] | |
| Affine Maybe | |
| Affine Identity | |
| Affine ZipList | |
| Affine Time | |
| Affine Complex | |
| Affine Vector | |
| Affine IntMap | |
| Affine V2 | |
| Affine V3 | |
| Affine Plucker | |
| Affine Quaternion | |
Defined in Linear.Affine Associated Types type Diff Quaternion :: Type -> Type # Methods (.-.) :: Num a => Quaternion a -> Quaternion a -> Diff Quaternion a # (.+^) :: Num a => Quaternion a -> Diff Quaternion a -> Quaternion a # (.-^) :: Num a => Quaternion a -> Diff Quaternion a -> Quaternion a # | |
| Affine V0 | |
| Affine V4 | |
| Affine V1 | |
| Ord k => Affine (Map k) | |
| (Eq k, Hashable k) => Affine (HashMap k) | |
| Additive f => Affine (Point f) | |
| Dim n => Affine (V n) | |
| Affine ((->) b :: Type -> Type) | |
qdA :: (Affine p, Foldable (Diff p), Num a) => p a -> p a -> a #
Compute the quadrance of the difference (the square of the distance)
distanceA :: (Floating a, Foldable (Diff p), Affine p) => p a -> p a -> a #
Distance between two points in an affine space
data family MVector s a :: Type #
Instances
data family Vector a :: Type #
Instances
animRect' :: (InSpace V2 n t, Monoid' m, TrailLike t, Enveloped t, Transformable t, Monoid t) => Rational -> QAnimation b V2 n m -> t #
Like animRect, but with an adjustible sample rate. The first
parameter is the number of samples per time unit to use. Lower
rates will be faster but less accurate; higher rates are more
accurate but slower.
animRect :: (InSpace V2 n t, Monoid' m, TrailLike t, Enveloped t, Transformable t, Monoid t) => QAnimation b V2 n m -> t #
animRect works similarly to animEnvelope for 2D diagrams, but
instead of adjusting the envelope, simply returns the smallest
bounding rectangle which encloses the entire animation. Useful
for e.g. creating a background to go behind an animation.
Uses 30 samples per time unit by default; to adjust this number
see animRect'.
animEnvelope' :: (OrderedField n, Metric v, Monoid' m) => Rational -> QAnimation b v n m -> QAnimation b v n m #
Like animEnvelope, but with an adjustible sample rate. The first
parameter is the number of samples per time unit to use. Lower
rates will be faster but less accurate; higher rates are more
accurate but slower.
animEnvelope :: (OrderedField n, Metric v, Monoid' m) => QAnimation b v n m -> QAnimation b v n m #
Automatically assign fixed a envelope to the entirety of an animation by sampling the envelope at a number of points in time and taking the union of all the sampled envelopes to form the "hull". This hull is then used uniformly throughout the animation.
This is useful when you have an animation that grows and shrinks
in size or shape over time, but you want it to take up a fixed
amount of space, e.g. so that the final rendered movie does not
zoom in and out, or so that it occupies a fixed location with
respect to another animation, when combining animations with
something like |||.
By default, 30 samples per time unit are used; to adjust this
number see animEnvelope'.
See also animRect for help constructing a background to go
behind an animation.
type QAnimation b (v :: Type -> Type) n m = Active (QDiagram b v n m) #
A value of type QAnimation b v m is an animation (a
time-varying diagram with start and end times) that can be
rendered by backend b, with vector space v and monoidal
annotations of type m.
type Animation b (v :: Type -> Type) n = QAnimation b v n Any #
A value of type Animation b v is an animation (a time-varying
diagram with start and end times) in vector space v that can be
rendered by backspace b.
Note that Animation is actually a synonym for QAnimation
where the type of the monoidal annotations has been fixed to
Any (the default).
mkSizeSpec2D :: Num n => Maybe n -> Maybe n -> SizeSpec V2 n #
Make a SizeSpec from possibly-specified width and height.
extentY :: (InSpace v n a, R2 v, Enveloped a) => a -> Maybe (n, n) #
Compute the absolute y-coordinate range of an enveloped object in
the form (lo,hi). Return Nothing for objects with an empty
envelope.
extentX :: (InSpace v n a, R1 v, Enveloped a) => a -> Maybe (n, n) #
Compute the absolute x-coordinate range of an enveloped object in
the form (lo,hi). Return Nothing for objects with an empty
envelope.
Note this is just extent unitX.
width :: (InSpace V2 n a, Enveloped a) => a -> n #
Compute the width of an enveloped object.
Note this is just diameter unitX.
sizeAdjustment :: (Additive v, Foldable v, OrderedField n) => SizeSpec v n -> BoundingBox v n -> (v n, Transformation v n) #
Get the adjustment to fit a BoundingBox in the given SizeSpec. The
vector is the new size and the transformation to position the lower
corner at the origin and scale to the size spec.
sizedAs :: (InSpace v n a, SameSpace a b, HasLinearMap v, Transformable a, Enveloped a, Enveloped b) => b -> a -> a #
Uniformly scale an enveloped object so that it "has the same size as" (fits within the width and height of) some other object.
sized :: (InSpace v n a, HasLinearMap v, Transformable a, Enveloped a) => SizeSpec v n -> a -> a #
Uniformly scale any enveloped object so that it fits within the
given size. For non-uniform scaling see boxFit.
requiredScaling :: (Additive v, Foldable v, Fractional n, Ord n) => SizeSpec v n -> v n -> Transformation v n #
Return the Transformation calcuated from requiredScale.
requiredScale :: (Additive v, Foldable v, Fractional n, Ord n) => SizeSpec v n -> v n -> n #
requiredScale spec sz returns the largest scaling factor to make
something of size sz fit the requested size spec without changing the
aspect ratio. sz should be non-zero (otherwise a scale of 1 is
returned). For non-uniform scaling see boxFit.
mkSizeSpec :: (Functor v, Num n) => v (Maybe n) -> SizeSpec v n #
Make a SizeSpec from a vector of maybe values. Any negative values will
be ignored. For 2D SizeSpecs see mkWidth and mkHeight from
Diagrams.TwoD.Size.
getSpec :: (Functor v, Num n, Ord n) => SizeSpec v n -> v (Maybe n) #
Retrieve a size spec as a vector of maybe values. Only positive sizes are returned.
data SizeSpec (v :: Type -> Type) n #
A SizeSpec is a way of specifying a size without needed lengths for all
the dimensions.
Instances
| Functor v => Functor (SizeSpec v) | |
| Show (v n) => Show (SizeSpec v n) | |
| Generic (SizeSpec v n) | |
| Hashable (v n) => Hashable (SizeSpec v n) | |
Defined in Diagrams.Size | |
| type Rep (SizeSpec v n) | |
Defined in Diagrams.Size | |
| type V (SizeSpec v n) | |
Defined in Diagrams.Size | |
| type N (SizeSpec v n) | |
Defined in Diagrams.Size | |
bgFrame :: (TypeableFloat n, Renderable (Path V2 n) b) => n -> Colour Double -> QDiagram b V2 n Any -> QDiagram b V2 n Any #
Similar to bg but makes the colored background rectangle larger than
the diagram. The first parameter is used to set how far the background
extends beyond the diagram.
bg :: (TypeableFloat n, Renderable (Path V2 n) b) => Colour Double -> QDiagram b V2 n Any -> QDiagram b V2 n Any #
"Set the background color" of a diagram. That is, place a diagram atop a bounding rectangle of the given color.
boundingRect :: (InSpace V2 n a, SameSpace a t, Enveloped t, Transformable t, TrailLike t, Monoid t, Enveloped a) => a -> t #
Construct a bounding rectangle for an enveloped object, that is, the smallest axis-aligned rectangle which encloses the object.
rectEnvelope :: (OrderedField n, Monoid' m) => Point V2 n -> V2 n -> QDiagram b V2 n m -> QDiagram b V2 n m #
rectEnvelope p v sets the envelope of a diagram to a rectangle whose
lower-left corner is at p and whose upper-right corner is at p
.+^ v. Useful for selecting the rectangular portion of a
diagram which should actually be "viewed" in the final render,
if you don't want to see the entire diagram.
extrudeTop :: (OrderedField n, Monoid' m) => n -> QDiagram b V2 n m -> QDiagram b V2 n m #
extrudeTop s "extrudes" a diagram in the positive y-direction,
offsetting its envelope by the provided distance. When s < 0 ,
the envelope is inset instead.
See the documentation for extrudeEnvelope for more information.
extrudeBottom :: (OrderedField n, Monoid' m) => n -> QDiagram b V2 n m -> QDiagram b V2 n m #
extrudeBottom s "extrudes" a diagram in the negative y-direction,
offsetting its envelope by the provided distance. When s < 0 ,
the envelope is inset instead.
See the documentation for extrudeEnvelope for more information.
extrudeRight :: (OrderedField n, Monoid' m) => n -> QDiagram b V2 n m -> QDiagram b V2 n m #
extrudeRight s "extrudes" a diagram in the positive x-direction,
offsetting its envelope by the provided distance. When s < 0 ,
the envelope is inset instead.
See the documentation for extrudeEnvelope for more information.
extrudeLeft :: (OrderedField n, Monoid' m) => n -> QDiagram b V2 n m -> QDiagram b V2 n m #
extrudeLeft s "extrudes" a diagram in the negative x-direction,
offsetting its envelope by the provided distance. When s < 0 ,
the envelope is inset instead.
See the documentation for extrudeEnvelope for more information.
padY :: (Metric v, R2 v, Monoid' m, OrderedField n) => n -> QDiagram b v n m -> QDiagram b v n m #
padY s "pads" a diagram in the y-direction, expanding its
envelope vertically by a factor of s (factors between
0 and 1 can be used to shrink the envelope). Note that
the envelope will expand with respect to the local origin,
so if the origin is not centered vertically the padding may appear
"uneven". If this is not desired, the origin can be centered
(using centerY) before applying padY.
padX :: (Metric v, R2 v, OrderedField n, Monoid' m) => n -> QDiagram b v n m -> QDiagram b v n m #
padX s "pads" a diagram in the x-direction, expanding its
envelope horizontally by a factor of s (factors between 0 and 1
can be used to shrink the envelope). Note that the envelope will
expand with respect to the local origin, so if the origin is not
centered horizontally the padding may appear "uneven". If this
is not desired, the origin can be centered (using centerX)
before applying padX.
strutY :: (Metric v, R2 v, OrderedField n) => n -> QDiagram b v n m #
strutY h is an empty diagram with height h, width 0, and a
centered local origin. Note that strutY (-h) behaves the same as
strutY h.
strutX :: (Metric v, R1 v, OrderedField n) => n -> QDiagram b v n m #
strutX w is an empty diagram with width w, height 0, and a
centered local origin. Note that strutX (-w) behaves the same as
strutX w.
vsep :: (InSpace V2 n a, Floating n, Juxtaposable a, HasOrigin a, Monoid' a) => n -> [a] -> a #
A convenient synonym for vertical concatenation with
separation: vsep s === vcat' (with & sep .~ s).
vcat' :: (InSpace V2 n a, Floating n, Juxtaposable a, HasOrigin a, Monoid' a) => CatOpts n -> [a] -> a #
vcat :: (InSpace V2 n a, Floating n, Juxtaposable a, HasOrigin a, Monoid' a) => [a] -> a #
Lay out a list of juxtaposable objects in a column from top to bottom, so that their local origins lie along a single vertical line, with successive envelopes tangent to one another.
hsep :: (InSpace V2 n a, Floating n, Juxtaposable a, HasOrigin a, Monoid' a) => n -> [a] -> a #
A convenient synonym for horizontal concatenation with
separation: hsep s === hcat' (with & sep .~ s).
hcat' :: (InSpace V2 n a, Floating n, Juxtaposable a, HasOrigin a, Monoid' a) => CatOpts n -> [a] -> a #
hcat :: (InSpace V2 n a, Floating n, Juxtaposable a, HasOrigin a, Monoid' a) => [a] -> a #
Lay out a list of juxtaposable objects in a row from left to right, so that their local origins lie along a single horizontal line, with successive envelopes tangent to one another.
(|||) :: (InSpace V2 n a, Juxtaposable a, Semigroup a) => a -> a -> a infixl 6 #
Place two diagrams (or other juxtaposable objects) horizontally
adjacent to one another, with the first diagram to the left of
the second. The local origin of the resulting combined diagram
is the same as the local origin of the first. (|||) is
associative and has mempty as an identity. See the
documentation of beside for more information.
(===) :: (InSpace V2 n a, Juxtaposable a, Semigroup a) => a -> a -> a infixl 6 #
Place two diagrams (or other objects) vertically adjacent to one another, with the first diagram above the second. Since Haskell ignores whitespace in expressions, one can thus write
c
===
d
to place c above d. The local origin of the resulting
combined diagram is the same as the local origin of the first.
(===) is associative and has mempty as an identity. See the
documentation of beside for more information.
boxGrid :: (Traversable v, Additive v, Num n, Enum n) => n -> BoundingBox v n -> [Point v n] #
boxGrid f box returns a grid of regularly spaced points inside
the box, such that there are (1/f) points along each dimension.
For example, for a 3D box with corners at (0,0,0) and (2,2,2),
boxGrid 0.1 would yield a grid of approximately 1000 points (it
might actually be 11^3 instead of 10^3) spaced 0.2 units
apart.
outside' :: (Additive v, Foldable v, Ord n) => BoundingBox v n -> BoundingBox v n -> Bool #
Test whether the first bounding box lies strictly outside the second (they do not intersect at all).
inside' :: (Additive v, Foldable v, Ord n) => BoundingBox v n -> BoundingBox v n -> Bool #
Test whether the first bounding box is strictly contained inside the second.
contains' :: (Additive v, Foldable v, Ord n) => BoundingBox v n -> Point v n -> Bool #
Check whether a point is strictly contained in a bounding box.
boxFit :: (InSpace v n a, HasBasis v, Enveloped a, Transformable a, Monoid a) => BoundingBox v n -> a -> a #
Transforms an enveloped thing to fit within a BoundingBox. If the
bounding box is empty, then the result is also mempty.
boxTransform :: (Additive v, Fractional n) => BoundingBox v n -> BoundingBox v n -> Maybe (Transformation v n) #
Create a transformation mapping points from one bounding box to the
other. Returns Nothing if either of the boxes are empty.
centerPoint :: (InSpace v n a, HasBasis v, Enveloped a) => a -> Point v n #
Get the center of a the bounding box of an enveloped object, return the origin for object with empty envelope.
mCenterPoint :: (InSpace v n a, HasBasis v, Enveloped a) => a -> Maybe (Point v n) #
Get the center of a the bounding box of an enveloped object, return
Nothing for object with empty envelope.
boxCenter :: (Additive v, Fractional n) => BoundingBox v n -> Maybe (Point v n) #
Get the center point in a bounding box.
boxExtents :: (Additive v, Num n) => BoundingBox v n -> v n #
Get the size of the bounding box - the vector from the (component-wise) lesser point to the greater point.
getAllCorners :: (Additive v, Traversable v) => BoundingBox v n -> [Point v n] #
Computes all of the corners of the bounding box.
getCorners :: BoundingBox v n -> Maybe (Point v n, Point v n) #
Gets the lower and upper corners that define the bounding box.
isEmptyBox :: BoundingBox v n -> Bool #
Queries whether the BoundingBox is empty.
boundingBox :: (InSpace v n a, HasBasis v, Enveloped a) => a -> BoundingBox v n #
Create a bounding box for any enveloped object (such as a diagram or path).
fromPoints :: (Additive v, Ord n) => [Point v n] -> BoundingBox v n #
Create the smallest bounding box containing all the given points.
fromPoint :: Point v n -> BoundingBox v n #
Create a degenerate bounding "box" containing only a single point.
fromCorners :: (Additive v, Foldable v, Ord n) => Point v n -> Point v n -> BoundingBox v n #
Create a bounding box from a point that is component-wise (<=) than the
other. If this is not the case, then mempty is returned.
emptyBox :: BoundingBox v n #
An empty bounding box. This is the same thing as mempty, but it doesn't
require the same type constraints that the Monoid instance does.
data BoundingBox (v :: Type -> Type) n #
A bounding box is an axis-aligned region determined by two points
indicating its "lower" and "upper" corners. It can also represent
an empty bounding box - the points are wrapped in Maybe.
Instances
showLabels :: (TypeableFloat n, Renderable (Text n) b, Semigroup m) => QDiagram b V2 n m -> QDiagram b V2 n Any #
showTrace :: (Enum n, TypeableFloat n, Renderable (Path V2 n) b) => QDiagram b V2 n Any -> QDiagram b V2 n Any #
Mark the trace of a diagram by placing 64 red dots 1/100th its size along the trace.
showTrace' :: (Enum n, TypeableFloat n, Renderable (Path V2 n) b) => TraceOpts n -> QDiagram b V2 n Any -> QDiagram b V2 n Any #
Mark the trace of a diagram, with control over colour and scale of marker dot and the number of points on the trace.
showEnvelope :: (Enum n, TypeableFloat n, Renderable (Path V2 n) b) => QDiagram b V2 n Any -> QDiagram b V2 n Any #
Mark the envelope with an approximating cubic spline using 32 points, medium line width and red line color.
showEnvelope' :: (Enum n, TypeableFloat n, Renderable (Path V2 n) b) => EnvelopeOpts n -> QDiagram b V2 n Any -> QDiagram b V2 n Any #
Mark the envelope with an approximating cubic spline with control over the color, line width and number of points.
showOrigin' :: (TypeableFloat n, Renderable (Path V2 n) b, Monoid' m) => OriginOpts n -> QDiagram b V2 n m -> QDiagram b V2 n m #
Mark the origin of a diagram, with control over colour and scale of marker dot.
showOrigin :: (TypeableFloat n, Renderable (Path V2 n) b, Monoid' m) => QDiagram b V2 n m -> QDiagram b V2 n m #
Mark the origin of a diagram by placing a red dot 1/50th its size.
ePoints :: Lens' (EnvelopeOpts n) Int #
eLineWidth :: Lens (EnvelopeOpts n1) (EnvelopeOpts n2) (Measure n1) (Measure n2) #
oScale :: Lens' (OriginOpts n) n #
oMinSize :: Lens' (OriginOpts n) n #
data EnvelopeOpts n #
Constructors
| EnvelopeOpts | |
Instances
| OrderedField n => Default (EnvelopeOpts n) | |
Defined in Diagrams.TwoD.Model Methods def :: EnvelopeOpts n # | |
data OriginOpts n #
Instances
| Fractional n => Default (OriginOpts n) | |
Defined in Diagrams.TwoD.Model Methods def :: OriginOpts n # | |
cubicSpline :: (V t ~ v, N t ~ n, TrailLike t, Fractional (v n)) => Bool -> [Point v n] -> t #
Construct a spline path-like thing of cubic segments from a list of vertices, with the first vertex as the starting point. The first argument specifies whether the path should be closed.
pts = map p2 [(0,0), (2,3), (5,-2), (-4,1), (0,3)]
spot = circle 0.2 # fc blue # lw none
mkPath closed = position (zip pts (repeat spot))
<> cubicSpline closed pts
cubicSplineEx = (mkPath False ||| strutX 2 ||| mkPath True)
# centerXY # pad 1.1For more information, see http://mathworld.wolfram.com/CubicSpline.html.
bspline :: (TrailLike t, V t ~ v, N t ~ n) => BSpline v n -> t #
Generate a uniform cubic B-spline from the given control points. The spline starts and ends at the first and last control points, and is tangent to the line to the second(-to-last) control point. It does not necessarily pass through any of the other control points.
pts = map p2 [(0,0), (2,3), (5,-2), (-4,1), (0,3)] spot = circle 0.2 # fc blue # lw none bsplineEx = mconcat [ position (zip pts (repeat spot)) , bspline pts ] # frame 0.5
facingZ :: (R3 v, Functor v, Fractional n) => Deformation v v n #
perspectiveZ1 :: (R3 v, Functor v, Fractional n) => Deformation v v n #
The perspective division onto the plane z=1 along lines going through the origin.
parallelZ0 :: (R3 v, Num n) => Deformation v v n #
The parallel projection onto the plane z=0
facingY :: (R2 v, Functor v, Fractional n) => Deformation v v n #
facingX :: (R1 v, Functor v, Fractional n) => Deformation v v n #
The viewing transform for a viewer facing along the positive X
axis. X coördinates stay fixed, while Y coördinates are compressed
with increasing distance. asDeformation (translation unitX) <>
parallelX0 <> frustrumX = perspectiveX1
perspectiveY1 :: (R2 v, Functor v, Floating n) => Deformation v v n #
The perspective division onto the plane y=1 along lines going through the origin.
parallelY0 :: (R2 v, Num n) => Deformation v v n #
The parallel projection onto the plane y=0
perspectiveX1 :: (R1 v, Functor v, Fractional n) => Deformation v v n #
The perspective division onto the plane x=1 along lines going through the origin.
parallelX0 :: (R1 v, Num n) => Deformation v v n #
The parallel projection onto the plane x=0
asDeformation :: (Additive v, Num n) => Transformation v n -> Deformation v v n #
asDeformation converts a Transformation to a Deformation by
discarding the inverse transform. This allows reusing
Transformations in the construction of Deformations.
newtype Deformation (v :: Type -> Type) (u :: Type -> Type) n #
Deformations are a superset of the affine transformations
represented by the Transformation type. In general they are not
invertible. Deformations include projective transformations.
Deformation can represent other functions from points to points
which are "well-behaved", in that they do not introduce small wiggles.
Constructors
| Deformation (Point v n -> Point u n) |
Instances
| Semigroup (Deformation v v n) | |
Defined in Diagrams.Deform Methods (<>) :: Deformation v v n -> Deformation v v n -> Deformation v v n # sconcat :: NonEmpty (Deformation v v n) -> Deformation v v n # stimes :: Integral b => b -> Deformation v v n -> Deformation v v n # | |
| Monoid (Deformation v v n) | |
Defined in Diagrams.Deform Methods mempty :: Deformation v v n # mappend :: Deformation v v n -> Deformation v v n -> Deformation v v n # mconcat :: [Deformation v v n] -> Deformation v v n # | |
class Deformable a b where #
Methods
deform' :: N a -> Deformation (V a) (V b) (N a) -> a -> b #
deform' epsilon d a transforms a by the deformation d.
If the type of a is not closed under projection, approximate
to accuracy epsilon.
deform :: Deformation (V a) (V b) (N a) -> a -> b #
deform d a transforms a by the deformation d.
If the type of a is not closed under projection, deform
should call deform' with some reasonable default value of
epsilon.
Instances
| (Metric v, Metric u, OrderedField n, r ~ Located (Trail u n)) => Deformable (Located (Trail v n)) r | |
| r ~ Point u n => Deformable (Point v n) r | |
| (Metric v, Metric u, OrderedField n, r ~ Path u n) => Deformable (Path v n) r | |
connectOutside' :: (TypeableFloat n, Renderable (Path V2 n) b, IsName n1, IsName n2) => ArrowOpts n -> n1 -> n2 -> QDiagram b V2 n Any -> QDiagram b V2 n Any #
connectOutside :: (TypeableFloat n, Renderable (Path V2 n) b, IsName n1, IsName n2) => n1 -> n2 -> QDiagram b V2 n Any -> QDiagram b V2 n Any #
Draw an arrow from diagram named "n1" to diagram named "n2". The arrow lies on the line between the centres of the diagrams, but is drawn so that it stops at the boundaries of the diagrams, using traces to find the intersection points.
connectPerim' :: (TypeableFloat n, Renderable (Path V2 n) b, IsName n1, IsName n2) => ArrowOpts n -> n1 -> n2 -> Angle n -> Angle n -> QDiagram b V2 n Any -> QDiagram b V2 n Any #
connectPerim :: (TypeableFloat n, Renderable (Path V2 n) b, IsName n1, IsName n2) => n1 -> n2 -> Angle n -> Angle n -> QDiagram b V2 n Any -> QDiagram b V2 n Any #
Connect two diagrams at point on the perimeter of the diagrams, choosen by angle.
connect' :: (TypeableFloat n, Renderable (Path V2 n) b, IsName n1, IsName n2) => ArrowOpts n -> n1 -> n2 -> QDiagram b V2 n Any -> QDiagram b V2 n Any #
Connect two diagrams with an arbitrary arrow.
connect :: (TypeableFloat n, Renderable (Path V2 n) b, IsName n1, IsName n2) => n1 -> n2 -> QDiagram b V2 n Any -> QDiagram b V2 n Any #
Connect two diagrams with a straight arrow.
arrowV' :: (TypeableFloat n, Renderable (Path V2 n) b) => ArrowOpts n -> V2 n -> QDiagram b V2 n Any #
arrowV' v creates an arrow with the direction and norm of
the vector v (with its tail at the origin).
arrowV :: (TypeableFloat n, Renderable (Path V2 n) b) => V2 n -> QDiagram b V2 n Any #
arrowV v creates an arrow with the direction and norm of
the vector v (with its tail at the origin), using default
parameters.
arrowAt' :: (TypeableFloat n, Renderable (Path V2 n) b) => ArrowOpts n -> Point V2 n -> V2 n -> QDiagram b V2 n Any #
arrowAt :: (TypeableFloat n, Renderable (Path V2 n) b) => Point V2 n -> V2 n -> QDiagram b V2 n Any #
Create an arrow starting at s with length and direction determined by the vector v.
arrowBetween' :: (TypeableFloat n, Renderable (Path V2 n) b) => ArrowOpts n -> Point V2 n -> Point V2 n -> QDiagram b V2 n Any #
arrowBetween' opts s e creates an arrow pointing from s to
e using the given options. In particular, it scales and
rotates arrowShaft to go between s and e, taking head,
tail, and gaps into account.
arrowBetween :: (TypeableFloat n, Renderable (Path V2 n) b) => Point V2 n -> Point V2 n -> QDiagram b V2 n Any #
arrowBetween s e creates an arrow pointing from s to e
with default parameters.
arrow' :: (TypeableFloat n, Renderable (Path V2 n) b) => ArrowOpts n -> n -> QDiagram b V2 n Any #
arrow' opts len creates an arrow of length len using the
given options, starting at the origin and ending at the point
(len,0). In particular, it scales the given arrowShaft so
that the entire arrow has length len.
arrow :: (TypeableFloat n, Renderable (Path V2 n) b) => n -> QDiagram b V2 n Any #
arrow len creates an arrow of length len with default
parameters, starting at the origin and ending at the point
(len,0).
shaftTexture :: TypeableFloat n => Lens' (ArrowOpts n) (Texture n) #
A lens for setting or modifying the texture of an arrow shaft.
tailTexture :: TypeableFloat n => Lens' (ArrowOpts n) (Texture n) #
A lens for setting or modifying the texture of an arrow
tail. This is *not* a valid lens (see committed).
headTexture :: TypeableFloat n => Lens' (ArrowOpts n) (Texture n) #
A lens for setting or modifying the texture of an arrowhead. For
example, one may write ... (with & headTexture .~ grad) to get an
arrow with a head filled with a gradient, assuming grad has been
defined. Or ... (with & headTexture .~ solid blue to set the head
color to blue. For more general control over the style of arrowheads,
see headStyle.
lengths :: Traversal' (ArrowOpts n) (Measure n) #
Set both the headLength and tailLength simultaneously.
gap :: Traversal' (ArrowOpts n) (Measure n) #
Same as gaps, provided for backward compatiiblity.
gaps :: Traversal' (ArrowOpts n) (Measure n) #
Set both the headGap and tailGap simultaneously.
tailLength :: Lens' (ArrowOpts n) (Measure n) #
The length of the tail plus its joint.
tailGap :: Lens' (ArrowOpts n) (Measure n) #
Distance to leave between the starting point and the tail.
headStyle :: Lens' (ArrowOpts n) (Style V2 n) #
Style to apply to the head. headStyle is modified by using the lens
combinator %~ to change the current style. For example, to change
an opaque black arrowhead to translucent orange:
(with & headStyle %~ fc orange . opacity 0.75).
headLength :: Lens' (ArrowOpts n) (Measure n) #
The length from the start of the joint to the tip of the head.
headGap :: Lens' (ArrowOpts n) (Measure n) #
Distance to leave between the head and the target point.
straightShaft :: OrderedField n => Trail V2 n #
Straight line arrow shaft.
Constructors
| ArrowOpts | |
Fields
| |
Instances
| TypeableFloat n => Default (ArrowOpts n) | |
Defined in Diagrams.TwoD.Arrow | |
arrowtailQuill :: OrderedField n => Angle n -> ArrowHT n #
The angle is where the top left corner intersects the circle.
arrowtailBlock :: RealFloat n => Angle n -> ArrowHT n #
arrowheadThorn :: RealFloat n => Angle n -> ArrowHT n #
Curved sides, linear concave base. Illustrator CS5 #3
arrowheadSpike :: RealFloat n => Angle n -> ArrowHT n #
Isoceles triangle with curved concave base. Inkscape type 2.
arrowheadHalfDart :: RealFloat n => Angle n -> ArrowHT n #
Top half of an arrowheadDart.
arrowheadDart :: RealFloat n => Angle n -> ArrowHT n #
Isoceles triangle with linear concave base. Inkscape type 1 - dart like.
arrowheadTriangle :: RealFloat n => Angle n -> ArrowHT n #
Isoceles triangle style. The above example specifies an angle of `2/5 Turn`.
mediumWeight :: HasStyle a => a -> a #
Set all text using a medium font weight.
ultraLight :: HasStyle a => a -> a #
Set all text using a extra light font weight.
thinWeight :: HasStyle a => a -> a #
Set all text using a thin font weight.
_fontSize :: (Typeable n, OrderedField n) => Lens' (Style v n) (Measure n) #
Lens to commit a font size. This is *not* a valid lens (see
commited.
_fontSizeR :: (Typeable n, OrderedField n) => Lens' (Style v n) (Measured n (Recommend n)) #
fontSizeL :: (N a ~ n, Typeable n, Num n, HasStyle a) => n -> a -> a #
A convenient sysnonym for 'fontSize (Local w)'.
fontSizeO :: (N a ~ n, Typeable n, HasStyle a) => n -> a -> a #
A convenient synonym for 'fontSize (Output w)'.
fontSizeN :: (N a ~ n, Typeable n, Num n, HasStyle a) => n -> a -> a #
A convenient synonym for 'fontSize (Normalized w)'.
fontSizeG :: (N a ~ n, Typeable n, Num n, HasStyle a) => n -> a -> a #
A convenient synonym for 'fontSize (Global w)'.
fontSize :: (N a ~ n, Typeable n, HasStyle a) => Measure n -> a -> a #
Set the font size, that is, the size of the font's em-square as
measured within the current local vector space. The default size
is local 1 (which is applied by recommendFontSize).
font :: HasStyle a => String -> a -> a #
Specify a font family to be used for all text within a diagram.
baselineText :: (TypeableFloat n, Renderable (Text n) b) => String -> QDiagram b V2 n Any #
Create a primitive text diagram from the given string, with the origin set to be on the baseline, at the beginning (although not bounding). This is the reference point of showText in the Cairo graphics library.
Note that it takes up no space.
alignedText :: (TypeableFloat n, Renderable (Text n) b) => n -> n -> String -> QDiagram b V2 n Any #
Create a primitive text diagram from the given string, with the origin set to a point interpolated within the bounding box. The first parameter varies from 0 (left) to 1 (right), and the second parameter from 0 (bottom) to 1 (top). Some backends do not implement this and instead snap to closest corner or the center.
The height of this box is determined by the font's potential ascent and descent, rather than the height of the particular string.
Note that it takes up no space.
topLeftText :: (TypeableFloat n, Renderable (Text n) b) => String -> QDiagram b V2 n Any #
Create a primitive text diagram from the given string, origin at
the top left corner of the text's bounding box, equivalent to
.alignedText 0 1
Note that it takes up no space.
text :: (TypeableFloat n, Renderable (Text n) b) => String -> QDiagram b V2 n Any #
Create a primitive text diagram from the given string, with center
alignment, equivalent to .alignedText 0.5 0.5
Note that it takes up no space, as text size information is not available.
fcA :: (InSpace V2 n a, Floating n, Typeable n, HasStyle a) => AlphaColour Double -> a -> a #
A synonym for fillColor, specialized to
(i.e. colors with transparency). See comment after AlphaColour DoublefillColor about backends.
recommendFillColor :: (InSpace V2 n a, Color c, Typeable n, Floating n, HasStyle a) => c -> a -> a #
fillColor :: (InSpace V2 n a, Color c, Typeable n, Floating n, HasStyle a) => c -> a -> a #
Set the fill color. This function is polymorphic in the color
type (so it can be used with either Colour or AlphaColour),
but this can sometimes create problems for type inference, so the
fc and fcA variants are provided with more concrete types.
_fillTexture :: (Typeable n, Floating n) => Lens' (Style V2 n) (Texture n) #
Commit a fill texture in a style. This is not a valid setter
because it doesn't abide the functor law (see committed).
getFillTexture :: FillTexture n -> Texture n #
_FillTexture :: Iso' (FillTexture n) (Recommend (Texture n)) #
lcA :: (InSpace V2 n a, Typeable n, Floating n, HasStyle a) => AlphaColour Double -> a -> a #
A synonym for lineColor, specialized to
(i.e. colors with transparency). See comment in AlphaColour DoublelineColor
about backends.
lineColor :: (InSpace V2 n a, Color c, Typeable n, Floating n, HasStyle a) => c -> a -> a #
Set the line (stroke) color. This function is polymorphic in the
color type (so it can be used with either Colour or
AlphaColour), but this can sometimes create problems for type
inference, so the lc and lcA variants are provided with more
concrete types.
lineTextureA :: (InSpace V2 n a, Typeable n, Floating n, HasStyle a) => LineTexture n -> a -> a #
getLineTexture :: LineTexture n -> Texture n #
_LineTexture :: Iso (LineTexture n) (LineTexture n') (Texture n) (Texture n') #
mkRadialGradient :: Num n => [GradientStop n] -> Point V2 n -> n -> Point V2 n -> n -> SpreadMethod -> Texture n #
Make a radial gradient texture from a stop list, radius, start point,
end point, and SpreadMethod. The rGradTrans field is set to the identity
transfrom, to change it use the rGradTrans lens.
mkLinearGradient :: Num n => [GradientStop n] -> Point V2 n -> Point V2 n -> SpreadMethod -> Texture n #
Make a linear gradient texture from a stop list, start point, end point,
and SpreadMethod. The lGradTrans field is set to the identity
transfrom, to change it use the lGradTrans lens.
mkStops :: [(Colour Double, d, Double)] -> [GradientStop d] #
A convenient function for making gradient stops from a list of triples. (An opaque color, a stop fraction, an opacity).
defaultRG :: Fractional n => Texture n #
A default is provided so that radial gradients can easily be created using
lenses. For example, rg = defaultRG & rGradRadius1 .~ 0.25. Note that
no default value is provided for rGradStops, this must be set before
the gradient value is used, otherwise the object will appear transparent.
defaultLG :: Fractional n => Texture n #
A default is provided so that linear gradients can easily be created using
lenses. For example, lg = defaultLG & lGradStart .~ (0.25 ^& 0.33). Note that
no default value is provided for lGradStops, this must be set before
the gradient value is used, otherwise the object will appear transparent.
_AC :: Prism' (Texture n) (AlphaColour Double) #
Prism onto an AlphaColour Double of a SC texture.
rGradTrans :: Lens' (RGradient n) (Transformation V2 n) #
A transformation to be applied to the gradient. Usually this field will start as the identity transform and capture the transforms that are applied to the gradient.
rGradStops :: Lens' (RGradient n) [GradientStop n] #
A list of stops (colors and fractions).
rGradSpreadMethod :: Lens' (RGradient n) SpreadMethod #
For setting the spread method.
rGradRadius1 :: Lens' (RGradient n) n #
The radius of the outer circle in local coordinates.
rGradRadius0 :: Lens' (RGradient n) n #
The radius of the inner cirlce in local coordinates.
A Texture is either a color SC, linear gradient LG, or radial gradient RG.
An object can have only one texture which is determined by the Last
semigroup structure.
Instances
| Floating n => Transformable (Texture n) | |
Defined in Diagrams.TwoD.Attributes | |
| type V (Texture n) | |
Defined in Diagrams.TwoD.Attributes | |
| type N (Texture n) | |
Defined in Diagrams.TwoD.Attributes | |
lGradTrans :: Lens' (LGradient n) (Transformation V2 n) #
A transformation to be applied to the gradient. Usually this field will start as the identity transform and capture the transforms that are applied to the gradient.
lGradStops :: Lens' (LGradient n) [GradientStop n] #
A list of stops (colors and fractions).
lGradStart :: Lens' (LGradient n) (Point V2 n) #
The starting point for the first gradient stop. The coordinates are in
local units and the default is (-0.5, 0).
lGradSpreadMethod :: Lens' (LGradient n) SpreadMethod #
For setting the spread method.
lGradEnd :: Lens' (LGradient n) (Point V2 n) #
The ending point for the last gradient stop.The coordinates are in
local units and the default is (0.5, 0).
Radial Gradient
Constructors
| RGradient | |
Fields
| |
Instances
| Fractional n => Transformable (RGradient n) | |
Defined in Diagrams.TwoD.Attributes | |
| type V (RGradient n) | |
Defined in Diagrams.TwoD.Attributes | |
| type N (RGradient n) | |
Defined in Diagrams.TwoD.Attributes | |
stopFraction :: Lens' (GradientStop n) n #
The fraction for stop.
stopColor :: Lens' (GradientStop n) SomeColor #
A color for the stop.
data SpreadMethod #
The SpreadMethod determines what happens before lGradStart and after
lGradEnd. GradPad fills the space before the start of the gradient
with the color of the first stop and the color after end of the gradient
with the color of the last stop. GradRepeat restarts the gradient and
GradReflect restarts the gradient with the stops in reverse order.
Constructors
| GradPad | |
| GradReflect | |
| GradRepeat |
Linear Gradient
Constructors
| LGradient | |
Fields
| |
Instances
| Fractional n => Transformable (LGradient n) | |
Defined in Diagrams.TwoD.Attributes | |
| type V (LGradient n) | |
Defined in Diagrams.TwoD.Attributes | |
| type N (LGradient n) | |
Defined in Diagrams.TwoD.Attributes | |
data GradientStop d #
A gradient stop contains a color and fraction (usually between 0 and 1)
Constructors
| GradientStop | |
Fields
| |
raster :: Num n => (Int -> Int -> AlphaColour Double) -> Int -> Int -> DImage n Embedded #
Create an image "from scratch" by specifying the pixel data
rasterDia :: (TypeableFloat n, Renderable (DImage n Embedded) b) => (Int -> Int -> AlphaColour Double) -> Int -> Int -> QDiagram b V2 n Any #
Crate a diagram from raw raster data.
uncheckedImageRef :: Num n => FilePath -> Int -> Int -> DImage n External #
Make an "unchecked" image reference; have to specify a width and height. Unless the aspect ratio of the external image is the w :: h, then the image will be distorted.
loadImageExt :: Num n => FilePath -> IO (Either String (DImage n External)) #
Check that a file exists, and use JuicyPixels to figure out the right size, but save a reference to the image instead of the raster data
loadImageEmb :: Num n => FilePath -> IO (Either String (DImage n Embedded)) #
Use JuicyPixels to read a file in any format and wrap it in a DImage.
The width and height of the image are set to their actual values.
image :: (TypeableFloat n, Typeable a, Renderable (DImage n a) b) => DImage n a -> QDiagram b V2 n Any #
ImageData is either a JuicyPixels DynamicImage tagged as Embedded or
a reference tagged as External. Additionally Native is provided for
external libraries to hook into.
Constructors
| ImageRaster :: forall a. DynamicImage -> ImageData Embedded | |
| ImageRef :: forall a. FilePath -> ImageData External | |
| ImageNative :: forall a t. t -> ImageData (Native t) |
An image primitive, the two ints are width followed by height.
Will typically be created by loadImageEmb or loadImageExt which,
will handle setting the width and height to the actual width and height
of the image.
Instances
| Fractional n => Transformable (DImage n a) | |
Defined in Diagrams.TwoD.Image | |
| Fractional n => HasOrigin (DImage n a) | |
Defined in Diagrams.TwoD.Image | |
| Fractional n => Renderable (DImage n a) NullBackend | |
Defined in Diagrams.TwoD.Image Methods render :: NullBackend -> DImage n a -> Render NullBackend (V (DImage n a)) (N (DImage n a)) # | |
| SVGFloat n => Renderable (DImage n (Native Img)) SVG | |
| SVGFloat n => Renderable (DImage n Embedded) SVG | |
| RealFloat n => HasQuery (DImage n a) Any | |
| type V (DImage n a) | |
Defined in Diagrams.TwoD.Image | |
| type N (DImage n a) | |
Defined in Diagrams.TwoD.Image | |
intersectPointsT' :: OrderedField n => n -> Located (Trail V2 n) -> Located (Trail V2 n) -> [P2 n] #
Compute the intersect points between two located trails within the given tolerance.
intersectPointsT :: OrderedField n => Located (Trail V2 n) -> Located (Trail V2 n) -> [P2 n] #
Compute the intersect points between two located trails.
intersectPointsP' :: OrderedField n => n -> Path V2 n -> Path V2 n -> [P2 n] #
Compute the intersect points between two paths within given tolerance.
intersectPointsP :: OrderedField n => Path V2 n -> Path V2 n -> [P2 n] #
Compute the intersect points between two paths.
intersectPoints' :: (InSpace V2 n t, SameSpace t s, ToPath t, ToPath s, OrderedField n) => n -> t -> s -> [P2 n] #
Find the intersect points of two objects that can be converted to a path within the given tolerance.
intersectPoints :: (InSpace V2 n t, SameSpace t s, ToPath t, ToPath s, OrderedField n) => t -> s -> [P2 n] #
Find the intersect points of two objects that can be converted to a path.
clipped :: TypeableFloat n => Path V2 n -> QDiagram b V2 n Any -> QDiagram b V2 n Any #
Clip a diagram to the clip path taking the envelope and trace of the clip path.
clipTo :: TypeableFloat n => Path V2 n -> QDiagram b V2 n Any -> QDiagram b V2 n Any #
Clip a diagram to the given path setting its envelope to the pointwise minimum of the envelopes of the diagram and path. The trace consists of those parts of the original diagram's trace which fall within the clipping path, or parts of the path's trace within the original diagram.
clipBy :: (HasStyle a, V a ~ V2, N a ~ n, TypeableFloat n) => Path V2 n -> a -> a #
Clip a diagram by the given path:
- Only the parts of the diagram which lie in the interior of the path will be drawn.
- The envelope of the diagram is unaffected.
_clip :: (Typeable n, OrderedField n) => Lens' (Style V2 n) [Path V2 n] #
Lens onto the Clip in a style. An empty list means no clipping.
fillRule :: HasStyle a => FillRule -> a -> a #
Specify the fill rule that should be used for determining which points are inside a path.
strokeLocLoop :: (TypeableFloat n, Renderable (Path V2 n) b) => Located (Trail' Loop V2 n) -> QDiagram b V2 n Any #
A convenience function for converting a Located loop directly
into a diagram; strokeLocLoop = stroke . trailLike . mapLoc wrapLoop.
strokeLocLine :: (TypeableFloat n, Renderable (Path V2 n) b) => Located (Trail' Line V2 n) -> QDiagram b V2 n Any #
A convenience function for converting a Located line directly
into a diagram; strokeLocLine = stroke . trailLike . mapLoc wrapLine.
strokeLocT :: (TypeableFloat n, Renderable (Path V2 n) b) => Located (Trail V2 n) -> QDiagram b V2 n Any #
Deprecated synonym for strokeLocTrail.
strokeLocTrail :: (TypeableFloat n, Renderable (Path V2 n) b) => Located (Trail V2 n) -> QDiagram b V2 n Any #
A convenience function for converting a Located Trail directly
into a diagram; strokeLocTrail = stroke . trailLike.
strokeLoop :: (TypeableFloat n, Renderable (Path V2 n) b) => Trail' Loop V2 n -> QDiagram b V2 n Any #
strokeLine :: (TypeableFloat n, Renderable (Path V2 n) b) => Trail' Line V2 n -> QDiagram b V2 n Any #
strokeT' :: (TypeableFloat n, Renderable (Path V2 n) b, IsName a) => StrokeOpts a -> Trail V2 n -> QDiagram b V2 n Any #
Deprecated synonym for strokeTrail'.
strokeTrail' :: (TypeableFloat n, Renderable (Path V2 n) b, IsName a) => StrokeOpts a -> Trail V2 n -> QDiagram b V2 n Any #
A composition of stroke' and pathFromTrail for conveniently
converting a trail directly into a diagram.
strokeTrail :: (TypeableFloat n, Renderable (Path V2 n) b) => Trail V2 n -> QDiagram b V2 n Any #
strokePath' :: (TypeableFloat n, Renderable (Path V2 n) b, IsName a) => StrokeOpts a -> Path V2 n -> QDiagram b V2 n Any #
strokeP' :: (TypeableFloat n, Renderable (Path V2 n) b, IsName a) => StrokeOpts a -> Path V2 n -> QDiagram b V2 n Any #
strokePath :: (TypeableFloat n, Renderable (Path V2 n) b) => Path V2 n -> QDiagram b V2 n Any #
stroke' :: (InSpace V2 n t, ToPath t, TypeableFloat n, Renderable (Path V2 n) b, IsName a) => StrokeOpts a -> t -> QDiagram b V2 n Any #
A variant of stroke that takes an extra record of options to
customize its behaviour. In particular:
- Names can be assigned to the path's vertices
StrokeOpts is an instance of Default, so stroke' ( syntax may be used.with &
... )
stroke :: (InSpace V2 n t, ToPath t, TypeableFloat n, Renderable (Path V2 n) b) => t -> QDiagram b V2 n Any #
Convert a ToPath object into a diagram. The resulting diagram has the
names 0, 1, ... assigned to each of the path's vertices.
See also stroke', which takes an extra options record allowing
its behaviour to be customized.
stroke::PathV2Double->Diagrambstroke::Located(TrailV2Double) ->Diagrambstroke::Located(Trail'LoopV2Double) ->Diagrambstroke::Located(Trail'LineV2Double) ->Diagramb
vertexNames :: Lens (StrokeOpts a) (StrokeOpts a') [[a]] [[a']] #
Atomic names that should be assigned to the vertices of the path so that they can be referenced later. If there are not enough names, the extra vertices are not assigned names; if there are too many, the extra names are ignored. Note that this is a list of lists of names, since paths can consist of multiple trails. The first list of names are assigned to the vertices of the first trail, the second list to the second trail, and so on.
The default value is the empty list.
queryFillRule :: Lens' (StrokeOpts a) FillRule #
Enumeration of algorithms or "rules" for determining which points lie in the interior of a (possibly self-intersecting) path.
Constructors
| Winding | Interior points are those with a nonzero winding number. See http://en.wikipedia.org/wiki/Nonzero-rule. |
| EvenOdd | Interior points are those where a ray extended infinitely in a particular direction crosses the path an odd number of times. See http://en.wikipedia.org/wiki/Even-odd_rule. |
Instances
| Eq FillRule | |
| Ord FillRule | |
Defined in Diagrams.TwoD.Path | |
| Show FillRule | |
| Semigroup FillRule | |
| Default FillRule | |
Defined in Diagrams.TwoD.Path | |
| AttributeClass FillRule | |
Defined in Diagrams.TwoD.Path | |
data StrokeOpts a #
A record of options that control how a path is stroked.
StrokeOpts is an instance of Default, so a StrokeOpts
records can be created using notation.with { ... }
Constructors
| StrokeOpts | |
Fields
| |
Instances
| Default (StrokeOpts a) | |
Defined in Diagrams.TwoD.Path Methods def :: StrokeOpts a # | |
roundedRect' :: (InSpace V2 n t, TrailLike t, RealFloat n) => n -> n -> RoundedRectOpts n -> t #
roundedRect' works like roundedRect but allows you to set the radius of
each corner indivually, using RoundedRectOpts. The default corner radius is 0.
Each radius can also be negative, which results in the curves being reversed
to be inward instead of outward.
roundedRect :: (InSpace V2 n t, TrailLike t, RealFloat n) => n -> n -> n -> t #
roundedRect w h r generates a closed trail, or closed path
centered at the origin, of an axis-aligned rectangle with width
w, height h, and circular rounded corners of radius r. If
r is negative the corner will be cut out in a reverse arc. If
the size of r is larger than half the smaller dimension of w
and h, then it will be reduced to fit in that range, to prevent
the corners from overlapping. The trail or path begins with the
right edge and proceeds counterclockwise. If you need to specify
a different radius for each corner individually, use
roundedRect' instead.
roundedRectEx = pad 1.1 . centerXY $ hcat' (with & sep .~ 0.2)
[ roundedRect 0.5 0.4 0.1
, roundedRect 0.5 0.4 (-0.1)
, roundedRect' 0.7 0.4 (with & radiusTL .~ 0.2
& radiusTR .~ -0.2
& radiusBR .~ 0.1)
]radiusTR :: Lens' (RoundedRectOpts d) d #
radiusTL :: Lens' (RoundedRectOpts d) d #
radiusBR :: Lens' (RoundedRectOpts d) d #
radiusBL :: Lens' (RoundedRectOpts d) d #
dodecagon :: (InSpace V2 n t, TrailLike t) => n -> t #
A regular dodecagon, with sides of the given length and base parallel to the x-axis.
hendecagon :: (InSpace V2 n t, TrailLike t) => n -> t #
A regular hendecagon, with sides of the given length and base parallel to the x-axis.
decagon :: (InSpace V2 n t, TrailLike t) => n -> t #
A regular decagon, with sides of the given length and base parallel to the x-axis.
nonagon :: (InSpace V2 n t, TrailLike t) => n -> t #
A regular nonagon, with sides of the given length and base parallel to the x-axis.
octagon :: (InSpace V2 n t, TrailLike t) => n -> t #
A regular octagon, with sides of the given length and base parallel to the x-axis.
septagon :: (InSpace V2 n t, TrailLike t) => n -> t #
A synonym for heptagon. It is, however, completely inferior,
being a base admixture of the Latin septum (seven) and the
Greek γωνία (angle).
heptagon :: (InSpace V2 n t, TrailLike t) => n -> t #
A regular heptagon, with sides of the given length and base parallel to the x-axis.
hexagon :: (InSpace V2 n t, TrailLike t) => n -> t #
A regular hexagon, with sides of the given length and base parallel to the x-axis.
pentagon :: (InSpace V2 n t, TrailLike t) => n -> t #
A regular pentagon, with sides of the given length and base parallel to the x-axis.
triangle :: (InSpace V2 n t, TrailLike t) => n -> t #
An equilateral triangle, with sides of the given length and base parallel to the x-axis.
eqTriangle :: (InSpace V2 n t, TrailLike t) => n -> t #
A synonym for triangle, provided for backwards compatibility.
regPoly :: (InSpace V2 n t, TrailLike t) => Int -> n -> t #
Create a regular polygon. The first argument is the number of
sides, and the second is the length of the sides. (Compare to the
polygon function with a PolyRegular option, which produces
polygons of a given radius).
The polygon will be oriented with one edge parallel to the x-axis.
rect :: (InSpace V2 n t, TrailLike t) => n -> n -> t #
rect w h is an axis-aligned rectangle of width w and height
h, centered at the origin.
square :: (InSpace V2 n t, TrailLike t) => n -> t #
A square with its center at the origin and sides of the given length, oriented parallel to the axes.
unitSquare :: (InSpace V2 n t, TrailLike t) => t #
A square with its center at the origin and sides of length 1, oriented parallel to the axes.
vrule :: (InSpace V2 n t, TrailLike t) => n -> t #
Create a centered vertical (T-B) line of the given length.
vruleEx = hcat' (with & sep .~ 0.2) (map vrule [1, 1.2 .. 2])
# centerXY # pad 1.1hrule :: (InSpace V2 n t, TrailLike t) => n -> t #
Create a centered horizontal (L-R) line of the given length.
hruleEx = vcat' (with & sep .~ 0.2) (map hrule [1..5])
# centerXY # pad 1.1data RoundedRectOpts d #
Constructors
| RoundedRectOpts | |
Instances
| Num d => Default (RoundedRectOpts d) | |
Defined in Diagrams.TwoD.Shapes Methods def :: RoundedRectOpts d # | |
star :: OrderedField n => StarOpts -> [Point V2 n] -> Path V2 n #
Create a generalized star polygon. The StarOpts are used
to determine in which order the given vertices should be
connected. The intention is that the second argument of type
[Point v] could be generated by a call to polygon, regPoly, or
the like, since a list of vertices is TrailLike. But of course
the list can be generated any way you like. A is
returned (instead of any Path vTrailLike) because the resulting path
may have more than one component, for example if the vertices are
to be connected in several disjoint cycles.
polygon :: (InSpace V2 n t, TrailLike t) => PolygonOpts n -> t #
Generate the polygon described by the given options.
polyTrail :: OrderedField n => PolygonOpts n -> Located (Trail V2 n) #
Generate a polygon. See PolygonOpts for more information.
polyType :: Lens' (PolygonOpts n) (PolyType n) #
Specification for the polygon's vertices.
polyOrient :: Lens' (PolygonOpts n) (PolyOrientation n) #
Should a rotation be applied to the polygon in order to orient it in a particular way?
polyCenter :: Lens' (PolygonOpts n) (Point V2 n) #
Should a translation be applied to the polygon in order to place the center at a particular location?
Options for creating "star" polygons, where the edges connect possibly non-adjacent vertices.
Constructors
| StarFun (Int -> Int) | Specify the order in which the vertices should be connected by a function that maps each vertex index to the index of the vertex that should come next. Indexing of vertices begins at 0. |
| StarSkip Int | Specify a star polygon by a "skip". A skip of 1 indicates a normal polygon, where edges go between successive vertices. A skip of 2 means that edges will connect every second vertex, skipping one in between. Generally, a skip of n means that edges will connect every nth vertex. |
Method used to determine the vertices of a polygon.
Constructors
| PolyPolar [Angle n] [n] | A "polar" polygon.
To construct an n-gon, use a list of n-1 angles and n radii. Extra angles or radii are ignored. Cyclic polygons (with all vertices lying on a
circle) can be constructed using a second
argument of |
| PolySides [Angle n] [n] | A polygon determined by the distance between successive vertices and the external angles formed by each three successive vertices. In other words, a polygon specified by "turtle graphics": go straight ahead x1 units; turn by external angle a1; go straight ahead x2 units; turn by external angle a2; etc. The polygon will be centered at the centroid of its vertices.
To construct an n-gon, use a list of n-2 angles and n-1 edge lengths. Extra angles or lengths are ignored. |
| PolyRegular Int n | A regular polygon with the given number of sides (first argument) and the given radius (second argument). |
data PolyOrientation n #
Determine how a polygon should be oriented.
Constructors
| NoOrient | No special orientation; the first vertex will be at (1,0). |
| OrientH | Orient horizontally, so the bottommost edge is parallel to the x-axis. This is the default. |
| OrientV | Orient vertically, so the leftmost edge is parallel to the y-axis. |
| OrientTo (V2 n) | Orient so some edge is facing in the direction of, that is, perpendicular to, the given vector. |
Instances
data PolygonOpts n #
Options for specifying a polygon.
Constructors
| PolygonOpts | |
Fields
| |
Instances
| Num n => Default (PolygonOpts n) | The default polygon is a regular pentagon of radius 1, centered at the origin, aligned to the x-axis. |
Defined in Diagrams.TwoD.Polygons Methods def :: PolygonOpts n # | |
reversePath :: (Metric v, OrderedField n) => Path v n -> Path v n #
Reverse all the component trails of a path.
scalePath :: (HasLinearMap v, Metric v, OrderedField n) => n -> Path v n -> Path v n #
Scale a path using its centroid (see pathCentroid) as the base
point for the scale.
partitionPath :: (Located (Trail v n) -> Bool) -> Path v n -> (Path v n, Path v n) #
Partition a path into two paths based on a predicate on trails:
the first containing all the trails for which the predicate returns
True, and the second containing the remaining trails.
explodePath :: (V t ~ v, N t ~ n, TrailLike t) => Path v n -> [[t]] #
"Explode" a path by exploding every component trail (see
explodeTrail).
fixPath :: (Metric v, OrderedField n) => Path v n -> [[FixedSegment v n]] #
Convert a path into a list of lists of FixedSegments.
pathLocSegments :: (Metric v, OrderedField n) => Path v n -> [[Located (Segment Closed v n)]] #
Convert a path into a list of lists of located segments.
pathCentroid :: (Metric v, OrderedField n) => Path v n -> Point v n #
Compute the centroid of a path (i.e. the average location of
its vertices; see pathVertices).
pathOffsets :: (Metric v, OrderedField n) => Path v n -> [v n] #
Compute the total offset of each trail comprising a path (see trailOffset).
pathVertices :: (Metric v, OrderedField n) => Path v n -> [[Point v n]] #
Like pathVertices', with a default tolerance.
pathVertices' :: (Metric v, OrderedField n) => n -> Path v n -> [[Point v n]] #
Extract the vertices of a path, resulting in a separate list of
vertices for each component trail. Here a vertex is defined as
a non-differentiable point on the trail, i.e. a sharp corner.
(Vertices are thus a subset of the places where segments join; if
you want all joins between segments, see pathPoints.) The
tolerance determines how close the tangents of two segments must be
at their endpoints to consider the transition point to be
differentiable. See trailVertices for more information.
pathFromLocTrail :: (Metric v, OrderedField n) => Located (Trail v n) -> Path v n #
Convert a located trail to a singleton path. This is equivalent
to trailLike, but provided with a more specific name and type
for convenience.
pathFromTrailAt :: (Metric v, OrderedField n) => Trail v n -> Point v n -> Path v n #
Convert a trail to a path with a particular starting point.
pathFromTrail :: (Metric v, OrderedField n) => Trail v n -> Path v n #
Convert a trail to a path beginning at the origin.
newtype Path (v :: Type -> Type) n #
A path is a (possibly empty) list of Located Trails.
Hence, unlike trails, paths are not translationally invariant,
and they form a monoid under superposition (placing one path on
top of another) rather than concatenation.
Instances
| Eq (v n) => Eq (Path v n) | |
| Ord (v n) => Ord (Path v n) | |
Defined in Diagrams.Path | |
| Show (v n) => Show (Path v n) | |
| Generic (Path v n) | |
| Semigroup (Path v n) | |
| Monoid (Path v n) | |
| (OrderedField n, Metric v, Serialize (v n), Serialize (V (v n) (N (v n)))) => Serialize (Path v n) | |
| (Metric v, OrderedField n) => Juxtaposable (Path v n) | |
| (Metric v, OrderedField n) => Enveloped (Path v n) | |
Defined in Diagrams.Path | |
| (HasLinearMap v, Metric v, OrderedField n) => Transformable (Path v n) | |
Defined in Diagrams.Path | |
| (Additive v, Num n) => HasOrigin (Path v n) | |
Defined in Diagrams.Path | |
| ToPath (Path v n) | |
| (Metric v, OrderedField n) => TrailLike (Path v n) | Paths are trail-like; a trail can be used to construct a singleton path. |
| (Metric v, OrderedField n) => Alignable (Path v n) | |
Defined in Diagrams.Path Methods alignBy' :: (InSpace v0 n0 (Path v n), Fractional n0, HasOrigin (Path v n)) => (v0 n0 -> Path v n -> Point v0 n0) -> v0 n0 -> n0 -> Path v n -> Path v n # defaultBoundary :: (V (Path v n) ~ v0, N (Path v n) ~ n0) => v0 n0 -> Path v n -> Point v0 n0 # alignBy :: (InSpace v0 n0 (Path v n), Fractional n0, HasOrigin (Path v n)) => v0 n0 -> n0 -> Path v n -> Path v n # | |
| (Metric v, OrderedField n) => Reversing (Path v n) | Same as |
Defined in Diagrams.Path | |
| AsEmpty (Path v n) | |
Defined in Diagrams.Path | |
| Wrapped (Path v n) | |
| (HasLinearMap v, Metric v, OrderedField n) => Renderable (Path v n) NullBackend | |
Defined in Diagrams.Path Methods render :: NullBackend -> Path v n -> Render NullBackend (V (Path v n)) (N (Path v n)) # | |
| SVGFloat n => Renderable (Path V2 n) SVG | |
| (Metric v, Metric u, OrderedField n, r ~ Path u n) => Deformable (Path v n) r | |
| Rewrapped (Path v n) (Path v' n') | |
Defined in Diagrams.Path | |
| Snoc (Path v n) (Path v' n') (Located (Trail v n)) (Located (Trail v' n')) | |
| Cons (Path v n) (Path v' n') (Located (Trail v n)) (Located (Trail v' n')) | |
| Each (Path v n) (Path v' n') (Located (Trail v n)) (Located (Trail v' n')) | |
| type Rep (Path v n) | |
| type V (Path v n) | |
Defined in Diagrams.Path | |
| type N (Path v n) | |
Defined in Diagrams.Path | |
| type Unwrapped (Path v n) | |
Defined in Diagrams.Path | |
Type class for things that can be converted to a Path.
Note that this class is very different from TrailLike. TrailLike is
usually the result of a library function to give you a convenient,
polymorphic result (Path, Diagram etc.).
Methods
Instances
| ToPath a => ToPath [a] | |
| ToPath (Located [Segment Closed v n]) | |
| ToPath (Located (Trail' l v n)) | |
| ToPath (Located (Trail v n)) | |
| ToPath (Located (Segment Closed v n)) | |
| ToPath (Path v n) | |
| ToPath (Trail v n) | |
| ToPath (FixedSegment v n) | |
Defined in Diagrams.Path Methods toPath :: FixedSegment v n -> Path (V (FixedSegment v n)) (N (FixedSegment v n)) # | |
| ToPath (Trail' l v n) | |
boundaryFromMay :: (Metric v, OrderedField n, Semigroup m) => Subdiagram b v n m -> v n -> Maybe (Point v n) #
Compute the furthest point on the boundary of a subdiagram,
beginning from the location (local origin) of the subdiagram and
moving in the direction of the given vector, or Nothing if
there is no such point.
boundaryFrom :: (OrderedField n, Metric v, Semigroup m) => Subdiagram b v n m -> v n -> Point v n #
Compute the furthest point on the boundary of a subdiagram,
beginning from the location (local origin) of the subdiagram and
moving in the direction of the given vector. If there is no such
point, the origin is returned; see also boundaryFromMay.
Arguments
| :: (Monoid' m, Floating n, Ord n, Metric v) | |
| => (QDiagram b v n m -> QDiagram b v n m) | Alignment function |
| -> ([QDiagram b v n m] -> QDiagram b v n m) | Composition function |
| -> [QDiagram b v n m] | |
| -> QDiagram b v n m |
Compose a list of diagrams using the given composition function,
first aligning them all according to the given alignment, but
retain the local origin of the first diagram, as it would be if
the composition function were applied directly. That is,
composeAligned algn comp is equivalent to translate v . comp
. map algn for some appropriate translation vector v.
Unfortunately, this only works for diagrams (and not, say, paths) because there is no most general type for alignment functions, and no generic way to find out what an alignment function does to the origin of things. (However, it should be possible to make a version of this function that works specifically on paths, if such a thing were deemed useful.)
alignedEx1 = (hsep 2 # composeAligned alignT) (map circle [1,3,5,2])
# showOrigin
# frame 0.5alignedEx2 = (mconcat # composeAligned alignTL) [circle 1, square 1, triangle 1, pentagon 1]
# showOrigin
# frame 0.1cat' :: (InSpace v n a, Metric v, Floating n, Juxtaposable a, Monoid' a, HasOrigin a) => v n -> CatOpts n -> [a] -> a #
Like cat, but taking an extra CatOpts arguments allowing the
user to specify
- The spacing method: catenation (uniform spacing between envelopes) or distribution (uniform spacing between local origins). The default is catenation.
- The amount of separation between successive diagram envelopes/origins (depending on the spacing method). The default is 0.
CatOpts is an instance of Default, so with may be used for
the second argument, as in cat' (1,2) (with & sep .~ 2).
Note that cat' v (with & catMethod .~ Distrib) === mconcat
(distributing with a separation of 0 is the same as
superimposing).
cat :: (InSpace v n a, Metric v, Floating n, Juxtaposable a, Monoid' a, HasOrigin a) => v n -> [a] -> a #
cat v positions a list of objects so that their local origins
lie along a line in the direction of v. Successive objects
will have their envelopes just touching. The local origin
of the result will be the same as the local origin of the first
object.
See also cat', which takes an extra options record allowing
certain aspects of the operation to be tweaked.
How much separation should be used between successive diagrams
(default: 0)? When catMethod = Cat, this is the distance between
envelopes; when catMethod = Distrib, this is the distance
between origins.
catMethod :: Lens' (CatOpts n) CatMethod #
Which CatMethod should be used:
normal catenation (default), or distribution?
atPoints :: (InSpace v n a, HasOrigin a, Monoid' a) => [Point v n] -> [a] -> a #
Curried version of position, takes a list of points and a list of
objects.
position :: (InSpace v n a, HasOrigin a, Monoid' a) => [(Point v n, a)] -> a #
Position things absolutely: combine a list of objects (e.g. diagrams or paths) by assigning them absolute positions in the vector space of the combined object.
positionEx = position (zip (map mkPoint [-3, -2.8 .. 3]) (repeat spot))
where spot = circle 0.2 # fc black
mkPoint :: Double -> P2 Double
mkPoint x = p2 (x,x*x)appends :: (Juxtaposable a, Monoid' a) => a -> [(Vn a, a)] -> a #
appends x ys appends each of the objects in ys to the object
x in the corresponding direction. Note that each object in
ys is positioned beside x without reference to the other
objects in ys, so this is not the same as iterating beside.
appendsEx = appends c (zip (iterateN 6 (rotateBy (1/6)) unitX) (repeat c))
# centerXY # pad 1.1
where c = circle 1atDirection :: (InSpace v n a, Metric v, Floating n, Juxtaposable a, Semigroup a) => Direction v n -> a -> a -> a #
Place two diagrams (or other juxtaposable objects) adjacent to
one another, with the second diagram placed in the direction d
from the first. The local origin of the resulting combined
diagram is the same as the local origin of the first. See the
documentation of beside for more information.
beside :: (Juxtaposable a, Semigroup a) => Vn a -> a -> a -> a #
Place two monoidal objects (i.e. diagrams, paths, animations...) next to each other along the given vector. In particular, place the second object so that the vector points from the local origin of the first object to the local origin of the second object, at a distance so that their envelopes are just tangent. The local origin of the new, combined object is the local origin of the first object (unless the first object is the identity element, in which case the second object is returned unchanged).
besideEx = beside (r2 (20,30))
(circle 1 # fc orange)
(circle 1.5 # fc purple)
# showOrigin
# centerXY # pad 1.1Note that beside v is associative, so objects under beside v
form a semigroup for any given vector v. In fact, they also
form a monoid: mempty is clearly a right identity (beside v d1
mempty === d1), and there should also be a special case to make
it a left identity, as described above.
In older versions of diagrams, beside put the local origin of
the result at the point of tangency between the two inputs. That
semantics can easily be recovered by performing an alignment on
the first input before combining. That is, if beside' denotes
the old semantics,
beside' v x1 x2 = beside v (x1 # align v) x2
To get something like beside v x1 x2 whose local origin is
identified with that of x2 instead of x1, use beside
(negateV v) x2 x1.
beneath :: (Metric v, OrderedField n, Monoid' m) => QDiagram b v n m -> QDiagram b v n m -> QDiagram b v n m infixl 6 #
intrudeEnvelope :: (Metric v, OrderedField n, Monoid' m) => v n -> QDiagram b v n m -> QDiagram b v n m #
intrudeEnvelope v d asymmetrically "intrudes" the envelope of
a diagram away from the given direction. All parts of the envelope
within 90 degrees of this direction are modified, offset inwards
by the magnitude of the vector.
Note that this could create strange inverted envelopes, where
diameter v d < 0 .
extrudeEnvelope :: (Metric v, OrderedField n, Monoid' m) => v n -> QDiagram b v n m -> QDiagram b v n m #
extrudeEnvelope v d asymmetrically "extrudes" the envelope of
a diagram in the given direction. All parts of the envelope
within 90 degrees of this direction are modified, offset outwards
by the magnitude of the vector.
This works by offsetting the envelope distance proportionally to the cosine of the difference in angle, and leaving it unchanged when this factor is negative.
strut :: (Metric v, OrderedField n) => v n -> QDiagram b v n m #
strut v is a diagram which produces no output, but with respect
to alignment and envelope acts like a 1-dimensional segment
oriented along the vector v, with local origin at its
center. (Note, however, that it has an empty trace; for 2D struts
with a nonempty trace see strutR2 from
Diagrams.TwoD.Combinators.) Useful for manually creating
separation between two diagrams.
strutEx = (circle 1 ||| strut unitX ||| circle 1) # centerXY # pad 1.1
frame :: (Metric v, OrderedField n, Monoid' m) => n -> QDiagram b v n m -> QDiagram b v n m #
frame s increases the envelope of a diagram by and absolute amount s,
s is in the local units of the diagram. This function is similar to pad,
only it takes an absolute quantity and pre-centering should not be
necessary.
pad :: (Metric v, OrderedField n, Monoid' m) => n -> QDiagram b v n m -> QDiagram b v n m #
pad s "pads" a diagram, expanding its envelope by a factor of
s (factors between 0 and 1 can be used to shrink the envelope).
Note that the envelope will expand with respect to the local
origin, so if the origin is not centered the padding may appear
"uneven". If this is not desired, the origin can be centered
(using, e.g., centerXY for 2D diagrams) before applying pad.
phantom :: (InSpace v n a, Monoid' m, Enveloped a, Traced a) => a -> QDiagram b v n m #
phantom x produces a "phantom" diagram, which has the same
envelope and trace as x but produces no output.
withTrace :: (InSpace v n a, Metric v, OrderedField n, Monoid' m, Traced a) => a -> QDiagram b v n m -> QDiagram b v n m #
Use the trace from some object as the trace for a diagram, in place of the diagram's default trace.
withEnvelope :: (InSpace v n a, Monoid' m, Enveloped a) => a -> QDiagram b v n m -> QDiagram b v n m #
Use the envelope from some object as the envelope for a diagram, in place of the diagram's default envelope.
sqNewEnv =
circle 1 # fc green
|||
( c # dashingG [0.1,0.1] 0 # lc white
<> square 2 # withEnvelope (c :: D V2 Double) # fc blue
)
c = circle 0.8
withEnvelopeEx = sqNewEnv # centerXY # pad 1.5Methods for concatenating diagrams.
Constructors
| Cat | Normal catenation: simply put diagrams next to one another (possibly with a certain distance in between each). The distance between successive diagram envelopes will be consistent; the distance between origins may vary if the diagrams are of different sizes. |
| Distrib | Distribution: place the local origins of diagrams at regular intervals. With this method, the distance between successive origins will be consistent but the distance between envelopes may not be. Indeed, depending on the amount of separation, diagrams may overlap. |
Options for cat'.
ellipseXY :: (TrailLike t, V t ~ V2, N t ~ n, Transformable t) => n -> n -> t #
ellipseXY x y creates an axis-aligned ellipse, centered at the
origin, with radius x along the x-axis and radius y along the
y-axis.
ellipse :: (TrailLike t, V t ~ V2, N t ~ n, Transformable t) => n -> t #
ellipse e constructs an ellipse with eccentricity e by
scaling the unit circle in the X direction. The eccentricity must
be within the interval [0,1).
circle :: (TrailLike t, V t ~ V2, N t ~ n, Transformable t) => n -> t #
A circle of the given radius, centered at the origin. As a path, it begins at (r,0).
unitCircle :: (TrailLike t, V t ~ V2, N t ~ n) => t #
A circle of radius 1, with center at the origin.
annularWedge :: (TrailLike t, V t ~ V2, N t ~ n, RealFloat n) => n -> n -> Direction V2 n -> Angle n -> t #
Create an annular wedge of the given radii, beginning at the first direction and extending through the given sweep angle. The radius of the outer circle is given first.
annularWedgeEx = hsep 0.50 [ annularWedge 1 0.5 xDir (1/4 @@ turn) , annularWedge 1 0.3 (rotate (7/30 @@ turn) xDir) (4/30 @@ turn) , annularWedge 1 0.7 (rotate (1/8 @@ turn) xDir) (3/4 @@ turn) ] # fc blue # centerXY # pad 1.1
arcBetween :: (TrailLike t, V t ~ V2, N t ~ n, RealFloat n) => Point V2 n -> Point V2 n -> n -> t #
arcBetween p q height creates an arc beginning at p and
ending at q, with its midpoint at a distance of abs height
away from the straight line from p to q. A positive value of
height results in an arc to the left of the line from p to
q; a negative value yields one to the right.
arcBetweenEx = mconcat [ arcBetween origin (p2 (2,1)) ht | ht <- [-0.2, -0.1 .. 0.2] ] # centerXY # pad 1.1
wedge :: (InSpace V2 n t, OrderedField n, TrailLike t) => n -> Direction V2 n -> Angle n -> t #
Create a circular wedge of the given radius, beginning at the given direction and extending through the given angle.
wedgeEx = hcat' (with & sep .~ 0.5) [ wedge 1 xDir (1/4 @@ turn) , wedge 1 (rotate (7/30 @@ turn) xDir) (4/30 @@ turn) , wedge 1 (rotate (1/8 @@ turn) xDir) (3/4 @@ turn) ] # fc blue # centerXY # pad 1.1
arcCW :: (InSpace V2 n t, RealFloat n, TrailLike t) => Direction V2 n -> Direction V2 n -> t #
Like arcAngleCCW but clockwise.
arcCCW :: (InSpace V2 n t, RealFloat n, TrailLike t) => Direction V2 n -> Direction V2 n -> t #
Given a start direction s and end direction e, arcCCW s e is the
path of a radius one arc counterclockwise between the two directions.
The origin of the arc is its center.
arc' :: (InSpace V2 n t, OrderedField n, TrailLike t) => n -> Direction V2 n -> Angle n -> t #
Given a radus r, a start direction d and an angle s,
is the path of a radius arc' r d s(abs r) arc starting at
d and sweeping out the angle s counterclockwise (for positive
s). The origin of the arc is its center.
arc'Ex = mconcat [ arc' r xDir (1/4 @@ turn) | r <- [0.5,-1,1.5] ]
# centerXY # pad 1.1arc :: (InSpace V2 n t, OrderedField n, TrailLike t) => Direction V2 n -> Angle n -> t #
Given a start direction d and a sweep angle s, is the
path of a radius one arc starting at arc d sd and sweeping out the angle
s counterclockwise (for positive s). The resulting
Trail is allowed to wrap around and overlap itself.
explodeTrail :: (V t ~ v, N t ~ n, TrailLike t) => Located (Trail v n) -> [t] #
Given a concretely located trail, "explode" it by turning each segment into its own separate trail. Useful for (say) applying a different style to each segment.
explodeTrailEx = pentagon 1 # explodeTrail -- generate a list of diagrams # zipWith lc [orange, green, yellow, red, blue] # mconcat # centerXY # pad 1.1
(~~) :: (V t ~ v, N t ~ n, TrailLike t) => Point v n -> Point v n -> t #
Create a linear trail between two given points.
twiddleEx = mconcat ((~~) <$> hexagon 1 <*> hexagon 1) # centerXY # pad 1.1
fromVertices :: TrailLike t => [Point (V t) (N t)] -> t #
Construct a trail-like thing connecting the given vertices with linear segments, with the first vertex as the location. If no vertices are given, the empty trail is used with the origin as the location.
import Data.List (transpose)
fromVerticesEx =
( [ pentagon 1
, pentagon 1.3 # rotateBy (1/15)
, pentagon 1.5 # rotateBy (2/15)
]
# transpose
# concat
)
# fromVertices
# closeTrail # strokeTrail
# centerXY # pad 1.1fromLocOffsets :: (V t ~ v, N t ~ n, V (v n) ~ v, N (v n) ~ n, TrailLike t) => Located [v n] -> t #
Construct a trail-like thing of linear segments from a located list of offsets.
fromOffsets :: TrailLike t => [Vn t] -> t #
Construct a trail-like thing of linear segments from a list of offsets, with the origin as the location.
fromOffsetsEx = fromOffsets [ unitX , unitX # rotateBy (1/6) , unitX # rotateBy (-1/6) , unitX ] # centerXY # pad 1.1
fromLocSegments :: TrailLike t => Located [Segment Closed (V t) (N t)] -> t #
Construct a trail-like thing from a located list of segments.
fromSegments :: TrailLike t => [Segment Closed (V t) (N t)] -> t #
Construct a trail-like thing from a list of segments, with the origin as the location.
fromSegmentsEx = fromSegments [ straight (r2 (1,1)) , bézier3 (r2 (1,1)) unitX unit_Y , straight unit_X ] # centerXY # pad 1.1
class (Metric (V t), OrderedField (N t)) => TrailLike t where #
A type class for trail-like things, i.e. things which can be
constructed from a concretely located Trail. Instances include
lines, loops, trails, paths, lists of vertices, two-dimensional
Diagrams, and Located variants of all the above.
Usually, type variables with TrailLike constraints are used as
the output types of functions, like
foo :: (TrailLike t) => ... -> t
Functions with such a type can be used to construct trails, paths, diagrams, lists of points, and so on, depending on the context.
To write a function with a signature like the above, you can of
course call trailLike directly; more typically, one would use
one of the provided functions like fromOffsets, fromVertices,
fromSegments, or ~~.
Methods
Instances
| (Metric v, OrderedField n) => TrailLike [Point v n] | A list of points is trail-like; this instance simply
computes the vertices of the trail, using |
| TrailLike t => TrailLike (TransInv t) | Translationally invariant things are trail-like as long as the underlying type is. |
| TrailLike t => TrailLike (Located t) |
|
| (Metric v, OrderedField n) => TrailLike (Path v n) | Paths are trail-like; a trail can be used to construct a singleton path. |
| (Metric v, OrderedField n) => TrailLike (Trail v n) |
|
| (Metric v, OrderedField n) => TrailLike (Trail' Line v n) | Lines are trail-like. If given a |
| (Metric v, OrderedField n) => TrailLike (Trail' Loop v n) | Loops are trail-like. If given a |
reverseLocLoop :: (Metric v, OrderedField n) => Located (Trail' Loop v n) -> Located (Trail' Loop v n) #
Reverse a concretely located loop. See reverseLocTrail. Note
that this is guaranteed to preserve the location.
reverseLoop :: (Metric v, OrderedField n) => Trail' Loop v n -> Trail' Loop v n #
Reverse a loop. See reverseTrail.
reverseLocLine :: (Metric v, OrderedField n) => Located (Trail' Line v n) -> Located (Trail' Line v n) #
Reverse a concretely located line. See reverseLocTrail.
reverseLine :: (Metric v, OrderedField n) => Trail' Line v n -> Trail' Line v n #
Reverse a line. See reverseTrail.
reverseLocTrail :: (Metric v, OrderedField n) => Located (Trail v n) -> Located (Trail v n) #
Reverse a concretely located trail. The endpoint of the original
trail becomes the starting point of the reversed trail, so the
original and reversed trails comprise exactly the same set of
points. reverseLocTrail is an involution, i.e.
reverseLocTrail . reverseLocTrail === id
reverseTrail :: (Metric v, OrderedField n) => Trail v n -> Trail v n #
Reverse a trail. Semantically, if a trail given by a function t
from [0,1] to vectors, then the reverse of t is given by t'(s) =
t(1-s). reverseTrail is an involution, that is,
reverseTrail . reverseTrail === id
trailLocSegments :: (Metric v, OrderedField n) => Located (Trail v n) -> [Located (Segment Closed v n)] #
Convert a concretely located trail into a list of located segments.
unfixTrail :: (Metric v, Ord n, Floating n) => [FixedSegment v n] -> Located (Trail v n) #
Convert a list of fixed segments into a located trail. Note that
this may lose information: it throws away the locations of all
but the first FixedSegment. This does not matter precisely
when each FixedSegment begins where the previous one ends.
This is almost left inverse to fixTrail, that is, unfixTrail
. fixTrail == id, except for the fact that unfixTrail will
never yield a Loop. In the case of a loop, we instead have
glueTrail . unfixTrail . fixTrail == id. On the other hand, it
is not the case that fixTrail . unfixTrail == id since
unfixTrail may lose information.
fixTrail :: (Metric v, OrderedField n) => Located (Trail v n) -> [FixedSegment v n] #
Convert a concretely located trail into a list of fixed segments.
unfixTrail is almost its left inverse.
loopVertices :: (Metric v, OrderedField n) => Located (Trail' Loop v n) -> [Point v n] #
Same as loopVertices', with a default tolerance.
loopVertices' :: (Metric v, OrderedField n) => n -> Located (Trail' Loop v n) -> [Point v n] #
Extract the vertices of a concretely located loop. Note that the
initial vertex is not repeated at the end. See trailVertices for
more information.
lineVertices :: (Metric v, OrderedField n) => Located (Trail' Line v n) -> [Point v n] #
Like lineVertices', with a default tolerance.
lineVertices' :: (Metric v, OrderedField n) => n -> Located (Trail' Line v n) -> [Point v n] #
Extract the vertices of a concretely located line. See
trailVertices for more information.
trailVertices :: (Metric v, OrderedField n) => Located (Trail v n) -> [Point v n] #
Like trailVertices', with a default tolerance.
trailVertices' :: (Metric v, OrderedField n) => n -> Located (Trail v n) -> [Point v n] #
Extract the vertices of a concretely located trail. Here a vertex
is defined as a non-differentiable point on the trail, i.e. a
sharp corner. (Vertices are thus a subset of the places where
segments join; if you want all joins between segments, see
trailPoints.) The tolerance determines how close the tangents
of two segments must be at their endpoints to consider the
transition point to be differentiable.
Note that for loops, the starting vertex will not be repeated
at the end. If you want this behavior, you can use cutTrail to
make the loop into a line first, which happens to repeat the same
vertex at the start and end, e.g. with trailVertices . mapLoc
cutTrail.
It does not make sense to ask for the vertices of a Trail by
itself; if you want the vertices of a trail with the first vertex
at, say, the origin, you can use trailVertices . (`at`
origin).
lineOffset :: (Metric v, OrderedField n) => Trail' Line v n -> v n #
Compute the offset from the start of a line to the end. (Note,
there is no corresponding loopOffset function because by
definition it would be constantly zero.)
loopOffsets :: (Metric v, OrderedField n) => Trail' Loop v n -> [v n] #
Extract the offsets of the segments of a loop.
lineOffsets :: Trail' Line v n -> [v n] #
Extract the offsets of the segments of a line.
trailOffset :: (Metric v, OrderedField n) => Trail v n -> v n #
Compute the offset from the start of a trail to the end. Satisfies
trailOffset === sumV . trailOffsets
but is more efficient.
trailOffsetEx = (strokeLine almostClosed <> showOffset) # centerXY # pad 1.1
where showOffset = fromOffsets [trailOffset (wrapLine almostClosed)]
# strokeP # lc redtrailOffsets :: (Metric v, OrderedField n) => Trail v n -> [v n] #
Extract the offsets of the segments of a trail.
trailSegments :: (Metric v, OrderedField n) => Trail v n -> [Segment Closed v n] #
Extract the segments of a trail. If the trail is a loop it will
first have cutLoop applied.
loopSegments :: Trail' Loop v n -> ([Segment Closed v n], Segment Open v n) #
Extract the segments comprising a loop: a list of closed segments, and one final open segment.
onLineSegments :: (Metric v, OrderedField n) => ([Segment Closed v n] -> [Segment Closed v n]) -> Trail' Line v n -> Trail' Line v n #
Modify a line by applying a function to its list of segments.
isTrailEmpty :: (Metric v, OrderedField n) => Trail v n -> Bool #
Test whether a trail is empty. Note that loops are never empty.
isLineEmpty :: (Metric v, OrderedField n) => Trail' Line v n -> Bool #
Test whether a line is empty.
cutLoop :: (Metric v, OrderedField n) => Trail' Loop v n -> Trail' Line v n #
Turn a loop into a line by "cutting" it at the common start/end point, resulting in a line which just happens to start and end at the same place.
cutLoop is right inverse to glueLine, that is,
glueLine . cutLoop === id
closeTrail :: Trail v n -> Trail v n #
closeLine :: Trail' Line v n -> Trail' Loop v n #
Make a line into a loop by adding a new linear segment from the line's end to its start.
closeLine does not have any particularly nice theoretical
properties, but can be useful e.g. when you want to make a
closed polygon out of a list of points where the initial point is
not repeated at the end. To use glueLine, one would first have
to duplicate the initial vertex, like
glueLine.lineFromVertices$ ps ++ [head ps]
Using closeLine, however, one can simply
closeLine . lineFromVertices $ ps
closeLineEx = pad 1.1 . centerXY . hcat' (with & sep .~ 1) $ [almostClosed # strokeLine, almostClosed # closeLine # strokeLoop]
glueLine :: (Metric v, OrderedField n) => Trail' Line v n -> Trail' Loop v n #
Make a line into a loop by "gluing" the endpoint to the
starting point. In particular, the offset of the final segment
is modified so that it ends at the starting point of the entire
trail. Typically, you would first construct a line which you
know happens to end where it starts, and then call glueLine to
turn it into a loop.
glueLineEx = pad 1.1 . hsep 1 $ [almostClosed # strokeLine, almostClosed # glueLine # strokeLoop] almostClosed :: Trail' Line V2 Double almostClosed = fromOffsets $ map r2 [(2, -1), (-3, -0.5), (-2, 1), (1, 0.5)]
glueLine is left inverse to cutLoop, that is,
glueLine . cutLoop === id
trailFromVertices :: (Metric v, OrderedField n) => [Point v n] -> Trail v n #
trailFromVertices === , for
conveniently constructing a wrapTrail . lineFromVerticesTrail instead of a Trail' Line.
lineFromVertices :: (Metric v, OrderedField n) => [Point v n] -> Trail' Line v n #
Construct a line containing only linear segments from a list of
vertices. Note that only the relative offsets between the
vertices matters; the information about their absolute position
will be discarded. That is, for all vectors v,
lineFromVertices === lineFromVertices . translate v
If you want to retain the position information, you should
instead use the more general fromVertices function to
construct, say, a or a Located (Trail' Line v).Located
(Trail v)
import Diagrams.Coordinates lineFromVerticesEx = pad 1.1 . centerXY . strokeLine $ lineFromVertices [origin, 0 ^& 1, 1 ^& 2, 5 ^& 1]
trailFromOffsets :: (Metric v, OrderedField n) => [v n] -> Trail v n #
trailFromOffsets === , for
conveniently constructing a wrapTrail . lineFromOffsetsTrail instead of a Trail' Line.
lineFromOffsets :: (Metric v, OrderedField n) => [v n] -> Trail' Line v n #
Construct a line containing only linear segments from a list of
vectors, where each vector represents the offset from one vertex
to the next. See also fromOffsets.
import Diagrams.Coordinates lineFromOffsetsEx = strokeLine $ lineFromOffsets [ 2 ^& 1, 2 ^& (-1), 2 ^& 0.5 ]
trailFromSegments :: (Metric v, OrderedField n) => [Segment Closed v n] -> Trail v n #
trailFromSegments === , for
conveniently constructing a wrapTrail . lineFromSegmentsTrail instead of a Trail'.
loopFromSegments :: (Metric v, OrderedField n) => [Segment Closed v n] -> Segment Open v n -> Trail' Loop v n #
Construct a loop from a list of closed segments and an open segment that completes the loop.
lineFromSegments :: (Metric v, OrderedField n) => [Segment Closed v n] -> Trail' Line v n #
Construct a line from a list of closed segments.
emptyTrail :: (Metric v, OrderedField n) => Trail v n #
A wrapped variant of emptyLine.
emptyLine :: (Metric v, OrderedField n) => Trail' Line v n #
The empty line, which is the identity for concatenation of lines.
onLine :: (Metric v, OrderedField n) => (Trail' Line v n -> Trail' Line v n) -> Trail v n -> Trail v n #
Modify a Trail by specifying a transformation on lines. If the
trail is a line, the transformation will be applied directly. If
it is a loop, it will first be cut using cutLoop, the
transformation applied, and then glued back into a loop with
glueLine. That is,
onLine f === onTrail f (glueLine . f . cutLoop)
Note that there is no corresponding onLoop function, because
there is no nice way in general to convert a line into a loop,
operate on it, and then convert back.
onTrail :: (Trail' Line v n -> Trail' l1 v n) -> (Trail' Loop v n -> Trail' l2 v n) -> Trail v n -> Trail v n #
Modify a Trail, specifying two separate transformations for the
cases of a line or a loop.
withTrail :: (Trail' Line v n -> r) -> (Trail' Loop v n -> r) -> Trail v n -> r #
A generic eliminator for Trail, taking functions specifying
what to do in the case of a line or a loop.
getSegment :: t -> GetSegment t #
Create a GetSegment wrapper around a trail, after which you can
call atParam, atStart, or atEnd to extract a segment.
withTrail' :: (Trail' Line v n -> r) -> (Trail' Loop v n -> r) -> Trail' l v n -> r #
A generic eliminator for Trail', taking functions specifying
what to do in the case of a line or a loop.
offset :: (OrderedField n, Metric v, Measured (SegMeasure v n) t) => t -> v n #
Compute the total offset of anything measured by SegMeasure.
numSegs :: (Num c, Measured (SegMeasure v n) a) => a -> c #
Compute the number of segments of anything measured by
SegMeasure (e.g. SegMeasure itself, Segment, SegTree,
Trails...)
trailMeasure :: (SegMeasure v n :>: m, Measured (SegMeasure v n) t) => a -> (m -> a) -> t -> a #
Given a default result (to be used in the case of an empty trail), and a function to map a single measure to a result, extract the given measure for a trail and use it to compute a result. Put another way, lift a function on a single measure (along with a default value) to a function on an entire trail.
newtype SegTree (v :: Type -> Type) n #
A SegTree represents a sequence of closed segments, stored in a
fingertree so we can easily recover various monoidal measures of
the segments (number of segments, arc length, envelope...) and
also easily slice and dice them according to the measures
(e.g., split off the smallest number of segments from the
beginning which have a combined arc length of at least 5).
Constructors
| SegTree (FingerTree (SegMeasure v n) (Segment Closed v n)) |
Instances
Type tag for trails with distinct endpoints.
Instances
| (Metric v, OrderedField n) => Parametric (GetSegment (Trail' Line v n)) | Parameters less than 0 yield the first segment; parameters greater than 1 yield the last. A parameter exactly at the junction of two segments yields the second segment (i.e. the one with higher parameter values). |
Defined in Diagrams.Trail Methods atParam :: GetSegment (Trail' Line v n) -> N (GetSegment (Trail' Line v n)) -> Codomain (GetSegment (Trail' Line v n)) (N (GetSegment (Trail' Line v n))) # | |
| (Metric v, OrderedField n) => EndValues (GetSegment (Trail' Line v n)) | |
Defined in Diagrams.Trail Methods atStart :: GetSegment (Trail' Line v n) -> Codomain (GetSegment (Trail' Line v n)) (N (GetSegment (Trail' Line v n))) # atEnd :: GetSegment (Trail' Line v n) -> Codomain (GetSegment (Trail' Line v n)) (N (GetSegment (Trail' Line v n))) # | |
| (OrderedField n, Metric v) => Semigroup (Trail' Line v n) | |
| (Metric v, OrderedField n) => Monoid (Trail' Line v n) | The empty trail is constantly the zero vector. Trails are composed via concatenation. Note that only lines have a monoid instance (and not loops). |
| (Metric v, OrderedField n) => TrailLike (Trail' Line v n) | Lines are trail-like. If given a |
| (Metric v, OrderedField n, Real n) => Sectionable (Trail' Line v n) | |
| (Metric v, OrderedField n) => AsEmpty (Trail' Line v n) | |
| Wrapped (Trail' Line v n) | |
| Rewrapped (Trail' Line v n) (Trail' Line v' n') | |
Defined in Diagrams.Trail | |
| (Metric v, OrderedField n, Metric u, OrderedField n') => Snoc (Trail' Line v n) (Trail' Line u n') (Segment Closed v n) (Segment Closed u n') | |
| (Metric v, OrderedField n, Metric u, OrderedField n') => Cons (Trail' Line v n) (Trail' Line u n') (Segment Closed v n) (Segment Closed u n') | |
| type Unwrapped (Trail' Line v n) | |
Defined in Diagrams.Trail | |
Type tag for "loopy" trails which return to their starting point.
Instances
| (Metric v, OrderedField n, Real n) => Parametric (GetSegment (Trail' Loop v n)) | The parameterization for loops wraps around, i.e. parameters are first reduced "mod 1". |
Defined in Diagrams.Trail Methods atParam :: GetSegment (Trail' Loop v n) -> N (GetSegment (Trail' Loop v n)) -> Codomain (GetSegment (Trail' Loop v n)) (N (GetSegment (Trail' Loop v n))) # | |
| (Metric v, OrderedField n, Real n) => EndValues (GetSegment (Trail' Loop v n)) | |
Defined in Diagrams.Trail Methods atStart :: GetSegment (Trail' Loop v n) -> Codomain (GetSegment (Trail' Loop v n)) (N (GetSegment (Trail' Loop v n))) # atEnd :: GetSegment (Trail' Loop v n) -> Codomain (GetSegment (Trail' Loop v n)) (N (GetSegment (Trail' Loop v n))) # | |
| (Metric v, OrderedField n) => TrailLike (Trail' Loop v n) | Loops are trail-like. If given a |
data Trail' l (v :: Type -> Type) n where #
Intuitively, a trail is a single, continuous path through space. However, a trail has no fixed starting point; it merely specifies how to move through space, not where. For example, "take three steps forward, then turn right twenty degrees and take two more steps" is an intuitive analog of a trail; these instructions specify a path through space from any given starting location. To be precise, trails are translation-invariant; applying a translation to a trail has no effect.
A , on the other hand, is a trail paired with
some concrete starting location ("start at the big tree on the
corner, then take three steps forward, ..."). See the
Diagrams.Located module for help working with Located TrailLocated values.
Formally, the semantics of a trail is a continuous (though not
necessarily differentiable) function from the real interval [0,1]
to vectors in some vector space. (In contrast, a Located trail
is a continuous function from [0,1] to points in some affine
space.)
There are two types of trails:
- A "line" (think of the "train", "subway", or "bus"
variety, rather than the "straight" variety...) is a trail
with two distinct endpoints. Actually, a line can have the
same start and end points, but it is still drawn as if it had
distinct endpoints: the two endpoints will have the appropriate
end caps, and the trail will not be filled. Lines have a
Monoidinstance wheremappendcorresponds to concatenation, i.e. chaining one line after the other. - A "loop" is required to end in the same place it starts (that
is, t(0) = t(1)). Loops are filled and are drawn as one
continuous loop, with the appropriate join at the
start/endpoint rather than end caps. Loops do not have a
Monoidinstance.
To convert between lines and loops, see glueLine,
closeLine, and cutLoop.
To construct trails, see emptyTrail, trailFromSegments,
trailFromVertices, trailFromOffsets, and friends. You can
also get any type of trail from any function which returns a
TrailLike (e.g. functions in Diagrams.TwoD.Shapes, and many
others; see Diagrams.TrailLike).
To extract information from trails, see withLine, isLoop,
trailSegments, trailOffsets, trailVertices, and friends.
Constructors
| Line :: forall l (v :: Type -> Type) n. SegTree v n -> Trail' Line v n | |
| Loop :: forall l (v :: Type -> Type) n. SegTree v n -> Segment Open v n -> Trail' Loop v n |
Instances
| ToPath (Located (Trail' l v n)) | |
| (Metric v, OrderedField n) => Parametric (GetSegment (Trail' Line v n)) | Parameters less than 0 yield the first segment; parameters greater than 1 yield the last. A parameter exactly at the junction of two segments yields the second segment (i.e. the one with higher parameter values). |
Defined in Diagrams.Trail Methods atParam :: GetSegment (Trail' Line v n) -> N (GetSegment (Trail' Line v n)) -> Codomain (GetSegment (Trail' Line v n)) (N (GetSegment (Trail' Line v n))) # | |
| (Metric v, OrderedField n, Real n) => Parametric (GetSegment (Trail' Loop v n)) | The parameterization for loops wraps around, i.e. parameters are first reduced "mod 1". |
Defined in Diagrams.Trail Methods atParam :: GetSegment (Trail' Loop v n) -> N (GetSegment (Trail' Loop v n)) -> Codomain (GetSegment (Trail' Loop v n)) (N (GetSegment (Trail' Loop v n))) # | |
| (Parametric (GetSegment (Trail' c v n)), Additive v, Num n) => Parametric (Tangent (Trail' c v n)) | |
| (Metric v, OrderedField n) => EndValues (GetSegment (Trail' Line v n)) | |
Defined in Diagrams.Trail Methods atStart :: GetSegment (Trail' Line v n) -> Codomain (GetSegment (Trail' Line v n)) (N (GetSegment (Trail' Line v n))) # atEnd :: GetSegment (Trail' Line v n) -> Codomain (GetSegment (Trail' Line v n)) (N (GetSegment (Trail' Line v n))) # | |
| (Metric v, OrderedField n, Real n) => EndValues (GetSegment (Trail' Loop v n)) | |
Defined in Diagrams.Trail Methods atStart :: GetSegment (Trail' Loop v n) -> Codomain (GetSegment (Trail' Loop v n)) (N (GetSegment (Trail' Loop v n))) # atEnd :: GetSegment (Trail' Loop v n) -> Codomain (GetSegment (Trail' Loop v n)) (N (GetSegment (Trail' Loop v n))) # | |
| (Parametric (GetSegment (Trail' c v n)), EndValues (GetSegment (Trail' c v n)), Additive v, Num n) => EndValues (Tangent (Trail' c v n)) | |
| (Metric v, OrderedField n) => Reversing (Located (Trail' l v n)) | Same as |
| Eq (v n) => Eq (Trail' l v n) | |
| Ord (v n) => Ord (Trail' l v n) | |
Defined in Diagrams.Trail | |
| Show (v n) => Show (Trail' l v n) | |
| (OrderedField n, Metric v) => Semigroup (Trail' Line v n) | |
| (Metric v, OrderedField n) => Monoid (Trail' Line v n) | The empty trail is constantly the zero vector. Trails are composed via concatenation. Note that only lines have a monoid instance (and not loops). |
| (Metric v, OrderedField n) => Enveloped (Trail' l v n) | The envelope for a trail is based at the trail's start. |
Defined in Diagrams.Trail | |
| (HasLinearMap v, Metric v, OrderedField n) => Transformable (Trail' l v n) | |
Defined in Diagrams.Trail | |
| ToPath (Trail' l v n) | |
| (Metric v, OrderedField n) => TrailLike (Trail' Line v n) | Lines are trail-like. If given a |
| (Metric v, OrderedField n) => TrailLike (Trail' Loop v n) | Loops are trail-like. If given a |
| (Metric v, OrderedField n, Real n) => Parametric (Trail' l v n) | |
| Num n => DomainBounds (Trail' l v n) | |
Defined in Diagrams.Trail Methods domainLower :: Trail' l v n -> N (Trail' l v n) # domainUpper :: Trail' l v n -> N (Trail' l v n) # | |
| (Metric v, OrderedField n, Real n) => EndValues (Trail' l v n) | |
| (Metric v, OrderedField n, Real n) => Sectionable (Trail' Line v n) | |
| (Metric v, OrderedField n, Real n) => HasArcLength (Trail' l v n) | |
Defined in Diagrams.Trail Methods arcLengthBounded :: N (Trail' l v n) -> Trail' l v n -> Interval (N (Trail' l v n)) # arcLength :: N (Trail' l v n) -> Trail' l v n -> N (Trail' l v n) # stdArcLength :: Trail' l v n -> N (Trail' l v n) # arcLengthToParam :: N (Trail' l v n) -> Trail' l v n -> N (Trail' l v n) -> N (Trail' l v n) # stdArcLengthToParam :: Trail' l v n -> N (Trail' l v n) -> N (Trail' l v n) # | |
| (Metric v, OrderedField n) => Reversing (Trail' l v n) | Same as |
Defined in Diagrams.Trail | |
| (Metric v, OrderedField n) => AsEmpty (Trail' Line v n) | |
| Wrapped (Trail' Line v n) | |
| (HasLinearMap v, Metric v, OrderedField n) => Renderable (Trail' o v n) NullBackend | |
Defined in Diagrams.Trail Methods render :: NullBackend -> Trail' o v n -> Render NullBackend (V (Trail' o v n)) (N (Trail' o v n)) # | |
| Rewrapped (Trail' Line v n) (Trail' Line v' n') | |
Defined in Diagrams.Trail | |
| (Metric v, OrderedField n, Metric u, OrderedField n') => Snoc (Trail' Line v n) (Trail' Line u n') (Segment Closed v n) (Segment Closed u n') | |
| (Metric v, OrderedField n, Metric u, OrderedField n') => Cons (Trail' Line v n) (Trail' Line u n') (Segment Closed v n) (Segment Closed u n') | |
| type V (Trail' l v n) | |
Defined in Diagrams.Trail | |
| type N (Trail' l v n) | |
Defined in Diagrams.Trail | |
| type Codomain (Trail' l v n) | |
Defined in Diagrams.Trail | |
| type Unwrapped (Trail' Line v n) | |
Defined in Diagrams.Trail | |
newtype GetSegment t #
A newtype wrapper around trails which exists solely for its
Parametric, DomainBounds and EndValues instances. The idea
is that if tr is a trail, you can write, e.g.
getSegment tr atParam 0.6
or
atStart (getSegment tr)
to get the segment at parameter 0.6 or the first segment in the trail, respectively.
The codomain for GetSegment, i.e. the result you get from
calling atParam, atStart, or atEnd, is
GetSegmentCodomain, which is a newtype wrapper around Maybe
(v, Segment Closed v, AnIso' n n). Nothing results if the
trail is empty; otherwise, you get:
- the offset from the start of the trail to the beginning of the segment,
- the segment itself, and
- a reparameterization isomorphism: in the forward direction, it
translates from parameters on the whole trail to a parameters
on the segment. Note that for technical reasons you have to
call
cloneIsoon theAnIso'value to get a real isomorphism you can use.
Constructors
| GetSegment t |
Instances
newtype GetSegmentCodomain (v :: Type -> Type) n #
Constructors
| GetSegmentCodomain (Maybe (v n, Segment Closed v n, AnIso' n n)) |
data Trail (v :: Type -> Type) n where #
Trail is a wrapper around Trail', hiding whether the
underlying Trail' is a line or loop (though which it is can be
recovered; see e.g. withTrail).
Instances
| ToPath (Located (Trail v n)) | |
| (Metric v, OrderedField n, Real n) => Parametric (GetSegment (Trail v n)) | |
Defined in Diagrams.Trail Methods atParam :: GetSegment (Trail v n) -> N (GetSegment (Trail v n)) -> Codomain (GetSegment (Trail v n)) (N (GetSegment (Trail v n))) # | |
| (Metric v, OrderedField n, Real n) => Parametric (Tangent (Trail v n)) | |
| (Metric v, OrderedField n, Real n) => EndValues (GetSegment (Trail v n)) | |
Defined in Diagrams.Trail Methods atStart :: GetSegment (Trail v n) -> Codomain (GetSegment (Trail v n)) (N (GetSegment (Trail v n))) # atEnd :: GetSegment (Trail v n) -> Codomain (GetSegment (Trail v n)) (N (GetSegment (Trail v n))) # | |
| (Metric v, OrderedField n, Real n) => EndValues (Tangent (Trail v n)) | |
| (Metric v, OrderedField n) => Reversing (Located (Trail v n)) | Same as |
| (Metric v, Metric u, OrderedField n, r ~ Located (Trail u n)) => Deformable (Located (Trail v n)) r | |
| Eq (v n) => Eq (Trail v n) | |
| Ord (v n) => Ord (Trail v n) | |
| Show (v n) => Show (Trail v n) | |
| (OrderedField n, Metric v) => Semigroup (Trail v n) | Two |
| (Metric v, OrderedField n) => Monoid (Trail v n) |
|
| (Serialize (v n), OrderedField n, Metric v) => Serialize (Trail v n) | |
| (Metric v, OrderedField n) => Enveloped (Trail v n) | |
Defined in Diagrams.Trail | |
| (HasLinearMap v, Metric v, OrderedField n) => Transformable (Trail v n) | |
Defined in Diagrams.Trail | |
| ToPath (Trail v n) | |
| (Metric v, OrderedField n) => TrailLike (Trail v n) |
|
| (Metric v, OrderedField n, Real n) => Parametric (Trail v n) | |
| Num n => DomainBounds (Trail v n) | |
Defined in Diagrams.Trail | |
| (Metric v, OrderedField n, Real n) => EndValues (Trail v n) | |
| (Metric v, OrderedField n, Real n) => Sectionable (Trail v n) | Note that there is no |
| (Metric v, OrderedField n, Real n) => HasArcLength (Trail v n) | |
Defined in Diagrams.Trail Methods arcLengthBounded :: N (Trail v n) -> Trail v n -> Interval (N (Trail v n)) # arcLength :: N (Trail v n) -> Trail v n -> N (Trail v n) # stdArcLength :: Trail v n -> N (Trail v n) # arcLengthToParam :: N (Trail v n) -> Trail v n -> N (Trail v n) -> N (Trail v n) # stdArcLengthToParam :: Trail v n -> N (Trail v n) -> N (Trail v n) # | |
| (Metric v, OrderedField n) => Reversing (Trail v n) | Same as |
Defined in Diagrams.Trail | |
| (Metric v, OrderedField n) => AsEmpty (Trail v n) | |
Defined in Diagrams.Trail | |
| Wrapped (Trail v n) | |
| Rewrapped (Trail v n) (Trail v' n') | |
Defined in Diagrams.Trail | |
| Snoc (Path v n) (Path v' n') (Located (Trail v n)) (Located (Trail v' n')) | |
| Cons (Path v n) (Path v' n') (Located (Trail v n)) (Located (Trail v' n')) | |
| Each (Path v n) (Path v' n') (Located (Trail v n)) (Located (Trail v' n')) | |
| type V (Trail v n) | |
Defined in Diagrams.Trail | |
| type N (Trail v n) | |
Defined in Diagrams.Trail | |
| type Codomain (Trail v n) | |
Defined in Diagrams.Trail | |
| type Unwrapped (Trail v n) | |
normalAtEnd :: (InSpace V2 n t, EndValues (Tangent t), Floating n) => t -> V2 n #
Compute the normal vector at the end of a segment or trail.
normalAtStart :: (InSpace V2 n t, EndValues (Tangent t), Floating n) => t -> V2 n #
Compute the normal vector at the start of a segment or trail.
normalAtParam :: (InSpace V2 n t, Parametric (Tangent t), Floating n) => t -> n -> V2 n #
Compute the (unit) normal vector to a segment or trail at a particular parameter.
Examples of more specific types this function can have include
Segment Closed V2 Double -> Double -> V2 Double
Trail' Line V2 Double -> Double -> V2 Double
Located (Trail V2 Double) -> Double -> V2 Double
See the instances listed for the Tangent newtype for more.
tangentAtEnd :: EndValues (Tangent t) => t -> Vn t #
Compute the tangent vector at the end of a segment or trail.
tangentAtStart :: EndValues (Tangent t) => t -> Vn t #
Compute the tangent vector at the start of a segment or trail.
tangentAtParam :: Parametric (Tangent t) => t -> N t -> Vn t #
Compute the tangent vector to a segment or trail at a particular parameter.
Examples of more specific types this function can have include
Segment Closed V2 -> Double -> V2 Double
Trail' Line V2 -> Double -> V2 Double
Located (Trail V2) -> Double -> V2 Double
See the instances listed for the Tangent newtype for more.
A newtype wrapper used to give different instances of
Parametric and EndValues that compute tangent vectors.
Constructors
| Tangent t |
Instances
oeOffset :: Lens' (OffsetEnvelope v n) (TotalOffset v n) #
oeEnvelope :: Lens' (OffsetEnvelope v n) (Envelope v n) #
type SegMeasure (v :: Type -> Type) n = SegCount ::: (ArcLength n ::: (OffsetEnvelope v n ::: ())) #
SegMeasure collects up all the measurements over a chain of
segments.
getArcLengthBounded :: (Num n, Ord n) => n -> ArcLength n -> Interval n #
Given a specified tolerance, project out the cached arc length if it is accurate enough; otherwise call the generic arc length function with the given tolerance.
getArcLengthFun :: ArcLength n -> n -> Interval n #
Project out the generic arc length function taking the tolerance as an argument.
getArcLengthCached :: ArcLength n -> Interval n #
Project out the cached arc length, stored together with error bounds.
fixedSegIso :: (Num n, Additive v) => Iso' (FixedSegment v n) (Located (Segment Closed v n)) #
Use a FixedSegment to make an Iso between an
a fixed segment and a located segment.
fromFixedSeg :: (Num n, Additive v) => FixedSegment v n -> Located (Segment Closed v n) #
Convert a FixedSegment back into a located Segment.
mkFixedSeg :: (Num n, Additive v) => Located (Segment Closed v n) -> FixedSegment v n #
Create a FixedSegment from a located Segment.
reverseSegment :: (Num n, Additive v) => Segment Closed v n -> Segment Closed v n #
Reverse the direction of a segment.
openCubic :: v n -> v n -> Segment Open v n #
An open cubic segment. This means the trail makes a cubic bézier
with control vectors v1 and v2 to form a loop.
openLinear :: Segment Open v n #
An open linear segment. This means the trail makes a straight line from the last segment the beginning to form a loop.
segOffset :: Segment Closed v n -> v n #
Compute the offset from the start of a segment to the
end. Note that in the case of a Bézier segment this is not the
same as the length of the curve itself; for that, see arcLength.
bézier3 :: v n -> v n -> v n -> Segment Closed v n #
bézier3 is the same as bezier3, but with more snobbery.
bezier3 :: v n -> v n -> v n -> Segment Closed v n #
bezier3 c1 c2 x constructs a translationally invariant cubic
Bézier curve where the offsets from the first endpoint to the
first and second control point and endpoint are respectively
given by c1, c2, and x.
straight :: v n -> Segment Closed v n #
constructs a translationally invariant linear
segment with direction and length given by the vector straight vv.
mapSegmentVectors :: (v n -> v' n') -> Segment c v n -> Segment c v' n' #
Map over the vectors of each segment.
Type tag for open segments.
Type tag for closed segments.
Instances
data Offset c (v :: Type -> Type) n where #
The offset of a segment is the vector from its starting point to its end. The offset for an open segment is determined by the context, i.e. its endpoint is not fixed. The offset for a closed segment is stored explicitly, i.e. its endpoint is at a fixed offset from its start.
Constructors
| OffsetOpen :: forall c (v :: Type -> Type) n. Offset Open v n | |
| OffsetClosed :: forall c (v :: Type -> Type) n. v n -> Offset Closed v n |
Instances
| Functor v => Functor (Offset c v) | |
| Eq (v n) => Eq (Offset c v n) | |
| Ord (v n) => Ord (Offset c v n) | |
Defined in Diagrams.Segment | |
| Show (v n) => Show (Offset c v n) | |
| Transformable (Offset c v n) | |
Defined in Diagrams.Segment | |
| (Additive v, Num n) => Reversing (Offset c v n) | Reverses the direction of closed offsets. |
Defined in Diagrams.Segment | |
| Each (Offset c v n) (Offset c v' n') (v n) (v' n') | |
| type V (Offset c v n) | |
Defined in Diagrams.Segment | |
| type N (Offset c v n) | |
Defined in Diagrams.Segment | |
data Segment c (v :: Type -> Type) n #
The atomic constituents of the concrete representation currently used for trails are segments, currently limited to single straight lines or cubic Bézier curves. Segments are translationally invariant, that is, they have no particular "location" and are unaffected by translations. They are, however, affected by other transformations such as rotations and scales.
Constructors
| Linear !(Offset c v n) | A linear segment with given offset. |
| Cubic !(v n) !(v n) !(Offset c v n) | A cubic Bézier segment specified by three offsets from the starting point to the first control point, second control point, and ending point, respectively. |
Instances
data FixedSegment (v :: Type -> Type) n #
FixedSegments are like Segments except that they have
absolute locations. FixedSegment v is isomorphic to Located
(Segment Closed v), as witnessed by mkFixedSeg and
fromFixedSeg, but FixedSegment is convenient when one needs
the absolute locations of the vertices and control points.
Instances
A type to track the count of segments in a Trail.
Instances
| Semigroup SegCount | |
| Monoid SegCount | |
| Wrapped SegCount | |
| Rewrapped SegCount SegCount | |
Defined in Diagrams.Segment | |
| (Metric v, OrderedField n) => Measured (SegMeasure v n) (SegMeasure v n) | |
Defined in Diagrams.Segment Methods measure :: SegMeasure v n -> SegMeasure v n # | |
| (Floating n, Ord n, Metric v) => Measured (SegMeasure v n) (SegTree v n) | |
Defined in Diagrams.Trail Methods measure :: SegTree v n -> SegMeasure v n # | |
| (OrderedField n, Metric v) => Measured (SegMeasure v n) (Segment Closed v n) | |
Defined in Diagrams.Segment Methods measure :: Segment Closed v n -> SegMeasure v n # | |
| type Unwrapped SegCount | |
Defined in Diagrams.Segment | |
A type to represent the total arc length of a chain of
segments. The first component is a "standard" arc length,
computed to within a tolerance of 10e-6. The second component is
a generic arc length function taking the tolerance as an
argument.
Instances
| (Num n, Ord n) => Semigroup (ArcLength n) | |
| (Num n, Ord n) => Monoid (ArcLength n) | |
| Wrapped (ArcLength n) | |
| Rewrapped (ArcLength n) (ArcLength n') | |
Defined in Diagrams.Segment | |
| (Metric v, OrderedField n) => Measured (SegMeasure v n) (SegMeasure v n) | |
Defined in Diagrams.Segment Methods measure :: SegMeasure v n -> SegMeasure v n # | |
| (Floating n, Ord n, Metric v) => Measured (SegMeasure v n) (SegTree v n) | |
Defined in Diagrams.Trail Methods measure :: SegTree v n -> SegMeasure v n # | |
| (OrderedField n, Metric v) => Measured (SegMeasure v n) (Segment Closed v n) | |
Defined in Diagrams.Segment Methods measure :: Segment Closed v n -> SegMeasure v n # | |
| type Unwrapped (ArcLength n) | |
newtype TotalOffset (v :: Type -> Type) n #
A type to represent the total cumulative offset of a chain of segments.
Constructors
| TotalOffset (v n) |
Instances
| (Num n, Additive v) => Semigroup (TotalOffset v n) | |
Defined in Diagrams.Segment Methods (<>) :: TotalOffset v n -> TotalOffset v n -> TotalOffset v n # sconcat :: NonEmpty (TotalOffset v n) -> TotalOffset v n # stimes :: Integral b => b -> TotalOffset v n -> TotalOffset v n # | |
| (Num n, Additive v) => Monoid (TotalOffset v n) | |
Defined in Diagrams.Segment Methods mempty :: TotalOffset v n # mappend :: TotalOffset v n -> TotalOffset v n -> TotalOffset v n # mconcat :: [TotalOffset v n] -> TotalOffset v n # | |
| Wrapped (TotalOffset v n) | |
Defined in Diagrams.Segment Associated Types type Unwrapped (TotalOffset v n) :: Type # Methods _Wrapped' :: Iso' (TotalOffset v n) (Unwrapped (TotalOffset v n)) # | |
| Rewrapped (TotalOffset v n) (TotalOffset v' n') | |
Defined in Diagrams.Segment | |
| type Unwrapped (TotalOffset v n) | |
Defined in Diagrams.Segment | |
data OffsetEnvelope (v :: Type -> Type) n #
A type to represent the offset and envelope of a chain of segments. They have to be paired into one data structure, since combining the envelopes of two consecutive chains needs to take the offset of the first into account.
Constructors
| OffsetEnvelope | |
Fields
| |
Instances
| (Metric v, OrderedField n) => Semigroup (OffsetEnvelope v n) | |
Defined in Diagrams.Segment Methods (<>) :: OffsetEnvelope v n -> OffsetEnvelope v n -> OffsetEnvelope v n # sconcat :: NonEmpty (OffsetEnvelope v n) -> OffsetEnvelope v n # stimes :: Integral b => b -> OffsetEnvelope v n -> OffsetEnvelope v n # | |
| (Metric v, OrderedField n) => Measured (SegMeasure v n) (SegMeasure v n) | |
Defined in Diagrams.Segment Methods measure :: SegMeasure v n -> SegMeasure v n # | |
| (Floating n, Ord n, Metric v) => Measured (SegMeasure v n) (SegTree v n) | |
Defined in Diagrams.Trail Methods measure :: SegTree v n -> SegMeasure v n # | |
| (OrderedField n, Metric v) => Measured (SegMeasure v n) (Segment Closed v n) | |
Defined in Diagrams.Segment Methods measure :: Segment Closed v n -> SegMeasure v n # | |
located :: SameSpace a b => Lens (Located a) (Located b) a b #
A lens giving access to the object within a Located wrapper.
mapLoc :: SameSpace a b => (a -> b) -> Located a -> Located b #
Located is not a Functor, since changing the type could
change the type of the associated vector space, in which case the
associated location would no longer have the right type. mapLoc
has an extra constraint specifying that the vector space must
stay the same.
(Technically, one can say that for every vector space v,
Located is a little-f (endo)functor on the category of types
with associated vector space v; but that is not covered by the
standard Functor class.)
viewLoc :: Located a -> (Point (V a) (N a), a) #
Deconstruct a Located a into a location and a value of type
a. viewLoc can be especially useful in conjunction with the
ViewPatterns extension.
at :: a -> Point (V a) (N a) -> Located a infix 5 #
Construct a Located a from a value of type a and a location.
at is intended to be used infix, like x `at` origin.
"Located" things, i.e. things with a concrete location:
intuitively, Located a ~ (Point, a). Wrapping a translationally
invariant thing (e.g. a Segment or Trail) in Located pins
it down to a particular location and makes it no longer
translationally invariant.
Located is intentionally abstract. To construct Located
values, use at. To destruct, use viewLoc, unLoc, or loc.
To map, use mapLoc.
Much of the utility of having a concrete type for the Located
concept lies in the type class instances we can give it. The
HasOrigin, Transformable, Enveloped, Traced, and
TrailLike instances are particularly useful; see the documented
instances below for more information.
Constructors
| Loc | |
Instances
| (Eq (V a (N a)), Eq a) => Eq (Located a) | |
| (Ord (V a (N a)), Ord a) => Ord (Located a) | |
| (Read (V a (N a)), Read a) => Read (Located a) | |
| (Show (V a (N a)), Show a) => Show (Located a) | |
| Generic (Located a) | |
| (Serialize a, Serialize (V a (N a))) => Serialize (Located a) | |
| Enveloped a => Juxtaposable (Located a) | |
| Enveloped a => Enveloped (Located a) | The envelope of a |
Defined in Diagrams.Located | |
| (Traced a, Num (N a)) => Traced (Located a) | The trace of a |
| Qualifiable a => Qualifiable (Located a) | |
| (Additive (V a), Num (N a), Transformable a) => Transformable (Located a) | Applying a transformation |
Defined in Diagrams.Located | |
| (Num (N a), Additive (V a)) => HasOrigin (Located a) |
|
Defined in Diagrams.Located | |
| ToPath (Located [Segment Closed v n]) | |
| ToPath (Located (Trail' l v n)) | |
| ToPath (Located (Trail v n)) | |
| ToPath (Located (Segment Closed v n)) | |
| TrailLike t => TrailLike (Located t) |
|
| Alignable a => Alignable (Located a) | |
Defined in Diagrams.Located Methods alignBy' :: (InSpace v n (Located a), Fractional n, HasOrigin (Located a)) => (v n -> Located a -> Point v n) -> v n -> n -> Located a -> Located a # defaultBoundary :: (V (Located a) ~ v, N (Located a) ~ n) => v n -> Located a -> Point v n # alignBy :: (InSpace v n (Located a), Fractional n, HasOrigin (Located a)) => v n -> n -> Located a -> Located a # | |
| Parametric (Tangent t) => Parametric (Tangent (Located t)) | |
| (InSpace v n a, Parametric a, Codomain a ~ v) => Parametric (Located a) | |
| DomainBounds a => DomainBounds (Located a) | |
Defined in Diagrams.Located | |
| (DomainBounds t, EndValues (Tangent t)) => EndValues (Tangent (Located t)) | |
| (InSpace v n a, EndValues a, Codomain a ~ v) => EndValues (Located a) | |
| (InSpace v n a, Fractional n, Parametric a, Sectionable a, Codomain a ~ v) => Sectionable (Located a) | |
| (InSpace v n a, Fractional n, HasArcLength a, Codomain a ~ v) => HasArcLength (Located a) | |
Defined in Diagrams.Located Methods arcLengthBounded :: N (Located a) -> Located a -> Interval (N (Located a)) # arcLength :: N (Located a) -> Located a -> N (Located a) # stdArcLength :: Located a -> N (Located a) # arcLengthToParam :: N (Located a) -> Located a -> N (Located a) -> N (Located a) # stdArcLengthToParam :: Located a -> N (Located a) -> N (Located a) # | |
| (Metric v, OrderedField n) => Reversing (Located (Trail' l v n)) | Same as |
| (Metric v, OrderedField n) => Reversing (Located (Trail v n)) | Same as |
| (Metric v, Metric u, OrderedField n, r ~ Located (Trail u n)) => Deformable (Located (Trail v n)) r | |
| Snoc (Path v n) (Path v' n') (Located (Trail v n)) (Located (Trail v' n')) | |
| Cons (Path v n) (Path v' n') (Located (Trail v n)) (Located (Trail v' n')) | |
| Each (Path v n) (Path v' n') (Located (Trail v n)) (Located (Trail v' n')) | |
| type Rep (Located a) | |
Defined in Diagrams.Located type Rep (Located a) = D1 (MetaData "Located" "Diagrams.Located" "diagrams-lib-1.4.2.3-4IkVVBmK9qBElHMtgqeLQ1" False) (C1 (MetaCons "Loc" PrefixI True) (S1 (MetaSel (Just "loc") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Point (V a) (N a))) :*: S1 (MetaSel (Just "unLoc") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a))) | |
| type V (Located a) | |
Defined in Diagrams.Located | |
| type N (Located a) | |
Defined in Diagrams.Located | |
| type Codomain (Located a) | |
Defined in Diagrams.Located | |
snugCenterXYZ :: (InSpace v n a, R3 v, Fractional n, Alignable a, HasOrigin a, Traced a) => a -> a #
centerXYZ :: (InSpace v n a, R3 v, Fractional n, Alignable a, HasOrigin a) => a -> a #
Center an object in three dimensions.
snugCenterYZ :: (InSpace v n a, R3 v, Fractional n, Alignable a, HasOrigin a, Traced a) => a -> a #
centerYZ :: (InSpace v n a, R3 v, Fractional n, Alignable a, HasOrigin a) => a -> a #
Center along both the Y- and Z-axes.
snugCenterXZ :: (InSpace v n a, R3 v, Fractional n, Alignable a, HasOrigin a, Traced a) => a -> a #
centerXZ :: (InSpace v n a, R3 v, Fractional n, Alignable a, HasOrigin a) => a -> a #
Center along both the X- and Z-axes.
snugCenterZ :: (InSpace v n a, R3 v, Fractional n, Alignable a, HasOrigin a, Traced a) => a -> a #
centerZ :: (InSpace v n a, R3 v, Fractional n, Alignable a, HasOrigin a) => a -> a #
Center the local origin along the Z-axis.
snugZ :: (V a ~ v, N a ~ n, Alignable a, Traced a, HasOrigin a, R3 v, Fractional n) => n -> a -> a #
See the documentation for alignZ.
alignZ :: (InSpace v n a, R3 v, Fractional n, Alignable a, HasOrigin a) => n -> a -> a #
Like alignX, but moving the local origin in the Z direction, with an
argument of 1 corresponding to the top edge and (-1) corresponding
to the bottom edge.
alignZMax :: (InSpace v n a, R3 v, Fractional n, Alignable a, HasOrigin a) => a -> a #
Translate the diagram along unitZ so that all points have negative z-values.
alignZMin :: (InSpace v n a, R3 v, Fractional n, Alignable a, HasOrigin a) => a -> a #
Translate the diagram along unitZ so that all points have positive z-values.
alignYMax :: (InSpace v n a, R2 v, Fractional n, Alignable a, HasOrigin a) => a -> a #
Translate the diagram along unitY so that all points have negative y-values.
alignYMin :: (InSpace v n a, R2 v, Fractional n, Alignable a, HasOrigin a) => a -> a #
Translate the diagram along unitY so that all points have positive y-values.
alignXMax :: (InSpace v n a, R1 v, Fractional n, Alignable a, HasOrigin a) => a -> a #
Translate the diagram along unitX so that all points have negative x-values.
alignXMin :: (InSpace v n a, R1 v, Fractional n, Alignable a, HasOrigin a) => a -> a #
Translate the diagram along unitX so that all points have positive x-values.
snugCenterXY :: (InSpace v n a, R2 v, Fractional n, Alignable a, Traced a, HasOrigin a) => a -> a #
centerXY :: (InSpace v n a, R2 v, Fractional n, Alignable a, HasOrigin a) => a -> a #
Center along both the X- and Y-axes.
snugCenterY :: (InSpace v n a, R2 v, Fractional n, Alignable a, Traced a, HasOrigin a) => a -> a #
centerY :: (InSpace v n a, R2 v, Fractional n, Alignable a, HasOrigin a) => a -> a #
Center the local origin along the Y-axis.
snugCenterX :: (InSpace v n a, R1 v, Fractional n, Alignable a, Traced a, HasOrigin a) => a -> a #
centerX :: (InSpace v n a, R1 v, Fractional n, Alignable a, HasOrigin a) => a -> a #
Center the local origin along the X-axis.
snugY :: (InSpace v n a, R2 v, Fractional n, Alignable a, Traced a, HasOrigin a) => n -> a -> a #
See the documentation for alignY.
alignY :: (InSpace v n a, R2 v, Fractional n, Alignable a, HasOrigin a) => n -> a -> a #
Like alignX, but moving the local origin vertically, with an
argument of 1 corresponding to the top edge and (-1) corresponding
to the bottom edge.
snugX :: (InSpace v n a, R1 v, Fractional n, Alignable a, Traced a, HasOrigin a) => n -> a -> a #
See the documentation for alignX.
alignX :: (InSpace v n a, R1 v, Fractional n, Alignable a, HasOrigin a) => n -> a -> a #
alignX and snugX move the local origin horizontally as follows:
alignX (-1)moves the local origin to the left edge of the boundary;align 1moves the local origin to the right edge;- any other argument interpolates linearly between these. For
example,
alignX 0centers,alignX 2moves the origin one "radius" to the right of the right edge, and so on. snugXworks the same way.
alignB :: (InSpace V2 n a, Fractional n, Alignable a, HasOrigin a) => a -> a #
Align along the bottom edge.
alignT :: (InSpace V2 n a, Fractional n, Alignable a, HasOrigin a) => a -> a #
Align along the top edge.
alignR :: (InSpace V2 n a, Fractional n, Alignable a, HasOrigin a) => a -> a #
Align along the right edge.
alignL :: (InSpace V2 n a, Fractional n, Alignable a, HasOrigin a) => a -> a #
Align along the left edge, i.e. translate the diagram in a horizontal direction so that the local origin is on the left edge of the envelope.
snugCenter :: (InSpace v n a, Traversable v, Fractional n, Alignable a, HasOrigin a, Traced a) => a -> a #
Like center using trace.
snugCenterV :: (InSpace v n a, Fractional n, Alignable a, Traced a, HasOrigin a) => v n -> a -> a #
Like centerV using trace.
center :: (InSpace v n a, Fractional n, Traversable v, Alignable a, HasOrigin a) => a -> a #
center centers an enveloped object along all of its basis vectors.
centerV :: (InSpace v n a, Fractional n, Alignable a, HasOrigin a) => v n -> a -> a #
centerV v centers an enveloped object along the direction of
v.
snug :: (InSpace v n a, Fractional n, Alignable a, Traced a, HasOrigin a) => v n -> a -> a #
Like align but uses trace.
snugBy :: (InSpace v n a, Fractional n, Alignable a, Traced a, HasOrigin a) => v n -> n -> a -> a #
Version of alignBy specialized to use traceBoundary
align :: (InSpace v n a, Fractional n, Alignable a, HasOrigin a) => v n -> a -> a #
align v aligns an enveloped object along the edge in the
direction of v. That is, it moves the local origin in the
direction of v until it is on the edge of the envelope. (Note
that if the local origin is outside the envelope to begin with,
it may have to move "backwards".)
envelopeBoundary :: (V a ~ v, N a ~ n, Enveloped a) => v n -> a -> Point v n #
Some standard functions which can be used as the boundary argument to
alignBy'.
alignBy'Default :: (InSpace v n a, Fractional n, HasOrigin a) => (v n -> a -> Point v n) -> v n -> n -> a -> a #
Class of things which can be aligned.
Minimal complete definition
Methods
alignBy' :: (InSpace v n a, Fractional n, HasOrigin a) => (v n -> a -> Point v n) -> v n -> n -> a -> a #
alignBy v d a moves the origin of a along the vector
v. If d = 1, the origin is moved to the edge of the
boundary in the direction of v; if d = -1, it moves to the
edge of the boundary in the direction of the negation of v.
Other values of d interpolate linearly (so for example, d =
0 centers the origin along the direction of v).
defaultBoundary :: (V a ~ v, N a ~ n) => v n -> a -> Point v n #
alignBy :: (InSpace v n a, Fractional n, HasOrigin a) => v n -> n -> a -> a #
Instances
| (V b ~ v, N b ~ n, Metric v, OrderedField n, Alignable b) => Alignable [b] | |
Defined in Diagrams.Align | |
| (V b ~ v, N b ~ n, Metric v, OrderedField n, Alignable b) => Alignable (Set b) | |
Defined in Diagrams.Align Methods alignBy' :: (InSpace v n (Set b), Fractional n, HasOrigin (Set b)) => (v n -> Set b -> Point v n) -> v n -> n -> Set b -> Set b # defaultBoundary :: (V (Set b) ~ v, N (Set b) ~ n) => v n -> Set b -> Point v n # alignBy :: (InSpace v n (Set b), Fractional n, HasOrigin (Set b)) => v n -> n -> Set b -> Set b # | |
| Alignable a => Alignable (Located a) | |
Defined in Diagrams.Located Methods alignBy' :: (InSpace v n (Located a), Fractional n, HasOrigin (Located a)) => (v n -> Located a -> Point v n) -> v n -> n -> Located a -> Located a # defaultBoundary :: (V (Located a) ~ v, N (Located a) ~ n) => v n -> Located a -> Point v n # alignBy :: (InSpace v n (Located a), Fractional n, HasOrigin (Located a)) => v n -> n -> Located a -> Located a # | |
| (InSpace v n a, HasOrigin a, Alignable a) => Alignable (b -> a) | Although the |
Defined in Diagrams.Align Methods alignBy' :: (InSpace v n (b -> a), Fractional n, HasOrigin (b -> a)) => (v n -> (b -> a) -> Point v n) -> v n -> n -> (b -> a) -> b -> a # defaultBoundary :: (V (b -> a) ~ v, N (b -> a) ~ n) => v n -> (b -> a) -> Point v n # alignBy :: (InSpace v n (b -> a), Fractional n, HasOrigin (b -> a)) => v n -> n -> (b -> a) -> b -> a # | |
| (V b ~ v, N b ~ n, Metric v, OrderedField n, Alignable b) => Alignable (Map k b) | |
Defined in Diagrams.Align Methods alignBy' :: (InSpace v n (Map k b), Fractional n, HasOrigin (Map k b)) => (v n -> Map k b -> Point v n) -> v n -> n -> Map k b -> Map k b # defaultBoundary :: (V (Map k b) ~ v, N (Map k b) ~ n) => v n -> Map k b -> Point v n # alignBy :: (InSpace v n (Map k b), Fractional n, HasOrigin (Map k b)) => v n -> n -> Map k b -> Map k b # | |
| (Metric v, OrderedField n) => Alignable (Envelope v n) | |
Defined in Diagrams.Align Methods alignBy' :: (InSpace v0 n0 (Envelope v n), Fractional n0, HasOrigin (Envelope v n)) => (v0 n0 -> Envelope v n -> Point v0 n0) -> v0 n0 -> n0 -> Envelope v n -> Envelope v n # defaultBoundary :: (V (Envelope v n) ~ v0, N (Envelope v n) ~ n0) => v0 n0 -> Envelope v n -> Point v0 n0 # alignBy :: (InSpace v0 n0 (Envelope v n), Fractional n0, HasOrigin (Envelope v n)) => v0 n0 -> n0 -> Envelope v n -> Envelope v n # | |
| (Metric v, OrderedField n) => Alignable (Trace v n) | |
Defined in Diagrams.Align Methods alignBy' :: (InSpace v0 n0 (Trace v n), Fractional n0, HasOrigin (Trace v n)) => (v0 n0 -> Trace v n -> Point v0 n0) -> v0 n0 -> n0 -> Trace v n -> Trace v n # defaultBoundary :: (V (Trace v n) ~ v0, N (Trace v n) ~ n0) => v0 n0 -> Trace v n -> Point v0 n0 # alignBy :: (InSpace v0 n0 (Trace v n), Fractional n0, HasOrigin (Trace v n)) => v0 n0 -> n0 -> Trace v n -> Trace v n # | |
| (Metric v, Traversable v, OrderedField n) => Alignable (BoundingBox v n) | |
Defined in Diagrams.BoundingBox Methods alignBy' :: (InSpace v0 n0 (BoundingBox v n), Fractional n0, HasOrigin (BoundingBox v n)) => (v0 n0 -> BoundingBox v n -> Point v0 n0) -> v0 n0 -> n0 -> BoundingBox v n -> BoundingBox v n # defaultBoundary :: (V (BoundingBox v n) ~ v0, N (BoundingBox v n) ~ n0) => v0 n0 -> BoundingBox v n -> Point v0 n0 # alignBy :: (InSpace v0 n0 (BoundingBox v n), Fractional n0, HasOrigin (BoundingBox v n)) => v0 n0 -> n0 -> BoundingBox v n -> BoundingBox v n # | |
| (Metric v, OrderedField n) => Alignable (Path v n) | |
Defined in Diagrams.Path Methods alignBy' :: (InSpace v0 n0 (Path v n), Fractional n0, HasOrigin (Path v n)) => (v0 n0 -> Path v n -> Point v0 n0) -> v0 n0 -> n0 -> Path v n -> Path v n # defaultBoundary :: (V (Path v n) ~ v0, N (Path v n) ~ n0) => v0 n0 -> Path v n -> Point v0 n0 # alignBy :: (InSpace v0 n0 (Path v n), Fractional n0, HasOrigin (Path v n)) => v0 n0 -> n0 -> Path v n -> Path v n # | |
| (Metric v, OrderedField n, Monoid' m) => Alignable (QDiagram b v n m) | |
Defined in Diagrams.Align Methods alignBy' :: (InSpace v0 n0 (QDiagram b v n m), Fractional n0, HasOrigin (QDiagram b v n m)) => (v0 n0 -> QDiagram b v n m -> Point v0 n0) -> v0 n0 -> n0 -> QDiagram b v n m -> QDiagram b v n m # defaultBoundary :: (V (QDiagram b v n m) ~ v0, N (QDiagram b v n m) ~ n0) => v0 n0 -> QDiagram b v n m -> Point v0 n0 # alignBy :: (InSpace v0 n0 (QDiagram b v n m), Fractional n0, HasOrigin (QDiagram b v n m)) => v0 n0 -> n0 -> QDiagram b v n m -> QDiagram b v n m # | |
globalPackage :: IO FilePath #
Find ghc's global package database. Throws an error if it isn't found.
findSandbox :: [FilePath] -> IO (Maybe FilePath) #
Search for a sandbox in the following order:
- Test given FilePaths if they point directly to a database or contain a cabal config file (or any parent directory containing a config file).
- Same test for
DIAGRAMS_SANDBOXenvironment value - Environment values of
GHC_PACKAGE_PATH,HSENVandPACKAGE_DB_FOR_GHCthat point to a database. - Test for config file (cabal.sandbox.config) in the current directory and its parents.
findHsFile :: FilePath -> IO (Maybe FilePath) #
Given some file (no extension or otherwise) try to find a haskell source file.
foldB :: (a -> a -> a) -> a -> [a] -> a #
Given an associative binary operation and a default value to use in the case of an empty list, perform a balanced fold over a list. For example,
foldB (+) z [a,b,c,d,e,f] == ((a+b) + (c+d)) + (e+f)
The circle constant, the ratio of a circle's circumference to its
radius. Note that pi = tau/2.
For more information and a well-reasoned argument why we should all be using tau instead of pi, see The Tau Manifesto, http://tauday.com/.
To hear what it sounds like (and to easily memorize the first 30 digits or so), try http://youtu.be/3174T-3-59Q.
iterateN :: Int -> (a -> a) -> a -> [a] #
iterateN n f x returns the list of the first n iterates of
f starting at x, that is, the list [x, f x, f (f x), ...]
of length n. (Note that the last element of the list will be
f applied to x (n-1) times.)
(#) :: a -> (a -> b) -> b infixl 8 #
Postfix function application, for conveniently applying
attributes. Unlike ($), (#) has a high precedence (8), so d
# foo # bar can be combined with other things using operators
like (|||) or (<>) without needing parentheses.
applyAll :: [a -> a] -> a -> a #
applyAll takes a list of functions and applies them all to a
value, in sequence from the last function in the list to the first.
For example, applyAll [f1, f2, f3] a == f1 . f2 . f3 $ a.
Several functions exported by the diagrams library take a number
of arguments giving the user control to "tweak" various aspects
of their behavior. Rather than give such functions a long list
of arguments, and to make it possible for the user to selectively
override only certain arguments and use default values for
others, such sets of arguments are collected into a record with
named fields (see PolygonOpts in Diagrams.TwoD.Shapes for an
example). Such record types are made instances of the Default
class, which provides a single record structure (def)
collecting the "default" arguments to the function. with is
a synonym for def, which provides nice-looking syntax for
simulating optional, named arguments in Haskell. For example,
polygon with {sides = 7, edgeSkip = 2}
calls the polygon function with a single argument (note that
record update binds more tightly than function application!),
namely, with (the record of default arguments) where the
sides and edgeSkip fields have been updated.
camForward :: Camera l n -> Direction V3 n #
mm50Narrow :: Floating n => PerspectiveLens n #
mm50Narrow has the same vertical field of view as mm50, but an aspect ratio of 4:3, for VGA and similar computer resolutions.
mm50Wide :: Floating n => PerspectiveLens n #
mm50blWide has the same vertical field of view as mm50, but an aspect ratio of 1.6, suitable for wide screen computer monitors.
mm50 :: Floating n => PerspectiveLens n #
mm50 has the field of view of a 50mm lens on standard 35mm film, hence an aspect ratio of 3:2.
facing_ZCamera :: (Floating n, Ord n, Typeable n, CameraLens l, Renderable (Camera l n) b) => l n -> QDiagram b V3 n Any #
'facing_ZCamera l' is a camera at the origin facing along the negative Z axis, with its up-axis coincident with the positive Y axis, with the projection defined by l.
mm50Camera :: (Typeable n, Floating n, Ord n, Renderable (Camera PerspectiveLens n) b) => QDiagram b V3 n Any #
A camera at the origin facing along the negative Z axis, with its up-axis coincident with the positive Y axis. The field of view is chosen to match a 50mm camera on 35mm film. Note that Cameras take up no space in the Diagram.
orthoWidth :: Lens' (OrthoLens n) n #
orthoHeight :: Lens' (OrthoLens n) n #
verticalFieldOfView :: Lens' (PerspectiveLens n) (Angle n) #
horizontalFieldOfView :: Lens' (PerspectiveLens n) (Angle n) #
An orthographic projection
Constructors
| OrthoLens | |
Fields
| |
data Camera (l :: Type -> Type) n #
Instances
| Num n => Transformable (Camera l n) | |
Defined in Diagrams.ThreeD.Camera | |
| Num n => Renderable (Camera l n) NullBackend | |
Defined in Diagrams.ThreeD.Camera Methods render :: NullBackend -> Camera l n -> Render NullBackend (V (Camera l n)) (N (Camera l n)) # | |
| type V (Camera l n) | |
Defined in Diagrams.ThreeD.Camera | |
| type N (Camera l n) | |
Defined in Diagrams.ThreeD.Camera | |
data PerspectiveLens n #
A perspective projection
Constructors
| PerspectiveLens | |
Fields
| |
Instances
| CameraLens PerspectiveLens | |
Defined in Diagrams.ThreeD.Camera Methods aspect :: Floating n => PerspectiveLens n -> n # | |
| type V (PerspectiveLens n) | |
Defined in Diagrams.ThreeD.Camera | |
| type N (PerspectiveLens n) | |
Defined in Diagrams.ThreeD.Camera | |
difference :: (CsgPrim a, CsgPrim b) => a n -> b n -> CSG n #
intersection :: (CsgPrim a, CsgPrim b) => a n -> b n -> CSG n #
cylinder :: Num n => Frustum n #
A circular cylinder of radius 1 with one end cap centered on the origin, and extending to Z=1.
A cone with its base centered on the origin, with radius 1 at the base, height 1, and it's apex on the positive Z axis.
A cube with side length 1, in the positive octant, with one vertex at the origin.
Constructors
| Ellipsoid (Transformation V3 n) |
Instances
| CsgPrim Ellipsoid | |
Defined in Diagrams.ThreeD.Shapes | |
| OrderedField n => Enveloped (Ellipsoid n) | |
Defined in Diagrams.ThreeD.Shapes | |
| OrderedField n => Traced (Ellipsoid n) | |
| Fractional n => Transformable (Ellipsoid n) | |
Defined in Diagrams.ThreeD.Shapes | |
| OrderedField n => Skinned (Ellipsoid n) | |
Defined in Diagrams.ThreeD.Shapes | |
| Fractional n => Renderable (Ellipsoid n) NullBackend | |
Defined in Diagrams.ThreeD.Shapes Methods render :: NullBackend -> Ellipsoid n -> Render NullBackend (V (Ellipsoid n)) (N (Ellipsoid n)) # | |
| (Num n, Ord n) => HasQuery (Ellipsoid n) Any | |
| type V (Ellipsoid n) | |
Defined in Diagrams.ThreeD.Shapes | |
| type N (Ellipsoid n) | |
Defined in Diagrams.ThreeD.Shapes | |
Constructors
| Box (Transformation V3 n) |
Instances
| CsgPrim Box | |
Defined in Diagrams.ThreeD.Shapes | |
| OrderedField n => Enveloped (Box n) | |
Defined in Diagrams.ThreeD.Shapes | |
| (Fractional n, Ord n) => Traced (Box n) | |
| Fractional n => Transformable (Box n) | |
Defined in Diagrams.ThreeD.Shapes | |
| OrderedField n => Skinned (Box n) | |
Defined in Diagrams.ThreeD.Shapes | |
| Fractional n => Renderable (Box n) NullBackend | |
Defined in Diagrams.ThreeD.Shapes Methods render :: NullBackend -> Box n -> Render NullBackend (V (Box n)) (N (Box n)) # | |
| (Num n, Ord n) => HasQuery (Box n) Any | |
| type V (Box n) | |
Defined in Diagrams.ThreeD.Shapes | |
| type N (Box n) | |
Defined in Diagrams.ThreeD.Shapes | |
Constructors
| Frustum n n (Transformation V3 n) |
Instances
| CsgPrim Frustum | |
Defined in Diagrams.ThreeD.Shapes | |
| (OrderedField n, RealFloat n) => Enveloped (Frustum n) | |
Defined in Diagrams.ThreeD.Shapes | |
| (RealFloat n, Ord n) => Traced (Frustum n) | |
| Fractional n => Transformable (Frustum n) | |
Defined in Diagrams.ThreeD.Shapes | |
| Skinned (Frustum n) | |
Defined in Diagrams.ThreeD.Shapes | |
| Fractional n => Renderable (Frustum n) NullBackend | |
Defined in Diagrams.ThreeD.Shapes Methods render :: NullBackend -> Frustum n -> Render NullBackend (V (Frustum n)) (N (Frustum n)) # | |
| OrderedField n => HasQuery (Frustum n) Any | |
| type V (Frustum n) | |
Defined in Diagrams.ThreeD.Shapes | |
| type N (Frustum n) | |
Defined in Diagrams.ThreeD.Shapes | |
Types which can be rendered as 3D Diagrams.
Methods
skin :: (Renderable t b, N t ~ n, TypeableFloat n) => t -> QDiagram b V3 n Any #
Instances
| OrderedField n => Skinned (Ellipsoid n) | |
Defined in Diagrams.ThreeD.Shapes | |
| OrderedField n => Skinned (Box n) | |
Defined in Diagrams.ThreeD.Shapes | |
| Skinned (Frustum n) | |
Defined in Diagrams.ThreeD.Shapes | |
| (RealFloat n, Ord n) => Skinned (CSG n) | |
Defined in Diagrams.ThreeD.Shapes | |
A tree of Constructive Solid Geometry operations and the primitives that can be used in them.
Constructors
| CsgEllipsoid (Ellipsoid n) | |
| CsgBox (Box n) | |
| CsgFrustum (Frustum n) | |
| CsgUnion [CSG n] | |
| CsgIntersection [CSG n] | |
| CsgDifference (CSG n) (CSG n) |
Instances
| CsgPrim CSG | |
Defined in Diagrams.ThreeD.Shapes | |
| RealFloat n => Enveloped (CSG n) | The Envelope for an Intersection or Difference is simply the Envelope of the Union. This is wrong but easy to implement. |
Defined in Diagrams.ThreeD.Shapes | |
| (RealFloat n, Ord n) => Traced (CSG n) | |
| Fractional n => Transformable (CSG n) | |
Defined in Diagrams.ThreeD.Shapes | |
| (RealFloat n, Ord n) => Skinned (CSG n) | |
Defined in Diagrams.ThreeD.Shapes | |
| (Floating n, Ord n) => HasQuery (CSG n) Any | |
| type V (CSG n) | |
Defined in Diagrams.ThreeD.Shapes | |
| type N (CSG n) | |
Defined in Diagrams.ThreeD.Shapes | |
reflectAcross :: (InSpace v n t, Metric v, Fractional n, Transformable t) => Point v n -> v n -> t -> t #
reflectAcross p v reflects a diagram across the plane though
the point p and the vector v. This also works as a 2D transform
where v is the normal to the line passing through point p.
reflectionAcross :: (Metric v, Fractional n) => Point v n -> v n -> Transformation v n #
reflectionAcross p v is a reflection across the plane through
the point p and normal to vector v. This also works as a 2D
transform where v is the normal to the line passing through point
p.
reflectZ :: (InSpace v n t, R3 v, Transformable t) => t -> t #
Flip a diagram across z=0, i.e. send the point (x,y,z) to (x,y,-z).
reflectionZ :: (Additive v, R3 v, Num n) => Transformation v n #
Construct a transformation which flips a diagram across z=0, i.e. sends the point (x,y,z) to (x,y,-z).
translateZ :: (InSpace v n t, R3 v, Transformable t) => n -> t -> t #
Translate a diagram by the given distance in the y direction.
translationZ :: (Additive v, R3 v, Num n) => n -> Transformation v n #
Construct a transformation which translates by the given distance in the z direction.
scaleZ :: (InSpace v n t, R3 v, Fractional n, Transformable t) => n -> t -> t #
Scale a diagram by the given factor in the z direction. To scale
uniformly, use scale.
scalingZ :: (Additive v, R3 v, Fractional n) => n -> Transformation v n #
Construct a transformation which scales by the given factor in the z direction.
pointAt' :: (Floating n, Ord n) => V3 n -> V3 n -> V3 n -> Transformation V3 n #
pointAt' has the same behavior as pointAt, but takes vectors
instead of directions.
pointAt :: (Floating n, Ord n) => Direction V3 n -> Direction V3 n -> Direction V3 n -> Transformation V3 n #
pointAt about initial final produces a rotation which brings
the direction initial to point in the direction final by first
panning around about, then tilting about the axis perpendicular
to about and final. In particular, if this can be accomplished
without tilting, it will be, otherwise if only tilting is
necessary, no panning will occur. The tilt will always be between
± 1/4 turn.
Arguments
| :: (InSpace V3 n t, Floating n, Transformable t) | |
| => Point V3 n | origin of rotation |
| -> Direction V3 n | direction of rotation axis |
| -> Angle n | angle of rotation |
| -> t | |
| -> t |
rotationAbout p d a is a rotation about a line parallel to d
passing through p.
Arguments
| :: Floating n | |
| => Point V3 n | origin of rotation |
| -> Direction V3 n | direction of rotation axis |
| -> Angle n | angle of rotation |
| -> Transformation V3 n |
rotationAbout p d a is a rotation about a line parallel to d
passing through p.
aboutY :: Floating n => Angle n -> Transformation V3 n #
Like aboutZ, but rotates about the Y axis, bringing postive
x-values towards the negative z-axis.
aboutX :: Floating n => Angle n -> Transformation V3 n #
Like aboutZ, but rotates about the X axis, bringing positive y-values
towards the positive z-axis.
aboutZ :: Floating n => Angle n -> Transformation V3 n #
Create a transformation which rotates by the given angle about a line parallel the Z axis passing through the local origin. A positive angle brings positive x-values towards the positive-y axis.
The angle can be expressed using any type which is an
instance of Angle. For example, aboutZ (1/4 @@
, turn)aboutZ (tau/4 @@ , and rad)aboutZ (90 @@
all represent the same transformation, namely, a
counterclockwise rotation by a right angle. For more general rotations,
see deg)rotationAbout.
Note that writing aboutZ (1/4), with no type annotation, will
yield an error since GHC cannot figure out which sort of angle
you want to use.
shearY :: (InSpace V2 n t, Transformable t) => n -> t -> t #
shearY d performs a shear in the y-direction which sends
(1,0) to (1,d).
shearingY :: Num n => n -> T2 n #
shearingY d is the linear transformation which is the identity on
x coordinates and sends (1,0) to (1,d).
shearX :: (InSpace V2 n t, Transformable t) => n -> t -> t #
shearX d performs a shear in the x-direction which sends
(0,1) to (d,1).
shearingX :: Num n => n -> T2 n #
shearingX d is the linear transformation which is the identity on
y coordinates and sends (0,1) to (d,1).
reflectAbout :: (InSpace V2 n t, OrderedField n, Transformable t) => P2 n -> Direction V2 n -> t -> t #
reflectAbout p d reflects a diagram in the line determined by
the point p and direction d.
reflectionAbout :: OrderedField n => P2 n -> Direction V2 n -> T2 n #
reflectionAbout p d is a reflection in the line determined by
the point p and direction d.
reflectXY :: (InSpace v n t, R2 v, Transformable t) => t -> t #
Flips the diagram about x=y, i.e. send the point (x,y) to (y,x).
reflectionXY :: (Additive v, R2 v, Num n) => Transformation v n #
Construct a transformation which flips the diagram about x=y, i.e. sends the point (x,y) to (y,x).
reflectY :: (InSpace v n t, R2 v, Transformable t) => t -> t #
Flip a diagram from top to bottom, i.e. send the point (x,y) to (x,-y).
reflectionY :: (Additive v, R2 v, Num n) => Transformation v n #
Construct a transformation which flips a diagram from top to bottom, i.e. sends the point (x,y) to (x,-y).
reflectX :: (InSpace v n t, R1 v, Transformable t) => t -> t #
Flip a diagram from left to right, i.e. send the point (x,y) to (-x,y).
reflectionX :: (Additive v, R1 v, Num n) => Transformation v n #
Construct a transformation which flips a diagram from left to right, i.e. sends the point (x,y) to (-x,y).
scaleRotateTo :: (InSpace V2 n t, Transformable t, Floating n) => V2 n -> t -> t #
Rotate and uniformly scale around the local origin such that the x-axis aligns with the given vector. This satisfies the equation
scaleRotateTo v = rotateTo (dir v) . scale (norm v)
up to floating point rounding errors, but is more accurate and performant since it avoids cancellable uses of trigonometric functions.
scalingRotationTo :: Floating n => V2 n -> T2 n #
The angle-preserving linear map that aligns the x-axis unit vector
with the given vector. See also scaleRotateTo.
translateY :: (InSpace v n t, R2 v, Transformable t) => n -> t -> t #
Translate a diagram by the given distance in the y (vertical) direction.
translationY :: (Additive v, R2 v, Num n) => n -> Transformation v n #
Construct a transformation which translates by the given distance in the y (vertical) direction.
translateX :: (InSpace v n t, R1 v, Transformable t) => n -> t -> t #
Translate a diagram by the given distance in the x (horizontal) direction.
translationX :: (Additive v, R1 v, Num n) => n -> Transformation v n #
Construct a transformation which translates by the given distance in the x (horizontal) direction.
scaleUToY :: (InSpace v n t, R2 v, Enveloped t, Transformable t) => n -> t -> t #
scaleUToY h scales a diagram uniformly by whatever factor
required to make its height h. scaleUToY should not be applied
to diagrams with a height of 0, such as hrule.
scaleUToX :: (InSpace v n t, R1 v, Enveloped t, Transformable t) => n -> t -> t #
scaleUToX w scales a diagram uniformly by whatever factor
required to make its width w. scaleUToX should not be
applied to diagrams with a width of 0, such as vrule.
scaleToY :: (InSpace v n t, R2 v, Enveloped t, Transformable t) => n -> t -> t #
scaleToY h scales a diagram in the y (vertical) direction by
whatever factor required to make its height h. scaleToY
should not be applied to diagrams with a height of 0, such as
hrule.
scaleToX :: (InSpace v n t, R2 v, Enveloped t, Transformable t) => n -> t -> t #
scaleToX w scales a diagram in the x (horizontal) direction by
whatever factor required to make its width w. scaleToX
should not be applied to diagrams with a width of 0, such as
vrule.
scaleY :: (InSpace v n t, R2 v, Fractional n, Transformable t) => n -> t -> t #
Scale a diagram by the given factor in the y (vertical)
direction. To scale uniformly, use scale.
scalingY :: (Additive v, R2 v, Fractional n) => n -> Transformation v n #
Construct a transformation which scales by the given factor in the y (vertical) direction.
scaleX :: (InSpace v n t, R2 v, Fractional n, Transformable t) => n -> t -> t #
Scale a diagram by the given factor in the x (horizontal)
direction. To scale uniformly, use scale.
scalingX :: (Additive v, R1 v, Fractional n) => n -> Transformation v n #
Construct a transformation which scales by the given factor in the x (horizontal) direction.
rotateTo :: (InSpace V2 n t, OrderedField n, Transformable t) => Direction V2 n -> t -> t #
Rotate around the local origin such that the x axis aligns with the given direction.
rotationTo :: OrderedField n => Direction V2 n -> T2 n #
The rotation that aligns the x-axis with the given direction.
rotateAround :: (InSpace V2 n t, Transformable t, Floating n) => P2 n -> Angle n -> t -> t #
rotateAbout p is like rotate, except it rotates around the
point p instead of around the local origin.
rotationAround :: Floating n => P2 n -> Angle n -> T2 n #
rotationAbout p is a rotation about the point p (instead of
around the local origin).
rotated :: (InSpace V2 n a, Floating n, SameSpace a b, Transformable a, Transformable b) => Angle n -> Iso a b a b #
signedAngleBetweenDirs :: RealFloat n => Direction V2 n -> Direction V2 n -> Angle n #
Same as signedAngleBetween but for Directionss.
signedAngleBetween :: RealFloat n => V2 n -> V2 n -> Angle n #
Signed angle between two vectors. Currently defined as
signedAngleBetween u v = (u ^. _theta) ^-^ (v ^. _theta)
leftTurn :: (Num n, Ord n) => V2 n -> V2 n -> Bool #
leftTurn v1 v2 tests whether the direction of v2 is a left
turn from v1 (that is, if the direction of v2 can be obtained
from that of v1 by adding an angle 0 <= theta <= tau/2).
angleV :: Floating n => Angle n -> V2 n #
A unit vector at a specified angle counter-clockwise from the positive x-axis
angleDir :: Floating n => Angle n -> Direction V2 n #
A direction at a specified angle counter-clockwise from the xDir.
Arguments
| :: (Typeable n, OrderedField n, Renderable (ParallelLight n) b) | |
| => Direction V3 n | The direction in which the light travels. |
| -> Colour Double | The color of the light. |
| -> QDiagram b V3 n Any |
Construct a Diagram with a single ParallelLight, which takes up no space.
Arguments
| :: (Typeable n, Num n, Ord n, Renderable (PointLight n) b) | |
| => Colour Double | The color of the light |
| -> QDiagram b V3 n Any |
Construct a Diagram with a single PointLight at the origin, which takes up no space.
data PointLight n #
A PointLight radiates uniformly in all directions from a given
point.
Constructors
| PointLight (Point V3 n) (Colour Double) |
Instances
| Fractional n => Transformable (PointLight n) | |
Defined in Diagrams.ThreeD.Light Methods transform :: Transformation (V (PointLight n)) (N (PointLight n)) -> PointLight n -> PointLight n # | |
| type V (PointLight n) | |
Defined in Diagrams.ThreeD.Light | |
| type N (PointLight n) | |
Defined in Diagrams.ThreeD.Light | |
data ParallelLight n #
A ParallelLight casts parallel rays in the specified direction,
from some distant location outside the scene.
Constructors
| ParallelLight (V3 n) (Colour Double) |
Instances
| Transformable (ParallelLight n) | |
Defined in Diagrams.ThreeD.Light Methods transform :: Transformation (V (ParallelLight n)) (N (ParallelLight n)) -> ParallelLight n -> ParallelLight n # | |
| type V (ParallelLight n) | |
Defined in Diagrams.ThreeD.Light | |
| type N (ParallelLight n) | |
Defined in Diagrams.ThreeD.Light | |
type T3 = Transformation V3 #
type T2 = Transformation V2 #
class HasR (t :: Type -> Type) where #
A space which has magnitude _r that can be calculated numerically.
translated :: (InSpace v n a, SameSpace a b, Transformable a, Transformable b) => v n -> Iso a b a b #
Use a vector to make an Iso between an object translated and
untranslated.
under (translated v) f == translate (-v) . f . translate v translated v ## a == translate v a a ^. translated v == translate (-v) a over (translated v) f == translate v . f . translate (-v)
movedFrom :: (InSpace v n a, SameSpace a b, HasOrigin a, HasOrigin b) => Point v n -> Iso a b a b #
Use a Transformation to make an Iso between an object
transformed and untransformed. We have
under (movedFrom p) f == moveTo p . f . moveTo (-p) movedFrom p == from (movedTo p) movedFrom p ## a == moveOriginTo p a a ^. movedFrom p == moveTo p a over (movedFrom p) f == moveTo (-p) . f . moveTo p
transformed :: (InSpace v n a, SameSpace a b, Transformable a, Transformable b) => Transformation v n -> Iso a b a b #
Use a Transformation to make an Iso between an object
transformed and untransformed. This is useful for carrying out
functions under another transform:
under (transformed t) f == transform (inv t) . f . transform t under (transformed t1) (transform t2) == transform (conjugate t1 t2) transformed t ## a == transform t a a ^. transformed t == transform (inv t) a
underT :: (InSpace v n a, SameSpace a b, Transformable a, Transformable b) => (a -> b) -> Transformation v n -> a -> b #
Carry out some transformation "under" another one: f ` first applies underT`
tt, then f, then the inverse of t. For
example,
is the transformation which scales by a factor of 2 along the
diagonal line y = x.scaleX 2 `underT` rotation (-1/8 @@ Turn)
Note that
(transform t2) underT t1 == transform (conjugate t1 t2)
for all transformations t1 and t2.
See also the isomorphisms like transformed, movedTo,
movedFrom, and translated.
conjugate :: (Additive v, Num n) => Transformation v n -> Transformation v n -> Transformation v n #
Conjugate one transformation by another. conjugate t1 t2 is the
transformation which performs first t1, then t2, then the
inverse of t1.
highlightSize :: Traversal' (Style v n) Double #
Traversal over the highlight size in a style. If the style has no
Specular, setting this will do nothing.
highlightIntensity :: Traversal' (Style v n) Double #
Traversal over the highlight intensity of a style. If the style has
no Specular, setting this will do nothing.
_highlight :: Lens' (Style v n) (Maybe Specular) #
Lens onto the possible specular highlight in a style
Instances
| Show Highlight | |
| Semigroup Highlight | |
| AttributeClass Highlight | |
Defined in Diagrams.ThreeD.Attributes | |
_diffuse :: Lens' (Style v n) (Maybe Double) #
Lens onto the possible diffuse reflectance in a style.
newtype SurfaceColor #
SurfaceColor is the inherent pigment of an object, assumed to
be opaque.
Constructors
| SurfaceColor (Last (Colour Double)) |
Instances
| Show SurfaceColor | |
Defined in Diagrams.ThreeD.Attributes Methods showsPrec :: Int -> SurfaceColor -> ShowS # show :: SurfaceColor -> String # showList :: [SurfaceColor] -> ShowS # | |
| Semigroup SurfaceColor | |
Defined in Diagrams.ThreeD.Attributes Methods (<>) :: SurfaceColor -> SurfaceColor -> SurfaceColor # sconcat :: NonEmpty SurfaceColor -> SurfaceColor # stimes :: Integral b => b -> SurfaceColor -> SurfaceColor # | |
| AttributeClass SurfaceColor | |
Defined in Diagrams.ThreeD.Attributes | |
Diffuse is the fraction of incident light reflected diffusely,
that is, in all directions. The actual light reflected is the
product of this value, the incident light, and the SurfaceColor
Attribute. For physical reasonableness, Diffuse should have a
value between 0 and 1; this is not checked.
Instances
| Show Diffuse | |
| Semigroup Diffuse | |
| AttributeClass Diffuse | |
Defined in Diagrams.ThreeD.Attributes | |
Ambient is an ad-hoc representation of indirect lighting. The
product of Ambient and SurfaceColor is added to the light
leaving an object due to diffuse and specular terms. Ambient can
be set per-object, and can be loosely thought of as the product of
indirect lighting incident on that object and the diffuse
reflectance.
Instances
| Show Ambient | |
| Semigroup Ambient | |
| AttributeClass Ambient | |
Defined in Diagrams.ThreeD.Attributes | |
A specular highlight has two terms, the intensity, between 0 and
1, and the size. The highlight size is assumed to be the exponent
in a Phong shading model (though Backends are free to use a
different shading model). In this model, reasonable values are
between 1 and 50 or so, with higher values for shinier objects.
Physically, the intensity and the value of Diffuse must add up to
less than 1; this is not enforced.
Constructors
| Specular | |
Fields | |
clearValue :: QDiagram b v n m -> QDiagram b v n Any #
Set all the query values of a diagram to False.
class HasQuery t m | t -> m where #
Types which can answer a Query about points inside the geometric
object.
If t and m are both a Semigroups, getQuery should satisfy
getQuery(t1 <> t2) =getQueryt1 <>getQueryt2
Instances
| RealFloat n => HasQuery (Clip n) All | A point inside a clip if the point is in |
| (Num n, Ord n) => HasQuery (Ellipsoid n) Any | |
| (Num n, Ord n) => HasQuery (Box n) Any | |
| OrderedField n => HasQuery (Frustum n) Any | |
| (Floating n, Ord n) => HasQuery (CSG n) Any | |
| (Additive v, Foldable v, Ord n) => HasQuery (BoundingBox v n) Any | |
Defined in Diagrams.BoundingBox Methods getQuery :: BoundingBox v n -> Query (V (BoundingBox v n)) (N (BoundingBox v n)) Any # | |
| RealFloat n => HasQuery (DImage n a) Any | |
| HasQuery (Query v n m) m | |
| Monoid m => HasQuery (QDiagram b v n m) m | |
dirBetween :: (Additive v, Num n) => Point v n -> Point v n -> Direction v n #
dirBetween p q returns the direction from p to q.
angleBetweenDirs :: (Metric v, Floating n, Ord n) => Direction v n -> Direction v n -> Angle n #
compute the positive angle between the two directions in their common plane
fromDirection :: (Metric v, Floating n) => Direction v n -> v n #
fromDirection d is the unit vector in the direction d.
direction :: v n -> Direction v n #
direction v is the direction in which v points. Returns an
unspecified value when given the zero vector as input.
_Dir :: Iso' (Direction v n) (v n) #
_Dir is provided to allow efficient implementations of functions in particular vector-spaces, but should be used with care as it exposes too much information.
data Direction (v :: Type -> Type) n #
A vector is described by a Direction and a magnitude. So we
can think of a Direction as a vector that has forgotten its
magnitude. Directions can be used with fromDirection and the
lenses provided by its instances.
Instances
| Functor v => Functor (Direction v) | |
| HasTheta v => HasTheta (Direction v) | |
| HasPhi v => HasPhi (Direction v) | |
| Eq (v n) => Eq (Direction v n) | |
| Ord (v n) => Ord (Direction v n) | |
Defined in Diagrams.Direction Methods compare :: Direction v n -> Direction v n -> Ordering # (<) :: Direction v n -> Direction v n -> Bool # (<=) :: Direction v n -> Direction v n -> Bool # (>) :: Direction v n -> Direction v n -> Bool # (>=) :: Direction v n -> Direction v n -> Bool # | |
| Read (v n) => Read (Direction v n) | |
| Show (v n) => Show (Direction v n) | |
| (V (v n) ~ v, N (v n) ~ n, Transformable (v n)) => Transformable (Direction v n) | |
Defined in Diagrams.Direction | |
| type V (Direction v n) | |
Defined in Diagrams.Direction | |
| type N (Direction v n) | |
Defined in Diagrams.Direction | |
rotate :: (InSpace V2 n t, Transformable t, Floating n) => Angle n -> t -> t #
Rotate about the local origin by the given angle. Positive angles
correspond to counterclockwise rotation, negative to
clockwise. The angle can be expressed using any of the Isos on
Angle. For example, rotate (1/4 @@ , turn)rotate
(tau/4 @@ rad), and rotate (90 @@ deg) all
represent the same transformation, namely, a counterclockwise
rotation by a right angle. To rotate about some point other than
the local origin, see rotateAbout.
Note that writing rotate (1/4), with no Angle constructor,
will yield an error since GHC cannot figure out which sort of
angle you want to use. In this common situation you can use
rotateBy, which interprets its argument as a number of turns.
rotation :: Floating n => Angle n -> Transformation V2 n #
Create a transformation which performs a rotation about the local
origin by the given angle. See also rotate.
normalizeAngle :: (Floating n, Real n) => Angle n -> Angle n #
Normalize an angle so that it lies in the [0,tau) range.
angleBetween :: (Metric v, Floating n, Ord n) => v n -> v n -> Angle n #
Compute the positive angle between the two vectors in their common
plane in the [0,pi] range. For a signed angle see
signedAngleBetween.
Returns NaN if either of the vectors are zero.
(@@) :: b -> AReview a b -> a infixl 5 #
30 @@ deg is an Angle of the given measure and units.
>>>pi @@ rad3.141592653589793 @@ rad
>>>1 @@ turn6.283185307179586 @@ rad
>>>30 @@ deg0.5235987755982988 @@ rad
For Iso's, (@@) reverses the Iso' on its right, and applies
the Iso' to the value on the left. Angles are the motivating
example where this order improves readability.
This is the same as a flipped review.
(@@) :: a ->Iso's a -> s (@@) :: a ->Prism's a -> s (@@) :: a ->Reviews a -> s (@@) :: a ->Equality's a -> s
atan2A' :: OrderedField n => n -> n -> Angle n #
atan2A :: RealFloat n => n -> n -> Angle n #
atan2A y x is the angle between the positive x-axis and the vector given
by the coordinates (x, y). The Angle returned is in the [-pi,pi] range.
angleRatio :: Floating n => Angle n -> Angle n -> n #
Calculate ratio between two angles.
quarterTurn :: Floating v => Angle v #
An angle representing a quarter turn.
Angles can be expressed in a variety of units. Internally, they are represented in radians.
Instances
| Functor Angle | |
| Applicative Angle | |
| Additive Angle | |
| Enum n => Enum (Angle n) | |
| Eq n => Eq (Angle n) | |
| Ord n => Ord (Angle n) | |
| Read n => Read (Angle n) | |
| Show n => Show (Angle n) | |
| Num n => Semigroup (Angle n) | |
| Num n => Monoid (Angle n) | |
| (V t ~ V2, N t ~ n, Transformable t, Floating n) => Action (Angle n) t | Angles act on other things by rotation. |
Defined in Diagrams.Angle | |
| type N (Angle n) | |
Defined in Diagrams.Angle | |
class HasTheta (t :: Type -> Type) where #
The class of types with at least one angle coordinate, called _theta.
class Coordinates c where #
Types which are instances of the Coordinates class can be
constructed using ^& (for example, a three-dimensional vector
could be constructed by 1 ^& 6 ^& 3), and deconstructed using
coords. A common pattern is to use coords in conjunction
with the ViewPatterns extension, like so:
foo :: Vector3 -> ... foo (coords -> x :& y :& z) = ...
Associated Types
type FinalCoord c :: Type #
The type of the final coordinate.
The type of everything other than the final coordinate.
type Decomposition c :: Type #
Decomposition of c into applications of :&.
Methods
(^&) :: PrevDim c -> FinalCoord c -> c infixl 7 #
Construct a value of type c by providing something of one
less dimension (which is perhaps itself recursively constructed
using (^&)) and a final coordinate. For example,
2 ^& 3 :: P2 3 ^& 5 ^& 6 :: V3
Note that ^& is left-associative.
pr :: PrevDim c -> FinalCoord c -> c #
Prefix synonym for ^&. pr stands for pair of PrevDim, FinalCoord
coords :: c -> Decomposition c #
Decompose a value of type c into its constituent coordinates,
stored in a nested (:&) structure.
Instances
| Coordinates (V2 n) | |
| Coordinates (V3 n) | |
| Coordinates (V4 n) | |
| Coordinates (a, b) | |
Defined in Diagrams.Coordinates Methods (^&) :: PrevDim (a, b) -> FinalCoord (a, b) -> (a, b) # pr :: PrevDim (a, b) -> FinalCoord (a, b) -> (a, b) # coords :: (a, b) -> Decomposition (a, b) # | |
| Coordinates (v n) => Coordinates (Point v n) | |
Defined in Diagrams.Coordinates | |
| Coordinates (a :& b) | |
Defined in Diagrams.Coordinates | |
| Coordinates (a, b, c) | |
Defined in Diagrams.Coordinates Associated Types type FinalCoord (a, b, c) :: Type # type PrevDim (a, b, c) :: Type # type Decomposition (a, b, c) :: Type # Methods (^&) :: PrevDim (a, b, c) -> FinalCoord (a, b, c) -> (a, b, c) # pr :: PrevDim (a, b, c) -> FinalCoord (a, b, c) -> (a, b, c) # coords :: (a, b, c) -> Decomposition (a, b, c) # | |
| Coordinates (a, b, c, d) | |
Defined in Diagrams.Coordinates Associated Types type FinalCoord (a, b, c, d) :: Type # type PrevDim (a, b, c, d) :: Type # type Decomposition (a, b, c, d) :: Type # Methods (^&) :: PrevDim (a, b, c, d) -> FinalCoord (a, b, c, d) -> (a, b, c, d) # pr :: PrevDim (a, b, c, d) -> FinalCoord (a, b, c, d) -> (a, b, c, d) # coords :: (a, b, c, d) -> Decomposition (a, b, c, d) # | |
A pair of values, with a convenient infix (left-associative) data constructor.
Constructors
| a :& b infixl 7 |
Instances
| (Eq a, Eq b) => Eq (a :& b) | |
| (Ord a, Ord b) => Ord (a :& b) | |
Defined in Diagrams.Coordinates | |
| (Show a, Show b) => Show (a :& b) | |
| Coordinates (a :& b) | |
Defined in Diagrams.Coordinates | |
| type Decomposition (a :& b) | |
Defined in Diagrams.Coordinates | |
| type PrevDim (a :& b) | |
Defined in Diagrams.Coordinates | |
| type FinalCoord (a :& b) | |
Defined in Diagrams.Coordinates | |
centroid :: (Additive v, Fractional n) => [Point v n] -> Point v n #
The centroid of a set of n points is their sum divided by n. Returns the origin for an empty list of points.
adjust :: (N t ~ n, Sectionable t, HasArcLength t, Fractional n) => t -> AdjustOpts n -> t #
Adjust the length of a parametric object such as a segment or
trail. The second parameter is an option record which controls how
the adjustment should be performed; see AdjustOpts.
adjSide :: Lens' (AdjustOpts n) AdjustSide #
Which end(s) of the object should be adjusted?
adjMethod :: Lens' (AdjustOpts n) (AdjustMethod n) #
Which method should be used for adjusting?
adjEps :: Lens' (AdjustOpts n) n #
Tolerance to use when doing adjustment.
data AdjustMethod n #
What method should be used for adjusting a segment, trail, or path?
Constructors
| ByParam n | Extend by the given parameter value (use a negative parameter to shrink) |
| ByAbsolute n | Extend by the given arc length (use a negative length to shrink) |
| ToAbsolute n | Extend or shrink to the given arc length |
Instances
| Fractional n => Default (AdjustMethod n) | |
Defined in Diagrams.Parametric.Adjust Methods def :: AdjustMethod n # | |
data AdjustSide #
Which side of a segment, trail, or path should be adjusted?
Instances
data AdjustOpts n #
How should a segment, trail, or path be adjusted?
Instances
| Fractional n => Default (AdjustOpts n) | |
Defined in Diagrams.Parametric.Adjust Methods def :: AdjustOpts n # | |
stdTolerance :: Fractional a => a #
The standard tolerance used by std... functions (like
stdArcLength and stdArcLengthToParam, currently set at
1e-6.
domainBounds :: DomainBounds p => p -> (N p, N p) #
Return the lower and upper bounds of a parametric domain together as a pair.
type family Codomain p :: Type -> Type #
Codomain of parametric classes. This is usually either (V p), for relative
vector results, or (Point (V p)), for functions with absolute coordinates.
Instances
| type Codomain (GetSegment t) | |
Defined in Diagrams.Trail | |
| type Codomain (Tangent t) | |
Defined in Diagrams.Tangent | |
| type Codomain (Located a) | |
Defined in Diagrams.Located | |
| type Codomain (BernsteinPoly n) | |
Defined in Diagrams.TwoD.Segment.Bernstein | |
| type Codomain (SegTree v n) | |
Defined in Diagrams.Trail | |
| type Codomain (Trail v n) | |
Defined in Diagrams.Trail | |
| type Codomain (FixedSegment v n) | |
Defined in Diagrams.Segment | |
| type Codomain (Trail' l v n) | |
Defined in Diagrams.Trail | |
| type Codomain (Segment Closed v n) | |
Defined in Diagrams.Segment | |
class Parametric p where #
Type class for parametric functions.
Methods
Instances
| (Metric v, OrderedField n) => Parametric (GetSegment (Trail' Line v n)) | Parameters less than 0 yield the first segment; parameters greater than 1 yield the last. A parameter exactly at the junction of two segments yields the second segment (i.e. the one with higher parameter values). |
Defined in Diagrams.Trail Methods atParam :: GetSegment (Trail' Line v n) -> N (GetSegment (Trail' Line v n)) -> Codomain (GetSegment (Trail' Line v n)) (N (GetSegment (Trail' Line v n))) # | |
| (Metric v, OrderedField n, Real n) => Parametric (GetSegment (Trail' Loop v n)) | The parameterization for loops wraps around, i.e. parameters are first reduced "mod 1". |
Defined in Diagrams.Trail Methods atParam :: GetSegment (Trail' Loop v n) -> N (GetSegment (Trail' Loop v n)) -> Codomain (GetSegment (Trail' Loop v n)) (N (GetSegment (Trail' Loop v n))) # | |
| (Metric v, OrderedField n, Real n) => Parametric (GetSegment (Trail v n)) | |
Defined in Diagrams.Trail Methods atParam :: GetSegment (Trail v n) -> N (GetSegment (Trail v n)) -> Codomain (GetSegment (Trail v n)) (N (GetSegment (Trail v n))) # | |
| (Parametric (GetSegment (Trail' c v n)), Additive v, Num n) => Parametric (Tangent (Trail' c v n)) | |
| (Metric v, OrderedField n, Real n) => Parametric (Tangent (Trail v n)) | |
| (Additive v, Num n) => Parametric (Tangent (Segment Closed v n)) | |
| (Additive v, Num n) => Parametric (Tangent (FixedSegment v n)) | |
Defined in Diagrams.Tangent Methods atParam :: Tangent (FixedSegment v n) -> N (Tangent (FixedSegment v n)) -> Codomain (Tangent (FixedSegment v n)) (N (Tangent (FixedSegment v n))) # | |
| Parametric (Tangent t) => Parametric (Tangent (Located t)) | |
| (InSpace v n a, Parametric a, Codomain a ~ v) => Parametric (Located a) | |
| Fractional n => Parametric (BernsteinPoly n) | |
Defined in Diagrams.TwoD.Segment.Bernstein Methods atParam :: BernsteinPoly n -> N (BernsteinPoly n) -> Codomain (BernsteinPoly n) (N (BernsteinPoly n)) # | |
| (Metric v, OrderedField n, Real n) => Parametric (SegTree v n) | |
| (Metric v, OrderedField n, Real n) => Parametric (Trail v n) | |
| (Additive v, Num n) => Parametric (FixedSegment v n) | |
Defined in Diagrams.Segment Methods atParam :: FixedSegment v n -> N (FixedSegment v n) -> Codomain (FixedSegment v n) (N (FixedSegment v n)) # | |
| (Metric v, OrderedField n, Real n) => Parametric (Trail' l v n) | |
| (Additive v, Num n) => Parametric (Segment Closed v n) |
|
class DomainBounds p where #
Type class for parametric functions with a bounded domain. The
default bounds are [0,1].
Note that this domain indicates the main "interesting" portion of the function. It must be defined within this range, but for some instances may still have sensible values outside.
Minimal complete definition
Nothing
Methods
domainLower :: p -> N p #
domainLower defaults to being constantly 0 (for vector spaces with
numeric scalars).
domainUpper :: p -> N p #
domainUpper defaults to being constantly 1 (for vector spaces
with numeric scalars).
Instances
class (Parametric p, DomainBounds p) => EndValues p where #
Type class for querying the values of a parametric object at the ends of its domain.
Minimal complete definition
Nothing
Methods
atStart :: p -> Codomain p (N p) #
atStart is the value at the start of the domain. That is,
atStart x = x `atParam` domainLower x
This is the default implementation, but some representations will have a more efficient and/or precise implementation.
atEnd :: p -> Codomain p (N p) #
atEnd is the value at the end of the domain. That is,
atEnd x = x `atParam` domainUpper x
This is the default implementation, but some representations will have a more efficient and/or precise implementation.
Instances
class DomainBounds p => Sectionable p where #
Type class for parametric objects which can be split into subobjects.
Minimal definition: Either splitAtParam or section,
plus reverseDomain.
Minimal complete definition
Methods
splitAtParam :: p -> N p -> (p, p) #
splitAtParam splits an object p into two new objects
(l,r) at the parameter t, where l corresponds to the
portion of p for parameter values from 0 to t and r for
to that from t to 1. The following property should hold:
prop_splitAtParam f t u =
| u < t = atParam f u == atParam l (u / t)
| otherwise = atParam f u == atParam f t ??? atParam l ((u - t) / (domainUpper f - t))
where (l,r) = splitAtParam f t
where (???) = (^+^) if the codomain is a vector type, or
const flip if the codomain is a point type. Stated more
intuitively, all this is to say that the parameterization
scales linearly with splitting.
splitAtParam can also be used with parameters outside the
range of the domain. For example, using the parameter 2 with
a path (where the domain is the default [0,1]) gives two
result paths where the first is the original path extended to
the parameter 2, and the second result path travels backwards
from the end of the first to the end of the original path.
section :: p -> N p -> N p -> p #
Extract a particular section of the domain, linearly reparameterized to the same domain as the original. Should satisfy the property:
prop_section x l u t =
let s = section x l u
in domainBounds x == domainBounds x
&& (x `atParam` lerp l u t) == (s `atParam` t)That is, the section should have the same domain as the original, and the reparameterization should be linear.
reverseDomain :: p -> p #
Flip the parameterization on the domain.
Instances
| (InSpace v n a, Fractional n, Parametric a, Sectionable a, Codomain a ~ v) => Sectionable (Located a) | |
| Fractional n => Sectionable (BernsteinPoly n) | |
Defined in Diagrams.TwoD.Segment.Bernstein Methods splitAtParam :: BernsteinPoly n -> N (BernsteinPoly n) -> (BernsteinPoly n, BernsteinPoly n) # section :: BernsteinPoly n -> N (BernsteinPoly n) -> N (BernsteinPoly n) -> BernsteinPoly n # reverseDomain :: BernsteinPoly n -> BernsteinPoly n # | |
| (Metric v, OrderedField n, Real n) => Sectionable (SegTree v n) | |
| (Metric v, OrderedField n, Real n) => Sectionable (Trail v n) | Note that there is no |
| (Additive v, Fractional n) => Sectionable (FixedSegment v n) | |
Defined in Diagrams.Segment Methods splitAtParam :: FixedSegment v n -> N (FixedSegment v n) -> (FixedSegment v n, FixedSegment v n) # section :: FixedSegment v n -> N (FixedSegment v n) -> N (FixedSegment v n) -> FixedSegment v n # reverseDomain :: FixedSegment v n -> FixedSegment v n # | |
| (Metric v, OrderedField n, Real n) => Sectionable (Trail' Line v n) | |
| (Additive v, Fractional n) => Sectionable (Segment Closed v n) | |
Defined in Diagrams.Segment | |
class Parametric p => HasArcLength p where #
Type class for parametric things with a notion of arc length.
Minimal complete definition
Methods
arcLengthBounded :: N p -> p -> Interval (N p) #
arcLengthBounded eps x approximates the arc length of x.
The true arc length is guaranteed to lie within the interval
returned, which will have a size of at most eps.
arcLength :: N p -> p -> N p #
arcLength eps s approximates the arc length of x up to the
accuracy eps (plus or minus).
stdArcLength :: p -> N p #
Approximate the arc length up to a standard accuracy of
stdTolerance (1e-6).
arcLengthToParam :: N p -> p -> N p -> N p #
converts the absolute arc length
arcLengthToParam eps s ll, measured from the start of the domain, to a parameter on
the object s. The true arc length at the parameter returned
is guaranteed to be within eps of the requested arc length.
This should work for any arc length, and may return any parameter value (not just parameters in the domain).
stdArcLengthToParam :: p -> N p -> N p #
A simple interface to convert arc length to a parameter,
guaranteed to be accurate within stdTolerance, or 1e-6.
Instances
namePoint :: (IsName nm, Metric v, OrderedField n, Semigroup m) => (QDiagram b v n m -> Point v n) -> nm -> QDiagram b v n m -> QDiagram b v n m #
Attach an atomic name to a certain point (which may be computed from the given diagram), treated as a subdiagram with no content and a point envelope.
named :: (IsName nm, Metric v, OrderedField n, Semigroup m) => nm -> QDiagram b v n m -> QDiagram b v n m #
Attach an atomic name to a diagram.
committed :: Iso (Recommend a) (Recommend b) a b #
Commit a value for any Recommend. This is *not* a valid Iso
because the resulting Recommend b is always a Commit. This is
useful because it means any Recommend styles set with a lens will
not be accidentally overridden. If you want a valid lens onto a
recommend value use _recommend.
Other lenses that use this are labeled with a warning.
isCommitted :: Lens' (Recommend a) Bool #
Lens onto whether something is committed or not.
_recommend :: Lens (Recommend a) (Recommend b) a b #
_Recommend :: Prism' (Recommend a) a #
Prism onto a Recommend.
_lineMiterLimit :: Lens' (Style v n) Double #
Lens onto the line miter limit in a style.
lineMiterLimitA :: HasStyle a => LineMiterLimit -> a -> a #
Apply a LineMiterLimit attribute.
lineMiterLimit :: HasStyle a => Double -> a -> a #
Set the miter limit for joins with LineJoinMiter.
getLineJoin :: LineJoin -> LineJoin #
getLineCap :: LineCap -> LineCap #
_strokeOpacity :: Lens' (Style v n) Double #
Lens onto the stroke opacity in a style.
strokeOpacity :: HasStyle a => Double -> a -> a #
Multiply the stroke opacity (see StrokeOpacity) by the given value. For
example, strokeOpacity 0.8 means "decrease this diagram's
stroke opacity to 80% of its previous value".
getStrokeOpacity :: StrokeOpacity -> Double #
_fillOpacity :: Lens' (Style v n) Double #
Lens onto the fill opacity in a style.
fillOpacity :: HasStyle a => Double -> a -> a #
Multiply the fill opacity (see FillOpacity) by the given value. For
example, fillOpacity 0.8 means "decrease this diagram's fill opacity to
80% of its previous value".
getFillOpacity :: FillOpacity -> Double #
opacity :: HasStyle a => Double -> a -> a #
Multiply the opacity (see Opacity) by the given value. For
example, opacity 0.8 means "decrease this diagram's opacity to
80% of its previous opacity".
getOpacity :: Opacity -> Double #
someToAlpha :: SomeColor -> AlphaColour Double #
_SomeColor :: Iso' SomeColor (AlphaColour Double) #
Isomorphism between SomeColor and AlphaColour Double.
_dashingU :: Typeable n => Lens' (Style v n) (Maybe (Dashing n)) #
Lens onto the unmeasured Dashing attribute. This is useful for
backends to use on styles once they have been unmeasured. Using on
a diagram style could lead to unexpected results.
_dashing :: Typeable n => Lens' (Style v n) (Maybe (Measured n (Dashing n))) #
Lens onto a measured dashing attribute in a style.
dashingL :: (N a ~ n, HasStyle a, Typeable n, Num n) => [n] -> n -> a -> a #
A convenient sysnonym for 'dashing (local w)'.
dashingO :: (N a ~ n, HasStyle a, Typeable n) => [n] -> n -> a -> a #
A convenient synonym for 'dashing (output w)'.
dashingN :: (N a ~ n, HasStyle a, Typeable n, Num n) => [n] -> n -> a -> a #
A convenient synonym for 'dashing (normalized w)'.
dashingG :: (N a ~ n, HasStyle a, Typeable n, Num n) => [n] -> n -> a -> a #
A convenient synonym for 'dashing (global w)'.
Arguments
| :: (N a ~ n, HasStyle a, Typeable n) | |
| => [Measure n] | A list specifying alternate lengths of on and off portions of the stroke. The empty list indicates no dashing. |
| -> Measure n | An offset into the dash pattern at which the stroke should start. |
| -> a | |
| -> a |
Set the line dashing style.
getDashing :: Dashing n -> Dashing n #
_lineWidthU :: Typeable n => Lens' (Style v n) (Maybe n) #
Lens onto the unmeasured linewith attribute. This is useful for backends to use on styles once they have been unmeasured. Using on a diagram style could lead to unexpected results.
_lw :: (Typeable n, OrderedField n) => Lens' (Style v n) (Measure n) #
Lens onto a measured line width in a style.
_lineWidth :: (Typeable n, OrderedField n) => Lens' (Style v n) (Measure n) #
Lens onto a measured line width in a style.
lwL :: (N a ~ n, HasStyle a, Typeable n, Num n) => n -> a -> a #
A convenient sysnonym for 'lineWidth (local w)'.
lwO :: (N a ~ n, HasStyle a, Typeable n) => n -> a -> a #
A convenient synonym for 'lineWidth (output w)'.
lwN :: (N a ~ n, HasStyle a, Typeable n, Num n) => n -> a -> a #
A convenient synonym for 'lineWidth (normalized w)'.
lwG :: (N a ~ n, HasStyle a, Typeable n, Num n) => n -> a -> a #
A convenient synonym for 'lineWidth (global w)'.
lineWidthM :: (N a ~ n, HasStyle a, Typeable n) => LineWidthM n -> a -> a #
Apply a LineWidth attribute.
getLineWidth :: LineWidth n -> n #
_LineWidthM :: Iso' (LineWidthM n) (Measure n) #
_LineWidth :: Iso' (LineWidth n) n #
huge :: OrderedField n => Measure n #
veryLarge :: OrderedField n => Measure n #
large :: OrderedField n => Measure n #
normal :: OrderedField n => Measure n #
small :: OrderedField n => Measure n #
verySmall :: OrderedField n => Measure n #
tiny :: OrderedField n => Measure n #
ultraThick :: OrderedField n => Measure n #
veryThick :: OrderedField n => Measure n #
thick :: OrderedField n => Measure n #
medium :: OrderedField n => Measure n #
thin :: OrderedField n => Measure n #
veryThin :: OrderedField n => Measure n #
ultraThin :: OrderedField n => Measure n #
none :: OrderedField n => Measure n #
Line widths specified on child nodes always override line widths specified at parent nodes.
Instances
| Semigroup (LineWidth n) | |
| OrderedField n => Default (LineWidthM n) | |
Defined in Diagrams.Attributes | |
| Typeable n => AttributeClass (LineWidth n) | |
Defined in Diagrams.Attributes | |
Create lines that are dashing... er, dashed.
Constructors
| Dashing [n] n |
The Color type class encompasses color representations which
can be used by the Diagrams library. Instances are provided for
both the Colour and AlphaColour types
from the Data.Colour library.
Methods
toAlphaColour :: c -> AlphaColour Double #
Convert a color to its standard representation, AlphaColour.
fromAlphaColour :: AlphaColour Double -> c #
Convert from an AlphaColour Double. Note that this direction
may lose some information. For example, the instance for
Colour drops the alpha channel.
Instances
| Color SomeColor | |
Defined in Diagrams.Attributes Methods toAlphaColour :: SomeColor -> AlphaColour Double # | |
| a ~ Double => Color (Colour a) | |
Defined in Diagrams.Attributes Methods toAlphaColour :: Colour a -> AlphaColour Double # fromAlphaColour :: AlphaColour Double -> Colour a # | |
| a ~ Double => Color (AlphaColour a) | |
Defined in Diagrams.Attributes Methods toAlphaColour :: AlphaColour a -> AlphaColour Double # fromAlphaColour :: AlphaColour Double -> AlphaColour a # | |
An existential wrapper for instances of the Color class.
Instances
| Show SomeColor | |
| Color SomeColor | |
Defined in Diagrams.Attributes Methods toAlphaColour :: SomeColor -> AlphaColour Double # | |
Although the individual colors in a diagram can have
transparency, the opacity/transparency of a diagram as a whole
can be specified with the Opacity attribute. The opacity is a
value between 1 (completely opaque, the default) and 0
(completely transparent). Opacity is multiplicative, that is,
. In other
words, for example, opacity o1 . opacity o2 === opacity (o1 * o2)opacity 0.8 means "decrease this diagram's
opacity to 80% of its previous opacity".
data FillOpacity #
Like Opacity, but set the opacity only for fills (as opposed to strokes).
As with Opacity, the fill opacity is a value between 1
(completely opaque, the default) and 0 (completely transparent),
and is multiplicative.
Instances
| Semigroup FillOpacity | |
Defined in Diagrams.Attributes Methods (<>) :: FillOpacity -> FillOpacity -> FillOpacity # sconcat :: NonEmpty FillOpacity -> FillOpacity # stimes :: Integral b => b -> FillOpacity -> FillOpacity # | |
| AttributeClass FillOpacity | |
Defined in Diagrams.Attributes | |
data StrokeOpacity #
Like Opacity, but set the opacity only for strokes (as opposed to fills).
As with Opacity, the fill opacity is a value between 1
(completely opaque, the default) and 0 (completely transparent),
and is multiplicative.
Instances
| Semigroup StrokeOpacity | |
Defined in Diagrams.Attributes Methods (<>) :: StrokeOpacity -> StrokeOpacity -> StrokeOpacity # sconcat :: NonEmpty StrokeOpacity -> StrokeOpacity # stimes :: Integral b => b -> StrokeOpacity -> StrokeOpacity # | |
| AttributeClass StrokeOpacity | |
Defined in Diagrams.Attributes | |
What sort of shape should be placed at the endpoints of lines?
Constructors
| LineCapButt | Lines end precisely at their endpoints. |
| LineCapRound | Lines are capped with semicircles centered on endpoints. |
| LineCapSquare | Lines are capped with a squares centered on endpoints. |
Instances
| Eq LineCap | |
| Ord LineCap | |
| Show LineCap | |
| Semigroup LineCap | Last semigroup structure. |
| Default LineCap | |
Defined in Diagrams.Attributes | |
| AttributeClass LineCap | |
Defined in Diagrams.Attributes | |
How should the join points between line segments be drawn?
Constructors
| LineJoinMiter | Use a "miter" shape (whatever that is). |
| LineJoinRound | Use rounded join points. |
| LineJoinBevel | Use a "bevel" shape (whatever that is). Are these... carpentry terms? |
Instances
| Eq LineJoin | |
| Ord LineJoin | |
Defined in Diagrams.Attributes | |
| Show LineJoin | |
| Semigroup LineJoin | Last semigroup structure. |
| Default LineJoin | |
Defined in Diagrams.Attributes | |
| AttributeClass LineJoin | |
Defined in Diagrams.Attributes | |
newtype LineMiterLimit #
Miter limit attribute affecting the LineJoinMiter joins.
For some backends this value may have additional effects.
Constructors
| LineMiterLimit (Last Double) |
Instances
| Eq LineMiterLimit | |
Defined in Diagrams.Attributes Methods (==) :: LineMiterLimit -> LineMiterLimit -> Bool # (/=) :: LineMiterLimit -> LineMiterLimit -> Bool # | |
| Ord LineMiterLimit | |
Defined in Diagrams.Attributes Methods compare :: LineMiterLimit -> LineMiterLimit -> Ordering # (<) :: LineMiterLimit -> LineMiterLimit -> Bool # (<=) :: LineMiterLimit -> LineMiterLimit -> Bool # (>) :: LineMiterLimit -> LineMiterLimit -> Bool # (>=) :: LineMiterLimit -> LineMiterLimit -> Bool # max :: LineMiterLimit -> LineMiterLimit -> LineMiterLimit # min :: LineMiterLimit -> LineMiterLimit -> LineMiterLimit # | |
| Semigroup LineMiterLimit | |
Defined in Diagrams.Attributes Methods (<>) :: LineMiterLimit -> LineMiterLimit -> LineMiterLimit # sconcat :: NonEmpty LineMiterLimit -> LineMiterLimit # stimes :: Integral b => b -> LineMiterLimit -> LineMiterLimit # | |
| Default LineMiterLimit | |
Defined in Diagrams.Attributes Methods def :: LineMiterLimit # | |
| AttributeClass LineMiterLimit | |
Defined in Diagrams.Attributes | |
project :: (Metric v, Fractional a) => v a -> v a -> v a #
project u v computes the projection of v onto u.
class R1 (t :: Type -> Type) where #
A space that has at least 1 basis vector _x.
class R1 t => R2 (t :: Type -> Type) where #
Minimal complete definition
Methods
>>>V2 1 2 ^._y2
>>>V2 1 2 & _y .~ 3V2 1 3
A 2-dimensional vector
>>>pure 1 :: V2 IntV2 1 1
>>>V2 1 2 + V2 3 4V2 4 6
>>>V2 1 2 * V2 3 4V2 3 8
>>>sum (V2 1 2)3
Constructors
| V2 !a !a |
Instances
perp :: Num a => V2 a -> V2 a #
the counter-clockwise perpendicular vector
>>>perp $ V2 10 20V2 (-20) 10
A 3-dimensional vector
Constructors
| V3 !a !a !a |
Instances
class Profunctor p => Choice (p :: Type -> Type -> Type) where #
The generalization of Costar of Functor that is strong with respect
to Either.
Note: This is also a notion of strength, except with regards to another monoidal structure that we can choose to equip Hask with: the cocartesian coproduct.
Methods
left' :: p a b -> p (Either a c) (Either b c) #
Laws:
left'≡dimapswapE swapE.right'where swapE ::Eithera b ->Eitherb a swapE =eitherRightLeftrmapLeft≡lmapLeft.left'lmap(rightf).left'≡rmap(rightf).left'left'.left'≡dimapassocE unassocE.left'where assocE ::Either(Eithera b) c ->Eithera (Eitherb c) assocE (Left(Lefta)) =Lefta assocE (Left(Rightb)) =Right(Leftb) assocE (Rightc) =Right(Rightc) unassocE ::Eithera (Eitherb c) ->Either(Eithera b) c unassocE (Lefta) =Left(Lefta) unassocE (Right(Leftb) =Left(Rightb) unassocE (Right(Rightc)) =Rightc)
right' :: p a b -> p (Either c a) (Either c b) #
Laws:
right'≡dimapswapE swapE.left'where swapE ::Eithera b ->Eitherb a swapE =eitherRightLeftrmapRight≡lmapRight.right'lmap(leftf).right'≡rmap(leftf).right'right'.right'≡dimapunassocE assocE.right'where assocE ::Either(Eithera b) c ->Eithera (Eitherb c) assocE (Left(Lefta)) =Lefta assocE (Left(Rightb)) =Right(Leftb) assocE (Rightc) =Right(Rightc) unassocE ::Eithera (Eitherb c) ->Either(Eithera b) c unassocE (Lefta) =Left(Lefta) unassocE (Right(Leftb) =Left(Rightb) unassocE (Right(Rightc)) =Rightc)
Instances
sequenceBy :: Traversable t => (forall x. x -> f x) -> (forall x y. f (x -> y) -> f x -> f y) -> t (f a) -> f (t a) #
Sequence a container using its Traversable instance using
explicitly provided Applicative operations. This is like sequence
where the Applicative instance can be manually specified.
traverseBy :: Traversable t => (forall x. x -> f x) -> (forall x y. f (x -> y) -> f x -> f y) -> (a -> f b) -> t a -> f (t b) #
Traverse a container using its Traversable instance using
explicitly provided Applicative operations. This is like traverse
where the Applicative instance can be manually specified.
class (Foldable1 t, Traversable t) => Traversable1 (t :: Type -> Type) where #
Instances
data Sequenced a (m :: Type -> Type) #
Used internally by mapM_ and the like.
The argument a of the result should not be used!
See 4.16 Changelog entry for the explanation of "why not Apply f =>"?
data Traversed a (f :: Type -> Type) #
Used internally by traverseOf_ and the like.
The argument a of the result should not be used!
Instances
| Applicative f => Semigroup (Traversed a f) | |
| Applicative f => Monoid (Traversed a f) | |
A function with access to a index. This constructor may be useful when you need to store
an Indexable in a container to avoid ImpredicativeTypes.
index :: Indexed i a b -> i -> a -> b
Constructors
| Indexed | |
Fields
| |
Instances
class Conjoined p => Indexable i (p :: Type -> Type -> Type) #
This class permits overloading of function application for things that also admit a notion of a key or index.
Minimal complete definition
class (Choice p, Corepresentable p, Comonad (Corep p), Traversable (Corep p), Strong p, Representable p, Monad (Rep p), MonadFix (Rep p), Distributive (Rep p), Costrong p, ArrowLoop p, ArrowApply p, ArrowChoice p, Closed p) => Conjoined (p :: Type -> Type -> Type) where #
This is a Profunctor that is both Corepresentable by f and Representable by g such
that f is left adjoint to g. From this you can derive a lot of structure due
to the preservation of limits and colimits.
Minimal complete definition
Nothing
Methods
distrib :: Functor f => p a b -> p (f a) (f b) #
Conjoined is strong enough to let us distribute every Conjoined
Profunctor over every Haskell Functor. This is effectively a
generalization of fmap.
conjoined :: ((p ~ ((->) :: Type -> Type -> Type)) -> q (a -> b) r) -> q (p a b) r -> q (p a b) r #
This permits us to make a decision at an outermost point about whether or not we use an index.
Ideally any use of this function should be done in such a way so that you compute the same answer, but this cannot be enforced at the type level.
Instances
| Conjoined ReifiedGetter | |
Defined in Control.Lens.Reified Methods distrib :: Functor f => ReifiedGetter a b -> ReifiedGetter (f a) (f b) # conjoined :: ((ReifiedGetter ~ (->)) -> q (a -> b) r) -> q (ReifiedGetter a b) r -> q (ReifiedGetter a b) r # | |
| Conjoined (Indexed i) | |
| Conjoined ((->) :: Type -> Type -> Type) | |
indexing :: Indexable Int p => ((a -> Indexing f b) -> s -> Indexing f t) -> p a (f b) -> s -> f t #
Transform a Traversal into an IndexedTraversal or
a Fold into an IndexedFold, etc.
indexing::Traversals t a b ->IndexedTraversalInts t a bindexing::Prisms t a b ->IndexedTraversalInts t a bindexing::Lenss t a b ->IndexedLensInts t a bindexing::Isos t a b ->IndexedLensInts t a bindexing::Folds a ->IndexedFoldInts aindexing::Getters a ->IndexedGetterInts a
indexing::IndexableIntp =>LensLike(Indexingf) s t a b ->Overp f s t a b
indexing64 :: Indexable Int64 p => ((a -> Indexing64 f b) -> s -> Indexing64 f t) -> p a (f b) -> s -> f t #
Transform a Traversal into an IndexedTraversal or
a Fold into an IndexedFold, etc.
This combinator is like indexing except that it handles large traversals and folds gracefully.
indexing64::Traversals t a b ->IndexedTraversalInt64s t a bindexing64::Prisms t a b ->IndexedTraversalInt64s t a bindexing64::Lenss t a b ->IndexedLensInt64s t a bindexing64::Isos t a b ->IndexedLensInt64s t a bindexing64::Folds a ->IndexedFoldInt64s aindexing64::Getters a ->IndexedGetterInt64s a
indexing64::IndexableInt64p =>LensLike(Indexing64f) s t a b ->Overp f s t a b
withIndex :: (Indexable i p, Functor f) => p (i, s) (f (j, t)) -> Indexed i s (f t) #
Fold a container with indices returning both the indices and the values.
The result is only valid to compose in a Traversal, if you don't edit the
index as edits to the index have no effect.
>>>[10, 20, 30] ^.. ifolded . withIndex[(0,10),(1,20),(2,30)]
>>>[10, 20, 30] ^.. ifolded . withIndex . alongside negated (re _Show)[(0,"10"),(-1,"20"),(-2,"30")]
asIndex :: (Indexable i p, Contravariant f, Functor f) => p i (f i) -> Indexed i s (f s) #
When composed with an IndexedFold or IndexedTraversal this yields an
(Indexed) Fold of the indices.
The indexed store can be used to characterize a Lens
and is used by cloneLens.
is isomorphic to
Context a b tnewtype ,
and to Context a b t = Context { runContext :: forall f. Functor f => (a -> f b) -> f t }exists s. (s, .Lens s t a b)
A Context is like a Lens that has already been applied to a some structure.
Constructors
| Context (b -> t) a |
Instances
| IndexedFunctor Context | |
Defined in Control.Lens.Internal.Context | |
| IndexedComonad Context | |
| IndexedComonadStore Context | |
| a ~ b => ComonadStore a (Context a b) | |
Defined in Control.Lens.Internal.Context | |
| Functor (Context a b) | |
| a ~ b => Comonad (Context a b) | |
| Sellable ((->) :: Type -> Type -> Type) Context | |
Defined in Control.Lens.Internal.Context | |
newtype Bazaar1 (p :: Type -> Type -> Type) a b t #
This is used to characterize a Traversal.
a.k.a. indexed Cartesian store comonad, indexed Kleene store comonad, or an indexed FunList.
http://twanvl.nl/blog/haskell/non-regular1
A Bazaar1 is like a Traversal that has already been applied to some structure.
Where a holds an Context a b ta and a function from b to
t, a holds Bazaar1 a b tN as and a function from N
bs to t, (where N might be infinite).
Mnemonically, a Bazaar1 holds many stores and you can easily add more.
This is a final encoding of Bazaar1.
Constructors
| Bazaar1 | |
Fields
| |
Instances
| Profunctor p => Bizarre1 p (Bazaar1 p) | |
Defined in Control.Lens.Internal.Bazaar | |
| Corepresentable p => Sellable p (Bazaar1 p) | |
Defined in Control.Lens.Internal.Bazaar | |
| IndexedFunctor (Bazaar1 p) | |
Defined in Control.Lens.Internal.Bazaar | |
| Conjoined p => IndexedComonad (Bazaar1 p) | |
| Functor (Bazaar1 p a b) | |
| Apply (Bazaar1 p a b) | |
Defined in Control.Lens.Internal.Bazaar Methods (<.>) :: Bazaar1 p a b (a0 -> b0) -> Bazaar1 p a b a0 -> Bazaar1 p a b b0 # (.>) :: Bazaar1 p a b a0 -> Bazaar1 p a b b0 -> Bazaar1 p a b b0 # (<.) :: Bazaar1 p a b a0 -> Bazaar1 p a b b0 -> Bazaar1 p a b a0 # liftF2 :: (a0 -> b0 -> c) -> Bazaar1 p a b a0 -> Bazaar1 p a b b0 -> Bazaar1 p a b c # | |
| (a ~ b, Conjoined p) => Comonad (Bazaar1 p a b) | |
| (a ~ b, Conjoined p) => ComonadApply (Bazaar1 p a b) | |
newtype Bazaar (p :: Type -> Type -> Type) a b t #
This is used to characterize a Traversal.
a.k.a. indexed Cartesian store comonad, indexed Kleene store comonad, or an indexed FunList.
http://twanvl.nl/blog/haskell/non-regular1
A Bazaar is like a Traversal that has already been applied to some structure.
Where a holds an Context a b ta and a function from b to
t, a holds Bazaar a b tN as and a function from N
bs to t, (where N might be infinite).
Mnemonically, a Bazaar holds many stores and you can easily add more.
This is a final encoding of Bazaar.
Constructors
| Bazaar | |
Fields
| |
Instances
| Profunctor p => Bizarre p (Bazaar p) | |
Defined in Control.Lens.Internal.Bazaar Methods bazaar :: Applicative f => p a (f b) -> Bazaar p a b t -> f t # | |
| Corepresentable p => Sellable p (Bazaar p) | |
Defined in Control.Lens.Internal.Bazaar | |
| IndexedFunctor (Bazaar p) | |
Defined in Control.Lens.Internal.Bazaar | |
| Conjoined p => IndexedComonad (Bazaar p) | |
| Functor (Bazaar p a b) | |
| Applicative (Bazaar p a b) | |
Defined in Control.Lens.Internal.Bazaar Methods pure :: a0 -> Bazaar p a b a0 # (<*>) :: Bazaar p a b (a0 -> b0) -> Bazaar p a b a0 -> Bazaar p a b b0 # liftA2 :: (a0 -> b0 -> c) -> Bazaar p a b a0 -> Bazaar p a b b0 -> Bazaar p a b c # (*>) :: Bazaar p a b a0 -> Bazaar p a b b0 -> Bazaar p a b b0 # (<*) :: Bazaar p a b a0 -> Bazaar p a b b0 -> Bazaar p a b a0 # | |
| Apply (Bazaar p a b) | |
Defined in Control.Lens.Internal.Bazaar | |
| (a ~ b, Conjoined p) => Comonad (Bazaar p a b) | |
| (a ~ b, Conjoined p) => ComonadApply (Bazaar p a b) | |
This class provides a generalized notion of list reversal extended to other containers.
Instances
This data type represents a path-compressed copy of one level of a source data structure. We can safely use path-compression because we know the depth of the tree.
Path compression is performed by viewing a Level as a PATRICIA trie of the
paths into the structure to leaves at a given depth, similar in many ways
to a IntMap, but unlike a regular PATRICIA trie we do not need
to store the mask bits merely the depth of the fork.
One invariant of this structure is that underneath a Two node you will not
find any Zero nodes, so Zero can only occur at the root.
Instances
| TraversableWithIndex i (Level i) | |
Defined in Control.Lens.Indexed Methods itraverse :: Applicative f => (i -> a -> f b) -> Level i a -> f (Level i b) # itraversed :: IndexedTraversal i (Level i a) (Level i b) a b # | |
| FoldableWithIndex i (Level i) | |
| FunctorWithIndex i (Level i) | |
Defined in Control.Lens.Indexed | |
| Functor (Level i) | |
| Foldable (Level i) | |
Defined in Control.Lens.Internal.Level Methods fold :: Monoid m => Level i m -> m # foldMap :: Monoid m => (a -> m) -> Level i a -> m # foldr :: (a -> b -> b) -> b -> Level i a -> b # foldr' :: (a -> b -> b) -> b -> Level i a -> b # foldl :: (b -> a -> b) -> b -> Level i a -> b # foldl' :: (b -> a -> b) -> b -> Level i a -> b # foldr1 :: (a -> a -> a) -> Level i a -> a # foldl1 :: (a -> a -> a) -> Level i a -> a # elem :: Eq a => a -> Level i a -> Bool # maximum :: Ord a => Level i a -> a # minimum :: Ord a => Level i a -> a # | |
| Traversable (Level i) | |
| (Eq i, Eq a) => Eq (Level i a) | |
| (Ord i, Ord a) => Ord (Level i a) | |
| (Read i, Read a) => Read (Level i a) | |
| (Show i, Show a) => Show (Level i a) | |
This provides a way to peek at the internal structure of a
Traversal or IndexedTraversal
Instances
| TraversableWithIndex i (Magma i t b) | |
Defined in Control.Lens.Indexed Methods itraverse :: Applicative f => (i -> a -> f b0) -> Magma i t b a -> f (Magma i t b b0) # itraversed :: IndexedTraversal i (Magma i t b a) (Magma i t b b0) a b0 # | |
| FoldableWithIndex i (Magma i t b) | |
Defined in Control.Lens.Indexed Methods ifoldMap :: Monoid m => (i -> a -> m) -> Magma i t b a -> m # ifolded :: IndexedFold i (Magma i t b a) a # ifoldr :: (i -> a -> b0 -> b0) -> b0 -> Magma i t b a -> b0 # ifoldl :: (i -> b0 -> a -> b0) -> b0 -> Magma i t b a -> b0 # ifoldr' :: (i -> a -> b0 -> b0) -> b0 -> Magma i t b a -> b0 # ifoldl' :: (i -> b0 -> a -> b0) -> b0 -> Magma i t b a -> b0 # | |
| FunctorWithIndex i (Magma i t b) | |
Defined in Control.Lens.Indexed | |
| Functor (Magma i t b) | |
| Foldable (Magma i t b) | |
Defined in Control.Lens.Internal.Magma Methods fold :: Monoid m => Magma i t b m -> m # foldMap :: Monoid m => (a -> m) -> Magma i t b a -> m # foldr :: (a -> b0 -> b0) -> b0 -> Magma i t b a -> b0 # foldr' :: (a -> b0 -> b0) -> b0 -> Magma i t b a -> b0 # foldl :: (b0 -> a -> b0) -> b0 -> Magma i t b a -> b0 # foldl' :: (b0 -> a -> b0) -> b0 -> Magma i t b a -> b0 # foldr1 :: (a -> a -> a) -> Magma i t b a -> a # foldl1 :: (a -> a -> a) -> Magma i t b a -> a # toList :: Magma i t b a -> [a] # null :: Magma i t b a -> Bool # length :: Magma i t b a -> Int # elem :: Eq a => a -> Magma i t b a -> Bool # maximum :: Ord a => Magma i t b a -> a # minimum :: Ord a => Magma i t b a -> a # | |
| Traversable (Magma i t b) | |
Defined in Control.Lens.Internal.Magma | |
| (Show i, Show a) => Show (Magma i t b a) | |
class (Profunctor p, Bifunctor p) => Reviewable (p :: Type -> Type -> Type) #
This class is provided mostly for backwards compatibility with lens 3.8, but it can also shorten type signatures.
Instances
| (Profunctor p, Bifunctor p) => Reviewable p | |
Defined in Control.Lens.Internal.Review | |
retagged :: (Profunctor p, Bifunctor p) => p a b -> p s b #
This is a profunctor used internally to implement Review
It plays a role similar to that of Accessor
or Const do for Control.Lens.Getter
class (Applicative f, Distributive f, Traversable f) => Settable (f :: Type -> Type) #
Minimal complete definition
Instances
| Settable Identity | So you can pass our |
Defined in Control.Lens.Internal.Setter Methods untainted :: Identity a -> a # untaintedDot :: Profunctor p => p a (Identity b) -> p a b # taintedDot :: Profunctor p => p a b -> p a (Identity b) # | |
| Settable f => Settable (Backwards f) | |
Defined in Control.Lens.Internal.Setter Methods untainted :: Backwards f a -> a # untaintedDot :: Profunctor p => p a (Backwards f b) -> p a b # taintedDot :: Profunctor p => p a b -> p a (Backwards f b) # | |
| (Settable f, Settable g) => Settable (Compose f g) | |
Defined in Control.Lens.Internal.Setter Methods untainted :: Compose f g a -> a # untaintedDot :: Profunctor p => p a (Compose f g b) -> p a b # taintedDot :: Profunctor p => p a b -> p a (Compose f g b) # | |
type Over (p :: k -> Type -> Type) (f :: k1 -> Type) s (t :: k1) (a :: k) (b :: k1) = p a (f b) -> s -> f t #
This is a convenient alias for use when you need to consume either indexed or non-indexed lens-likes based on context.
type IndexedLensLike' i (f :: Type -> Type) s a = IndexedLensLike i f s s a a #
Convenient alias for constructing simple indexed lenses and their ilk.
type IndexedLensLike i (f :: k -> Type) s (t :: k) a (b :: k) = forall (p :: Type -> Type -> Type). Indexable i p => p a (f b) -> s -> f t #
Convenient alias for constructing indexed lenses and their ilk.
type LensLike (f :: k -> Type) s (t :: k) a (b :: k) = (a -> f b) -> s -> f t #
Many combinators that accept a Lens can also accept a
Traversal in limited situations.
They do so by specializing the type of Functor that they require of the
caller.
If a function accepts a for some LensLike f s t a bFunctor f,
then they may be passed a Lens.
Further, if f is an Applicative, they may also be passed a
Traversal.
type Optical' (p :: k1 -> k -> Type) (q :: k1 -> k -> Type) (f :: k1 -> k) (s :: k1) (a :: k1) = Optical p q f s s a a #
type Optical (p :: k2 -> k -> Type) (q :: k1 -> k -> Type) (f :: k3 -> k) (s :: k1) (t :: k3) (a :: k2) (b :: k3) = p a (f b) -> q s (f t) #
type Optic (p :: k1 -> k -> Type) (f :: k2 -> k) (s :: k1) (t :: k2) (a :: k1) (b :: k2) = p a (f b) -> p s (f t) #
A valid Optic l should satisfy the laws:
lpure≡purel (Procomposef g) =Procompose(l f) (l g)
This gives rise to the laws for Equality, Iso, Prism, Lens,
Traversal, Traversal1, Setter, Fold, Fold1, and Getter as well
along with their index-preserving variants.
typeLensLikef s t a b =Optic(->) f s t a b
type Simple (f :: k -> k -> k1 -> k1 -> k2) (s :: k) (a :: k1) = f s s a a #
A Simple Lens, Simple Traversal, ... can
be used instead of a Lens,Traversal, ...
whenever the type variables don't change upon setting a value.
_imagPart::SimpleLens(Complexa) atraversed::Simple(IndexedTraversalInt) [a] a
Note: To use this alias in your own code with or
LensLike fSetter, you may have to turn on LiberalTypeSynonyms.
This is commonly abbreviated as a "prime" marker, e.g. Lens' = Simple Lens.
type IndexPreservingFold1 s a = forall (p :: Type -> Type -> Type) (f :: Type -> Type). (Conjoined p, Contravariant f, Apply f) => p a (f a) -> p s (f s) #
type IndexedFold1 i s a = forall (p :: Type -> Type -> Type) (f :: Type -> Type). (Indexable i p, Contravariant f, Apply f) => p a (f a) -> s -> f s #
type Fold1 s a = forall (f :: Type -> Type). (Contravariant f, Apply f) => (a -> f a) -> s -> f s #
A relevant Fold (aka Fold1) has one or more targets.
type IndexPreservingFold s a = forall (p :: Type -> Type -> Type) (f :: Type -> Type). (Conjoined p, Contravariant f, Applicative f) => p a (f a) -> p s (f s) #
An IndexPreservingFold can be used as a Fold, but when composed with an IndexedTraversal,
IndexedFold, or IndexedLens yields an IndexedFold respectively.
type IndexedFold i s a = forall (p :: Type -> Type -> Type) (f :: Type -> Type). (Indexable i p, Contravariant f, Applicative f) => p a (f a) -> s -> f s #
Every IndexedFold is a valid Fold and can be used for Getting.
type Fold s a = forall (f :: Type -> Type). (Contravariant f, Applicative f) => (a -> f a) -> s -> f s #
A Fold describes how to retrieve multiple values in a way that can be composed
with other LensLike constructions.
A provides a structure with operations very similar to those of the Fold s aFoldable
typeclass, see foldMapOf and the other Fold combinators.
By convention, if there exists a foo method that expects a , then there should be a
Foldable (f a)fooOf method that takes a and a value of type Fold s as.
A Getter is a legal Fold that just ignores the supplied Monoid.
Unlike a Traversal a Fold is read-only. Since a Fold cannot be used to write back
there are no Lens laws that apply.
type IndexPreservingGetter s a = forall (p :: Type -> Type -> Type) (f :: Type -> Type). (Conjoined p, Contravariant f, Functor f) => p a (f a) -> p s (f s) #
An IndexPreservingGetter can be used as a Getter, but when composed with an IndexedTraversal,
IndexedFold, or IndexedLens yields an IndexedFold, IndexedFold or IndexedGetter respectively.
type IndexedGetter i s a = forall (p :: Type -> Type -> Type) (f :: Type -> Type). (Indexable i p, Contravariant f, Functor f) => p a (f a) -> s -> f s #
Every IndexedGetter is a valid IndexedFold and can be used for Getting like a Getter.
type Getter s a = forall (f :: Type -> Type). (Contravariant f, Functor f) => (a -> f a) -> s -> f s #
A Getter describes how to retrieve a single value in a way that can be
composed with other LensLike constructions.
Unlike a Lens a Getter is read-only. Since a Getter
cannot be used to write back there are no Lens laws that can be applied to
it. In fact, it is isomorphic to an arbitrary function from (s -> a).
Moreover, a Getter can be used directly as a Fold,
since it just ignores the Applicative.
type As (a :: k2) = Equality' a a #
Composable asTypeOf. Useful for constraining excess
polymorphism, foo . (id :: As Int) . bar.
type Equality (s :: k1) (t :: k2) (a :: k1) (b :: k2) = forall k3 (p :: k1 -> k3 -> Type) (f :: k2 -> k3). p a (f b) -> p s (f t) #
A witness that (a ~ s, b ~ t).
Note: Composition with an Equality is index-preserving.
type Prism s t a b = forall (p :: Type -> Type -> Type) (f :: Type -> Type). (Choice p, Applicative f) => p a (f b) -> p s (f t) #
A Prism l is a Traversal that can also be turned
around with re to obtain a Getter in the
opposite direction.
There are three laws that a Prism should satisfy:
First, if I re or review a value with a Prism and then preview or use (^?), I will get it back:
previewl (reviewl b) ≡Justb
Second, if you can extract a value a using a Prism l from a value s, then the value s is completely described by l and a:
previewl s ≡Justa ⟹reviewl a ≡ s
Third, if you get non-match t, you can convert it result back to s:
matchingl s ≡Leftt ⟹matchingl t ≡Lefts
The first two laws imply that the Traversal laws hold for every Prism and that we traverse at most 1 element:
lengthOfl x<=1
It may help to think of this as a Iso that can be partial in one direction.
Every Prism is a valid Traversal.
For example, you might have a allows you to always
go from a Prism' Integer NaturalNatural to an Integer, and provide you with tools to check if an Integer is
a Natural and/or to edit one if it is.
nat::Prism'IntegerNaturalnat=prismtoInteger$\ i -> if i<0 thenLefti elseRight(fromIntegeri)
Now we can ask if an Integer is a Natural.
>>>5^?natJust 5
>>>(-5)^?natNothing
We can update the ones that are:
>>>(-3,4) & both.nat *~ 2(-3,8)
And we can then convert from a Natural to an Integer.
>>>5 ^. re nat -- :: Natural5
Similarly we can use a Prism to traverse the Left half of an Either:
>>>Left "hello" & _Left %~ lengthLeft 5
or to construct an Either:
>>>5^.re _LeftLeft 5
such that if you query it with the Prism, you will get your original input back.
>>>5^.re _Left ^? _LeftJust 5
Another interesting way to think of a Prism is as the categorical dual of a Lens
-- a co-Lens, so to speak. This is what permits the construction of outside.
Note: Composition with a Prism is index-preserving.
type Review t b = forall (p :: Type -> Type -> Type) (f :: Type -> Type). (Choice p, Bifunctor p, Settable f) => Optic' p f t b #
type Iso s t a b = forall (p :: Type -> Type -> Type) (f :: Type -> Type). (Profunctor p, Functor f) => p a (f b) -> p s (f t) #
type IndexPreservingSetter' s a = IndexPreservingSetter s s a a #
typeIndexedPreservingSetter'i =SimpleIndexedPreservingSetter
type IndexPreservingSetter s t a b = forall (p :: Type -> Type -> Type) (f :: Type -> Type). (Conjoined p, Settable f) => p a (f b) -> p s (f t) #
An IndexPreservingSetter can be composed with a IndexedSetter, IndexedTraversal or IndexedLens
and leaves the index intact, yielding an IndexedSetter.
type IndexedSetter' i s a = IndexedSetter i s s a a #
typeIndexedSetter'i =Simple(IndexedSetteri)
type IndexedSetter i s t a b = forall (f :: Type -> Type) (p :: Type -> Type -> Type). (Indexable i p, Settable f) => p a (f b) -> s -> f t #
Every IndexedSetter is a valid Setter.
The Setter laws are still required to hold.
type Setter s t a b = forall (f :: Type -> Type). Settable f => (a -> f b) -> s -> f t #
The only LensLike law that can apply to a Setter l is that
setl y (setl x a) ≡setl y a
You can't view a Setter in general, so the other two laws are irrelevant.
However, two Functor laws apply to a Setter:
overlid≡idoverl f.overl g ≡overl (f.g)
These can be stated more directly:
lpure≡purel f.untainted.l g ≡ l (f.untainted.g)
You can compose a Setter with a Lens or a Traversal using (.) from the Prelude
and the result is always only a Setter and nothing more.
>>>over traverse f [a,b,c,d][f a,f b,f c,f d]
>>>over _1 f (a,b)(f a,b)
>>>over (traverse._1) f [(a,b),(c,d)][(f a,b),(f c,d)]
>>>over both f (a,b)(f a,f b)
>>>over (traverse.both) f [(a,b),(c,d)][(f a,f b),(f c,f d)]
type IndexPreservingTraversal1' s a = IndexPreservingTraversal1 s s a a #
type IndexPreservingTraversal1 s t a b = forall (p :: Type -> Type -> Type) (f :: Type -> Type). (Conjoined p, Apply f) => p a (f b) -> p s (f t) #
type IndexPreservingTraversal' s a = IndexPreservingTraversal s s a a #
type IndexPreservingTraversal s t a b = forall (p :: Type -> Type -> Type) (f :: Type -> Type). (Conjoined p, Applicative f) => p a (f b) -> p s (f t) #
An IndexPreservingLens leaves any index it is composed with alone.
type IndexedTraversal1' i s a = IndexedTraversal1 i s s a a #
type IndexedTraversal1 i s t a b = forall (p :: Type -> Type -> Type) (f :: Type -> Type). (Indexable i p, Apply f) => p a (f b) -> s -> f t #
type IndexedTraversal' i s a = IndexedTraversal i s s a a #
typeIndexedTraversal'i =Simple(IndexedTraversali)
type IndexedTraversal i s t a b = forall (p :: Type -> Type -> Type) (f :: Type -> Type). (Indexable i p, Applicative f) => p a (f b) -> s -> f t #
Every IndexedTraversal is a valid Traversal or
IndexedFold.
The Indexed constraint is used to allow an IndexedTraversal to be used
directly as a Traversal.
The Traversal laws are still required to hold.
In addition, the index i should satisfy the requirement that it stays
unchanged even when modifying the value a, otherwise traversals like
indices break the Traversal laws.
type Traversal1' s a = Traversal1 s s a a #
type Traversal1 s t a b = forall (f :: Type -> Type). Apply f => (a -> f b) -> s -> f t #
type Traversal' s a = Traversal s s a a #
typeTraversal'=SimpleTraversal
type Traversal s t a b = forall (f :: Type -> Type). Applicative f => (a -> f b) -> s -> f t #
A Traversal can be used directly as a Setter or a Fold (but not as a Lens) and provides
the ability to both read and update multiple fields, subject to some relatively weak Traversal laws.
These have also been known as multilenses, but they have the signature and spirit of
traverse::Traversablef =>Traversal(f a) (f b) a b
and the more evocative name suggests their application.
Most of the time the Traversal you will want to use is just traverse, but you can also pass any
Lens or Iso as a Traversal, and composition of a Traversal (or Lens or Iso) with a Traversal (or Lens or Iso)
using (.) forms a valid Traversal.
The laws for a Traversal t follow from the laws for Traversable as stated in "The Essence of the Iterator Pattern".
tpure≡purefmap(t f).t g ≡getCompose.t (Compose.fmapf.g)
One consequence of this requirement is that a Traversal needs to leave the same number of elements as a
candidate for subsequent Traversal that it started with. Another testament to the strength of these laws
is that the caveat expressed in section 5.5 of the "Essence of the Iterator Pattern" about exotic
Traversable instances that traverse the same entry multiple times was actually already ruled out by the
second law in that same paper!
type IndexPreservingLens' s a = IndexPreservingLens s s a a #
type IndexPreservingLens s t a b = forall (p :: Type -> Type -> Type) (f :: Type -> Type). (Conjoined p, Functor f) => p a (f b) -> p s (f t) #
An IndexPreservingLens leaves any index it is composed with alone.
type IndexedLens' i s a = IndexedLens i s s a a #
typeIndexedLens'i =Simple(IndexedLensi)
type IndexedLens i s t a b = forall (f :: Type -> Type) (p :: Type -> Type -> Type). (Indexable i p, Functor f) => p a (f b) -> s -> f t #
Every IndexedLens is a valid Lens and a valid IndexedTraversal.
type Lens s t a b = forall (f :: Type -> Type). Functor f => (a -> f b) -> s -> f t #
A Lens is actually a lens family as described in
http://comonad.com/reader/2012/mirrored-lenses/.
With great power comes great responsibility and a Lens is subject to the
three common sense Lens laws:
1) You get back what you put in:
viewl (setl v s) ≡ v
2) Putting back what you got doesn't change anything:
setl (viewl s) s ≡ s
3) Setting twice is the same as setting once:
setl v' (setl v s) ≡setl v' s
These laws are strong enough that the 4 type parameters of a Lens cannot
vary fully independently. For more on how they interact, read the "Why is
it a Lens Family?" section of
http://comonad.com/reader/2012/mirrored-lenses/.
There are some emergent properties of these laws:
1) must be injective for every set l ss This is a consequence of law #1
2) must be surjective, because of law #2, which indicates that it is possible to obtain any set lv from some s such that set s v = s
3) Given just the first two laws you can prove a weaker form of law #3 where the values v that you are setting match:
setl v (setl v s) ≡setl v s
Every Lens can be used directly as a Setter or Traversal.
You can also use a Lens for Getting as if it were a
Fold or Getter.
Since every Lens is a valid Traversal, the
Traversal laws are required of any Lens you create:
lpure≡purefmap(l f).l g ≡getCompose.l (Compose.fmapf.g)
typeLenss t a b = forall f.Functorf =>LensLikef s t a b
type Setting' (p :: Type -> Type -> Type) s a = Setting p s s a a #
This is a convenient alias when defining highly polymorphic code that takes both
ASetter' and AnIndexedSetter' as appropriate. If a function takes this it is
expecting one of those two things based on context.
type Setting (p :: Type -> Type -> Type) s t a b = p a (Identity b) -> s -> Identity t #
This is a convenient alias when defining highly polymorphic code that takes both
ASetter and AnIndexedSetter as appropriate. If a function takes this it is
expecting one of those two things based on context.
type AnIndexedSetter' i s a = AnIndexedSetter i s s a a #
typeAnIndexedSetter'i =Simple(AnIndexedSetteri)
type AnIndexedSetter i s t a b = Indexed i a (Identity b) -> s -> Identity t #
Running an IndexedSetter instantiates it to a concrete type.
When consuming a setter directly to perform a mapping, you can use this type, but most user code will not need to use this type.
type ASetter s t a b = (a -> Identity b) -> s -> Identity t #
Running a Setter instantiates it to a concrete type.
When consuming a setter directly to perform a mapping, you can use this type, but most user code will not need to use this type.
mapped :: Functor f => Setter (f a) (f b) a b #
This Setter can be used to map over all of the values in a Functor.
fmap≡overmappedfmapDefault≡overtraverse(<$) ≡setmapped
>>>over mapped f [a,b,c][f a,f b,f c]
>>>over mapped (+1) [1,2,3][2,3,4]
>>>set mapped x [a,b,c][x,x,x]
>>>[[a,b],[c]] & mapped.mapped +~ x[[a + x,b + x],[c + x]]
>>>over (mapped._2) length [("hello","world"),("leaders","!!!")][("hello",5),("leaders",3)]
mapped::Functorf =>Setter(f a) (f b) a b
If you want an IndexPreservingSetter use .setting fmap
lifted :: Monad m => Setter (m a) (m b) a b #
This setter can be used to modify all of the values in a Monad.
You sometimes have to use this rather than mapped -- due to
temporary insanity Functor was not a superclass of Monad until
GHC 7.10.
liftM≡overlifted
>>>over lifted f [a,b,c][f a,f b,f c]
>>>set lifted b (Just a)Just b
If you want an IndexPreservingSetter use .setting liftM
contramapped :: Contravariant f => Setter (f b) (f a) a b #
This Setter can be used to map over all of the inputs to a Contravariant.
contramap≡overcontramapped
>>>getPredicate (over contramapped (*2) (Predicate even)) 5True
>>>getOp (over contramapped (*5) (Op show)) 100"500"
>>>Prelude.map ($ 1) $ over (mapped . _Unwrapping' Op . contramapped) (*12) [(*2),(+1),(^3)][24,13,1728]
setting :: ((a -> b) -> s -> t) -> IndexPreservingSetter s t a b #
Build an index-preserving Setter from a map-like function.
Your supplied function f is required to satisfy:
fid≡idf g.f h ≡ f (g.h)
Equational reasoning:
setting.over≡idover.setting≡id
Another way to view sets is that it takes a "semantic editor combinator"
and transforms it into a Setter.
setting:: ((a -> b) -> s -> t) ->Setters t a b
sets :: (Profunctor p, Profunctor q, Settable f) => (p a b -> q s t) -> Optical p q f s t a b #
Build a Setter, IndexedSetter or IndexPreservingSetter depending on your choice of Profunctor.
sets:: ((a -> b) -> s -> t) ->Setters t a b
cloneIndexPreservingSetter :: ASetter s t a b -> IndexPreservingSetter s t a b #
Build an IndexPreservingSetter from any Setter.
cloneIndexedSetter :: AnIndexedSetter i s t a b -> IndexedSetter i s t a b #
Clone an IndexedSetter.
over :: ASetter s t a b -> (a -> b) -> s -> t #
Modify the target of a Lens or all the targets of a Setter or Traversal
with a function.
fmap≡overmappedfmapDefault≡overtraversesets.over≡idover.sets≡id
Given any valid Setter l, you can also rely on the law:
overl f.overl g =overl (f.g)
e.g.
>>>over mapped f (over mapped g [a,b,c]) == over mapped (f . g) [a,b,c]True
Another way to view over is to say that it transforms a Setter into a
"semantic editor combinator".
>>>over mapped f (Just a)Just (f a)
>>>over mapped (*10) [1,2,3][10,20,30]
>>>over _1 f (a,b)(f a,b)
>>>over _1 show (10,20)("10",20)
over::Setters t a b -> (a -> b) -> s -> tover::ASetters t a b -> (a -> b) -> s -> t
set :: ASetter s t a b -> b -> s -> t #
Replace the target of a Lens or all of the targets of a Setter
or Traversal with a constant value.
(<$) ≡setmapped
>>>set _2 "hello" (1,())(1,"hello")
>>>set mapped () [1,2,3,4][(),(),(),()]
Note: Attempting to set a Fold or Getter will fail at compile time with an
relatively nice error message.
set::Setters t a b -> b -> s -> tset::Isos t a b -> b -> s -> tset::Lenss t a b -> b -> s -> tset::Traversals t a b -> b -> s -> t
set' :: ASetter' s a -> a -> s -> s #
Replace the target of a Lens or all of the targets of a Setter'
or Traversal with a constant value, without changing its type.
This is a type restricted version of set, which retains the type of the original.
>>>set' mapped x [a,b,c,d][x,x,x,x]
>>>set' _2 "hello" (1,"world")(1,"hello")
>>>set' mapped 0 [1,2,3,4][0,0,0,0]
Note: Attempting to adjust set' a Fold or Getter will fail at compile time with an
relatively nice error message.
set'::Setter's a -> a -> s -> sset'::Iso's a -> a -> s -> sset'::Lens's a -> a -> s -> sset'::Traversal's a -> a -> s -> s
(%~) :: ASetter s t a b -> (a -> b) -> s -> t infixr 4 #
Modifies the target of a Lens or all of the targets of a Setter or
Traversal with a user supplied function.
This is an infix version of over.
fmapf ≡mapped%~ffmapDefaultf ≡traverse%~f
>>>(a,b,c) & _3 %~ f(a,b,f c)
>>>(a,b) & both %~ f(f a,f b)
>>>_2 %~ length $ (1,"hello")(1,5)
>>>traverse %~ f $ [a,b,c][f a,f b,f c]
>>>traverse %~ even $ [1,2,3][False,True,False]
>>>traverse.traverse %~ length $ [["hello","world"],["!!!"]][[5,5],[3]]
(%~) ::Setters t a b -> (a -> b) -> s -> t (%~) ::Isos t a b -> (a -> b) -> s -> t (%~) ::Lenss t a b -> (a -> b) -> s -> t (%~) ::Traversals t a b -> (a -> b) -> s -> t
(.~) :: ASetter s t a b -> b -> s -> t infixr 4 #
Replace the target of a Lens or all of the targets of a Setter
or Traversal with a constant value.
This is an infix version of set, provided for consistency with (.=).
f<$a ≡mapped.~f$a
>>>(a,b,c,d) & _4 .~ e(a,b,c,e)
>>>(42,"world") & _1 .~ "hello"("hello","world")
>>>(a,b) & both .~ c(c,c)
(.~) ::Setters t a b -> b -> s -> t (.~) ::Isos t a b -> b -> s -> t (.~) ::Lenss t a b -> b -> s -> t (.~) ::Traversals t a b -> b -> s -> t
(?~) :: ASetter s t a (Maybe b) -> b -> s -> t infixr 4 #
Set the target of a Lens, Traversal or Setter to Just a value.
l?~t ≡setl (Justt)
>>>Nothing & id ?~ aJust a
>>>Map.empty & at 3 ?~ xfromList [(3,x)]
?~ can be used type-changily:
>>>('a', ('b', 'c')) & _2.both ?~ 'x'('a',(Just 'x',Just 'x'))
(?~) ::Setters t a (Maybeb) -> b -> s -> t (?~) ::Isos t a (Maybeb) -> b -> s -> t (?~) ::Lenss t a (Maybeb) -> b -> s -> t (?~) ::Traversals t a (Maybeb) -> b -> s -> t
(<.~) :: ASetter s t a b -> b -> s -> (b, t) infixr 4 #
Set with pass-through.
This is mostly present for consistency, but may be useful for chaining assignments.
If you do not need a copy of the intermediate result, then using l directly is a good idea..~ t
>>>(a,b) & _1 <.~ c(c,(c,b))
>>>("good","morning","vietnam") & _3 <.~ "world"("world",("good","morning","world"))
>>>(42,Map.fromList [("goodnight","gracie")]) & _2.at "hello" <.~ Just "world"(Just "world",(42,fromList [("goodnight","gracie"),("hello","world")]))
(<.~) ::Setters t a b -> b -> s -> (b, t) (<.~) ::Isos t a b -> b -> s -> (b, t) (<.~) ::Lenss t a b -> b -> s -> (b, t) (<.~) ::Traversals t a b -> b -> s -> (b, t)
(<?~) :: ASetter s t a (Maybe b) -> b -> s -> (b, t) infixr 4 #
Set to Just a value with pass-through.
This is mostly present for consistency, but may be useful for for chaining assignments.
If you do not need a copy of the intermediate result, then using l directly is a good idea.?~ d
>>>import Data.Map as Map>>>_2.at "hello" <?~ "world" $ (42,Map.fromList [("goodnight","gracie")])("world",(42,fromList [("goodnight","gracie"),("hello","world")]))
(<?~) ::Setters t a (Maybeb) -> b -> s -> (b, t) (<?~) ::Isos t a (Maybeb) -> b -> s -> (b, t) (<?~) ::Lenss t a (Maybeb) -> b -> s -> (b, t) (<?~) ::Traversals t a (Maybeb) -> b -> s -> (b, t)
(+~) :: Num a => ASetter s t a a -> a -> s -> t infixr 4 #
Increment the target(s) of a numerically valued Lens, Setter or Traversal.
>>>(a,b) & _1 +~ c(a + c,b)
>>>(a,b) & both +~ c(a + c,b + c)
>>>(1,2) & _2 +~ 1(1,3)
>>>[(a,b),(c,d)] & traverse.both +~ e[(a + e,b + e),(c + e,d + e)]
(+~) ::Numa =>Setter's a -> a -> s -> s (+~) ::Numa =>Iso's a -> a -> s -> s (+~) ::Numa =>Lens's a -> a -> s -> s (+~) ::Numa =>Traversal's a -> a -> s -> s
(*~) :: Num a => ASetter s t a a -> a -> s -> t infixr 4 #
Multiply the target(s) of a numerically valued Lens, Iso, Setter or Traversal.
>>>(a,b) & _1 *~ c(a * c,b)
>>>(a,b) & both *~ c(a * c,b * c)
>>>(1,2) & _2 *~ 4(1,8)
>>>Just 24 & mapped *~ 2Just 48
(*~) ::Numa =>Setter's a -> a -> s -> s (*~) ::Numa =>Iso's a -> a -> s -> s (*~) ::Numa =>Lens's a -> a -> s -> s (*~) ::Numa =>Traversal's a -> a -> s -> s
(-~) :: Num a => ASetter s t a a -> a -> s -> t infixr 4 #
Decrement the target(s) of a numerically valued Lens, Iso, Setter or Traversal.
>>>(a,b) & _1 -~ c(a - c,b)
>>>(a,b) & both -~ c(a - c,b - c)
>>>_1 -~ 2 $ (1,2)(-1,2)
>>>mapped.mapped -~ 1 $ [[4,5],[6,7]][[3,4],[5,6]]
(-~) ::Numa =>Setter's a -> a -> s -> s (-~) ::Numa =>Iso's a -> a -> s -> s (-~) ::Numa =>Lens's a -> a -> s -> s (-~) ::Numa =>Traversal's a -> a -> s -> s
(//~) :: Fractional a => ASetter s t a a -> a -> s -> t infixr 4 #
Divide the target(s) of a numerically valued Lens, Iso, Setter or Traversal.
>>>(a,b) & _1 //~ c(a / c,b)
>>>(a,b) & both //~ c(a / c,b / c)
>>>("Hawaii",10) & _2 //~ 2("Hawaii",5.0)
(//~) ::Fractionala =>Setter's a -> a -> s -> s (//~) ::Fractionala =>Iso's a -> a -> s -> s (//~) ::Fractionala =>Lens's a -> a -> s -> s (//~) ::Fractionala =>Traversal's a -> a -> s -> s
(^~) :: (Num a, Integral e) => ASetter s t a a -> e -> s -> t infixr 4 #
Raise the target(s) of a numerically valued Lens, Setter or Traversal to a non-negative integral power.
>>>(1,3) & _2 ^~ 2(1,9)
(^~) :: (Numa,Integrale) =>Setter's a -> e -> s -> s (^~) :: (Numa,Integrale) =>Iso's a -> e -> s -> s (^~) :: (Numa,Integrale) =>Lens's a -> e -> s -> s (^~) :: (Numa,Integrale) =>Traversal's a -> e -> s -> s
(^^~) :: (Fractional a, Integral e) => ASetter s t a a -> e -> s -> t infixr 4 #
Raise the target(s) of a fractionally valued Lens, Setter or Traversal to an integral power.
>>>(1,2) & _2 ^^~ (-1)(1,0.5)
(^^~) :: (Fractionala,Integrale) =>Setter's a -> e -> s -> s (^^~) :: (Fractionala,Integrale) =>Iso's a -> e -> s -> s (^^~) :: (Fractionala,Integrale) =>Lens's a -> e -> s -> s (^^~) :: (Fractionala,Integrale) =>Traversal's a -> e -> s -> s
(**~) :: Floating a => ASetter s t a a -> a -> s -> t infixr 4 #
Raise the target(s) of a floating-point valued Lens, Setter or Traversal to an arbitrary power.
>>>(a,b) & _1 **~ c(a**c,b)
>>>(a,b) & both **~ c(a**c,b**c)
>>>_2 **~ 10 $ (3,2)(3,1024.0)
(**~) ::Floatinga =>Setter's a -> a -> s -> s (**~) ::Floatinga =>Iso's a -> a -> s -> s (**~) ::Floatinga =>Lens's a -> a -> s -> s (**~) ::Floatinga =>Traversal's a -> a -> s -> s
(||~) :: ASetter s t Bool Bool -> Bool -> s -> t infixr 4 #
Logically || the target(s) of a Bool-valued Lens or Setter.
>>>both ||~ True $ (False,True)(True,True)
>>>both ||~ False $ (False,True)(False,True)
(||~) ::Setter'sBool->Bool-> s -> s (||~) ::Iso'sBool->Bool-> s -> s (||~) ::Lens'sBool->Bool-> s -> s (||~) ::Traversal'sBool->Bool-> s -> s
(&&~) :: ASetter s t Bool Bool -> Bool -> s -> t infixr 4 #
Logically && the target(s) of a Bool-valued Lens or Setter.
>>>both &&~ True $ (False, True)(False,True)
>>>both &&~ False $ (False, True)(False,False)
(&&~) ::Setter'sBool->Bool-> s -> s (&&~) ::Iso'sBool->Bool-> s -> s (&&~) ::Lens'sBool->Bool-> s -> s (&&~) ::Traversal'sBool->Bool-> s -> s
assign :: MonadState s m => ASetter s s a b -> b -> m () #
Replace the target of a Lens or all of the targets of a Setter or Traversal in our monadic
state with a new value, irrespective of the old.
This is an alias for (.=).
>>>execState (do assign _1 c; assign _2 d) (a,b)(c,d)
>>>execState (both .= c) (a,b)(c,c)
assign::MonadStates m =>Iso's a -> a -> m ()assign::MonadStates m =>Lens's a -> a -> m ()assign::MonadStates m =>Traversal's a -> a -> m ()assign::MonadStates m =>Setter's a -> a -> m ()
(.=) :: MonadState s m => ASetter s s a b -> b -> m () infix 4 #
Replace the target of a Lens or all of the targets of a Setter
or Traversal in our monadic state with a new value, irrespective of the
old.
This is an infix version of assign.
>>>execState (do _1 .= c; _2 .= d) (a,b)(c,d)
>>>execState (both .= c) (a,b)(c,c)
(.=) ::MonadStates m =>Iso's a -> a -> m () (.=) ::MonadStates m =>Lens's a -> a -> m () (.=) ::MonadStates m =>Traversal's a -> a -> m () (.=) ::MonadStates m =>Setter's a -> a -> m ()
It puts the state in the monad or it gets the hose again.
(%=) :: MonadState s m => ASetter s s a b -> (a -> b) -> m () infix 4 #
Map over the target of a Lens or all of the targets of a Setter or Traversal in our monadic state.
>>>execState (do _1 %= f;_2 %= g) (a,b)(f a,g b)
>>>execState (do both %= f) (a,b)(f a,f b)
(%=) ::MonadStates m =>Iso's a -> (a -> a) -> m () (%=) ::MonadStates m =>Lens's a -> (a -> a) -> m () (%=) ::MonadStates m =>Traversal's a -> (a -> a) -> m () (%=) ::MonadStates m =>Setter's a -> (a -> a) -> m ()
(%=) ::MonadStates m =>ASetters s a b -> (a -> b) -> m ()
modifying :: MonadState s m => ASetter s s a b -> (a -> b) -> m () #
This is an alias for (%=).
(?=) :: MonadState s m => ASetter s s a (Maybe b) -> b -> m () infix 4 #
Replace the target of a Lens or all of the targets of a Setter or Traversal in our monadic
state with Just a new value, irrespective of the old.
>>>execState (do at 1 ?= a; at 2 ?= b) Map.emptyfromList [(1,a),(2,b)]
>>>execState (do _1 ?= b; _2 ?= c) (Just a, Nothing)(Just b,Just c)
(?=) ::MonadStates m =>Iso's (Maybea) -> a -> m () (?=) ::MonadStates m =>Lens's (Maybea) -> a -> m () (?=) ::MonadStates m =>Traversal's (Maybea) -> a -> m () (?=) ::MonadStates m =>Setter's (Maybea) -> a -> m ()
(+=) :: (MonadState s m, Num a) => ASetter' s a -> a -> m () infix 4 #
Modify the target(s) of a Lens', Iso, Setter or Traversal by adding a value.
Example:
fresh::MonadStateIntm => mIntfresh= doid+=1useid
>>>execState (do _1 += c; _2 += d) (a,b)(a + c,b + d)
>>>execState (do _1.at 1.non 0 += 10) (Map.fromList [(2,100)],"hello")(fromList [(1,10),(2,100)],"hello")
(+=) :: (MonadStates m,Numa) =>Setter's a -> a -> m () (+=) :: (MonadStates m,Numa) =>Iso's a -> a -> m () (+=) :: (MonadStates m,Numa) =>Lens's a -> a -> m () (+=) :: (MonadStates m,Numa) =>Traversal's a -> a -> m ()
(-=) :: (MonadState s m, Num a) => ASetter' s a -> a -> m () infix 4 #
Modify the target(s) of a Lens', Iso, Setter or Traversal by subtracting a value.
>>>execState (do _1 -= c; _2 -= d) (a,b)(a - c,b - d)
(-=) :: (MonadStates m,Numa) =>Setter's a -> a -> m () (-=) :: (MonadStates m,Numa) =>Iso's a -> a -> m () (-=) :: (MonadStates m,Numa) =>Lens's a -> a -> m () (-=) :: (MonadStates m,Numa) =>Traversal's a -> a -> m ()
(*=) :: (MonadState s m, Num a) => ASetter' s a -> a -> m () infix 4 #
Modify the target(s) of a Lens', Iso, Setter or Traversal by multiplying by value.
>>>execState (do _1 *= c; _2 *= d) (a,b)(a * c,b * d)
(*=) :: (MonadStates m,Numa) =>Setter's a -> a -> m () (*=) :: (MonadStates m,Numa) =>Iso's a -> a -> m () (*=) :: (MonadStates m,Numa) =>Lens's a -> a -> m () (*=) :: (MonadStates m,Numa) =>Traversal's a -> a -> m ()
(//=) :: (MonadState s m, Fractional a) => ASetter' s a -> a -> m () infix 4 #
Modify the target(s) of a Lens', Iso, Setter or Traversal by dividing by a value.
>>>execState (do _1 //= c; _2 //= d) (a,b)(a / c,b / d)
(//=) :: (MonadStates m,Fractionala) =>Setter's a -> a -> m () (//=) :: (MonadStates m,Fractionala) =>Iso's a -> a -> m () (//=) :: (MonadStates m,Fractionala) =>Lens's a -> a -> m () (//=) :: (MonadStates m,Fractionala) =>Traversal's a -> a -> m ()
(^=) :: (MonadState s m, Num a, Integral e) => ASetter' s a -> e -> m () infix 4 #
Raise the target(s) of a numerically valued Lens, Setter or Traversal to a non-negative integral power.
(^=) :: (MonadStates m,Numa,Integrale) =>Setter's a -> e -> m () (^=) :: (MonadStates m,Numa,Integrale) =>Iso's a -> e -> m () (^=) :: (MonadStates m,Numa,Integrale) =>Lens's a -> e -> m () (^=) :: (MonadStates m,Numa,Integrale) =>Traversal's a -> e -> m ()
(^^=) :: (MonadState s m, Fractional a, Integral e) => ASetter' s a -> e -> m () infix 4 #
Raise the target(s) of a numerically valued Lens, Setter or Traversal to an integral power.
(^^=) :: (MonadStates m,Fractionala,Integrale) =>Setter's a -> e -> m () (^^=) :: (MonadStates m,Fractionala,Integrale) =>Iso's a -> e -> m () (^^=) :: (MonadStates m,Fractionala,Integrale) =>Lens's a -> e -> m () (^^=) :: (MonadStates m,Fractionala,Integrale) =>Traversal's a -> e -> m ()
(**=) :: (MonadState s m, Floating a) => ASetter' s a -> a -> m () infix 4 #
Raise the target(s) of a numerically valued Lens, Setter or Traversal to an arbitrary power
>>>execState (do _1 **= c; _2 **= d) (a,b)(a**c,b**d)
(**=) :: (MonadStates m,Floatinga) =>Setter's a -> a -> m () (**=) :: (MonadStates m,Floatinga) =>Iso's a -> a -> m () (**=) :: (MonadStates m,Floatinga) =>Lens's a -> a -> m () (**=) :: (MonadStates m,Floatinga) =>Traversal's a -> a -> m ()
(&&=) :: MonadState s m => ASetter' s Bool -> Bool -> m () infix 4 #
Modify the target(s) of a Lens', Iso, Setter or Traversal by taking their logical && with a value.
>>>execState (do _1 &&= True; _2 &&= False; _3 &&= True; _4 &&= False) (True,True,False,False)(True,False,False,False)
(&&=) ::MonadStates m =>Setter'sBool->Bool-> m () (&&=) ::MonadStates m =>Iso'sBool->Bool-> m () (&&=) ::MonadStates m =>Lens'sBool->Bool-> m () (&&=) ::MonadStates m =>Traversal'sBool->Bool-> m ()
(||=) :: MonadState s m => ASetter' s Bool -> Bool -> m () infix 4 #
Modify the target(s) of a Lens', 'Iso, Setter or Traversal by taking their logical || with a value.
>>>execState (do _1 ||= True; _2 ||= False; _3 ||= True; _4 ||= False) (True,True,False,False)(True,True,True,False)
(||=) ::MonadStates m =>Setter'sBool->Bool-> m () (||=) ::MonadStates m =>Iso'sBool->Bool-> m () (||=) ::MonadStates m =>Lens'sBool->Bool-> m () (||=) ::MonadStates m =>Traversal'sBool->Bool-> m ()
(<~) :: MonadState s m => ASetter s s a b -> m b -> m () infixr 2 #
Run a monadic action, and set all of the targets of a Lens, Setter or Traversal to its result.
(<~) ::MonadStates m =>Isos s a b -> m b -> m () (<~) ::MonadStates m =>Lenss s a b -> m b -> m () (<~) ::MonadStates m =>Traversals s a b -> m b -> m () (<~) ::MonadStates m =>Setters s a b -> m b -> m ()
As a reasonable mnemonic, this lets you store the result of a monadic action in a Lens rather than
in a local variable.
do foo <- bar ...
will store the result in a variable, while
do foo <~ bar
...
(<.=) :: MonadState s m => ASetter s s a b -> b -> m b infix 4 #
Set with pass-through
This is useful for chaining assignment without round-tripping through your Monad stack.
do x <-_2<.=ninety_nine_bottles_of_beer_on_the_wall
If you do not need a copy of the intermediate result, then using l will avoid unused binding warnings..= d
(<.=) ::MonadStates m =>Setters s a b -> b -> m b (<.=) ::MonadStates m =>Isos s a b -> b -> m b (<.=) ::MonadStates m =>Lenss s a b -> b -> m b (<.=) ::MonadStates m =>Traversals s a b -> b -> m b
(<?=) :: MonadState s m => ASetter s s a (Maybe b) -> b -> m b infix 4 #
Set Just a value with pass-through
This is useful for chaining assignment without round-tripping through your Monad stack.
do x <-at"foo"<?=ninety_nine_bottles_of_beer_on_the_wall
If you do not need a copy of the intermediate result, then using l will avoid unused binding warnings.?= d
(<?=) ::MonadStates m =>Setters s a (Maybeb) -> b -> m b (<?=) ::MonadStates m =>Isos s a (Maybeb) -> b -> m b (<?=) ::MonadStates m =>Lenss s a (Maybeb) -> b -> m b (<?=) ::MonadStates m =>Traversals s a (Maybeb) -> b -> m b
(<>~) :: Monoid a => ASetter s t a a -> a -> s -> t infixr 4 #
Modify the target of a monoidally valued by mappending another value.
>>>(Sum a,b) & _1 <>~ Sum c(Sum {getSum = a + c},b)
>>>(Sum a,Sum b) & both <>~ Sum c(Sum {getSum = a + c},Sum {getSum = b + c})
>>>both <>~ "!!!" $ ("hello","world")("hello!!!","world!!!")
(<>~) ::Monoida =>Setters t a a -> a -> s -> t (<>~) ::Monoida =>Isos t a a -> a -> s -> t (<>~) ::Monoida =>Lenss t a a -> a -> s -> t (<>~) ::Monoida =>Traversals t a a -> a -> s -> t
(<>=) :: (MonadState s m, Monoid a) => ASetter' s a -> a -> m () infix 4 #
Modify the target(s) of a Lens', Iso, Setter or Traversal by mappending a value.
>>>execState (do _1 <>= Sum c; _2 <>= Product d) (Sum a,Product b)(Sum {getSum = a + c},Product {getProduct = b * d})
>>>execState (both <>= "!!!") ("hello","world")("hello!!!","world!!!")
(<>=) :: (MonadStates m,Monoida) =>Setter's a -> a -> m () (<>=) :: (MonadStates m,Monoida) =>Iso's a -> a -> m () (<>=) :: (MonadStates m,Monoida) =>Lens's a -> a -> m () (<>=) :: (MonadStates m,Monoida) =>Traversal's a -> a -> m ()
scribe :: (MonadWriter t m, Monoid s) => ASetter s t a b -> b -> m () #
Write to a fragment of a larger Writer format.
passing :: MonadWriter w m => Setter w w u v -> m (a, u -> v) -> m a #
This is a generalization of pass that allows you to modify just a
portion of the resulting MonadWriter.
ipassing :: MonadWriter w m => IndexedSetter i w w u v -> m (a, i -> u -> v) -> m a #
This is a generalization of pass that allows you to modify just a
portion of the resulting MonadWriter with access to the index of an
IndexedSetter.
censoring :: MonadWriter w m => Setter w w u v -> (u -> v) -> m a -> m a #
This is a generalization of censor that allows you to censor just a
portion of the resulting MonadWriter.
icensoring :: MonadWriter w m => IndexedSetter i w w u v -> (i -> u -> v) -> m a -> m a #
This is a generalization of censor that allows you to censor just a
portion of the resulting MonadWriter, with access to the index of an
IndexedSetter.
locally :: MonadReader s m => ASetter s s a b -> (a -> b) -> m r -> m r #
Modify the value of the Reader environment associated with the target of a
Setter, Lens, or Traversal.
locallylida ≡ alocallyl f.locally l g ≡locallyl (f.g)
>>>(1,1) & locally _1 (+1) (uncurry (+))3
>>>"," & locally ($) ("Hello" <>) (<> " world!")"Hello, world!"
locally :: MonadReader s m =>Isos s a b -> (a -> b) -> m r -> m r locally :: MonadReader s m =>Lenss s a b -> (a -> b) -> m r -> m r locally :: MonadReader s m =>Traversals s a b -> (a -> b) -> m r -> m r locally :: MonadReader s m =>Setters s a b -> (a -> b) -> m r -> m r
ilocally :: MonadReader s m => AnIndexedSetter i s s a b -> (i -> a -> b) -> m r -> m r #
This is a generalization of locally that allows one to make indexed
local changes to a Reader environment associated with the target of a
Setter, Lens, or Traversal.
locallyl f ≡ilocallyl f . constilocallyl f ≡locallyl f .Indexed
ilocally :: MonadReader s m =>IndexedLenss s a b -> (i -> a -> b) -> m r -> m r ilocally :: MonadReader s m =>IndexedTraversals s a b -> (i -> a -> b) -> m r -> m r ilocally :: MonadReader s m =>IndexedSetters s a b -> (i -> a -> b) -> m r -> m r
iover :: AnIndexedSetter i s t a b -> (i -> a -> b) -> s -> t #
Map with index. This is an alias for imapOf.
When you do not need access to the index, then over is more liberal in what it can accept.
overl ≡ioverl.constioverl ≡overl.Indexed
iover::IndexedSetteri s t a b -> (i -> a -> b) -> s -> tiover::IndexedLensi s t a b -> (i -> a -> b) -> s -> tiover::IndexedTraversali s t a b -> (i -> a -> b) -> s -> t
iset :: AnIndexedSetter i s t a b -> (i -> b) -> s -> t #
Set with index. Equivalent to iover with the current value ignored.
When you do not need access to the index, then set is more liberal in what it can accept.
setl ≡isetl.const
iset::IndexedSetteri s t a b -> (i -> b) -> s -> tiset::IndexedLensi s t a b -> (i -> b) -> s -> tiset::IndexedTraversali s t a b -> (i -> b) -> s -> t
isets :: ((i -> a -> b) -> s -> t) -> IndexedSetter i s t a b #
Build an IndexedSetter from an imap-like function.
Your supplied function f is required to satisfy:
fid≡idf g.f h ≡ f (g.h)
Equational reasoning:
isets.iover≡idiover.isets≡id
Another way to view isets is that it takes a "semantic editor combinator"
which has been modified to carry an index and transforms it into a IndexedSetter.
(%@~) :: AnIndexedSetter i s t a b -> (i -> a -> b) -> s -> t infixr 4 #
Adjust every target of an IndexedSetter, IndexedLens or IndexedTraversal
with access to the index.
(%@~) ≡iover
When you do not need access to the index then (%~) is more liberal in what it can accept.
l%~f ≡ l%@~constf
(%@~) ::IndexedSetteri s t a b -> (i -> a -> b) -> s -> t (%@~) ::IndexedLensi s t a b -> (i -> a -> b) -> s -> t (%@~) ::IndexedTraversali s t a b -> (i -> a -> b) -> s -> t
(.@~) :: AnIndexedSetter i s t a b -> (i -> b) -> s -> t infixr 4 #
Replace every target of an IndexedSetter, IndexedLens or IndexedTraversal
with access to the index.
(.@~) ≡iset
When you do not need access to the index then (.~) is more liberal in what it can accept.
l.~b ≡ l.@~constb
(.@~) ::IndexedSetteri s t a b -> (i -> b) -> s -> t (.@~) ::IndexedLensi s t a b -> (i -> b) -> s -> t (.@~) ::IndexedTraversali s t a b -> (i -> b) -> s -> t
(%@=) :: MonadState s m => AnIndexedSetter i s s a b -> (i -> a -> b) -> m () infix 4 #
Adjust every target in the current state of an IndexedSetter, IndexedLens or IndexedTraversal
with access to the index.
When you do not need access to the index then (%=) is more liberal in what it can accept.
l%=f ≡ l%@=constf
(%@=) ::MonadStates m =>IndexedSetteri s s a b -> (i -> a -> b) -> m () (%@=) ::MonadStates m =>IndexedLensi s s a b -> (i -> a -> b) -> m () (%@=) ::MonadStates m =>IndexedTraversali s t a b -> (i -> a -> b) -> m ()
imodifying :: MonadState s m => AnIndexedSetter i s s a b -> (i -> a -> b) -> m () #
This is an alias for (%@=).
(.@=) :: MonadState s m => AnIndexedSetter i s s a b -> (i -> b) -> m () infix 4 #
Replace every target in the current state of an IndexedSetter, IndexedLens or IndexedTraversal
with access to the index.
When you do not need access to the index then (.=) is more liberal in what it can accept.
l.=b ≡ l.@=constb
(.@=) ::MonadStates m =>IndexedSetteri s s a b -> (i -> b) -> m () (.@=) ::MonadStates m =>IndexedLensi s s a b -> (i -> b) -> m () (.@=) ::MonadStates m =>IndexedTraversali s t a b -> (i -> b) -> m ()
assignA :: Arrow p => ASetter s t a b -> p s b -> p s t #
Run an arrow command and use the output to set all the targets of
a Lens, Setter or Traversal to the result.
assignA can be used very similarly to (<~), except that the type of
the object being modified can change; for example:
runKleisli action ((), (), ()) where
action = assignA _1 (Kleisli (const getVal1))
>>> assignA _2 (Kleisli (const getVal2))
>>> assignA _3 (Kleisli (const getVal3))
getVal1 :: Either String Int
getVal1 = ...
getVal2 :: Either String Bool
getVal2 = ...
getVal3 :: Either String Char
getVal3 = ...
has the type Either String (Int, Bool, Char)
assignA::Arrowp =>Isos t a b -> p s b -> p s tassignA::Arrowp =>Lenss t a b -> p s b -> p s tassignA::Arrowp =>Traversals t a b -> p s b -> p s tassignA::Arrowp =>Setters t a b -> p s b -> p s t
imapOf :: AnIndexedSetter i s t a b -> (i -> a -> b) -> s -> t #
Map with index. (Deprecated alias for iover).
When you do not need access to the index, then mapOf is more liberal in what it can accept.
mapOfl ≡imapOfl.const
imapOf::IndexedSetteri s t a b -> (i -> a -> b) -> s -> timapOf::IndexedLensi s t a b -> (i -> a -> b) -> s -> timapOf::IndexedTraversali s t a b -> (i -> a -> b) -> s -> t
type AnIndexedLens' i s a = AnIndexedLens i s s a a #
typeAnIndexedLens'=Simple(AnIndexedLensi)
type AnIndexedLens i s t a b = Optical (Indexed i) ((->) :: Type -> Type -> Type) (Pretext (Indexed i) a b) s t a b #
When you see this as an argument to a function, it expects an IndexedLens
iplens :: (s -> a) -> (s -> b -> t) -> IndexPreservingLens s t a b #
ilens :: (s -> (i, a)) -> (s -> b -> t) -> IndexedLens i s t a b #
Build an IndexedLens from a Getter and
a Setter.
(&~) :: s -> State s a -> s infixl 1 #
This can be used to chain lens operations using op= syntax
rather than op~ syntax for simple non-type-changing cases.
>>>(10,20) & _1 .~ 30 & _2 .~ 40(30,40)
>>>(10,20) &~ do _1 .= 30; _2 .= 40(30,40)
This does not support type-changing assignment, e.g.
>>>(10,20) & _1 .~ "hello"("hello",20)
(%%~) :: LensLike f s t a b -> (a -> f b) -> s -> f t infixr 4 #
(%%~) can be used in one of two scenarios:
When applied to a Lens, it can edit the target of the Lens in a
structure, extracting a functorial result.
When applied to a Traversal, it can edit the
targets of the traversals, extracting an applicative summary of its
actions.
>>>[66,97,116,109,97,110] & each %%~ \a -> ("na", chr a)("nananananana","Batman")
For all that the definition of this combinator is just:
(%%~) ≡id
It may be beneficial to think about it as if it had these even more restricted types, however:
(%%~) ::Functorf =>Isos t a b -> (a -> f b) -> s -> f t (%%~) ::Functorf =>Lenss t a b -> (a -> f b) -> s -> f t (%%~) ::Applicativef =>Traversals t a b -> (a -> f b) -> s -> f t
When applied to a Traversal, it can edit the
targets of the traversals, extracting a supplemental monoidal summary
of its actions, by choosing f = ((,) m)
(%%~) ::Isos t a b -> (a -> (r, b)) -> s -> (r, t) (%%~) ::Lenss t a b -> (a -> (r, b)) -> s -> (r, t) (%%~) ::Monoidm =>Traversals t a b -> (a -> (m, b)) -> s -> (m, t)
(%%=) :: MonadState s m => Over p ((,) r) s s a b -> p a (r, b) -> m r infix 4 #
Modify the target of a Lens in the current state returning some extra
information of type r or modify all targets of a
Traversal in the current state, extracting extra
information of type r and return a monoidal summary of the changes.
>>>runState (_1 %%= \x -> (f x, g x)) (a,b)(f a,(g a,b))
(%%=) ≡ (state.)
It may be useful to think of (%%=), instead, as having either of the
following more restricted type signatures:
(%%=) ::MonadStates m =>Isos s a b -> (a -> (r, b)) -> m r (%%=) ::MonadStates m =>Lenss s a b -> (a -> (r, b)) -> m r (%%=) :: (MonadStates m,Monoidr) =>Traversals s a b -> (a -> (r, b)) -> m r
(??) :: Functor f => f (a -> b) -> a -> f b infixl 1 #
This is convenient to flip argument order of composite functions defined as:
fab ?? a = fmap ($ a) fab
For the Functor instance f = ((->) r) you can reason about this function as if the definition was (:??) ≡ flip
>>>(h ?? x) ah a x
>>>execState ?? [] $ modify (1:)[1]
>>>over _2 ?? ("hello","world") $ length("hello",5)
>>>over ?? length ?? ("hello","world") $ _2("hello",5)
choosing :: Functor f => LensLike f s t a b -> LensLike f s' t' a b -> LensLike f (Either s s') (Either t t') a b #
Merge two lenses, getters, setters, folds or traversals.
chosen≡choosingidid
choosing::Getters a ->Getters' a ->Getter(Eithers s') achoosing::Folds a ->Folds' a ->Fold(Eithers s') achoosing::Lens's a ->Lens's' a ->Lens'(Eithers s') achoosing::Traversal's a ->Traversal's' a ->Traversal'(Eithers s') achoosing::Setter's a ->Setter's' a ->Setter'(Eithers s') a
chosen :: IndexPreservingLens (Either a a) (Either b b) a b #
This is a Lens that updates either side of an Either, where both sides have the same type.
chosen≡choosingidid
>>>Left a^.chosena
>>>Right a^.chosena
>>>Right "hello"^.chosen"hello"
>>>Right a & chosen *~ bRight (a * b)
chosen::Lens(Eithera a) (Eitherb b) a bchosenf (Lefta) =Left<$>f achosenf (Righta) =Right<$>f a
alongside :: LensLike (AlongsideLeft f b') s t a b -> LensLike (AlongsideRight f t) s' t' a' b' -> LensLike f (s, s') (t, t') (a, a') (b, b') #
alongside makes a Lens from two other lenses or a Getter from two other getters
by executing them on their respective halves of a product.
>>>(Left a, Right b)^.alongside chosen chosen(a,b)
>>>(Left a, Right b) & alongside chosen chosen .~ (c,d)(Left c,Right d)
alongside::Lenss t a b ->Lenss' t' a' b' ->Lens(s,s') (t,t') (a,a') (b,b')alongside::Getters a ->Getters' a' ->Getter(s,s') (a,a')
locus :: IndexedComonadStore p => Lens (p a c s) (p b c s) a b #
This Lens lets you view the current pos of any indexed
store comonad and seek to a new position. This reduces the API
for working these instances to a single Lens.
iposw ≡ w^.locusiseeks w ≡ w&locus.~siseeksf w ≡ w&locus%~f
locus::Lens'(Context'a s) alocus::Conjoinedp =>Lens'(Pretext'p a s) alocus::Conjoinedp =>Lens'(PretextT'p g a s) a
cloneLens :: ALens s t a b -> Lens s t a b #
Cloning a Lens is one way to make sure you aren't given
something weaker, such as a Traversal and can be
used as a way to pass around lenses that have to be monomorphic in f.
Note: This only accepts a proper Lens.
>>>let example l x = set (cloneLens l) (x^.cloneLens l + 1) x in example _2 ("hello",1,"you")("hello",2,"you")
cloneIndexPreservingLens :: ALens s t a b -> IndexPreservingLens s t a b #
Clone a Lens as an IndexedPreservingLens that just passes through whatever
index is on any IndexedLens, IndexedFold, IndexedGetter or IndexedTraversal it is composed with.
cloneIndexedLens :: AnIndexedLens i s t a b -> IndexedLens i s t a b #
Clone an IndexedLens as an IndexedLens with the same index.
(<//~) :: Fractional a => LensLike ((,) a) s t a a -> a -> s -> (a, t) infixr 4 #
Divide the target of a fractionally valued Lens and return the result.
When you do not need the result of the division, (//~) is more flexible.
(<//~) ::Fractionala =>Lens's a -> a -> s -> (a, s) (<//~) ::Fractionala =>Iso's a -> a -> s -> (a, s)
(<^^~) :: (Fractional a, Integral e) => LensLike ((,) a) s t a a -> e -> s -> (a, t) infixr 4 #
Raise the target of a fractionally valued Lens to an Integral power
and return the result.
When you do not need the result of the operation, (^^~) is more flexible.
(<^^~) :: (Fractionala,Integrale) =>Lens's a -> e -> s -> (a, s) (<^^~) :: (Fractionala,Integrale) =>Iso's a -> e -> s -> (a, s)
(<<?~) :: LensLike ((,) a) s t a (Maybe b) -> b -> s -> (a, t) infixr 4 #
Replace the target of a Lens with a Just value, but return the old value.
If you do not need the old value (?~) is more flexible.
>>>import Data.Map as Map>>>_2.at "hello" <<?~ "world" $ (42,Map.fromList [("goodnight","gracie")])(Nothing,(42,fromList [("goodnight","gracie"),("hello","world")]))
(<<?~) ::Isos t a (Maybeb) -> b -> s -> (a, t) (<<?~) ::Lenss t a (Maybeb) -> b -> s -> (a, t) (<<?~) ::Traversals t a (Maybeb) -> b -> s -> (a, t)
(<<+~) :: Num a => LensLike' ((,) a) s a -> a -> s -> (a, s) infixr 4 #
Increment the target of a numerically valued Lens and return the old value.
When you do not need the old value, (+~) is more flexible.
>>>(a,b) & _1 <<+~ c(a,(a + c,b))
>>>(a,b) & _2 <<+~ c(b,(a,b + c))
(<<+~) ::Numa =>Lens's a -> a -> s -> (a, s) (<<+~) ::Numa =>Iso's a -> a -> s -> (a, s)
(<<-~) :: Num a => LensLike' ((,) a) s a -> a -> s -> (a, s) infixr 4 #
Decrement the target of a numerically valued Lens and return the old value.
When you do not need the old value, (-~) is more flexible.
>>>(a,b) & _1 <<-~ c(a,(a - c,b))
>>>(a,b) & _2 <<-~ c(b,(a,b - c))
(<<-~) ::Numa =>Lens's a -> a -> s -> (a, s) (<<-~) ::Numa =>Iso's a -> a -> s -> (a, s)
(<<*~) :: Num a => LensLike' ((,) a) s a -> a -> s -> (a, s) infixr 4 #
Multiply the target of a numerically valued Lens and return the old value.
When you do not need the old value, (-~) is more flexible.
>>>(a,b) & _1 <<*~ c(a,(a * c,b))
>>>(a,b) & _2 <<*~ c(b,(a,b * c))
(<<*~) ::Numa =>Lens's a -> a -> s -> (a, s) (<<*~) ::Numa =>Iso's a -> a -> s -> (a, s)
(<<//~) :: Fractional a => LensLike' ((,) a) s a -> a -> s -> (a, s) infixr 4 #
Divide the target of a numerically valued Lens and return the old value.
When you do not need the old value, (//~) is more flexible.
>>>(a,b) & _1 <<//~ c(a,(a / c,b))
>>>("Hawaii",10) & _2 <<//~ 2(10.0,("Hawaii",5.0))
(<<//~) :: Fractional a =>Lens's a -> a -> s -> (a, s) (<<//~) :: Fractional a =>Iso's a -> a -> s -> (a, s)
(<<^^~) :: (Fractional a, Integral e) => LensLike' ((,) a) s a -> e -> s -> (a, s) infixr 4 #
Raise the target of a fractionally valued Lens to an integral power and return the old value.
When you do not need the old value, (^^~) is more flexible.
(<<^^~) :: (Fractionala,Integrale) =>Lens's a -> e -> s -> (a, s) (<<^^~) :: (Fractionala,Integrale) =>Iso's a -> e -> S -> (a, s)
(<<**~) :: Floating a => LensLike' ((,) a) s a -> a -> s -> (a, s) infixr 4 #
Raise the target of a floating-point valued Lens to an arbitrary power and return the old value.
When you do not need the old value, (**~) is more flexible.
>>>(a,b) & _1 <<**~ c(a,(a**c,b))
>>>(a,b) & _2 <<**~ c(b,(a,b**c))
(<<**~) ::Floatinga =>Lens's a -> a -> s -> (a, s) (<<**~) ::Floatinga =>Iso's a -> a -> s -> (a, s)
(<<||~) :: LensLike' ((,) Bool) s Bool -> Bool -> s -> (Bool, s) infixr 4 #
Logically || the target of a Bool-valued Lens and return the old value.
When you do not need the old value, (||~) is more flexible.
>>>(False,6) & _1 <<||~ True(False,(True,6))
>>>("hello",True) & _2 <<||~ False(True,("hello",True))
(<<||~) ::Lens'sBool->Bool-> s -> (Bool, s) (<<||~) ::Iso'sBool->Bool-> s -> (Bool, s)
(<<&&~) :: LensLike' ((,) Bool) s Bool -> Bool -> s -> (Bool, s) infixr 4 #
Logically && the target of a Bool-valued Lens and return the old value.
When you do not need the old value, (&&~) is more flexible.
>>>(False,6) & _1 <<&&~ True(False,(False,6))
>>>("hello",True) & _2 <<&&~ False(True,("hello",False))
(<<&&~) ::Lens's Bool -> Bool -> s -> (Bool, s) (<<&&~) ::Iso's Bool -> Bool -> s -> (Bool, s)
(<<<>~) :: Monoid r => LensLike' ((,) r) s r -> r -> s -> (r, s) infixr 4 #
Modify the target of a monoidally valued Lens by mappending a new value and return the old value.
When you do not need the old value, (<>~) is more flexible.
>>>(Sum a,b) & _1 <<<>~ Sum c(Sum {getSum = a},(Sum {getSum = a + c},b))
>>>_2 <<<>~ ", 007" $ ("James", "Bond")("Bond",("James","Bond, 007"))
(<<<>~) ::Monoidr =>Lens's r -> r -> s -> (r, s) (<<<>~) ::Monoidr =>Iso's r -> r -> s -> (r, s)
(<%=) :: MonadState s m => LensLike ((,) b) s s a b -> (a -> b) -> m b infix 4 #
Modify the target of a Lens into your Monad's state by a user supplied
function and return the result.
When applied to a Traversal, it this will return a monoidal summary of all of the intermediate
results.
When you do not need the result of the operation, (%=) is more flexible.
(<%=) ::MonadStates m =>Lens's a -> (a -> a) -> m a (<%=) ::MonadStates m =>Iso's a -> (a -> a) -> m a (<%=) :: (MonadStates m,Monoida) =>Traversal's a -> (a -> a) -> m a
(<+=) :: (MonadState s m, Num a) => LensLike' ((,) a) s a -> a -> m a infix 4 #
Add to the target of a numerically valued Lens into your Monad's state
and return the result.
When you do not need the result of the addition, (+=) is more
flexible.
(<+=) :: (MonadStates m,Numa) =>Lens's a -> a -> m a (<+=) :: (MonadStates m,Numa) =>Iso's a -> a -> m a
(<-=) :: (MonadState s m, Num a) => LensLike' ((,) a) s a -> a -> m a infix 4 #
Subtract from the target of a numerically valued Lens into your Monad's
state and return the result.
When you do not need the result of the subtraction, (-=) is more
flexible.
(<-=) :: (MonadStates m,Numa) =>Lens's a -> a -> m a (<-=) :: (MonadStates m,Numa) =>Iso's a -> a -> m a
(<*=) :: (MonadState s m, Num a) => LensLike' ((,) a) s a -> a -> m a infix 4 #
Multiply the target of a numerically valued Lens into your Monad's
state and return the result.
When you do not need the result of the multiplication, (*=) is more
flexible.
(<*=) :: (MonadStates m,Numa) =>Lens's a -> a -> m a (<*=) :: (MonadStates m,Numa) =>Iso's a -> a -> m a
(<//=) :: (MonadState s m, Fractional a) => LensLike' ((,) a) s a -> a -> m a infix 4 #
Divide the target of a fractionally valued Lens into your Monad's state
and return the result.
When you do not need the result of the division, (//=) is more flexible.
(<//=) :: (MonadStates m,Fractionala) =>Lens's a -> a -> m a (<//=) :: (MonadStates m,Fractionala) =>Iso's a -> a -> m a
(<^=) :: (MonadState s m, Num a, Integral e) => LensLike' ((,) a) s a -> e -> m a infix 4 #
Raise the target of a numerically valued Lens into your Monad's state
to a non-negative Integral power and return the result.
When you do not need the result of the operation, (^=) is more flexible.
(<^=) :: (MonadStates m,Numa,Integrale) =>Lens's a -> e -> m a (<^=) :: (MonadStates m,Numa,Integrale) =>Iso's a -> e -> m a
(<^^=) :: (MonadState s m, Fractional a, Integral e) => LensLike' ((,) a) s a -> e -> m a infix 4 #
Raise the target of a fractionally valued Lens into your Monad's state
to an Integral power and return the result.
When you do not need the result of the operation, (^^=) is more flexible.
(<^^=) :: (MonadStates m,Fractionalb,Integrale) =>Lens's a -> e -> m a (<^^=) :: (MonadStates m,Fractionalb,Integrale) =>Iso's a -> e -> m a
(<**=) :: (MonadState s m, Floating a) => LensLike' ((,) a) s a -> a -> m a infix 4 #
Raise the target of a floating-point valued Lens into your Monad's
state to an arbitrary power and return the result.
When you do not need the result of the operation, (**=) is more flexible.
(<**=) :: (MonadStates m,Floatinga) =>Lens's a -> a -> m a (<**=) :: (MonadStates m,Floatinga) =>Iso's a -> a -> m a
(<<%=) :: (Strong p, MonadState s m) => Over p ((,) a) s s a b -> p a b -> m a infix 4 #
Modify the target of a Lens into your Monad's state by a user supplied
function and return the old value that was replaced.
When applied to a Traversal, this will return a monoidal summary of all of the old values
present.
When you do not need the result of the operation, (%=) is more flexible.
(<<%=) ::MonadStates m =>Lens's a -> (a -> a) -> m a (<<%=) ::MonadStates m =>Iso's a -> (a -> a) -> m a (<<%=) :: (MonadStates m,Monoida) =>Traversal's a -> (a -> a) -> m a
(<<%=) ::MonadStates m =>LensLike((,)a) s s a b -> (a -> b) -> m a
(<<.=) :: MonadState s m => LensLike ((,) a) s s a b -> b -> m a infix 4 #
Replace the target of a Lens into your Monad's state with a user supplied
value and return the old value that was replaced.
When applied to a Traversal, this will return a monoidal summary of all of the old values
present.
When you do not need the result of the operation, (.=) is more flexible.
(<<.=) ::MonadStates m =>Lens's a -> a -> m a (<<.=) ::MonadStates m =>Iso's a -> a -> m a (<<.=) :: (MonadStates m,Monoida) =>Traversal's a -> a -> m a
(<<?=) :: MonadState s m => LensLike ((,) a) s s a (Maybe b) -> b -> m a infix 4 #
Replace the target of a Lens into your Monad's state with Just a user supplied
value and return the old value that was replaced.
When applied to a Traversal, this will return a monoidal summary of all of the old values
present.
When you do not need the result of the operation, (?=) is more flexible.
(<<?=) ::MonadStates m =>Lenss t a (Maybe b) -> b -> m a (<<?=) ::MonadStates m =>Isos t a (Maybe b) -> b -> m a (<<?=) :: (MonadStates m,Monoida) =>Traversals t a (Maybe b) -> b -> m a
(<<+=) :: (MonadState s m, Num a) => LensLike' ((,) a) s a -> a -> m a infix 4 #
Modify the target of a Lens into your Monad's state by adding a value
and return the old value that was replaced.
When you do not need the result of the operation, (+=) is more flexible.
(<<+=) :: (MonadStates m,Numa) =>Lens's a -> a -> m a (<<+=) :: (MonadStates m,Numa) =>Iso's a -> a -> m a
(<<-=) :: (MonadState s m, Num a) => LensLike' ((,) a) s a -> a -> m a infix 4 #
Modify the target of a Lens into your Monad's state by subtracting a value
and return the old value that was replaced.
When you do not need the result of the operation, (-=) is more flexible.
(<<-=) :: (MonadStates m,Numa) =>Lens's a -> a -> m a (<<-=) :: (MonadStates m,Numa) =>Iso's a -> a -> m a
(<<*=) :: (MonadState s m, Num a) => LensLike' ((,) a) s a -> a -> m a infix 4 #
Modify the target of a Lens into your Monad's state by multipling a value
and return the old value that was replaced.
When you do not need the result of the operation, (*=) is more flexible.
(<<*=) :: (MonadStates m,Numa) =>Lens's a -> a -> m a (<<*=) :: (MonadStates m,Numa) =>Iso's a -> a -> m a
(<<//=) :: (MonadState s m, Fractional a) => LensLike' ((,) a) s a -> a -> m a infix 4 #
Modify the target of a Lens into your Monads state by dividing by a value
and return the old value that was replaced.
When you do not need the result of the operation, (//=) is more flexible.
(<<//=) :: (MonadStates m,Fractionala) =>Lens's a -> a -> m a (<<//=) :: (MonadStates m,Fractionala) =>Iso's a -> a -> m a
(<<^=) :: (MonadState s m, Num a, Integral e) => LensLike' ((,) a) s a -> e -> m a infix 4 #
Modify the target of a Lens into your Monad's state by raising it by a non-negative power
and return the old value that was replaced.
When you do not need the result of the operation, (^=) is more flexible.
(<<^=) :: (MonadStates m,Numa,Integrale) =>Lens's a -> e -> m a (<<^=) :: (MonadStates m,Numa,Integrale) =>Iso's a -> a -> m a
(<<^^=) :: (MonadState s m, Fractional a, Integral e) => LensLike' ((,) a) s a -> e -> m a infix 4 #
Modify the target of a Lens into your Monad's state by raising it by an integral power
and return the old value that was replaced.
When you do not need the result of the operation, (^^=) is more flexible.
(<<^^=) :: (MonadStates m,Fractionala,Integrale) =>Lens's a -> e -> m a (<<^^=) :: (MonadStates m,Fractionala,Integrale) =>Iso's a -> e -> m a
(<<**=) :: (MonadState s m, Floating a) => LensLike' ((,) a) s a -> a -> m a infix 4 #
Modify the target of a Lens into your Monad's state by raising it by an arbitrary power
and return the old value that was replaced.
When you do not need the result of the operation, (**=) is more flexible.
(<<**=) :: (MonadStates m,Floatinga) =>Lens's a -> a -> m a (<<**=) :: (MonadStates m,Floatinga) =>Iso's a -> a -> m a
(<<||=) :: MonadState s m => LensLike' ((,) Bool) s Bool -> Bool -> m Bool infix 4 #
Modify the target of a Lens into your Monad's state by taking its logical || with a value
and return the old value that was replaced.
When you do not need the result of the operation, (||=) is more flexible.
(<<||=) ::MonadStates m =>Lens'sBool->Bool-> mBool(<<||=) ::MonadStates m =>Iso'sBool->Bool-> mBool
(<<&&=) :: MonadState s m => LensLike' ((,) Bool) s Bool -> Bool -> m Bool infix 4 #
Modify the target of a Lens into your Monad's state by taking its logical && with a value
and return the old value that was replaced.
When you do not need the result of the operation, (&&=) is more flexible.
(<<&&=) ::MonadStates m =>Lens'sBool->Bool-> mBool(<<&&=) ::MonadStates m =>Iso'sBool->Bool-> mBool
(<<<>=) :: (MonadState s m, Monoid r) => LensLike' ((,) r) s r -> r -> m r infix 4 #
Modify the target of a Lens into your Monad's state by mappending a value
and return the old value that was replaced.
When you do not need the result of the operation, (<>=) is more flexible.
(<<<>=) :: (MonadStates m,Monoidr) =>Lens's r -> r -> m r (<<<>=) :: (MonadStates m,Monoidr) =>Iso's r -> r -> m r
(<<~) :: MonadState s m => ALens s s a b -> m b -> m b infixr 2 #
Run a monadic action, and set the target of Lens to its result.
(<<~) ::MonadStates m =>Isos s a b -> m b -> m b (<<~) ::MonadStates m =>Lenss s a b -> m b -> m b
NB: This is limited to taking an actual Lens than admitting a Traversal because
there are potential loss of state issues otherwise.
(<%@~) :: Over (Indexed i) ((,) b) s t a b -> (i -> a -> b) -> s -> (b, t) infixr 4 #
Adjust the target of an IndexedLens returning the intermediate result, or
adjust all of the targets of an IndexedTraversal and return a monoidal summary
along with the answer.
l<%~f ≡ l<%@~constf
When you do not need access to the index then (<%~) is more liberal in what it can accept.
If you do not need the intermediate result, you can use (%@~) or even (%~).
(<%@~) ::IndexedLensi s t a b -> (i -> a -> b) -> s -> (b, t) (<%@~) ::Monoidb =>IndexedTraversali s t a b -> (i -> a -> b) -> s -> (b, t)
(<<%@~) :: Over (Indexed i) ((,) a) s t a b -> (i -> a -> b) -> s -> (a, t) infixr 4 #
Adjust the target of an IndexedLens returning the old value, or
adjust all of the targets of an IndexedTraversal and return a monoidal summary
of the old values along with the answer.
(<<%@~) ::IndexedLensi s t a b -> (i -> a -> b) -> s -> (a, t) (<<%@~) ::Monoida =>IndexedTraversali s t a b -> (i -> a -> b) -> s -> (a, t)
(%%@~) :: Over (Indexed i) f s t a b -> (i -> a -> f b) -> s -> f t infixr 4 #
Adjust the target of an IndexedLens returning a supplementary result, or
adjust all of the targets of an IndexedTraversal and return a monoidal summary
of the supplementary results and the answer.
(%%@~) ≡withIndex
(%%@~) ::Functorf =>IndexedLensi s t a b -> (i -> a -> f b) -> s -> f t (%%@~) ::Applicativef =>IndexedTraversali s t a b -> (i -> a -> f b) -> s -> f t
In particular, it is often useful to think of this function as having one of these even more restricted type signatures:
(%%@~) ::IndexedLensi s t a b -> (i -> a -> (r, b)) -> s -> (r, t) (%%@~) ::Monoidr =>IndexedTraversali s t a b -> (i -> a -> (r, b)) -> s -> (r, t)
(%%@=) :: MonadState s m => Over (Indexed i) ((,) r) s s a b -> (i -> a -> (r, b)) -> m r infix 4 #
Adjust the target of an IndexedLens returning a supplementary result, or
adjust all of the targets of an IndexedTraversal within the current state, and
return a monoidal summary of the supplementary results.
l%%@=f ≡state(l%%@~f)
(%%@=) ::MonadStates m =>IndexedLensi s s a b -> (i -> a -> (r, b)) -> s -> m r (%%@=) :: (MonadStates m,Monoidr) =>IndexedTraversali s s a b -> (i -> a -> (r, b)) -> s -> m r
(<%@=) :: MonadState s m => Over (Indexed i) ((,) b) s s a b -> (i -> a -> b) -> m b infix 4 #
Adjust the target of an IndexedLens returning the intermediate result, or
adjust all of the targets of an IndexedTraversal within the current state, and
return a monoidal summary of the intermediate results.
(<%@=) ::MonadStates m =>IndexedLensi s s a b -> (i -> a -> b) -> m b (<%@=) :: (MonadStates m,Monoidb) =>IndexedTraversali s s a b -> (i -> a -> b) -> m b
(<<%@=) :: MonadState s m => Over (Indexed i) ((,) a) s s a b -> (i -> a -> b) -> m a infix 4 #
Adjust the target of an IndexedLens returning the old value, or
adjust all of the targets of an IndexedTraversal within the current state, and
return a monoidal summary of the old values.
(<<%@=) ::MonadStates m =>IndexedLensi s s a b -> (i -> a -> b) -> m a (<<%@=) :: (MonadStates m,Monoidb) =>IndexedTraversali s s a b -> (i -> a -> b) -> m a
(#=) :: MonadState s m => ALens s s a b -> b -> m () infix 4 #
(#%=) :: MonadState s m => ALens s s a b -> (a -> b) -> m () infix 4 #
(<#%=) :: MonadState s m => ALens s s a b -> (a -> b) -> m b infix 4 #
(#%%=) :: MonadState s m => ALens s s a b -> (a -> (r, b)) -> m r infix 4 #
(<#=) :: MonadState s m => ALens s s a b -> b -> m b infix 4 #
We can always retrieve a () from any type.
>>>"hello"^.united()
>>>"hello" & united .~ ()"hello"
fusing :: Functor f => LensLike (Yoneda f) s t a b -> LensLike f s t a b #
Fuse a composition of lenses using Yoneda to provide fmap fusion.
In general, given a pair of lenses foo and bar
fusing (foo.bar) = foo.bar
however, foo and bar are either going to fmap internally or they are trivial.
fusing exploits the Yoneda lemma to merge these separate uses into a single fmap.
This is particularly effective when the choice of functor f is unknown at compile
time or when the Lens foo.bar in the above description is recursive or complex
enough to prevent inlining.
fusing::Lenss t a b ->Lenss t a b
class Field19 s t a b | s -> a, t -> b, s b -> t, t a -> s where #
Provides access to the 19th field of a tuple.
Minimal complete definition
Nothing
class Field18 s t a b | s -> a, t -> b, s b -> t, t a -> s where #
Provides access to the 18th field of a tuple.
Minimal complete definition
Nothing
Instances
| 18 <= n => Field18 (V n a) (V n a) a a | |
| Field18 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r') r r' | |
Defined in Control.Lens.Tuple | |
| Field18 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r', s) r r' | |
Defined in Control.Lens.Tuple | |
class Field17 s t a b | s -> a, t -> b, s b -> t, t a -> s where #
Provides access to the 17th field of a tuple.
Minimal complete definition
Nothing
Instances
| 17 <= n => Field17 (V n a) (V n a) a a | |
| Field17 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q') q q' | |
Defined in Control.Lens.Tuple | |
| Field17 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q', r) q q' | |
Defined in Control.Lens.Tuple | |
| Field17 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q', r, s) q q' | |
Defined in Control.Lens.Tuple | |
class Field16 s t a b | s -> a, t -> b, s b -> t, t a -> s where #
Provides access to the 16th field of a tuple.
Minimal complete definition
Nothing
Instances
| 16 <= n => Field16 (V n a) (V n a) a a | |
| Field16 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p') p p' | |
Defined in Control.Lens.Tuple | |
| Field16 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p', q) p p' | |
Defined in Control.Lens.Tuple | |
| Field16 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p', q, r) p p' | |
Defined in Control.Lens.Tuple | |
| Field16 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p', q, r, s) p p' | |
Defined in Control.Lens.Tuple | |
class Field15 s t a b | s -> a, t -> b, s b -> t, t a -> s where #
Provides access to the 15th field of a tuple.
Minimal complete definition
Nothing
Instances
| 15 <= n => Field15 (V n a) (V n a) a a | |
| Field15 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o') o o' | |
Defined in Control.Lens.Tuple | |
| Field15 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o', p) o o' | |
Defined in Control.Lens.Tuple | |
| Field15 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o', p, q) o o' | |
Defined in Control.Lens.Tuple | |
| Field15 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o', p, q, r) o o' | |
Defined in Control.Lens.Tuple | |
| Field15 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o', p, q, r, s) o o' | |
Defined in Control.Lens.Tuple | |
class Field14 s t a b | s -> a, t -> b, s b -> t, t a -> s where #
Provides access to the 14th field of a tuple.
Minimal complete definition
Nothing
Instances
| 14 <= n => Field14 (V n a) (V n a) a a | |
| Field14 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n') n n' | |
Defined in Control.Lens.Tuple | |
| Field14 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n', o) n n' | |
Defined in Control.Lens.Tuple | |
| Field14 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n', o, p) n n' | |
Defined in Control.Lens.Tuple | |
| Field14 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n', o, p, q) n n' | |
Defined in Control.Lens.Tuple | |
| Field14 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n', o, p, q, r) n n' | |
Defined in Control.Lens.Tuple | |
| Field14 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b, c, d, e, f, g, h, i, j, kk, l, m, n', o, p, q, r, s) n n' | |
Defined in Control.Lens.Tuple | |
class Field13 s t a b | s -> a, t -> b, s b -> t, t a -> s where #
Provides access to the 13th field of a tuple.
Minimal complete definition
Nothing
Instances
| 13 <= n => Field13 (V n a) (V n a) a a | |
| Field13 (a, b, c, d, e, f, g, h, i, j, kk, l, m) (a, b, c, d, e, f, g, h, i, j, kk, l, m') m m' | |
Defined in Control.Lens.Tuple | |
| Field13 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n) (a, b, c, d, e, f, g, h, i, j, kk, l, m', n) m m' | |
Defined in Control.Lens.Tuple | |
| Field13 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o) (a, b, c, d, e, f, g, h, i, j, kk, l, m', n, o) m m' | |
Defined in Control.Lens.Tuple | |
| Field13 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p) (a, b, c, d, e, f, g, h, i, j, kk, l, m', n, o, p) m m' | |
Defined in Control.Lens.Tuple | |
| Field13 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) (a, b, c, d, e, f, g, h, i, j, kk, l, m', n, o, p, q) m m' | |
Defined in Control.Lens.Tuple | |
| Field13 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a, b, c, d, e, f, g, h, i, j, kk, l, m', n, o, p, q, r) m m' | |
Defined in Control.Lens.Tuple | |
| Field13 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b, c, d, e, f, g, h, i, j, kk, l, m', n, o, p, q, r, s) m m' | |
Defined in Control.Lens.Tuple | |
class Field12 s t a b | s -> a, t -> b, s b -> t, t a -> s where #
Provides access to the 12th field of a tuple.
Minimal complete definition
Nothing
Instances
| 12 <= n => Field12 (V n a) (V n a) a a | |
| Field12 (a, b, c, d, e, f, g, h, i, j, kk, l) (a, b, c, d, e, f, g, h, i, j, kk, l') l l' | |
Defined in Control.Lens.Tuple | |
| Field12 (a, b, c, d, e, f, g, h, i, j, kk, l, m) (a, b, c, d, e, f, g, h, i, j, kk, l', m) l l' | |
Defined in Control.Lens.Tuple | |
| Field12 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n) (a, b, c, d, e, f, g, h, i, j, kk, l', m, n) l l' | |
Defined in Control.Lens.Tuple | |
| Field12 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o) (a, b, c, d, e, f, g, h, i, j, kk, l', m, n, o) l l' | |
Defined in Control.Lens.Tuple | |
| Field12 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p) (a, b, c, d, e, f, g, h, i, j, kk, l', m, n, o, p) l l' | |
Defined in Control.Lens.Tuple | |
| Field12 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) (a, b, c, d, e, f, g, h, i, j, kk, l', m, n, o, p, q) l l' | |
Defined in Control.Lens.Tuple | |
| Field12 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a, b, c, d, e, f, g, h, i, j, kk, l', m, n, o, p, q, r) l l' | |
Defined in Control.Lens.Tuple | |
| Field12 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b, c, d, e, f, g, h, i, j, kk, l', m, n, o, p, q, r, s) l l' | |
Defined in Control.Lens.Tuple | |
class Field11 s t a b | s -> a, t -> b, s b -> t, t a -> s where #
Provides access to the 11th field of a tuple.
Minimal complete definition
Nothing
Instances
| 11 <= n => Field11 (V n a) (V n a) a a | |
| Field11 (a, b, c, d, e, f, g, h, i, j, kk) (a, b, c, d, e, f, g, h, i, j, kk') kk kk' | |
Defined in Control.Lens.Tuple | |
| Field11 (a, b, c, d, e, f, g, h, i, j, kk, l) (a, b, c, d, e, f, g, h, i, j, kk', l) kk kk' | |
Defined in Control.Lens.Tuple | |
| Field11 (a, b, c, d, e, f, g, h, i, j, kk, l, m) (a, b, c, d, e, f, g, h, i, j, kk', l, m) kk kk' | |
Defined in Control.Lens.Tuple | |
| Field11 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n) (a, b, c, d, e, f, g, h, i, j, kk', l, m, n) kk kk' | |
Defined in Control.Lens.Tuple | |
| Field11 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o) (a, b, c, d, e, f, g, h, i, j, kk', l, m, n, o) kk kk' | |
Defined in Control.Lens.Tuple | |
| Field11 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p) (a, b, c, d, e, f, g, h, i, j, kk', l, m, n, o, p) kk kk' | |
Defined in Control.Lens.Tuple | |
| Field11 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) (a, b, c, d, e, f, g, h, i, j, kk', l, m, n, o, p, q) kk kk' | |
Defined in Control.Lens.Tuple | |
| Field11 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a, b, c, d, e, f, g, h, i, j, kk', l, m, n, o, p, q, r) kk kk' | |
Defined in Control.Lens.Tuple | |
| Field11 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b, c, d, e, f, g, h, i, j, kk', l, m, n, o, p, q, r, s) kk kk' | |
Defined in Control.Lens.Tuple | |
class Field10 s t a b | s -> a, t -> b, s b -> t, t a -> s where #
Provides access to the 10th field of a tuple.
Minimal complete definition
Nothing
Instances
| 10 <= n => Field10 (V n a) (V n a) a a | |
| Field10 (a, b, c, d, e, f, g, h, i, j) (a, b, c, d, e, f, g, h, i, j') j j' | |
Defined in Control.Lens.Tuple | |
| Field10 (a, b, c, d, e, f, g, h, i, j, kk) (a, b, c, d, e, f, g, h, i, j', kk) j j' | |
Defined in Control.Lens.Tuple | |
| Field10 (a, b, c, d, e, f, g, h, i, j, kk, l) (a, b, c, d, e, f, g, h, i, j', kk, l) j j' | |
Defined in Control.Lens.Tuple | |
| Field10 (a, b, c, d, e, f, g, h, i, j, kk, l, m) (a, b, c, d, e, f, g, h, i, j', kk, l, m) j j' | |
Defined in Control.Lens.Tuple | |
| Field10 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n) (a, b, c, d, e, f, g, h, i, j', kk, l, m, n) j j' | |
Defined in Control.Lens.Tuple | |
| Field10 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o) (a, b, c, d, e, f, g, h, i, j', kk, l, m, n, o) j j' | |
Defined in Control.Lens.Tuple | |
| Field10 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p) (a, b, c, d, e, f, g, h, i, j', kk, l, m, n, o, p) j j' | |
Defined in Control.Lens.Tuple | |
| Field10 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) (a, b, c, d, e, f, g, h, i, j', kk, l, m, n, o, p, q) j j' | |
Defined in Control.Lens.Tuple | |
| Field10 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a, b, c, d, e, f, g, h, i, j', kk, l, m, n, o, p, q, r) j j' | |
Defined in Control.Lens.Tuple | |
| Field10 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b, c, d, e, f, g, h, i, j', kk, l, m, n, o, p, q, r, s) j j' | |
Defined in Control.Lens.Tuple | |
class Field9 s t a b | s -> a, t -> b, s b -> t, t a -> s where #
Provides access to the 9th field of a tuple.
Minimal complete definition
Nothing
Instances
| 9 <= n => Field9 (V n a) (V n a) a a | |
| Field9 (a, b, c, d, e, f, g, h, i) (a, b, c, d, e, f, g, h, i') i i' | |
Defined in Control.Lens.Tuple | |
| Field9 (a, b, c, d, e, f, g, h, i, j) (a, b, c, d, e, f, g, h, i', j) i i' | |
Defined in Control.Lens.Tuple | |
| Field9 (a, b, c, d, e, f, g, h, i, j, kk) (a, b, c, d, e, f, g, h, i', j, kk) i i' | |
Defined in Control.Lens.Tuple | |
| Field9 (a, b, c, d, e, f, g, h, i, j, kk, l) (a, b, c, d, e, f, g, h, i', j, kk, l) i i' | |
Defined in Control.Lens.Tuple | |
| Field9 (a, b, c, d, e, f, g, h, i, j, kk, l, m) (a, b, c, d, e, f, g, h, i', j, kk, l, m) i i' | |
Defined in Control.Lens.Tuple | |
| Field9 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n) (a, b, c, d, e, f, g, h, i', j, kk, l, m, n) i i' | |
Defined in Control.Lens.Tuple | |
| Field9 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o) (a, b, c, d, e, f, g, h, i', j, kk, l, m, n, o) i i' | |
Defined in Control.Lens.Tuple | |
| Field9 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p) (a, b, c, d, e, f, g, h, i', j, kk, l, m, n, o, p) i i' | |
Defined in Control.Lens.Tuple | |
| Field9 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) (a, b, c, d, e, f, g, h, i', j, kk, l, m, n, o, p, q) i i' | |
Defined in Control.Lens.Tuple | |
| Field9 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a, b, c, d, e, f, g, h, i', j, kk, l, m, n, o, p, q, r) i i' | |
Defined in Control.Lens.Tuple | |
| Field9 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b, c, d, e, f, g, h, i', j, kk, l, m, n, o, p, q, r, s) i i' | |
Defined in Control.Lens.Tuple | |
class Field8 s t a b | s -> a, t -> b, s b -> t, t a -> s where #
Provide access to the 8th field of a tuple.
Minimal complete definition
Nothing
Instances
| 8 <= n => Field8 (V n a) (V n a) a a | |
| Field8 (a, b, c, d, e, f, g, h) (a, b, c, d, e, f, g, h') h h' | |
Defined in Control.Lens.Tuple | |
| Field8 (a, b, c, d, e, f, g, h, i) (a, b, c, d, e, f, g, h', i) h h' | |
Defined in Control.Lens.Tuple | |
| Field8 (a, b, c, d, e, f, g, h, i, j) (a, b, c, d, e, f, g, h', i, j) h h' | |
Defined in Control.Lens.Tuple | |
| Field8 (a, b, c, d, e, f, g, h, i, j, kk) (a, b, c, d, e, f, g, h', i, j, kk) h h' | |
Defined in Control.Lens.Tuple | |
| Field8 (a, b, c, d, e, f, g, h, i, j, kk, l) (a, b, c, d, e, f, g, h', i, j, kk, l) h h' | |
Defined in Control.Lens.Tuple | |
| Field8 (a, b, c, d, e, f, g, h, i, j, kk, l, m) (a, b, c, d, e, f, g, h', i, j, kk, l, m) h h' | |
Defined in Control.Lens.Tuple | |
| Field8 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n) (a, b, c, d, e, f, g, h', i, j, kk, l, m, n) h h' | |
Defined in Control.Lens.Tuple | |
| Field8 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o) (a, b, c, d, e, f, g, h', i, j, kk, l, m, n, o) h h' | |
Defined in Control.Lens.Tuple | |
| Field8 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p) (a, b, c, d, e, f, g, h', i, j, kk, l, m, n, o, p) h h' | |
Defined in Control.Lens.Tuple | |
| Field8 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) (a, b, c, d, e, f, g, h', i, j, kk, l, m, n, o, p, q) h h' | |
Defined in Control.Lens.Tuple | |
| Field8 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a, b, c, d, e, f, g, h', i, j, kk, l, m, n, o, p, q, r) h h' | |
Defined in Control.Lens.Tuple | |
| Field8 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b, c, d, e, f, g, h', i, j, kk, l, m, n, o, p, q, r, s) h h' | |
Defined in Control.Lens.Tuple | |
class Field7 s t a b | s -> a, t -> b, s b -> t, t a -> s where #
Provide access to the 7th field of a tuple.
Minimal complete definition
Nothing
Instances
| 7 <= n => Field7 (V n a) (V n a) a a | |
| Field7 (a, b, c, d, e, f, g) (a, b, c, d, e, f, g') g g' | |
Defined in Control.Lens.Tuple | |
| Field7 (a, b, c, d, e, f, g, h) (a, b, c, d, e, f, g', h) g g' | |
Defined in Control.Lens.Tuple | |
| Field7 (a, b, c, d, e, f, g, h, i) (a, b, c, d, e, f, g', h, i) g g' | |
Defined in Control.Lens.Tuple | |
| Field7 (a, b, c, d, e, f, g, h, i, j) (a, b, c, d, e, f, g', h, i, j) g g' | |
Defined in Control.Lens.Tuple | |
| Field7 (a, b, c, d, e, f, g, h, i, j, kk) (a, b, c, d, e, f, g', h, i, j, kk) g g' | |
Defined in Control.Lens.Tuple | |
| Field7 (a, b, c, d, e, f, g, h, i, j, kk, l) (a, b, c, d, e, f, g', h, i, j, kk, l) g g' | |
Defined in Control.Lens.Tuple | |
| Field7 (a, b, c, d, e, f, g, h, i, j, kk, l, m) (a, b, c, d, e, f, g', h, i, j, kk, l, m) g g' | |
Defined in Control.Lens.Tuple | |
| Field7 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n) (a, b, c, d, e, f, g', h, i, j, kk, l, m, n) g g' | |
Defined in Control.Lens.Tuple | |
| Field7 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o) (a, b, c, d, e, f, g', h, i, j, kk, l, m, n, o) g g' | |
Defined in Control.Lens.Tuple | |
| Field7 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p) (a, b, c, d, e, f, g', h, i, j, kk, l, m, n, o, p) g g' | |
Defined in Control.Lens.Tuple | |
| Field7 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) (a, b, c, d, e, f, g', h, i, j, kk, l, m, n, o, p, q) g g' | |
Defined in Control.Lens.Tuple | |
| Field7 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a, b, c, d, e, f, g', h, i, j, kk, l, m, n, o, p, q, r) g g' | |
Defined in Control.Lens.Tuple | |
| Field7 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b, c, d, e, f, g', h, i, j, kk, l, m, n, o, p, q, r, s) g g' | |
Defined in Control.Lens.Tuple | |
class Field6 s t a b | s -> a, t -> b, s b -> t, t a -> s where #
Provides access to the 6th element of a tuple.
Minimal complete definition
Nothing
Instances
| Field6 (Plucker a) (Plucker a) a a | |
| 6 <= n => Field6 (V n a) (V n a) a a | |
| Field6 (a, b, c, d, e, f) (a, b, c, d, e, f') f f' | |
Defined in Control.Lens.Tuple | |
| Field6 (a, b, c, d, e, f, g) (a, b, c, d, e, f', g) f f' | |
Defined in Control.Lens.Tuple | |
| Field6 (a, b, c, d, e, f, g, h) (a, b, c, d, e, f', g, h) f f' | |
Defined in Control.Lens.Tuple | |
| Field6 (a, b, c, d, e, f, g, h, i) (a, b, c, d, e, f', g, h, i) f f' | |
Defined in Control.Lens.Tuple | |
| Field6 (a, b, c, d, e, f, g, h, i, j) (a, b, c, d, e, f', g, h, i, j) f f' | |
Defined in Control.Lens.Tuple | |
| Field6 (a, b, c, d, e, f, g, h, i, j, kk) (a, b, c, d, e, f', g, h, i, j, kk) f f' | |
Defined in Control.Lens.Tuple | |
| Field6 (a, b, c, d, e, f, g, h, i, j, kk, l) (a, b, c, d, e, f', g, h, i, j, kk, l) f f' | |
Defined in Control.Lens.Tuple | |
| Field6 (a, b, c, d, e, f, g, h, i, j, kk, l, m) (a, b, c, d, e, f', g, h, i, j, kk, l, m) f f' | |
Defined in Control.Lens.Tuple | |
| Field6 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n) (a, b, c, d, e, f', g, h, i, j, kk, l, m, n) f f' | |
Defined in Control.Lens.Tuple | |
| Field6 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o) (a, b, c, d, e, f', g, h, i, j, kk, l, m, n, o) f f' | |
Defined in Control.Lens.Tuple | |
| Field6 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p) (a, b, c, d, e, f', g, h, i, j, kk, l, m, n, o, p) f f' | |
Defined in Control.Lens.Tuple | |
| Field6 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) (a, b, c, d, e, f', g, h, i, j, kk, l, m, n, o, p, q) f f' | |
Defined in Control.Lens.Tuple | |
| Field6 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a, b, c, d, e, f', g, h, i, j, kk, l, m, n, o, p, q, r) f f' | |
Defined in Control.Lens.Tuple | |
| Field6 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b, c, d, e, f', g, h, i, j, kk, l, m, n, o, p, q, r, s) f f' | |
Defined in Control.Lens.Tuple | |
class Field5 s t a b | s -> a, t -> b, s b -> t, t a -> s where #
Provides access to the 5th field of a tuple.
Minimal complete definition
Nothing
Instances
| Field5 (Plucker a) (Plucker a) a a | |
| 5 <= n => Field5 (V n a) (V n a) a a | |
| Field5 (a, b, c, d, e) (a, b, c, d, e') e e' | |
Defined in Control.Lens.Tuple | |
| Field5 (a, b, c, d, e, f) (a, b, c, d, e', f) e e' | |
Defined in Control.Lens.Tuple | |
| Field5 (a, b, c, d, e, f, g) (a, b, c, d, e', f, g) e e' | |
Defined in Control.Lens.Tuple | |
| Field5 (a, b, c, d, e, f, g, h) (a, b, c, d, e', f, g, h) e e' | |
Defined in Control.Lens.Tuple | |
| Field5 (a, b, c, d, e, f, g, h, i) (a, b, c, d, e', f, g, h, i) e e' | |
Defined in Control.Lens.Tuple | |
| Field5 (a, b, c, d, e, f, g, h, i, j) (a, b, c, d, e', f, g, h, i, j) e e' | |
Defined in Control.Lens.Tuple | |
| Field5 (a, b, c, d, e, f, g, h, i, j, kk) (a, b, c, d, e', f, g, h, i, j, kk) e e' | |
Defined in Control.Lens.Tuple | |
| Field5 (a, b, c, d, e, f, g, h, i, j, kk, l) (a, b, c, d, e', f, g, h, i, j, kk, l) e e' | |
Defined in Control.Lens.Tuple | |
| Field5 (a, b, c, d, e, f, g, h, i, j, kk, l, m) (a, b, c, d, e', f, g, h, i, j, kk, l, m) e e' | |
Defined in Control.Lens.Tuple | |
| Field5 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n) (a, b, c, d, e', f, g, h, i, j, kk, l, m, n) e e' | |
Defined in Control.Lens.Tuple | |
| Field5 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o) (a, b, c, d, e', f, g, h, i, j, kk, l, m, n, o) e e' | |
Defined in Control.Lens.Tuple | |
| Field5 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p) (a, b, c, d, e', f, g, h, i, j, kk, l, m, n, o, p) e e' | |
Defined in Control.Lens.Tuple | |
| Field5 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) (a, b, c, d, e', f, g, h, i, j, kk, l, m, n, o, p, q) e e' | |
Defined in Control.Lens.Tuple | |
| Field5 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a, b, c, d, e', f, g, h, i, j, kk, l, m, n, o, p, q, r) e e' | |
Defined in Control.Lens.Tuple | |
| Field5 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b, c, d, e', f, g, h, i, j, kk, l, m, n, o, p, q, r, s) e e' | |
Defined in Control.Lens.Tuple | |
class Field4 s t a b | s -> a, t -> b, s b -> t, t a -> s where #
Provide access to the 4th field of a tuple.
Minimal complete definition
Nothing
Instances
| Field4 (Plucker a) (Plucker a) a a | |
| Field4 (Quaternion a) (Quaternion a) a a | |
Defined in Linear.Quaternion Methods _4 :: Lens (Quaternion a) (Quaternion a) a a # | |
| Field4 (V4 a) (V4 a) a a | |
| 4 <= n => Field4 (V n a) (V n a) a a | |
| Field4 (a, b, c, d) (a, b, c, d') d d' | |
Defined in Control.Lens.Tuple | |
| Field4 (a, b, c, d, e) (a, b, c, d', e) d d' | |
Defined in Control.Lens.Tuple | |
| Field4 (a, b, c, d, e, f) (a, b, c, d', e, f) d d' | |
Defined in Control.Lens.Tuple | |
| Field4 (a, b, c, d, e, f, g) (a, b, c, d', e, f, g) d d' | |
Defined in Control.Lens.Tuple | |
| Field4 (a, b, c, d, e, f, g, h) (a, b, c, d', e, f, g, h) d d' | |
Defined in Control.Lens.Tuple | |
| Field4 (a, b, c, d, e, f, g, h, i) (a, b, c, d', e, f, g, h, i) d d' | |
Defined in Control.Lens.Tuple | |
| Field4 (a, b, c, d, e, f, g, h, i, j) (a, b, c, d', e, f, g, h, i, j) d d' | |
Defined in Control.Lens.Tuple | |
| Field4 (a, b, c, d, e, f, g, h, i, j, kk) (a, b, c, d', e, f, g, h, i, j, kk) d d' | |
Defined in Control.Lens.Tuple | |
| Field4 (a, b, c, d, e, f, g, h, i, j, kk, l) (a, b, c, d', e, f, g, h, i, j, kk, l) d d' | |
Defined in Control.Lens.Tuple | |
| Field4 (a, b, c, d, e, f, g, h, i, j, kk, l, m) (a, b, c, d', e, f, g, h, i, j, kk, l, m) d d' | |
Defined in Control.Lens.Tuple | |
| Field4 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n) (a, b, c, d', e, f, g, h, i, j, kk, l, m, n) d d' | |
Defined in Control.Lens.Tuple | |
| Field4 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o) (a, b, c, d', e, f, g, h, i, j, kk, l, m, n, o) d d' | |
Defined in Control.Lens.Tuple | |
| Field4 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p) (a, b, c, d', e, f, g, h, i, j, kk, l, m, n, o, p) d d' | |
Defined in Control.Lens.Tuple | |
| Field4 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) (a, b, c, d', e, f, g, h, i, j, kk, l, m, n, o, p, q) d d' | |
Defined in Control.Lens.Tuple | |
| Field4 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a, b, c, d', e, f, g, h, i, j, kk, l, m, n, o, p, q, r) d d' | |
Defined in Control.Lens.Tuple | |
| Field4 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b, c, d', e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) d d' | |
Defined in Control.Lens.Tuple | |
class Field3 s t a b | s -> a, t -> b, s b -> t, t a -> s where #
Provides access to the 3rd field of a tuple.
Minimal complete definition
Nothing
Instances
| Field3 (V3 a) (V3 a) a a | |
| Field3 (Plucker a) (Plucker a) a a | |
| Field3 (Quaternion a) (Quaternion a) a a | |
Defined in Linear.Quaternion Methods _3 :: Lens (Quaternion a) (Quaternion a) a a # | |
| Field3 (V4 a) (V4 a) a a | |
| Field3 (a, b, c) (a, b, c') c c' | |
Defined in Control.Lens.Tuple | |
| 3 <= n => Field3 (V n a) (V n a) a a | |
| Field3 (a, b, c, d) (a, b, c', d) c c' | |
Defined in Control.Lens.Tuple | |
| Field3 (a, b, c, d, e) (a, b, c', d, e) c c' | |
Defined in Control.Lens.Tuple | |
| Field3 (a, b, c, d, e, f) (a, b, c', d, e, f) c c' | |
Defined in Control.Lens.Tuple | |
| Field3 (a, b, c, d, e, f, g) (a, b, c', d, e, f, g) c c' | |
Defined in Control.Lens.Tuple | |
| Field3 (a, b, c, d, e, f, g, h) (a, b, c', d, e, f, g, h) c c' | |
Defined in Control.Lens.Tuple | |
| Field3 (a, b, c, d, e, f, g, h, i) (a, b, c', d, e, f, g, h, i) c c' | |
Defined in Control.Lens.Tuple | |
| Field3 (a, b, c, d, e, f, g, h, i, j) (a, b, c', d, e, f, g, h, i, j) c c' | |
Defined in Control.Lens.Tuple | |
| Field3 (a, b, c, d, e, f, g, h, i, j, kk) (a, b, c', d, e, f, g, h, i, j, kk) c c' | |
Defined in Control.Lens.Tuple | |
| Field3 (a, b, c, d, e, f, g, h, i, j, kk, l) (a, b, c', d, e, f, g, h, i, j, kk, l) c c' | |
Defined in Control.Lens.Tuple | |
| Field3 (a, b, c, d, e, f, g, h, i, j, kk, l, m) (a, b, c', d, e, f, g, h, i, j, kk, l, m) c c' | |
Defined in Control.Lens.Tuple | |
| Field3 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n) (a, b, c', d, e, f, g, h, i, j, kk, l, m, n) c c' | |
Defined in Control.Lens.Tuple | |
| Field3 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o) (a, b, c', d, e, f, g, h, i, j, kk, l, m, n, o) c c' | |
Defined in Control.Lens.Tuple | |
| Field3 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p) (a, b, c', d, e, f, g, h, i, j, kk, l, m, n, o, p) c c' | |
Defined in Control.Lens.Tuple | |
| Field3 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) (a, b, c', d, e, f, g, h, i, j, kk, l, m, n, o, p, q) c c' | |
Defined in Control.Lens.Tuple | |
| Field3 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a, b, c', d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) c c' | |
Defined in Control.Lens.Tuple | |
| Field3 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b, c', d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) c c' | |
Defined in Control.Lens.Tuple | |
class Field2 s t a b | s -> a, t -> b, s b -> t, t a -> s where #
Provides access to the 2nd field of a tuple.
Minimal complete definition
Nothing
Methods
Access the 2nd field of a tuple.
>>>_2 .~ "hello" $ (1,(),3,4)(1,"hello",3,4)
>>>(1,2,3,4) & _2 *~ 3(1,6,3,4)
>>>_2 print (1,2)2 (1,())
anyOf_2:: (s ->Bool) -> (a, s) ->Booltraverse._2:: (Applicativef,Traversablet) => (a -> f b) -> t (s, a) -> f (t (s, b))foldMapOf(traverse._2) :: (Traversablet,Monoidm) => (s -> m) -> t (b, s) -> m
Instances
| Field2 (V2 a) (V2 a) a a | |
| Field2 (V3 a) (V3 a) a a | |
| Field2 (Plucker a) (Plucker a) a a | |
| Field2 (Quaternion a) (Quaternion a) a a | |
Defined in Linear.Quaternion Methods _2 :: Lens (Quaternion a) (Quaternion a) a a # | |
| Field2 (V4 a) (V4 a) a a | |
| Field2 (a, b) (a, b') b b' |
|
Defined in Control.Lens.Tuple | |
| Field2 (a, b, c) (a, b', c) b b' | |
Defined in Control.Lens.Tuple | |
| 2 <= n => Field2 (V n a) (V n a) a a | |
| Field2 (a, b, c, d) (a, b', c, d) b b' | |
Defined in Control.Lens.Tuple | |
| Field2 ((f :*: g) p) ((f :*: g') p) (g p) (g' p) | |
| Field2 (Product f g a) (Product f g' a) (g a) (g' a) | |
| Field2 (a, b, c, d, e) (a, b', c, d, e) b b' | |
Defined in Control.Lens.Tuple | |
| Field2 (a, b, c, d, e, f) (a, b', c, d, e, f) b b' | |
Defined in Control.Lens.Tuple | |
| Field2 (a, b, c, d, e, f, g) (a, b', c, d, e, f, g) b b' | |
Defined in Control.Lens.Tuple | |
| Field2 (a, b, c, d, e, f, g, h) (a, b', c, d, e, f, g, h) b b' | |
Defined in Control.Lens.Tuple | |
| Field2 (a, b, c, d, e, f, g, h, i) (a, b', c, d, e, f, g, h, i) b b' | |
Defined in Control.Lens.Tuple | |
| Field2 (a, b, c, d, e, f, g, h, i, j) (a, b', c, d, e, f, g, h, i, j) b b' | |
Defined in Control.Lens.Tuple | |
| Field2 (a, b, c, d, e, f, g, h, i, j, kk) (a, b', c, d, e, f, g, h, i, j, kk) b b' | |
Defined in Control.Lens.Tuple | |
| Field2 (a, b, c, d, e, f, g, h, i, j, kk, l) (a, b', c, d, e, f, g, h, i, j, kk, l) b b' | |
Defined in Control.Lens.Tuple | |
| Field2 (a, b, c, d, e, f, g, h, i, j, kk, l, m) (a, b', c, d, e, f, g, h, i, j, kk, l, m) b b' | |
Defined in Control.Lens.Tuple | |
| Field2 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n) (a, b', c, d, e, f, g, h, i, j, kk, l, m, n) b b' | |
Defined in Control.Lens.Tuple | |
| Field2 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o) (a, b', c, d, e, f, g, h, i, j, kk, l, m, n, o) b b' | |
Defined in Control.Lens.Tuple | |
| Field2 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p) (a, b', c, d, e, f, g, h, i, j, kk, l, m, n, o, p) b b' | |
Defined in Control.Lens.Tuple | |
| Field2 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) (a, b', c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) b b' | |
Defined in Control.Lens.Tuple | |
| Field2 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a, b', c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) b b' | |
Defined in Control.Lens.Tuple | |
| Field2 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a, b', c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) b b' | |
Defined in Control.Lens.Tuple | |
class Field1 s t a b | s -> a, t -> b, s b -> t, t a -> s where #
Provides access to 1st field of a tuple.
Minimal complete definition
Nothing
Methods
Access the 1st field of a tuple (and possibly change its type).
>>>(1,2)^._11
>>>_1 .~ "hello" $ (1,2)("hello",2)
>>>(1,2) & _1 .~ "hello"("hello",2)
>>>_1 putStrLn ("hello","world")hello ((),"world")
This can also be used on larger tuples as well:
>>>(1,2,3,4,5) & _1 +~ 41(42,2,3,4,5)
_1::Lens(a,b) (a',b) a a'_1::Lens(a,b,c) (a',b,c) a a'_1::Lens(a,b,c,d) (a',b,c,d) a a' ..._1::Lens(a,b,c,d,e,f,g,h,i) (a',b,c,d,e,f,g,h,i) a a'
Instances
| Field1 (Identity a) (Identity b) a b | |
| Field1 (V2 a) (V2 a) a a | |
| Field1 (V3 a) (V3 a) a a | |
| Field1 (Plucker a) (Plucker a) a a | |
| Field1 (Quaternion a) (Quaternion a) a a | |
Defined in Linear.Quaternion Methods _1 :: Lens (Quaternion a) (Quaternion a) a a # | |
| Field1 (V4 a) (V4 a) a a | |
| Field1 (V1 a) (V1 b) a b | |
| Field1 (a, b) (a', b) a a' |
|
Defined in Control.Lens.Tuple | |
| Field1 (a, b, c) (a', b, c) a a' | |
Defined in Control.Lens.Tuple | |
| 1 <= n => Field1 (V n a) (V n a) a a | |
| Field1 (a, b, c, d) (a', b, c, d) a a' | |
Defined in Control.Lens.Tuple | |
| Field1 ((f :*: g) p) ((f' :*: g) p) (f p) (f' p) | |
| Field1 (Product f g a) (Product f' g a) (f a) (f' a) | |
| Field1 (a, b, c, d, e) (a', b, c, d, e) a a' | |
Defined in Control.Lens.Tuple | |
| Field1 (a, b, c, d, e, f) (a', b, c, d, e, f) a a' | |
Defined in Control.Lens.Tuple | |
| Field1 (a, b, c, d, e, f, g) (a', b, c, d, e, f, g) a a' | |
Defined in Control.Lens.Tuple | |
| Field1 (a, b, c, d, e, f, g, h) (a', b, c, d, e, f, g, h) a a' | |
Defined in Control.Lens.Tuple | |
| Field1 (a, b, c, d, e, f, g, h, i) (a', b, c, d, e, f, g, h, i) a a' | |
Defined in Control.Lens.Tuple | |
| Field1 (a, b, c, d, e, f, g, h, i, j) (a', b, c, d, e, f, g, h, i, j) a a' | |
Defined in Control.Lens.Tuple | |
| Field1 (a, b, c, d, e, f, g, h, i, j, kk) (a', b, c, d, e, f, g, h, i, j, kk) a a' | |
Defined in Control.Lens.Tuple | |
| Field1 (a, b, c, d, e, f, g, h, i, j, kk, l) (a', b, c, d, e, f, g, h, i, j, kk, l) a a' | |
Defined in Control.Lens.Tuple | |
| Field1 (a, b, c, d, e, f, g, h, i, j, kk, l, m) (a', b, c, d, e, f, g, h, i, j, kk, l, m) a a' | |
Defined in Control.Lens.Tuple | |
| Field1 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n) (a', b, c, d, e, f, g, h, i, j, kk, l, m, n) a a' | |
Defined in Control.Lens.Tuple | |
| Field1 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o) (a', b, c, d, e, f, g, h, i, j, kk, l, m, n, o) a a' | |
Defined in Control.Lens.Tuple | |
| Field1 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p) (a', b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p) a a' | |
Defined in Control.Lens.Tuple | |
| Field1 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) (a', b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q) a a' | |
Defined in Control.Lens.Tuple | |
| Field1 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) (a', b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r) a a' | |
Defined in Control.Lens.Tuple | |
| Field1 (a, b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) (a', b, c, d, e, f, g, h, i, j, kk, l, m, n, o, p, q, r, s) a a' | |
Defined in Control.Lens.Tuple | |
type Accessing (p :: Type -> Type -> Type) m s a = p a (Const m a) -> s -> Const m s #
This is a convenient alias used when consuming (indexed) getters and (indexed) folds in a highly general fashion.
type IndexedGetting i m s a = Indexed i a (Const m a) -> s -> Const m s #
Used to consume an IndexedFold.
type Getting r s a = (a -> Const r a) -> s -> Const r s #
When you see this in a type signature it indicates that you can
pass the function a Lens, Getter,
Traversal, Fold,
Prism, Iso, or one of
the indexed variants, and it will just "do the right thing".
Most Getter combinators are able to be used with both a Getter or a
Fold in limited situations, to do so, they need to be
monomorphic in what we are going to extract with Const. To be compatible
with Lens, Traversal and
Iso we also restricted choices of the irrelevant t and
b parameters.
If a function accepts a , then when Getting r s ar is a Monoid, then
you can pass a Fold (or
Traversal), otherwise you can only pass this a
Getter or Lens.
to :: (Profunctor p, Contravariant f) => (s -> a) -> Optic' p f s a #
ito :: (Indexable i p, Contravariant f) => (s -> (i, a)) -> Over' p f s a #
ito:: (s -> (i, a)) ->IndexedGetteri s a
like :: (Profunctor p, Contravariant f, Functor f) => a -> Optic' p f s a #
ilike :: (Indexable i p, Contravariant f, Functor f) => i -> a -> Over' p f s a #
ilike:: i -> a ->IndexedGetteri s a
view :: MonadReader s m => Getting a s a -> m a #
View the value pointed to by a Getter, Iso or
Lens or the result of folding over all the results of a
Fold or Traversal that points
at a monoidal value.
view.to≡id
>>>view (to f) af a
>>>view _2 (1,"hello")"hello"
>>>view (to succ) 56
>>>view (_2._1) ("hello",("world","!!!"))"world"
As view is commonly used to access the target of a Getter or obtain a monoidal summary of the targets of a Fold,
It may be useful to think of it as having one of these more restricted signatures:
view::Getters a -> s -> aview::Monoidm =>Folds m -> s -> mview::Iso's a -> s -> aview::Lens's a -> s -> aview::Monoidm =>Traversal's m -> s -> m
In a more general setting, such as when working with a Monad transformer stack you can use:
view::MonadReaders m =>Getters a -> m aview:: (MonadReaders m,Monoida) =>Folds a -> m aview::MonadReaders m =>Iso's a -> m aview::MonadReaders m =>Lens's a -> m aview:: (MonadReaders m,Monoida) =>Traversal's a -> m a
views :: MonadReader s m => LensLike' (Const r :: Type -> Type) s a -> (a -> r) -> m r #
View a function of the value pointed to by a Getter or Lens or the result of
folding over the result of mapping the targets of a Fold or
Traversal.
viewsl f ≡view(l.tof)
>>>views (to f) g ag (f a)
>>>views _2 length (1,"hello")5
As views is commonly used to access the target of a Getter or obtain a monoidal summary of the targets of a Fold,
It may be useful to think of it as having one of these more restricted signatures:
views::Getters a -> (a -> r) -> s -> rviews::Monoidm =>Folds a -> (a -> m) -> s -> mviews::Iso's a -> (a -> r) -> s -> rviews::Lens's a -> (a -> r) -> s -> rviews::Monoidm =>Traversal's a -> (a -> m) -> s -> m
In a more general setting, such as when working with a Monad transformer stack you can use:
views::MonadReaders m =>Getters a -> (a -> r) -> m rviews:: (MonadReaders m,Monoidr) =>Folds a -> (a -> r) -> m rviews::MonadReaders m =>Iso's a -> (a -> r) -> m rviews::MonadReaders m =>Lens's a -> (a -> r) -> m rviews:: (MonadReaders m,Monoidr) =>Traversal's a -> (a -> r) -> m r
views::MonadReaders m =>Gettingr s a -> (a -> r) -> m r
(^.) :: s -> Getting a s a -> a infixl 8 #
View the value pointed to by a Getter or Lens or the
result of folding over all the results of a Fold or
Traversal that points at a monoidal values.
This is the same operation as view with the arguments flipped.
The fixity and semantics are such that subsequent field accesses can be
performed with (.).
>>>(a,b)^._2b
>>>("hello","world")^._2"world"
>>>import Data.Complex>>>((0, 1 :+ 2), 3)^._1._2.to magnitude2.23606797749979
(^.) :: s ->Getters a -> a (^.) ::Monoidm => s ->Folds m -> m (^.) :: s ->Iso's a -> a (^.) :: s ->Lens's a -> a (^.) ::Monoidm => s ->Traversal's m -> m
use :: MonadState s m => Getting a s a -> m a #
Use the target of a Lens, Iso, or
Getter in the current state, or use a summary of a
Fold or Traversal that points
to a monoidal value.
>>>evalState (use _1) (a,b)a
>>>evalState (use _1) ("hello","world")"hello"
use::MonadStates m =>Getters a -> m ause:: (MonadStates m,Monoidr) =>Folds r -> m ruse::MonadStates m =>Iso's a -> m ause::MonadStates m =>Lens's a -> m ause:: (MonadStates m,Monoidr) =>Traversal's r -> m r
uses :: MonadState s m => LensLike' (Const r :: Type -> Type) s a -> (a -> r) -> m r #
Use the target of a Lens, Iso or
Getter in the current state, or use a summary of a
Fold or Traversal that
points to a monoidal value.
>>>evalState (uses _1 length) ("hello","world")5
uses::MonadStates m =>Getters a -> (a -> r) -> m ruses:: (MonadStates m,Monoidr) =>Folds a -> (a -> r) -> m ruses::MonadStates m =>Lens's a -> (a -> r) -> m ruses::MonadStates m =>Iso's a -> (a -> r) -> m ruses:: (MonadStates m,Monoidr) =>Traversal's a -> (a -> r) -> m r
uses::MonadStates m =>Gettingr s t a b -> (a -> r) -> m r
listening :: MonadWriter w m => Getting u w u -> m a -> m (a, u) #
This is a generalized form of listen that only extracts the portion of
the log that is focused on by a Getter. If given a Fold or a Traversal
then a monoidal summary of the parts of the log that are visited will be
returned.
listening::MonadWriterw m =>Getterw u -> m a -> m (a, u)listening::MonadWriterw m =>Lens'w u -> m a -> m (a, u)listening::MonadWriterw m =>Iso'w u -> m a -> m (a, u)listening:: (MonadWriterw m,Monoidu) =>Foldw u -> m a -> m (a, u)listening:: (MonadWriterw m,Monoidu) =>Traversal'w u -> m a -> m (a, u)listening:: (MonadWriterw m,Monoidu) =>Prism'w u -> m a -> m (a, u)
ilistening :: MonadWriter w m => IndexedGetting i (i, u) w u -> m a -> m (a, (i, u)) #
This is a generalized form of listen that only extracts the portion of
the log that is focused on by a Getter. If given a Fold or a Traversal
then a monoidal summary of the parts of the log that are visited will be
returned.
ilistening::MonadWriterw m =>IndexedGetteri w u -> m a -> m (a, (i, u))ilistening::MonadWriterw m =>IndexedLens'i w u -> m a -> m (a, (i, u))ilistening:: (MonadWriterw m,Monoidu) =>IndexedFoldi w u -> m a -> m (a, (i, u))ilistening:: (MonadWriterw m,Monoidu) =>IndexedTraversal'i w u -> m a -> m (a, (i, u))
listenings :: MonadWriter w m => Getting v w u -> (u -> v) -> m a -> m (a, v) #
This is a generalized form of listen that only extracts the portion of
the log that is focused on by a Getter. If given a Fold or a Traversal
then a monoidal summary of the parts of the log that are visited will be
returned.
listenings::MonadWriterw m =>Getterw u -> (u -> v) -> m a -> m (a, v)listenings::MonadWriterw m =>Lens'w u -> (u -> v) -> m a -> m (a, v)listenings::MonadWriterw m =>Iso'w u -> (u -> v) -> m a -> m (a, v)listenings:: (MonadWriterw m,Monoidv) =>Foldw u -> (u -> v) -> m a -> m (a, v)listenings:: (MonadWriterw m,Monoidv) =>Traversal'w u -> (u -> v) -> m a -> m (a, v)listenings:: (MonadWriterw m,Monoidv) =>Prism'w u -> (u -> v) -> m a -> m (a, v)
ilistenings :: MonadWriter w m => IndexedGetting i v w u -> (i -> u -> v) -> m a -> m (a, v) #
This is a generalized form of listen that only extracts the portion of
the log that is focused on by a Getter. If given a Fold or a Traversal
then a monoidal summary of the parts of the log that are visited will be
returned.
ilistenings::MonadWriterw m =>IndexedGetterw u -> (i -> u -> v) -> m a -> m (a, v)ilistenings::MonadWriterw m =>IndexedLens'w u -> (i -> u -> v) -> m a -> m (a, v)ilistenings:: (MonadWriterw m,Monoidv) =>IndexedFoldw u -> (i -> u -> v) -> m a -> m (a, v)ilistenings:: (MonadWriterw m,Monoidv) =>IndexedTraversal'w u -> (i -> u -> v) -> m a -> m (a, v)
iview :: MonadReader s m => IndexedGetting i (i, a) s a -> m (i, a) #
View the index and value of an IndexedGetter into the current environment as a pair.
When applied to an IndexedFold the result will most likely be a nonsensical monoidal summary of
the indices tupled with a monoidal summary of the values and probably not whatever it is you wanted.
iviews :: MonadReader s m => IndexedGetting i r s a -> (i -> a -> r) -> m r #
View a function of the index and value of an IndexedGetter into the current environment.
When applied to an IndexedFold the result will be a monoidal summary instead of a single answer.
iviews≡ifoldMapOf
iuse :: MonadState s m => IndexedGetting i (i, a) s a -> m (i, a) #
Use the index and value of an IndexedGetter into the current state as a pair.
When applied to an IndexedFold the result will most likely be a nonsensical monoidal summary of
the indices tupled with a monoidal summary of the values and probably not whatever it is you wanted.
iuses :: MonadState s m => IndexedGetting i r s a -> (i -> a -> r) -> m r #
Use a function of the index and value of an IndexedGetter into the current state.
When applied to an IndexedFold the result will be a monoidal summary instead of a single answer.
(^@.) :: s -> IndexedGetting i (i, a) s a -> (i, a) infixl 8 #
View the index and value of an IndexedGetter or IndexedLens.
This is the same operation as iview with the arguments flipped.
The fixity and semantics are such that subsequent field accesses can be
performed with (.).
(^@.) :: s ->IndexedGetteri s a -> (i, a) (^@.) :: s ->IndexedLens'i s a -> (i, a)
The result probably doesn't have much meaning when applied to an IndexedFold.
getting :: (Profunctor p, Profunctor q, Functor f, Contravariant f) => Optical p q f s t a b -> Optical' p q f s a #
Coerce a Getter-compatible Optical to an Optical'. This
is useful when using a Traversal that is not simple as a Getter or a
Fold.
getting::Traversals t a b ->Folds agetting::Lenss t a b ->Getters agetting::IndexedTraversali s t a b ->IndexedFoldi s agetting::IndexedLensi s t a b ->IndexedGetteri s a
re :: AReview t b -> Getter b t #
Turn a Prism or Iso around to build a Getter.
If you have an Iso, from is a more powerful version of this function
that will return an Iso instead of a mere Getter.
>>>5 ^.re _LeftLeft 5
>>>6 ^.re (_Left.unto succ)Left 7
review≡view.rereviews≡views.rereuse≡use.rereuses≡uses.re
re::Prisms t a b ->Getterb tre::Isos t a b ->Getterb t
review :: MonadReader b m => AReview t b -> m t #
This can be used to turn an Iso or Prism around and view a value (or the current environment) through it the other way.
review≡view.rereview.unto≡id
>>>review _Left "mustard"Left "mustard"
>>>review (unto succ) 56
Usually review is used in the (->) Monad with a Prism or Iso, in which case it may be useful to think of
it as having one of these more restricted type signatures:
review::Iso's a -> a -> sreview::Prism's a -> a -> s
However, when working with a Monad transformer stack, it is sometimes useful to be able to review the current environment, in which case
it may be beneficial to think of it as having one of these slightly more liberal type signatures:
review::MonadReadera m =>Iso's a -> m sreview::MonadReadera m =>Prism's a -> m s
reviews :: MonadReader b m => AReview t b -> (t -> r) -> m r #
This can be used to turn an Iso or Prism around and view a value (or the current environment) through it the other way,
applying a function.
reviews≡views.rereviews(untof) g ≡ g.f
>>>reviews _Left isRight "mustard"False
>>>reviews (unto succ) (*2) 38
Usually this function is used in the (->) Monad with a Prism or Iso, in which case it may be useful to think of
it as having one of these more restricted type signatures:
reviews::Iso's a -> (s -> r) -> a -> rreviews::Prism's a -> (s -> r) -> a -> r
However, when working with a Monad transformer stack, it is sometimes useful to be able to review the current environment, in which case
it may be beneficial to think of it as having one of these slightly more liberal type signatures:
reviews::MonadReadera m =>Iso's a -> (s -> r) -> m rreviews::MonadReadera m =>Prism's a -> (s -> r) -> m r
reuse :: MonadState b m => AReview t b -> m t #
This can be used to turn an Iso or Prism around and use a value (or the current environment) through it the other way.
reuse≡use.rereuse.unto≡gets
>>>evalState (reuse _Left) 5Left 5
>>>evalState (reuse (unto succ)) 56
reuse::MonadStatea m =>Prism's a -> m sreuse::MonadStatea m =>Iso's a -> m s
reuses :: MonadState b m => AReview t b -> (t -> r) -> m r #
This can be used to turn an Iso or Prism around and use the current state through it the other way,
applying a function.
reuses≡uses.rereuses(untof) g ≡gets(g.f)
>>>evalState (reuses _Left isLeft) (5 :: Int)True
reuses::MonadStatea m =>Prism's a -> (s -> r) -> m rreuses::MonadStatea m =>Iso's a -> (s -> r) -> m r
type APrism s t a b = Market a b a (Identity b) -> Market a b s (Identity t) #
If you see this in a signature for a function, the function is expecting a Prism.
withPrism :: APrism s t a b -> ((b -> t) -> (s -> Either t a) -> r) -> r #
Convert APrism to the pair of functions that characterize it.
clonePrism :: APrism s t a b -> Prism s t a b #
Clone a Prism so that you can reuse the same monomorphically typed Prism for different purposes.
See cloneLens and cloneTraversal for examples of why you might want to do this.
without :: APrism s t a b -> APrism u v c d -> Prism (Either s u) (Either t v) (Either a c) (Either b d) #
aside :: APrism s t a b -> Prism (e, s) (e, t) (e, a) (e, b) #
Use a Prism to work over part of a structure.
below :: Traversable f => APrism' s a -> Prism' (f s) (f a) #
lift a Prism through a Traversable functor, giving a Prism that matches only if all the elements of the container match the Prism.
>>>[Left 1, Right "foo", Left 4, Right "woot"]^..below _Right[]
>>>[Right "hail hydra!", Right "foo", Right "blah", Right "woot"]^..below _Right[["hail hydra!","foo","blah","woot"]]
isn't :: APrism s t a b -> s -> Bool #
Check to see if this Prism doesn't match.
>>>isn't _Left (Right 12)True
>>>isn't _Left (Left 12)False
>>>isn't _Empty []False
matching :: APrism s t a b -> s -> Either t a #
Retrieve the value targeted by a Prism or return the
original value while allowing the type to change if it does
not match.
>>>matching _Just (Just 12)Right 12
>>>matching _Just (Nothing :: Maybe Int) :: Either (Maybe Bool) IntLeft Nothing
_Left :: Prism (Either a c) (Either b c) a b #
This Prism provides a Traversal for tweaking the Left half of an Either:
>>>over _Left (+1) (Left 2)Left 3
>>>over _Left (+1) (Right 2)Right 2
>>>Right 42 ^._Left :: String""
>>>Left "hello" ^._Left"hello"
It also can be turned around to obtain the embedding into the Left half of an Either:
>>>_Left # 5Left 5
>>>5^.re _LeftLeft 5
_Right :: Prism (Either c a) (Either c b) a b #
This Prism provides a Traversal for tweaking the Right half of an Either:
>>>over _Right (+1) (Left 2)Left 2
>>>over _Right (+1) (Right 2)Right 3
>>>Right "hello" ^._Right"hello"
>>>Left "hello" ^._Right :: [Double][]
It also can be turned around to obtain the embedding into the Right half of an Either:
>>>_Right # 5Right 5
>>>5^.re _RightRight 5
_Just :: Prism (Maybe a) (Maybe b) a b #
This Prism provides a Traversal for tweaking the target of the value of Just in a Maybe.
>>>over _Just (+1) (Just 2)Just 3
Unlike traverse this is a Prism, and so you can use it to inject as well:
>>>_Just # 5Just 5
>>>5^.re _JustJust 5
Interestingly,
m^?_Just≡ m
>>>Just x ^? _JustJust x
>>>Nothing ^? _JustNothing
nearly :: a -> (a -> Bool) -> Prism' a () #
This Prism compares for approximate equality with a given value and a predicate for testing,
an example where the value is the empty list and the predicate checks that a list is empty (same
as _Empty with the AsEmpty list instance):
>>>nearly [] null # ()[]>>>[1,2,3,4] ^? nearly [] nullNothing
nearly[]null::Prism'[a] ()
To comply with the Prism laws the arguments you supply to nearly a p are somewhat constrained.
We assume p x holds iff x ≡ a. Under that assumption then this is a valid Prism.
This is useful when working with a type where you can test equality for only a subset of its values, and the prism selects such a value.
_Show :: (Read a, Show a) => Prism' String a #
This is an improper prism for text formatting based on Read and Show.
This Prism is "improper" in the sense that it normalizes the text formatting, but round tripping
is idempotent given sane 'Read'/'Show' instances.
>>>_Show # 2"2"
>>>"EQ" ^? _Show :: Maybe OrderingJust EQ
_Show≡prism'showreadMaybe
ifolding :: (Foldable f, Indexable i p, Contravariant g, Applicative g) => (s -> f (i, a)) -> Over p g s t a b #
foldring :: (Contravariant f, Applicative f) => ((a -> f a -> f a) -> f a -> s -> f a) -> LensLike f s t a b #
ifoldring :: (Indexable i p, Contravariant f, Applicative f) => ((i -> a -> f a -> f a) -> f a -> s -> f a) -> Over p f s t a b #
Obtain FoldWithIndex by lifting ifoldr like function.
folded :: Foldable f => IndexedFold Int (f a) a #
folded64 :: Foldable f => IndexedFold Int64 (f a) a #
replicated :: Int -> Fold a a #
A Fold that replicates its input n times.
replicaten ≡toListOf(replicatedn)
>>>5^..replicated 20[5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5]
filtered :: (Choice p, Applicative f) => (a -> Bool) -> Optic' p f a a #
Obtain a Fold that can be composed with to filter another Lens, Iso, Getter, Fold (or Traversal).
Note: This is not a legal Traversal, unless you are very careful not to invalidate the predicate on the target.
Note: This is also not a legal Prism, unless you are very careful not to inject a value that matches the predicate.
As a counter example, consider that given evens = the second filtered evenTraversal law is violated:
overevenssucc.overevenssucc/=overevens (succ.succ)
So, in order for this to qualify as a legal Traversal you can only use it for actions that preserve the result of the predicate!
>>>[1..10]^..folded.filtered even[2,4,6,8,10]
This will preserve an index if it is present.
takingWhile :: (Conjoined p, Applicative f) => (a -> Bool) -> Over p (TakingWhile p f a a) s t a a -> Over p f s t a a #
Obtain a Fold by taking elements from another Fold, Lens, Iso, Getter or Traversal while a predicate holds.
takeWhilep ≡toListOf(takingWhilepfolded)
>>>timingOut $ toListOf (takingWhile (<=3) folded) [1..][1,2,3]
takingWhile:: (a ->Bool) ->Folds a ->Folds atakingWhile:: (a ->Bool) ->Getters a ->Folds atakingWhile:: (a ->Bool) ->Traversal's a ->Folds a -- * See note belowtakingWhile:: (a ->Bool) ->Lens's a ->Folds a -- * See note belowtakingWhile:: (a ->Bool) ->Prism's a ->Folds a -- * See note belowtakingWhile:: (a ->Bool) ->Iso's a ->Folds a -- * See note belowtakingWhile:: (a ->Bool) ->IndexedTraversal'i s a ->IndexedFoldi s a -- * See note belowtakingWhile:: (a ->Bool) ->IndexedLens'i s a ->IndexedFoldi s a -- * See note belowtakingWhile:: (a ->Bool) ->IndexedFoldi s a ->IndexedFoldi s atakingWhile:: (a ->Bool) ->IndexedGetteri s a ->IndexedFoldi s a
Note: When applied to a Traversal, takingWhile yields something that can be used as if it were a Traversal, but
which is not a Traversal per the laws, unless you are careful to ensure that you do not invalidate the predicate when
writing back through it.
droppingWhile :: (Conjoined p, Profunctor q, Applicative f) => (a -> Bool) -> Optical p q (Compose (State Bool) f) s t a a -> Optical p q f s t a a #
Obtain a Fold by dropping elements from another Fold, Lens, Iso, Getter or Traversal while a predicate holds.
dropWhilep ≡toListOf(droppingWhilepfolded)
>>>toListOf (droppingWhile (<=3) folded) [1..6][4,5,6]
>>>toListOf (droppingWhile (<=3) folded) [1,6,1][6,1]
droppingWhile:: (a ->Bool) ->Folds a ->Folds adroppingWhile:: (a ->Bool) ->Getters a ->Folds adroppingWhile:: (a ->Bool) ->Traversal's a ->Folds a -- see notesdroppingWhile:: (a ->Bool) ->Lens's a ->Folds a -- see notesdroppingWhile:: (a ->Bool) ->Prism's a ->Folds a -- see notesdroppingWhile:: (a ->Bool) ->Iso's a ->Folds a -- see notes
droppingWhile:: (a ->Bool) ->IndexPreservingTraversal's a ->IndexPreservingFolds a -- see notesdroppingWhile:: (a ->Bool) ->IndexPreservingLens's a ->IndexPreservingFolds a -- see notesdroppingWhile:: (a ->Bool) ->IndexPreservingGetters a ->IndexPreservingFolds adroppingWhile:: (a ->Bool) ->IndexPreservingFolds a ->IndexPreservingFolds a
droppingWhile:: (a ->Bool) ->IndexedTraversal'i s a ->IndexedFoldi s a -- see notesdroppingWhile:: (a ->Bool) ->IndexedLens'i s a ->IndexedFoldi s a -- see notesdroppingWhile:: (a ->Bool) ->IndexedGetteri s a ->IndexedFoldi s adroppingWhile:: (a ->Bool) ->IndexedFoldi s a ->IndexedFoldi s a
Note: Many uses of this combinator will yield something that meets the types, but not the laws of a valid
Traversal or IndexedTraversal. The Traversal and IndexedTraversal laws are only satisfied if the
new values you assign to the first target also does not pass the predicate! Otherwise subsequent traversals
will visit fewer elements and Traversal fusion is not sound.
So for any traversal t and predicate p, may not be lawful, but
droppingWhile p t( is. For example:dropping 1 . droppingWhile p) t
>>>let l :: Traversal' [Int] Int; l = droppingWhile (<= 1) traverse>>>let l' :: Traversal' [Int] Int; l' = dropping 1 l
l is not a lawful setter because :over l f .
over l g ≢ over l (f . g)
>>>[1,2,3] & l .~ 0 & l .~ 4[1,0,0]>>>[1,2,3] & l .~ 4[1,4,4]
l' on the other hand behaves lawfully:
>>>[1,2,3] & l' .~ 0 & l' .~ 4[1,2,4]>>>[1,2,3] & l' .~ 4[1,2,4]
worded :: Applicative f => IndexedLensLike' Int f String String #
A Fold over the individual words of a String.
worded::FoldStringStringworded::Traversal'StringString
worded::IndexedFoldIntStringStringworded::IndexedTraversal'IntStringString
Note: This function type-checks as a Traversal but it doesn't satisfy the laws. It's only valid to use it
when you don't insert any whitespace characters while traversing, and if your original String contains only
isolated space characters (and no other characters that count as space, such as non-breaking spaces).
lined :: Applicative f => IndexedLensLike' Int f String String #
A Fold over the individual lines of a String.
lined::FoldStringStringlined::Traversal'StringString
lined::IndexedFoldIntStringStringlined::IndexedTraversal'IntStringString
Note: This function type-checks as a Traversal but it doesn't satisfy the laws. It's only valid to use it
when you don't insert any newline characters while traversing, and if your original String contains only
isolated newline characters.
foldMapOf :: Getting r s a -> (a -> r) -> s -> r #
Map each part of a structure viewed through a Lens, Getter,
Fold or Traversal to a monoid and combine the results.
>>>foldMapOf (folded . both . _Just) Sum [(Just 21, Just 21)]Sum {getSum = 42}
foldMap=foldMapOffolded
foldMapOf≡viewsifoldMapOfl =foldMapOfl.Indexed
foldMapOf::Getters a -> (a -> r) -> s -> rfoldMapOf::Monoidr =>Folds a -> (a -> r) -> s -> rfoldMapOf::Semigroupr =>Fold1s a -> (a -> r) -> s -> rfoldMapOf::Lens's a -> (a -> r) -> s -> rfoldMapOf::Iso's a -> (a -> r) -> s -> rfoldMapOf::Monoidr =>Traversal's a -> (a -> r) -> s -> rfoldMapOf::Semigroupr =>Traversal1's a -> (a -> r) -> s -> rfoldMapOf::Monoidr =>Prism's a -> (a -> r) -> s -> r
foldMapOf::Gettingr s a -> (a -> r) -> s -> r
foldOf :: Getting a s a -> s -> a #
Combine the elements of a structure viewed through a Lens, Getter,
Fold or Traversal using a monoid.
>>>foldOf (folded.folded) [[Sum 1,Sum 4],[Sum 8, Sum 8],[Sum 21]]Sum {getSum = 42}
fold=foldOffolded
foldOf≡view
foldOf::Getters m -> s -> mfoldOf::Monoidm =>Folds m -> s -> mfoldOf::Lens's m -> s -> mfoldOf::Iso's m -> s -> mfoldOf::Monoidm =>Traversal's m -> s -> mfoldOf::Monoidm =>Prism's m -> s -> m
foldrOf :: Getting (Endo r) s a -> (a -> r -> r) -> r -> s -> r #
Right-associative fold of parts of a structure that are viewed through a Lens, Getter, Fold or Traversal.
foldr≡foldrOffolded
foldrOf::Getters a -> (a -> r -> r) -> r -> s -> rfoldrOf::Folds a -> (a -> r -> r) -> r -> s -> rfoldrOf::Lens's a -> (a -> r -> r) -> r -> s -> rfoldrOf::Iso's a -> (a -> r -> r) -> r -> s -> rfoldrOf::Traversal's a -> (a -> r -> r) -> r -> s -> rfoldrOf::Prism's a -> (a -> r -> r) -> r -> s -> r
ifoldrOfl ≡foldrOfl.Indexed
foldrOf::Getting(Endor) s a -> (a -> r -> r) -> r -> s -> r
foldlOf :: Getting (Dual (Endo r)) s a -> (r -> a -> r) -> r -> s -> r #
Left-associative fold of the parts of a structure that are viewed through a Lens, Getter, Fold or Traversal.
foldl≡foldlOffolded
foldlOf::Getters a -> (r -> a -> r) -> r -> s -> rfoldlOf::Folds a -> (r -> a -> r) -> r -> s -> rfoldlOf::Lens's a -> (r -> a -> r) -> r -> s -> rfoldlOf::Iso's a -> (r -> a -> r) -> r -> s -> rfoldlOf::Traversal's a -> (r -> a -> r) -> r -> s -> rfoldlOf::Prism's a -> (r -> a -> r) -> r -> s -> r
toNonEmptyOf :: Getting (NonEmptyDList a) s a -> s -> NonEmpty a #
Extract a NonEmpty of the targets of Fold1.
>>>toNonEmptyOf both1 ("hello", "world")"hello" :| ["world"]
toNonEmptyOf::Getters a -> s -> NonEmpty atoNonEmptyOf::Fold1s a -> s -> NonEmpty atoNonEmptyOf::Lens's a -> s -> NonEmpty atoNonEmptyOf::Iso's a -> s -> NonEmpty atoNonEmptyOf::Traversal1's a -> s -> NonEmpty atoNonEmptyOf::Prism's a -> s -> NonEmpty a
(^..) :: s -> Getting (Endo [a]) s a -> [a] infixl 8 #
A convenient infix (flipped) version of toListOf.
>>>[[1,2],[3]]^..id[[[1,2],[3]]]>>>[[1,2],[3]]^..traverse[[1,2],[3]]>>>[[1,2],[3]]^..traverse.traverse[1,2,3]
>>>(1,2)^..both[1,2]
toListxs ≡ xs^..folded(^..) ≡fliptoListOf
(^..) :: s ->Getters a -> a :: s ->Folds a -> a :: s ->Lens's a -> a :: s ->Iso's a -> a :: s ->Traversal's a -> a :: s ->Prism's a -> [a]
andOf :: Getting All s Bool -> s -> Bool #
Returns True if every target of a Fold is True.
>>>andOf both (True,False)False>>>andOf both (True,True)True
and≡andOffolded
andOf::GettersBool-> s ->BoolandOf::FoldsBool-> s ->BoolandOf::Lens'sBool-> s ->BoolandOf::Iso'sBool-> s ->BoolandOf::Traversal'sBool-> s ->BoolandOf::Prism'sBool-> s ->Bool
orOf :: Getting Any s Bool -> s -> Bool #
Returns True if any target of a Fold is True.
>>>orOf both (True,False)True>>>orOf both (False,False)False
or≡orOffolded
orOf::GettersBool-> s ->BoolorOf::FoldsBool-> s ->BoolorOf::Lens'sBool-> s ->BoolorOf::Iso'sBool-> s ->BoolorOf::Traversal'sBool-> s ->BoolorOf::Prism'sBool-> s ->Bool
anyOf :: Getting Any s a -> (a -> Bool) -> s -> Bool #
Returns True if any target of a Fold satisfies a predicate.
>>>anyOf both (=='x') ('x','y')True>>>import Data.Data.Lens>>>anyOf biplate (== "world") (((),2::Int),"hello",("world",11::Int))True
any≡anyOffolded
ianyOfl ≡anyOfl.Indexed
anyOf::Getters a -> (a ->Bool) -> s ->BoolanyOf::Folds a -> (a ->Bool) -> s ->BoolanyOf::Lens's a -> (a ->Bool) -> s ->BoolanyOf::Iso's a -> (a ->Bool) -> s ->BoolanyOf::Traversal's a -> (a ->Bool) -> s ->BoolanyOf::Prism's a -> (a ->Bool) -> s ->Bool
allOf :: Getting All s a -> (a -> Bool) -> s -> Bool #
Returns True if every target of a Fold satisfies a predicate.
>>>allOf both (>=3) (4,5)True>>>allOf folded (>=2) [1..10]False
all≡allOffolded
iallOfl =allOfl.Indexed
allOf::Getters a -> (a ->Bool) -> s ->BoolallOf::Folds a -> (a ->Bool) -> s ->BoolallOf::Lens's a -> (a ->Bool) -> s ->BoolallOf::Iso's a -> (a ->Bool) -> s ->BoolallOf::Traversal's a -> (a ->Bool) -> s ->BoolallOf::Prism's a -> (a ->Bool) -> s ->Bool
noneOf :: Getting Any s a -> (a -> Bool) -> s -> Bool #
Returns True only if no targets of a Fold satisfy a predicate.
>>>noneOf each (is _Nothing) (Just 3, Just 4, Just 5)True>>>noneOf (folded.folded) (<10) [[13,99,20],[3,71,42]]False
inoneOfl =noneOfl.Indexed
noneOf::Getters a -> (a ->Bool) -> s ->BoolnoneOf::Folds a -> (a ->Bool) -> s ->BoolnoneOf::Lens's a -> (a ->Bool) -> s ->BoolnoneOf::Iso's a -> (a ->Bool) -> s ->BoolnoneOf::Traversal's a -> (a ->Bool) -> s ->BoolnoneOf::Prism's a -> (a ->Bool) -> s ->Bool
productOf :: Num a => Getting (Endo (Endo a)) s a -> s -> a #
Calculate the Product of every number targeted by a Fold.
>>>productOf both (4,5)20>>>productOf folded [1,2,3,4,5]120
product≡productOffolded
This operation may be more strict than you would expect. If you
want a lazier version use ala Product . foldMapOf
productOf::Numa =>Getters a -> s -> aproductOf::Numa =>Folds a -> s -> aproductOf::Numa =>Lens's a -> s -> aproductOf::Numa =>Iso's a -> s -> aproductOf::Numa =>Traversal's a -> s -> aproductOf::Numa =>Prism's a -> s -> a
sumOf :: Num a => Getting (Endo (Endo a)) s a -> s -> a #
Calculate the Sum of every number targeted by a Fold.
>>>sumOf both (5,6)11>>>sumOf folded [1,2,3,4]10>>>sumOf (folded.both) [(1,2),(3,4)]10>>>import Data.Data.Lens>>>sumOf biplate [(1::Int,[]),(2,[(3::Int,4::Int)])] :: Int10
sum≡sumOffolded
This operation may be more strict than you would expect. If you
want a lazier version use ala Sum . foldMapOf
sumOf_1::Numa => (a, b) -> asumOf(folded._1) :: (Foldablef,Numa) => f (a, b) -> a
sumOf::Numa =>Getters a -> s -> asumOf::Numa =>Folds a -> s -> asumOf::Numa =>Lens's a -> s -> asumOf::Numa =>Iso's a -> s -> asumOf::Numa =>Traversal's a -> s -> asumOf::Numa =>Prism's a -> s -> a
traverseOf_ :: Functor f => Getting (Traversed r f) s a -> (a -> f r) -> s -> f () #
Traverse over all of the targets of a Fold (or Getter), computing an Applicative (or Functor)-based answer,
but unlike traverseOf do not construct a new structure. traverseOf_ generalizes
traverse_ to work over any Fold.
When passed a Getter, traverseOf_ can work over any Functor, but when passed a Fold, traverseOf_ requires
an Applicative.
>>>traverseOf_ both putStrLn ("hello","world")hello world
traverse_≡traverseOf_folded
traverseOf__2::Functorf => (c -> f r) -> (d, c) -> f ()traverseOf__Left::Applicativef => (a -> f b) ->Eithera c -> f ()
itraverseOf_l ≡traverseOf_l.Indexed
The rather specific signature of traverseOf_ allows it to be used as if the signature was any of:
traverseOf_::Functorf =>Getters a -> (a -> f r) -> s -> f ()traverseOf_::Applicativef =>Folds a -> (a -> f r) -> s -> f ()traverseOf_::Functorf =>Lens's a -> (a -> f r) -> s -> f ()traverseOf_::Functorf =>Iso's a -> (a -> f r) -> s -> f ()traverseOf_::Applicativef =>Traversal's a -> (a -> f r) -> s -> f ()traverseOf_::Applicativef =>Prism's a -> (a -> f r) -> s -> f ()
forOf_ :: Functor f => Getting (Traversed r f) s a -> s -> (a -> f r) -> f () #
Traverse over all of the targets of a Fold (or Getter), computing an Applicative (or Functor)-based answer,
but unlike forOf do not construct a new structure. forOf_ generalizes
for_ to work over any Fold.
When passed a Getter, forOf_ can work over any Functor, but when passed a Fold, forOf_ requires
an Applicative.
for_≡forOf_folded
>>>forOf_ both ("hello","world") putStrLnhello world
The rather specific signature of forOf_ allows it to be used as if the signature was any of:
iforOf_l s ≡forOf_l s.Indexed
forOf_::Functorf =>Getters a -> s -> (a -> f r) -> f ()forOf_::Applicativef =>Folds a -> s -> (a -> f r) -> f ()forOf_::Functorf =>Lens's a -> s -> (a -> f r) -> f ()forOf_::Functorf =>Iso's a -> s -> (a -> f r) -> f ()forOf_::Applicativef =>Traversal's a -> s -> (a -> f r) -> f ()forOf_::Applicativef =>Prism's a -> s -> (a -> f r) -> f ()
sequenceAOf_ :: Functor f => Getting (Traversed a f) s (f a) -> s -> f () #
Evaluate each action in observed by a Fold on a structure from left to right, ignoring the results.
sequenceA_≡sequenceAOf_folded
>>>sequenceAOf_ both (putStrLn "hello",putStrLn "world")hello world
sequenceAOf_::Functorf =>Getters (f a) -> s -> f ()sequenceAOf_::Applicativef =>Folds (f a) -> s -> f ()sequenceAOf_::Functorf =>Lens's (f a) -> s -> f ()sequenceAOf_::Functorf =>Iso's (f a) -> s -> f ()sequenceAOf_::Applicativef =>Traversal's (f a) -> s -> f ()sequenceAOf_::Applicativef =>Prism's (f a) -> s -> f ()
traverse1Of_ :: Functor f => Getting (TraversedF r f) s a -> (a -> f r) -> s -> f () #
Traverse over all of the targets of a Fold1, computing an Apply based answer.
As long as you have Applicative or Functor effect you are better using traverseOf_.
The traverse1Of_ is useful only when you have genuine Apply effect.
>>>traverse1Of_ both1 (\ks -> Map.fromList [ (k, ()) | k <- ks ]) ("abc", "bcd")fromList [('b',()),('c',())]
traverse1Of_::Applyf =>Fold1s a -> (a -> f r) -> s -> f ()
Since: lens-4.16
for1Of_ :: Functor f => Getting (TraversedF r f) s a -> s -> (a -> f r) -> f () #
See forOf_ and traverse1Of_.
>>>for1Of_ both1 ("abc", "bcd") (\ks -> Map.fromList [ (k, ()) | k <- ks ])fromList [('b',()),('c',())]
for1Of_::Applyf =>Fold1s a -> s -> (a -> f r) -> f ()
Since: lens-4.16
sequence1Of_ :: Functor f => Getting (TraversedF a f) s (f a) -> s -> f () #
See sequenceAOf_ and traverse1Of_.
sequence1Of_::Applyf =>Fold1s (f a) -> s -> f ()
Since: lens-4.16
mapMOf_ :: Monad m => Getting (Sequenced r m) s a -> (a -> m r) -> s -> m () #
Map each target of a Fold on a structure to a monadic action, evaluate these actions from left to right, and ignore the results.
>>>mapMOf_ both putStrLn ("hello","world")hello world
mapM_≡mapMOf_folded
mapMOf_::Monadm =>Getters a -> (a -> m r) -> s -> m ()mapMOf_::Monadm =>Folds a -> (a -> m r) -> s -> m ()mapMOf_::Monadm =>Lens's a -> (a -> m r) -> s -> m ()mapMOf_::Monadm =>Iso's a -> (a -> m r) -> s -> m ()mapMOf_::Monadm =>Traversal's a -> (a -> m r) -> s -> m ()mapMOf_::Monadm =>Prism's a -> (a -> m r) -> s -> m ()
forMOf_ :: Monad m => Getting (Sequenced r m) s a -> s -> (a -> m r) -> m () #
forMOf_ is mapMOf_ with two of its arguments flipped.
>>>forMOf_ both ("hello","world") putStrLnhello world
forM_≡forMOf_folded
forMOf_::Monadm =>Getters a -> s -> (a -> m r) -> m ()forMOf_::Monadm =>Folds a -> s -> (a -> m r) -> m ()forMOf_::Monadm =>Lens's a -> s -> (a -> m r) -> m ()forMOf_::Monadm =>Iso's a -> s -> (a -> m r) -> m ()forMOf_::Monadm =>Traversal's a -> s -> (a -> m r) -> m ()forMOf_::Monadm =>Prism's a -> s -> (a -> m r) -> m ()
sequenceOf_ :: Monad m => Getting (Sequenced a m) s (m a) -> s -> m () #
Evaluate each monadic action referenced by a Fold on the structure from left to right, and ignore the results.
>>>sequenceOf_ both (putStrLn "hello",putStrLn "world")hello world
sequence_≡sequenceOf_folded
sequenceOf_::Monadm =>Getters (m a) -> s -> m ()sequenceOf_::Monadm =>Folds (m a) -> s -> m ()sequenceOf_::Monadm =>Lens's (m a) -> s -> m ()sequenceOf_::Monadm =>Iso's (m a) -> s -> m ()sequenceOf_::Monadm =>Traversal's (m a) -> s -> m ()sequenceOf_::Monadm =>Prism's (m a) -> s -> m ()
asumOf :: Alternative f => Getting (Endo (f a)) s (f a) -> s -> f a #
The sum of a collection of actions, generalizing concatOf.
>>>asumOf both ("hello","world")"helloworld"
>>>asumOf each (Nothing, Just "hello", Nothing)Just "hello"
asum≡asumOffolded
asumOf::Alternativef =>Getters (f a) -> s -> f aasumOf::Alternativef =>Folds (f a) -> s -> f aasumOf::Alternativef =>Lens's (f a) -> s -> f aasumOf::Alternativef =>Iso's (f a) -> s -> f aasumOf::Alternativef =>Traversal's (f a) -> s -> f aasumOf::Alternativef =>Prism's (f a) -> s -> f a
msumOf :: MonadPlus m => Getting (Endo (m a)) s (m a) -> s -> m a #
The sum of a collection of actions, generalizing concatOf.
>>>msumOf both ("hello","world")"helloworld"
>>>msumOf each (Nothing, Just "hello", Nothing)Just "hello"
msum≡msumOffolded
msumOf::MonadPlusm =>Getters (m a) -> s -> m amsumOf::MonadPlusm =>Folds (m a) -> s -> m amsumOf::MonadPlusm =>Lens's (m a) -> s -> m amsumOf::MonadPlusm =>Iso's (m a) -> s -> m amsumOf::MonadPlusm =>Traversal's (m a) -> s -> m amsumOf::MonadPlusm =>Prism's (m a) -> s -> m a
elemOf :: Eq a => Getting Any s a -> a -> s -> Bool #
Does the element occur anywhere within a given Fold of the structure?
>>>elemOf both "hello" ("hello","world")True
elem≡elemOffolded
elemOf::Eqa =>Getters a -> a -> s ->BoolelemOf::Eqa =>Folds a -> a -> s ->BoolelemOf::Eqa =>Lens's a -> a -> s ->BoolelemOf::Eqa =>Iso's a -> a -> s ->BoolelemOf::Eqa =>Traversal's a -> a -> s ->BoolelemOf::Eqa =>Prism's a -> a -> s ->Bool
notElemOf :: Eq a => Getting All s a -> a -> s -> Bool #
Does the element not occur anywhere within a given Fold of the structure?
>>>notElemOf each 'd' ('a','b','c')True
>>>notElemOf each 'a' ('a','b','c')False
notElem≡notElemOffolded
notElemOf::Eqa =>Getters a -> a -> s ->BoolnotElemOf::Eqa =>Folds a -> a -> s ->BoolnotElemOf::Eqa =>Iso's a -> a -> s ->BoolnotElemOf::Eqa =>Lens's a -> a -> s ->BoolnotElemOf::Eqa =>Traversal's a -> a -> s ->BoolnotElemOf::Eqa =>Prism's a -> a -> s ->Bool
concatMapOf :: Getting [r] s a -> (a -> [r]) -> s -> [r] #
Map a function over all the targets of a Fold of a container and concatenate the resulting lists.
>>>concatMapOf both (\x -> [x, x + 1]) (1,3)[1,2,3,4]
concatMap≡concatMapOffolded
concatMapOf::Getters a -> (a -> [r]) -> s -> [r]concatMapOf::Folds a -> (a -> [r]) -> s -> [r]concatMapOf::Lens's a -> (a -> [r]) -> s -> [r]concatMapOf::Iso's a -> (a -> [r]) -> s -> [r]concatMapOf::Traversal's a -> (a -> [r]) -> s -> [r]
concatOf :: Getting [r] s [r] -> s -> [r] #
Concatenate all of the lists targeted by a Fold into a longer list.
>>>concatOf both ("pan","ama")"panama"
concat≡concatOffoldedconcatOf≡view
concatOf::Getters [r] -> s -> [r]concatOf::Folds [r] -> s -> [r]concatOf::Iso's [r] -> s -> [r]concatOf::Lens's [r] -> s -> [r]concatOf::Traversal's [r] -> s -> [r]
lengthOf :: Getting (Endo (Endo Int)) s a -> s -> Int #
Calculate the number of targets there are for a Fold in a given container.
Note: This can be rather inefficient for large containers and just like length,
this will not terminate for infinite folds.
length≡lengthOffolded
>>>lengthOf _1 ("hello",())1
>>>lengthOf traverse [1..10]10
>>>lengthOf (traverse.traverse) [[1,2],[3,4],[5,6]]6
lengthOf(folded.folded) :: (Foldablef,Foldableg) => f (g a) ->Int
lengthOf::Getters a -> s ->IntlengthOf::Folds a -> s ->IntlengthOf::Lens's a -> s ->IntlengthOf::Iso's a -> s ->IntlengthOf::Traversal's a -> s ->Int
(^?) :: s -> Getting (First a) s a -> Maybe a infixl 8 #
Perform a safe head of a Fold or Traversal or retrieve Just the result
from a Getter or Lens.
When using a Traversal as a partial Lens, or a Fold as a partial Getter this can be a convenient
way to extract the optional value.
Note: if you get stack overflows due to this, you may want to use firstOf instead, which can deal
more gracefully with heavily left-biased trees.
>>>Left 4 ^?_LeftJust 4
>>>Right 4 ^?_LeftNothing
>>>"world" ^? ix 3Just 'l'
>>>"world" ^? ix 20Nothing
(^?) ≡flippreview
(^?) :: s ->Getters a ->Maybea (^?) :: s ->Folds a ->Maybea (^?) :: s ->Lens's a ->Maybea (^?) :: s ->Iso's a ->Maybea (^?) :: s ->Traversal's a ->Maybea
(^?!) :: HasCallStack => s -> Getting (Endo a) s a -> a infixl 8 #
firstOf :: Getting (Leftmost a) s a -> s -> Maybe a #
Retrieve the First entry of a Fold or Traversal or retrieve Just the result
from a Getter or Lens.
The answer is computed in a manner that leaks space less than
and gives you back access to the outermost ala First . foldMapOfJust constructor more quickly, but may have worse
constant factors.
Note: this could been named headOf.
>>>firstOf traverse [1..10]Just 1
>>>firstOf both (1,2)Just 1
>>>firstOf ignored ()Nothing
firstOf::Getters a -> s ->MaybeafirstOf::Folds a -> s ->MaybeafirstOf::Lens's a -> s ->MaybeafirstOf::Iso's a -> s ->MaybeafirstOf::Traversal's a -> s ->Maybea
first1Of :: Getting (First a) s a -> s -> a #
Retrieve the First entry of a Fold1 or Traversal1 or the result from a Getter or Lens.
>>>first1Of traverse1 (1 :| [2..10])1
>>>first1Of both1 (1,2)1
Note: this is different from ^..
>>>first1Of traverse1 ([1,2] :| [[3,4],[5,6]])[1,2]
>>>([1,2] :| [[3,4],[5,6]]) ^. traverse1[1,2,3,4,5,6]
first1Of::Getters a -> s -> afirst1Of::Fold1s a -> s -> afirst1Of::Lens's a -> s -> afirst1Of::Iso's a -> s -> afirst1Of::Traversal1's a -> s -> a
lastOf :: Getting (Rightmost a) s a -> s -> Maybe a #
Retrieve the Last entry of a Fold or Traversal or retrieve Just the result
from a Getter or Lens.
The answer is computed in a manner that leaks space less than
and gives you back access to the outermost ala Last . foldMapOfJust constructor more quickly, but may have worse
constant factors.
>>>lastOf traverse [1..10]Just 10
>>>lastOf both (1,2)Just 2
>>>lastOf ignored ()Nothing
lastOf::Getters a -> s ->MaybealastOf::Folds a -> s ->MaybealastOf::Lens's a -> s ->MaybealastOf::Iso's a -> s ->MaybealastOf::Traversal's a -> s ->Maybea
last1Of :: Getting (Last a) s a -> s -> a #
Retrieve the Last entry of a Fold1 or Traversal1 or retrieve the result
from a Getter or Lens.o
>>>last1Of traverse1 (1 :| [2..10])10
>>>last1Of both1 (1,2)2
last1Of::Getters a -> s ->Maybealast1Of::Fold1s a -> s ->Maybealast1Of::Lens's a -> s ->Maybealast1Of::Iso's a -> s ->Maybealast1Of::Traversal1's a -> s ->Maybea
nullOf :: Getting All s a -> s -> Bool #
Returns True if this Fold or Traversal has no targets in the given container.
Note: nullOf on a valid Iso, Lens or Getter should always return False.
null≡nullOffolded
This may be rather inefficient compared to the null check of many containers.
>>>nullOf _1 (1,2)False
>>>nullOf ignored ()True
>>>nullOf traverse []True
>>>nullOf (element 20) [1..10]True
nullOf(folded._1.folded) :: (Foldablef,Foldableg) => f (g a, b) ->Bool
nullOf::Getters a -> s ->BoolnullOf::Folds a -> s ->BoolnullOf::Iso's a -> s ->BoolnullOf::Lens's a -> s ->BoolnullOf::Traversal's a -> s ->Bool
notNullOf :: Getting Any s a -> s -> Bool #
Returns True if this Fold or Traversal has any targets in the given container.
A more "conversational" alias for this combinator is has.
Note: notNullOf on a valid Iso, Lens or Getter should always return True.
not.null≡notNullOffolded
This may be rather inefficient compared to the check of many containers.not . null
>>>notNullOf _1 (1,2)True
>>>notNullOf traverse [1..10]True
>>>notNullOf folded []False
>>>notNullOf (element 20) [1..10]False
notNullOf(folded._1.folded) :: (Foldablef,Foldableg) => f (g a, b) ->Bool
notNullOf::Getters a -> s ->BoolnotNullOf::Folds a -> s ->BoolnotNullOf::Iso's a -> s ->BoolnotNullOf::Lens's a -> s ->BoolnotNullOf::Traversal's a -> s ->Bool
maximumOf :: Ord a => Getting (Endo (Endo (Maybe a))) s a -> s -> Maybe a #
Obtain the maximum element (if any) targeted by a Fold or Traversal safely.
Note: maximumOf on a valid Iso, Lens or Getter will always return Just a value.
>>>maximumOf traverse [1..10]Just 10
>>>maximumOf traverse []Nothing
>>>maximumOf (folded.filtered even) [1,4,3,6,7,9,2]Just 6
maximum≡fromMaybe(error"empty").maximumOffolded
In the interest of efficiency, This operation has semantics more strict than strictly necessary.
has lazier semantics but could leak memory.rmap getMax (foldMapOf l Max)
maximumOf::Orda =>Getters a -> s ->MaybeamaximumOf::Orda =>Folds a -> s ->MaybeamaximumOf::Orda =>Iso's a -> s ->MaybeamaximumOf::Orda =>Lens's a -> s ->MaybeamaximumOf::Orda =>Traversal's a -> s ->Maybea
maximum1Of :: Ord a => Getting (Max a) s a -> s -> a #
Obtain the maximum element targeted by a Fold1 or Traversal1.
>>>maximum1Of traverse1 (1 :| [2..10])10
maximum1Of::Orda =>Getters a -> s -> amaximum1Of::Orda =>Fold1s a -> s -> amaximum1Of::Orda =>Iso's a -> s -> amaximum1Of::Orda =>Lens's a -> s -> amaximum1Of::Orda =>Traversal1's a -> s -> a
minimumOf :: Ord a => Getting (Endo (Endo (Maybe a))) s a -> s -> Maybe a #
Obtain the minimum element (if any) targeted by a Fold or Traversal safely.
Note: minimumOf on a valid Iso, Lens or Getter will always return Just a value.
>>>minimumOf traverse [1..10]Just 1
>>>minimumOf traverse []Nothing
>>>minimumOf (folded.filtered even) [1,4,3,6,7,9,2]Just 2
minimum≡fromMaybe(error"empty").minimumOffolded
In the interest of efficiency, This operation has semantics more strict than strictly necessary.
has lazier semantics but could leak memory.rmap getMin (foldMapOf l Min)
minimumOf::Orda =>Getters a -> s ->MaybeaminimumOf::Orda =>Folds a -> s ->MaybeaminimumOf::Orda =>Iso's a -> s ->MaybeaminimumOf::Orda =>Lens's a -> s ->MaybeaminimumOf::Orda =>Traversal's a -> s ->Maybea
minimum1Of :: Ord a => Getting (Min a) s a -> s -> a #
Obtain the minimum element targeted by a Fold1 or Traversal1.
>>>minimum1Of traverse1 (1 :| [2..10])1
minimum1Of::Orda =>Getters a -> s -> aminimum1Of::Orda =>Fold1s a -> s -> aminimum1Of::Orda =>Iso's a -> s -> aminimum1Of::Orda =>Lens's a -> s -> aminimum1Of::Orda =>Traversal1's a -> s -> a
maximumByOf :: Getting (Endo (Endo (Maybe a))) s a -> (a -> a -> Ordering) -> s -> Maybe a #
Obtain the maximum element (if any) targeted by a Fold, Traversal, Lens, Iso,
or Getter according to a user supplied Ordering.
>>>maximumByOf traverse (compare `on` length) ["mustard","relish","ham"]Just "mustard"
In the interest of efficiency, This operation has semantics more strict than strictly necessary.
maximumBycmp ≡fromMaybe(error"empty").maximumByOffoldedcmp
maximumByOf::Getters a -> (a -> a ->Ordering) -> s ->MaybeamaximumByOf::Folds a -> (a -> a ->Ordering) -> s ->MaybeamaximumByOf::Iso's a -> (a -> a ->Ordering) -> s ->MaybeamaximumByOf::Lens's a -> (a -> a ->Ordering) -> s ->MaybeamaximumByOf::Traversal's a -> (a -> a ->Ordering) -> s ->Maybea
minimumByOf :: Getting (Endo (Endo (Maybe a))) s a -> (a -> a -> Ordering) -> s -> Maybe a #
Obtain the minimum element (if any) targeted by a Fold, Traversal, Lens, Iso
or Getter according to a user supplied Ordering.
In the interest of efficiency, This operation has semantics more strict than strictly necessary.
>>>minimumByOf traverse (compare `on` length) ["mustard","relish","ham"]Just "ham"
minimumBycmp ≡fromMaybe(error"empty").minimumByOffoldedcmp
minimumByOf::Getters a -> (a -> a ->Ordering) -> s ->MaybeaminimumByOf::Folds a -> (a -> a ->Ordering) -> s ->MaybeaminimumByOf::Iso's a -> (a -> a ->Ordering) -> s ->MaybeaminimumByOf::Lens's a -> (a -> a ->Ordering) -> s ->MaybeaminimumByOf::Traversal's a -> (a -> a ->Ordering) -> s ->Maybea
findOf :: Getting (Endo (Maybe a)) s a -> (a -> Bool) -> s -> Maybe a #
The findOf function takes a Lens (or Getter, Iso, Fold, or Traversal),
a predicate and a structure and returns the leftmost element of the structure
matching the predicate, or Nothing if there is no such element.
>>>findOf each even (1,3,4,6)Just 4
>>>findOf folded even [1,3,5,7]Nothing
findOf::Getters a -> (a ->Bool) -> s ->MaybeafindOf::Folds a -> (a ->Bool) -> s ->MaybeafindOf::Iso's a -> (a ->Bool) -> s ->MaybeafindOf::Lens's a -> (a ->Bool) -> s ->MaybeafindOf::Traversal's a -> (a ->Bool) -> s ->Maybea
find≡findOffoldedifindOfl ≡findOfl.Indexed
A simpler version that didn't permit indexing, would be:
findOf::Getting(Endo(Maybea)) s a -> (a ->Bool) -> s ->MaybeafindOfl p =foldrOfl (a y -> if p a thenJusta else y)Nothing
findMOf :: Monad m => Getting (Endo (m (Maybe a))) s a -> (a -> m Bool) -> s -> m (Maybe a) #
The findMOf function takes a Lens (or Getter, Iso, Fold, or Traversal),
a monadic predicate and a structure and returns in the monad the leftmost element of the structure
matching the predicate, or Nothing if there is no such element.
>>>findMOf each ( \x -> print ("Checking " ++ show x) >> return (even x)) (1,3,4,6)"Checking 1" "Checking 3" "Checking 4" Just 4
>>>findMOf each ( \x -> print ("Checking " ++ show x) >> return (even x)) (1,3,5,7)"Checking 1" "Checking 3" "Checking 5" "Checking 7" Nothing
findMOf:: (Monadm,Getters a) -> (a -> mBool) -> s -> m (Maybea)findMOf:: (Monadm,Folds a) -> (a -> mBool) -> s -> m (Maybea)findMOf:: (Monadm,Iso's a) -> (a -> mBool) -> s -> m (Maybea)findMOf:: (Monadm,Lens's a) -> (a -> mBool) -> s -> m (Maybea)findMOf:: (Monadm,Traversal's a) -> (a -> mBool) -> s -> m (Maybea)
findMOffolded:: (Monad m, Foldable f) => (a -> m Bool) -> f a -> m (Maybe a)ifindMOfl ≡findMOfl.Indexed
A simpler version that didn't permit indexing, would be:
findMOf:: Monad m =>Getting(Endo(m (Maybea))) s a -> (a -> mBool) -> s -> m (Maybea)findMOfl p =foldrOfl (a y -> p a >>= x -> if x then return (Justa) else y) $ returnNothing
lookupOf :: Eq k => Getting (Endo (Maybe v)) s (k, v) -> k -> s -> Maybe v #
The lookupOf function takes a Fold (or Getter, Traversal,
Lens, Iso, etc.), a key, and a structure containing key/value pairs.
It returns the first value corresponding to the given key. This function
generalizes lookup to work on an arbitrary Fold instead of lists.
>>>lookupOf folded 4 [(2, 'a'), (4, 'b'), (4, 'c')]Just 'b'
>>>lookupOf each 2 [(2, 'a'), (4, 'b'), (4, 'c')]Just 'a'
lookupOf::Eqk =>Folds (k,v) -> k -> s ->Maybev
foldr1Of :: HasCallStack => Getting (Endo (Maybe a)) s a -> (a -> a -> a) -> s -> a #
A variant of foldrOf that has no base case and thus may only be applied
to lenses and structures such that the Lens views at least one element of
the structure.
>>>foldr1Of each (+) (1,2,3,4)10
foldr1Ofl f ≡foldr1f.toListOflfoldr1≡foldr1Offolded
foldr1Of::Getters a -> (a -> a -> a) -> s -> afoldr1Of::Folds a -> (a -> a -> a) -> s -> afoldr1Of::Iso's a -> (a -> a -> a) -> s -> afoldr1Of::Lens's a -> (a -> a -> a) -> s -> afoldr1Of::Traversal's a -> (a -> a -> a) -> s -> a
foldl1Of :: HasCallStack => Getting (Dual (Endo (Maybe a))) s a -> (a -> a -> a) -> s -> a #
A variant of foldlOf that has no base case and thus may only be applied to lenses and structures such
that the Lens views at least one element of the structure.
>>>foldl1Of each (+) (1,2,3,4)10
foldl1Ofl f ≡foldl1f.toListOflfoldl1≡foldl1Offolded
foldl1Of::Getters a -> (a -> a -> a) -> s -> afoldl1Of::Folds a -> (a -> a -> a) -> s -> afoldl1Of::Iso's a -> (a -> a -> a) -> s -> afoldl1Of::Lens's a -> (a -> a -> a) -> s -> afoldl1Of::Traversal's a -> (a -> a -> a) -> s -> a
foldrOf' :: Getting (Dual (Endo (Endo r))) s a -> (a -> r -> r) -> r -> s -> r #
Strictly fold right over the elements of a structure.
foldr'≡foldrOf'folded
foldrOf'::Getters a -> (a -> r -> r) -> r -> s -> rfoldrOf'::Folds a -> (a -> r -> r) -> r -> s -> rfoldrOf'::Iso's a -> (a -> r -> r) -> r -> s -> rfoldrOf'::Lens's a -> (a -> r -> r) -> r -> s -> rfoldrOf'::Traversal's a -> (a -> r -> r) -> r -> s -> r
foldlOf' :: Getting (Endo (Endo r)) s a -> (r -> a -> r) -> r -> s -> r #
Fold over the elements of a structure, associating to the left, but strictly.
foldl'≡foldlOf'folded
foldlOf'::Getters a -> (r -> a -> r) -> r -> s -> rfoldlOf'::Folds a -> (r -> a -> r) -> r -> s -> rfoldlOf'::Iso's a -> (r -> a -> r) -> r -> s -> rfoldlOf'::Lens's a -> (r -> a -> r) -> r -> s -> rfoldlOf'::Traversal's a -> (r -> a -> r) -> r -> s -> r
foldr1Of' :: HasCallStack => Getting (Dual (Endo (Endo (Maybe a)))) s a -> (a -> a -> a) -> s -> a #
A variant of foldrOf' that has no base case and thus may only be applied
to folds and structures such that the fold views at least one element of the
structure.
foldr1Ofl f ≡foldr1f.toListOfl
foldr1Of'::Getters a -> (a -> a -> a) -> s -> afoldr1Of'::Folds a -> (a -> a -> a) -> s -> afoldr1Of'::Iso's a -> (a -> a -> a) -> s -> afoldr1Of'::Lens's a -> (a -> a -> a) -> s -> afoldr1Of'::Traversal's a -> (a -> a -> a) -> s -> a
foldl1Of' :: HasCallStack => Getting (Endo (Endo (Maybe a))) s a -> (a -> a -> a) -> s -> a #
A variant of foldlOf' that has no base case and thus may only be applied
to folds and structures such that the fold views at least one element of
the structure.
foldl1Of'l f ≡foldl1'f.toListOfl
foldl1Of'::Getters a -> (a -> a -> a) -> s -> afoldl1Of'::Folds a -> (a -> a -> a) -> s -> afoldl1Of'::Iso's a -> (a -> a -> a) -> s -> afoldl1Of'::Lens's a -> (a -> a -> a) -> s -> afoldl1Of'::Traversal's a -> (a -> a -> a) -> s -> a
foldrMOf :: Monad m => Getting (Dual (Endo (r -> m r))) s a -> (a -> r -> m r) -> r -> s -> m r #
Monadic fold over the elements of a structure, associating to the right, i.e. from right to left.
foldrM≡foldrMOffolded
foldrMOf::Monadm =>Getters a -> (a -> r -> m r) -> r -> s -> m rfoldrMOf::Monadm =>Folds a -> (a -> r -> m r) -> r -> s -> m rfoldrMOf::Monadm =>Iso's a -> (a -> r -> m r) -> r -> s -> m rfoldrMOf::Monadm =>Lens's a -> (a -> r -> m r) -> r -> s -> m rfoldrMOf::Monadm =>Traversal's a -> (a -> r -> m r) -> r -> s -> m r
foldlMOf :: Monad m => Getting (Endo (r -> m r)) s a -> (r -> a -> m r) -> r -> s -> m r #
Monadic fold over the elements of a structure, associating to the left, i.e. from left to right.
foldlM≡foldlMOffolded
foldlMOf::Monadm =>Getters a -> (r -> a -> m r) -> r -> s -> m rfoldlMOf::Monadm =>Folds a -> (r -> a -> m r) -> r -> s -> m rfoldlMOf::Monadm =>Iso's a -> (r -> a -> m r) -> r -> s -> m rfoldlMOf::Monadm =>Lens's a -> (r -> a -> m r) -> r -> s -> m rfoldlMOf::Monadm =>Traversal's a -> (r -> a -> m r) -> r -> s -> m r
has :: Getting Any s a -> s -> Bool #
Check to see if this Fold or Traversal matches 1 or more entries.
>>>has (element 0) []False
>>>has _Left (Left 12)True
>>>has _Right (Left 12)False
This will always return True for a Lens or Getter.
>>>has _1 ("hello","world")True
has::Getters a -> s ->Boolhas::Folds a -> s ->Boolhas::Iso's a -> s ->Boolhas::Lens's a -> s ->Boolhas::Traversal's a -> s ->Bool
pre :: Getting (First a) s a -> IndexPreservingGetter s (Maybe a) #
This converts a Fold to a IndexPreservingGetter that returns the first element, if it
exists, as a Maybe.
pre::Getters a ->IndexPreservingGetters (Maybea)pre::Folds a ->IndexPreservingGetters (Maybea)pre::Traversal's a ->IndexPreservingGetters (Maybea)pre::Lens's a ->IndexPreservingGetters (Maybea)pre::Iso's a ->IndexPreservingGetters (Maybea)pre::Prism's a ->IndexPreservingGetters (Maybea)
ipre :: IndexedGetting i (First (i, a)) s a -> IndexPreservingGetter s (Maybe (i, a)) #
This converts an IndexedFold to an IndexPreservingGetter that returns the first index
and element, if they exist, as a Maybe.
ipre::IndexedGetteri s a ->IndexPreservingGetters (Maybe(i, a))ipre::IndexedFoldi s a ->IndexPreservingGetters (Maybe(i, a))ipre::IndexedTraversal'i s a ->IndexPreservingGetters (Maybe(i, a))ipre::IndexedLens'i s a ->IndexPreservingGetters (Maybe(i, a))
preview :: MonadReader s m => Getting (First a) s a -> m (Maybe a) #
Retrieve the first value targeted by a Fold or Traversal (or Just the result
from a Getter or Lens). See also (^?).
listToMaybe.toList≡previewfolded
This is usually applied in the Reader
Monad (->) s.
preview=view.pre
preview::Getters a -> s ->Maybeapreview::Folds a -> s ->Maybeapreview::Lens's a -> s ->Maybeapreview::Iso's a -> s ->Maybeapreview::Traversal's a -> s ->Maybea
However, it may be useful to think of its full generality when working with
a Monad transformer stack:
preview::MonadReaders m =>Getters a -> m (Maybea)preview::MonadReaders m =>Folds a -> m (Maybea)preview::MonadReaders m =>Lens's a -> m (Maybea)preview::MonadReaders m =>Iso's a -> m (Maybea)preview::MonadReaders m =>Traversal's a -> m (Maybea)
ipreview :: MonadReader s m => IndexedGetting i (First (i, a)) s a -> m (Maybe (i, a)) #
Retrieve the first index and value targeted by a Fold or Traversal (or Just the result
from a Getter or Lens). See also (^@?).
ipreview=view.ipre
This is usually applied in the Reader
Monad (->) s.
ipreview::IndexedGetteri s a -> s ->Maybe(i, a)ipreview::IndexedFoldi s a -> s ->Maybe(i, a)ipreview::IndexedLens'i s a -> s ->Maybe(i, a)ipreview::IndexedTraversal'i s a -> s ->Maybe(i, a)
However, it may be useful to think of its full generality when working with
a Monad transformer stack:
ipreview::MonadReaders m =>IndexedGetters a -> m (Maybe(i, a))ipreview::MonadReaders m =>IndexedFolds a -> m (Maybe(i, a))ipreview::MonadReaders m =>IndexedLens's a -> m (Maybe(i, a))ipreview::MonadReaders m =>IndexedTraversal's a -> m (Maybe(i, a))
ipreviews :: MonadReader s m => IndexedGetting i (First r) s a -> (i -> a -> r) -> m (Maybe r) #
Retrieve a function of the first index and value targeted by an IndexedFold or
IndexedTraversal (or Just the result from an IndexedGetter or IndexedLens).
See also (^@?).
ipreviews=views.ipre
This is usually applied in the Reader
Monad (->) s.
ipreviews::IndexedGetteri s a -> (i -> a -> r) -> s ->Mayberipreviews::IndexedFoldi s a -> (i -> a -> r) -> s ->Mayberipreviews::IndexedLens'i s a -> (i -> a -> r) -> s ->Mayberipreviews::IndexedTraversal'i s a -> (i -> a -> r) -> s ->Mayber
However, it may be useful to think of its full generality when working with
a Monad transformer stack:
ipreviews::MonadReaders m =>IndexedGetteri s a -> (i -> a -> r) -> m (Mayber)ipreviews::MonadReaders m =>IndexedFoldi s a -> (i -> a -> r) -> m (Mayber)ipreviews::MonadReaders m =>IndexedLens'i s a -> (i -> a -> r) -> m (Mayber)ipreviews::MonadReaders m =>IndexedTraversal'i s a -> (i -> a -> r) -> m (Mayber)
preuse :: MonadState s m => Getting (First a) s a -> m (Maybe a) #
Retrieve the first value targeted by a Fold or Traversal (or Just the result
from a Getter or Lens) into the current state.
preuse=use.pre
preuse::MonadStates m =>Getters a -> m (Maybea)preuse::MonadStates m =>Folds a -> m (Maybea)preuse::MonadStates m =>Lens's a -> m (Maybea)preuse::MonadStates m =>Iso's a -> m (Maybea)preuse::MonadStates m =>Traversal's a -> m (Maybea)
ipreuse :: MonadState s m => IndexedGetting i (First (i, a)) s a -> m (Maybe (i, a)) #
Retrieve the first index and value targeted by an IndexedFold or IndexedTraversal (or Just the index
and result from an IndexedGetter or IndexedLens) into the current state.
ipreuse=use.ipre
ipreuse::MonadStates m =>IndexedGetteri s a -> m (Maybe(i, a))ipreuse::MonadStates m =>IndexedFoldi s a -> m (Maybe(i, a))ipreuse::MonadStates m =>IndexedLens'i s a -> m (Maybe(i, a))ipreuse::MonadStates m =>IndexedTraversal'i s a -> m (Maybe(i, a))
preuses :: MonadState s m => Getting (First r) s a -> (a -> r) -> m (Maybe r) #
Retrieve a function of the first value targeted by a Fold or
Traversal (or Just the result from a Getter or Lens) into the current state.
preuses=uses.pre
preuses::MonadStates m =>Getters a -> (a -> r) -> m (Mayber)preuses::MonadStates m =>Folds a -> (a -> r) -> m (Mayber)preuses::MonadStates m =>Lens's a -> (a -> r) -> m (Mayber)preuses::MonadStates m =>Iso's a -> (a -> r) -> m (Mayber)preuses::MonadStates m =>Traversal's a -> (a -> r) -> m (Mayber)
ipreuses :: MonadState s m => IndexedGetting i (First r) s a -> (i -> a -> r) -> m (Maybe r) #
Retrieve a function of the first index and value targeted by an IndexedFold or
IndexedTraversal (or a function of Just the index and result from an IndexedGetter
or IndexedLens) into the current state.
ipreuses=uses.ipre
ipreuses::MonadStates m =>IndexedGetteri s a -> (i -> a -> r) -> m (Mayber)ipreuses::MonadStates m =>IndexedFoldi s a -> (i -> a -> r) -> m (Mayber)ipreuses::MonadStates m =>IndexedLens'i s a -> (i -> a -> r) -> m (Mayber)ipreuses::MonadStates m =>IndexedTraversal'i s a -> (i -> a -> r) -> m (Mayber)
ifoldMapOf :: IndexedGetting i m s a -> (i -> a -> m) -> s -> m #
Fold an IndexedFold or IndexedTraversal by mapping indices and values to an arbitrary Monoid with access
to the i.
When you don't need access to the index then foldMapOf is more flexible in what it accepts.
foldMapOfl ≡ifoldMapOfl.const
ifoldMapOf::IndexedGetteri s a -> (i -> a -> m) -> s -> mifoldMapOf::Monoidm =>IndexedFoldi s a -> (i -> a -> m) -> s -> mifoldMapOf::IndexedLens'i s a -> (i -> a -> m) -> s -> mifoldMapOf::Monoidm =>IndexedTraversal'i s a -> (i -> a -> m) -> s -> m
ifoldrOf :: IndexedGetting i (Endo r) s a -> (i -> a -> r -> r) -> r -> s -> r #
Right-associative fold of parts of a structure that are viewed through an IndexedFold or IndexedTraversal with
access to the i.
When you don't need access to the index then foldrOf is more flexible in what it accepts.
foldrOfl ≡ifoldrOfl.const
ifoldrOf::IndexedGetteri s a -> (i -> a -> r -> r) -> r -> s -> rifoldrOf::IndexedFoldi s a -> (i -> a -> r -> r) -> r -> s -> rifoldrOf::IndexedLens'i s a -> (i -> a -> r -> r) -> r -> s -> rifoldrOf::IndexedTraversal'i s a -> (i -> a -> r -> r) -> r -> s -> r
ifoldlOf :: IndexedGetting i (Dual (Endo r)) s a -> (i -> r -> a -> r) -> r -> s -> r #
Left-associative fold of the parts of a structure that are viewed through an IndexedFold or IndexedTraversal with
access to the i.
When you don't need access to the index then foldlOf is more flexible in what it accepts.
foldlOfl ≡ifoldlOfl.const
ifoldlOf::IndexedGetteri s a -> (i -> r -> a -> r) -> r -> s -> rifoldlOf::IndexedFoldi s a -> (i -> r -> a -> r) -> r -> s -> rifoldlOf::IndexedLens'i s a -> (i -> r -> a -> r) -> r -> s -> rifoldlOf::IndexedTraversal'i s a -> (i -> r -> a -> r) -> r -> s -> r
ianyOf :: IndexedGetting i Any s a -> (i -> a -> Bool) -> s -> Bool #
Return whether or not any element viewed through an IndexedFold or IndexedTraversal
satisfy a predicate, with access to the i.
When you don't need access to the index then anyOf is more flexible in what it accepts.
anyOfl ≡ianyOfl.const
ianyOf::IndexedGetteri s a -> (i -> a ->Bool) -> s ->BoolianyOf::IndexedFoldi s a -> (i -> a ->Bool) -> s ->BoolianyOf::IndexedLens'i s a -> (i -> a ->Bool) -> s ->BoolianyOf::IndexedTraversal'i s a -> (i -> a ->Bool) -> s ->Bool
iallOf :: IndexedGetting i All s a -> (i -> a -> Bool) -> s -> Bool #
Return whether or not all elements viewed through an IndexedFold or IndexedTraversal
satisfy a predicate, with access to the i.
When you don't need access to the index then allOf is more flexible in what it accepts.
allOfl ≡iallOfl.const
iallOf::IndexedGetteri s a -> (i -> a ->Bool) -> s ->BooliallOf::IndexedFoldi s a -> (i -> a ->Bool) -> s ->BooliallOf::IndexedLens'i s a -> (i -> a ->Bool) -> s ->BooliallOf::IndexedTraversal'i s a -> (i -> a ->Bool) -> s ->Bool
inoneOf :: IndexedGetting i Any s a -> (i -> a -> Bool) -> s -> Bool #
Return whether or not none of the elements viewed through an IndexedFold or IndexedTraversal
satisfy a predicate, with access to the i.
When you don't need access to the index then noneOf is more flexible in what it accepts.
noneOfl ≡inoneOfl.const
inoneOf::IndexedGetteri s a -> (i -> a ->Bool) -> s ->BoolinoneOf::IndexedFoldi s a -> (i -> a ->Bool) -> s ->BoolinoneOf::IndexedLens'i s a -> (i -> a ->Bool) -> s ->BoolinoneOf::IndexedTraversal'i s a -> (i -> a ->Bool) -> s ->Bool
itraverseOf_ :: Functor f => IndexedGetting i (Traversed r f) s a -> (i -> a -> f r) -> s -> f () #
Traverse the targets of an IndexedFold or IndexedTraversal with access to the i, discarding the results.
When you don't need access to the index then traverseOf_ is more flexible in what it accepts.
traverseOf_l ≡itraverseOfl.const
itraverseOf_::Functorf =>IndexedGetteri s a -> (i -> a -> f r) -> s -> f ()itraverseOf_::Applicativef =>IndexedFoldi s a -> (i -> a -> f r) -> s -> f ()itraverseOf_::Functorf =>IndexedLens'i s a -> (i -> a -> f r) -> s -> f ()itraverseOf_::Applicativef =>IndexedTraversal'i s a -> (i -> a -> f r) -> s -> f ()
iforOf_ :: Functor f => IndexedGetting i (Traversed r f) s a -> s -> (i -> a -> f r) -> f () #
Traverse the targets of an IndexedFold or IndexedTraversal with access to the index, discarding the results
(with the arguments flipped).
iforOf_≡flip.itraverseOf_
When you don't need access to the index then forOf_ is more flexible in what it accepts.
forOf_l a ≡iforOf_l a.const
iforOf_::Functorf =>IndexedGetteri s a -> s -> (i -> a -> f r) -> f ()iforOf_::Applicativef =>IndexedFoldi s a -> s -> (i -> a -> f r) -> f ()iforOf_::Functorf =>IndexedLens'i s a -> s -> (i -> a -> f r) -> f ()iforOf_::Applicativef =>IndexedTraversal'i s a -> s -> (i -> a -> f r) -> f ()
imapMOf_ :: Monad m => IndexedGetting i (Sequenced r m) s a -> (i -> a -> m r) -> s -> m () #
Run monadic actions for each target of an IndexedFold or IndexedTraversal with access to the index,
discarding the results.
When you don't need access to the index then mapMOf_ is more flexible in what it accepts.
mapMOf_l ≡imapMOfl.const
imapMOf_::Monadm =>IndexedGetteri s a -> (i -> a -> m r) -> s -> m ()imapMOf_::Monadm =>IndexedFoldi s a -> (i -> a -> m r) -> s -> m ()imapMOf_::Monadm =>IndexedLens'i s a -> (i -> a -> m r) -> s -> m ()imapMOf_::Monadm =>IndexedTraversal'i s a -> (i -> a -> m r) -> s -> m ()
iforMOf_ :: Monad m => IndexedGetting i (Sequenced r m) s a -> s -> (i -> a -> m r) -> m () #
Run monadic actions for each target of an IndexedFold or IndexedTraversal with access to the index,
discarding the results (with the arguments flipped).
iforMOf_≡flip.imapMOf_
When you don't need access to the index then forMOf_ is more flexible in what it accepts.
forMOf_l a ≡iforMOfl a.const
iforMOf_::Monadm =>IndexedGetteri s a -> s -> (i -> a -> m r) -> m ()iforMOf_::Monadm =>IndexedFoldi s a -> s -> (i -> a -> m r) -> m ()iforMOf_::Monadm =>IndexedLens'i s a -> s -> (i -> a -> m r) -> m ()iforMOf_::Monadm =>IndexedTraversal'i s a -> s -> (i -> a -> m r) -> m ()
iconcatMapOf :: IndexedGetting i [r] s a -> (i -> a -> [r]) -> s -> [r] #
Concatenate the results of a function of the elements of an IndexedFold or IndexedTraversal
with access to the index.
When you don't need access to the index then concatMapOf is more flexible in what it accepts.
concatMapOfl ≡iconcatMapOfl.consticoncatMapOf≡ifoldMapOf
iconcatMapOf::IndexedGetteri s a -> (i -> a -> [r]) -> s -> [r]iconcatMapOf::IndexedFoldi s a -> (i -> a -> [r]) -> s -> [r]iconcatMapOf::IndexedLens'i s a -> (i -> a -> [r]) -> s -> [r]iconcatMapOf::IndexedTraversal'i s a -> (i -> a -> [r]) -> s -> [r]
ifindOf :: IndexedGetting i (Endo (Maybe a)) s a -> (i -> a -> Bool) -> s -> Maybe a #
The ifindOf function takes an IndexedFold or IndexedTraversal, a predicate that is also
supplied the index, a structure and returns the left-most element of the structure
matching the predicate, or Nothing if there is no such element.
When you don't need access to the index then findOf is more flexible in what it accepts.
findOfl ≡ifindOfl.const
ifindOf::IndexedGetteri s a -> (i -> a ->Bool) -> s ->MaybeaifindOf::IndexedFoldi s a -> (i -> a ->Bool) -> s ->MaybeaifindOf::IndexedLens'i s a -> (i -> a ->Bool) -> s ->MaybeaifindOf::IndexedTraversal'i s a -> (i -> a ->Bool) -> s ->Maybea
ifindMOf :: Monad m => IndexedGetting i (Endo (m (Maybe a))) s a -> (i -> a -> m Bool) -> s -> m (Maybe a) #
The ifindMOf function takes an IndexedFold or IndexedTraversal, a monadic predicate that is also
supplied the index, a structure and returns in the monad the left-most element of the structure
matching the predicate, or Nothing if there is no such element.
When you don't need access to the index then findMOf is more flexible in what it accepts.
findMOfl ≡ifindMOfl.const
ifindMOf::Monadm =>IndexedGetteri s a -> (i -> a -> mBool) -> s -> m (Maybea)ifindMOf::Monadm =>IndexedFoldi s a -> (i -> a -> mBool) -> s -> m (Maybea)ifindMOf::Monadm =>IndexedLens'i s a -> (i -> a -> mBool) -> s -> m (Maybea)ifindMOf::Monadm =>IndexedTraversal'i s a -> (i -> a -> mBool) -> s -> m (Maybea)
ifoldrOf' :: IndexedGetting i (Dual (Endo (r -> r))) s a -> (i -> a -> r -> r) -> r -> s -> r #
Strictly fold right over the elements of a structure with an index.
When you don't need access to the index then foldrOf' is more flexible in what it accepts.
foldrOf'l ≡ifoldrOf'l.const
ifoldrOf'::IndexedGetteri s a -> (i -> a -> r -> r) -> r -> s -> rifoldrOf'::IndexedFoldi s a -> (i -> a -> r -> r) -> r -> s -> rifoldrOf'::IndexedLens'i s a -> (i -> a -> r -> r) -> r -> s -> rifoldrOf'::IndexedTraversal'i s a -> (i -> a -> r -> r) -> r -> s -> r
ifoldlOf' :: IndexedGetting i (Endo (r -> r)) s a -> (i -> r -> a -> r) -> r -> s -> r #
Fold over the elements of a structure with an index, associating to the left, but strictly.
When you don't need access to the index then foldlOf' is more flexible in what it accepts.
foldlOf'l ≡ifoldlOf'l.const
ifoldlOf'::IndexedGetteri s a -> (i -> r -> a -> r) -> r -> s -> rifoldlOf'::IndexedFoldi s a -> (i -> r -> a -> r) -> r -> s -> rifoldlOf'::IndexedLens'i s a -> (i -> r -> a -> r) -> r -> s -> rifoldlOf'::IndexedTraversal'i s a -> (i -> r -> a -> r) -> r -> s -> r
ifoldrMOf :: Monad m => IndexedGetting i (Dual (Endo (r -> m r))) s a -> (i -> a -> r -> m r) -> r -> s -> m r #
Monadic fold right over the elements of a structure with an index.
When you don't need access to the index then foldrMOf is more flexible in what it accepts.
foldrMOfl ≡ifoldrMOfl.const
ifoldrMOf::Monadm =>IndexedGetteri s a -> (i -> a -> r -> m r) -> r -> s -> m rifoldrMOf::Monadm =>IndexedFoldi s a -> (i -> a -> r -> m r) -> r -> s -> m rifoldrMOf::Monadm =>IndexedLens'i s a -> (i -> a -> r -> m r) -> r -> s -> m rifoldrMOf::Monadm =>IndexedTraversal'i s a -> (i -> a -> r -> m r) -> r -> s -> m r
ifoldlMOf :: Monad m => IndexedGetting i (Endo (r -> m r)) s a -> (i -> r -> a -> m r) -> r -> s -> m r #
Monadic fold over the elements of a structure with an index, associating to the left.
When you don't need access to the index then foldlMOf is more flexible in what it accepts.
foldlMOfl ≡ifoldlMOfl.const
ifoldlMOf::Monadm =>IndexedGetteri s a -> (i -> r -> a -> m r) -> r -> s -> m rifoldlMOf::Monadm =>IndexedFoldi s a -> (i -> r -> a -> m r) -> r -> s -> m rifoldlMOf::Monadm =>IndexedLens'i s a -> (i -> r -> a -> m r) -> r -> s -> m rifoldlMOf::Monadm =>IndexedTraversal'i s a -> (i -> r -> a -> m r) -> r -> s -> m r
itoListOf :: IndexedGetting i (Endo [(i, a)]) s a -> s -> [(i, a)] #
Extract the key-value pairs from a structure.
When you don't need access to the indices in the result, then toListOf is more flexible in what it accepts.
toListOfl ≡mapsnd.itoListOfl
itoListOf::IndexedGetteri s a -> s -> [(i,a)]itoListOf::IndexedFoldi s a -> s -> [(i,a)]itoListOf::IndexedLens'i s a -> s -> [(i,a)]itoListOf::IndexedTraversal'i s a -> s -> [(i,a)]
(^@..) :: s -> IndexedGetting i (Endo [(i, a)]) s a -> [(i, a)] infixl 8 #
An infix version of itoListOf.
(^@?) :: s -> IndexedGetting i (Endo (Maybe (i, a))) s a -> Maybe (i, a) infixl 8 #
Perform a safe head (with index) of an IndexedFold or IndexedTraversal or retrieve Just the index and result
from an IndexedGetter or IndexedLens.
When using a IndexedTraversal as a partial IndexedLens, or an IndexedFold as a partial IndexedGetter this can be a convenient
way to extract the optional value.
(^@?) :: s ->IndexedGetteri s a ->Maybe(i, a) (^@?) :: s ->IndexedFoldi s a ->Maybe(i, a) (^@?) :: s ->IndexedLens'i s a ->Maybe(i, a) (^@?) :: s ->IndexedTraversal'i s a ->Maybe(i, a)
(^@?!) :: HasCallStack => s -> IndexedGetting i (Endo (i, a)) s a -> (i, a) infixl 8 #
Perform an *UNSAFE* head (with index) of an IndexedFold or IndexedTraversal assuming that it is there.
(^@?!) :: s ->IndexedGetteri s a -> (i, a) (^@?!) :: s ->IndexedFoldi s a -> (i, a) (^@?!) :: s ->IndexedLens'i s a -> (i, a) (^@?!) :: s ->IndexedTraversal'i s a -> (i, a)
elemIndexOf :: Eq a => IndexedGetting i (First i) s a -> a -> s -> Maybe i #
Retrieve the index of the first value targeted by a IndexedFold or IndexedTraversal which is equal to a given value.
elemIndex≡elemIndexOffolded
elemIndexOf::Eqa =>IndexedFoldi s a -> a -> s ->MaybeielemIndexOf::Eqa =>IndexedTraversal'i s a -> a -> s ->Maybei
elemIndicesOf :: Eq a => IndexedGetting i (Endo [i]) s a -> a -> s -> [i] #
Retrieve the indices of the values targeted by a IndexedFold or IndexedTraversal which are equal to a given value.
elemIndices≡elemIndicesOffolded
elemIndicesOf::Eqa =>IndexedFoldi s a -> a -> s -> [i]elemIndicesOf::Eqa =>IndexedTraversal'i s a -> a -> s -> [i]
findIndexOf :: IndexedGetting i (First i) s a -> (a -> Bool) -> s -> Maybe i #
Retrieve the index of the first value targeted by a IndexedFold or IndexedTraversal which satisfies a predicate.
findIndex≡findIndexOffolded
findIndexOf::IndexedFoldi s a -> (a ->Bool) -> s ->MaybeifindIndexOf::IndexedTraversal'i s a -> (a ->Bool) -> s ->Maybei
findIndicesOf :: IndexedGetting i (Endo [i]) s a -> (a -> Bool) -> s -> [i] #
Retrieve the indices of the values targeted by a IndexedFold or IndexedTraversal which satisfy a predicate.
findIndices≡findIndicesOffolded
findIndicesOf::IndexedFoldi s a -> (a ->Bool) -> s -> [i]findIndicesOf::IndexedTraversal'i s a -> (a ->Bool) -> s -> [i]
ifiltered :: (Indexable i p, Applicative f) => (i -> a -> Bool) -> Optical' p (Indexed i) f a a #
Filter an IndexedFold or IndexedGetter, obtaining an IndexedFold.
>>>[0,0,0,5,5,5]^..traversed.ifiltered (\i a -> i <= a)[0,5,5,5]
Compose with ifiltered to filter another IndexedLens, IndexedIso, IndexedGetter, IndexedFold (or IndexedTraversal) with
access to both the value and the index.
Note: As with filtered, this is not a legal IndexedTraversal, unless you are very careful not to invalidate the predicate on the target!
itakingWhile :: (Indexable i p, Profunctor q, Contravariant f, Applicative f) => (i -> a -> Bool) -> Optical' (Indexed i) q (Const (Endo (f s)) :: Type -> Type) s a -> Optical' p q f s a #
Obtain an IndexedFold by taking elements from another
IndexedFold, IndexedLens, IndexedGetter or IndexedTraversal while a predicate holds.
itakingWhile:: (i -> a ->Bool) ->IndexedFoldi s a ->IndexedFoldi s aitakingWhile:: (i -> a ->Bool) ->IndexedTraversal'i s a ->IndexedFoldi s aitakingWhile:: (i -> a ->Bool) ->IndexedLens'i s a ->IndexedFoldi s aitakingWhile:: (i -> a ->Bool) ->IndexedGetteri s a ->IndexedFoldi s a
Note: Applying itakingWhile to an IndexedLens or IndexedTraversal will still allow you to use it as a
pseudo-IndexedTraversal, but if you change the value of any target to one where the predicate returns
False, then you will break the Traversal laws and Traversal fusion will no longer be sound.
idroppingWhile :: (Indexable i p, Profunctor q, Applicative f) => (i -> a -> Bool) -> Optical (Indexed i) q (Compose (State Bool) f) s t a a -> Optical p q f s t a a #
Obtain an IndexedFold by dropping elements from another IndexedFold, IndexedLens, IndexedGetter or IndexedTraversal while a predicate holds.
idroppingWhile:: (i -> a ->Bool) ->IndexedFoldi s a ->IndexedFoldi s aidroppingWhile:: (i -> a ->Bool) ->IndexedTraversal'i s a ->IndexedFoldi s a -- see notesidroppingWhile:: (i -> a ->Bool) ->IndexedLens'i s a ->IndexedFoldi s a -- see notesidroppingWhile:: (i -> a ->Bool) ->IndexedGetteri s a ->IndexedFoldi s a
Note: As with droppingWhile applying idroppingWhile to an IndexedLens or IndexedTraversal will still
allow you to use it as a pseudo-IndexedTraversal, but if you change the value of the first target to one
where the predicate returns True, then you will break the Traversal laws and Traversal fusion will
no longer be sound.
foldByOf :: Fold s a -> (a -> a -> a) -> a -> s -> a #
Fold a value using a specified Fold and Monoid operations.
This is like foldBy where the Foldable instance can be
manually specified.
foldByOffolded≡foldBy
foldByOf::Getters a -> (a -> a -> a) -> a -> s -> afoldByOf::Folds a -> (a -> a -> a) -> a -> s -> afoldByOf::Lens's a -> (a -> a -> a) -> a -> s -> afoldByOf::Traversal's a -> (a -> a -> a) -> a -> s -> afoldByOf::Iso's a -> (a -> a -> a) -> a -> s -> a
>>>foldByOf both (++) [] ("hello","world")"helloworld"
foldMapByOf :: Fold s a -> (r -> r -> r) -> r -> (a -> r) -> s -> r #
Fold a value using a specified Fold and Monoid operations.
This is like foldMapBy where the Foldable instance can be
manually specified.
foldMapByOffolded≡foldMapBy
foldMapByOf::Getters a -> (r -> r -> r) -> r -> (a -> r) -> s -> rfoldMapByOf::Folds a -> (r -> r -> r) -> r -> (a -> r) -> s -> rfoldMapByOf::Traversal's a -> (r -> r -> r) -> r -> (a -> r) -> s -> rfoldMapByOf::Lens's a -> (r -> r -> r) -> r -> (a -> r) -> s -> rfoldMapByOf::Iso's a -> (r -> r -> r) -> r -> (a -> r) -> s -> r
>>>foldMapByOf both (+) 0 length ("hello","world")10
class Ord k => TraverseMax k (m :: Type -> Type) | m -> k where #
Allows IndexedTraversal of the value at the largest index.
Methods
traverseMax :: IndexedTraversal' k (m v) v #
IndexedTraversal of the element at the largest index.
Instances
| TraverseMax Int IntMap | |
Defined in Control.Lens.Traversal Methods traverseMax :: IndexedTraversal' Int (IntMap v) v # | |
| Ord k => TraverseMax k (Map k) | |
Defined in Control.Lens.Traversal Methods traverseMax :: IndexedTraversal' k (Map k v) v # | |
class Ord k => TraverseMin k (m :: Type -> Type) | m -> k where #
Allows IndexedTraversal the value at the smallest index.
Methods
traverseMin :: IndexedTraversal' k (m v) v #
IndexedTraversal of the element with the smallest index.
Instances
| TraverseMin Int IntMap | |
Defined in Control.Lens.Traversal Methods traverseMin :: IndexedTraversal' Int (IntMap v) v # | |
| Ord k => TraverseMin k (Map k) | |
Defined in Control.Lens.Traversal Methods traverseMin :: IndexedTraversal' k (Map k v) v # | |
type Traversing1' (p :: Type -> Type -> Type) (f :: Type -> Type) s a = Traversing1 p f s s a a #
type Traversing' (p :: Type -> Type -> Type) (f :: Type -> Type) s a = Traversing p f s s a a #
typeTraversing'f =Simple(Traversingf)
type Traversing1 (p :: Type -> Type -> Type) (f :: Type -> Type) s t a b = Over p (BazaarT1 p f a b) s t a b #
type Traversing (p :: Type -> Type -> Type) (f :: Type -> Type) s t a b = Over p (BazaarT p f a b) s t a b #
When you see this as an argument to a function, it expects
- to be indexed if
pis an instance ofIndexedi, - to be unindexed if
pis(->), - a
TraversaliffisApplicative, - a
Getteriffis only aFunctorandContravariant, - a
Lensiffis only aFunctor, - a
FoldiffisApplicativeandContravariant.
type AnIndexedTraversal1' i s a = AnIndexedTraversal1 i s s a a #
typeAnIndexedTraversal1'=Simple(AnIndexedTraversal1i)
type AnIndexedTraversal' i s a = AnIndexedTraversal i s s a a #
typeAnIndexedTraversal'=Simple(AnIndexedTraversali)
type AnIndexedTraversal1 i s t a b = Over (Indexed i) (Bazaar1 (Indexed i) a b) s t a b #
When you see this as an argument to a function, it expects an IndexedTraversal1.
type AnIndexedTraversal i s t a b = Over (Indexed i) (Bazaar (Indexed i) a b) s t a b #
When you see this as an argument to a function, it expects an IndexedTraversal.
type ATraversal1' s a = ATraversal1 s s a a #
typeATraversal1'=SimpleATraversal1
type ATraversal1 s t a b = LensLike (Bazaar1 ((->) :: Type -> Type -> Type) a b) s t a b #
When you see this as an argument to a function, it expects a Traversal1.
type ATraversal' s a = ATraversal s s a a #
typeATraversal'=SimpleATraversal
type ATraversal s t a b = LensLike (Bazaar ((->) :: Type -> Type -> Type) a b) s t a b #
When you see this as an argument to a function, it expects a Traversal.
traverseOf :: LensLike f s t a b -> (a -> f b) -> s -> f t #
Map each element of a structure targeted by a Lens or Traversal,
evaluate these actions from left to right, and collect the results.
This function is only provided for consistency, id is strictly more general.
>>>traverseOf each print (1,2,3)1 2 3 ((),(),())
traverseOf≡iditraverseOfl ≡traverseOfl.IndexeditraverseOfitraversed≡itraverse
This yields the obvious law:
traverse≡traverseOftraverse
traverseOf::Functorf =>Isos t a b -> (a -> f b) -> s -> f ttraverseOf::Functorf =>Lenss t a b -> (a -> f b) -> s -> f ttraverseOf::Applyf =>Traversal1s t a b -> (a -> f b) -> s -> f ttraverseOf::Applicativef =>Traversals t a b -> (a -> f b) -> s -> f t
forOf :: LensLike f s t a b -> s -> (a -> f b) -> f t #
A version of traverseOf with the arguments flipped, such that:
>>>forOf each (1,2,3) print1 2 3 ((),(),())
This function is only provided for consistency, flip is strictly more general.
forOf≡flipforOf≡flip.traverseOf
for≡forOftraverseiforl s ≡forl s.Indexed
forOf::Functorf =>Isos t a b -> s -> (a -> f b) -> f tforOf::Functorf =>Lenss t a b -> s -> (a -> f b) -> f tforOf::Applicativef =>Traversals t a b -> s -> (a -> f b) -> f t
sequenceAOf :: LensLike f s t (f b) b -> s -> f t #
Evaluate each action in the structure from left to right, and collect the results.
>>>sequenceAOf both ([1,2],[3,4])[(1,3),(1,4),(2,3),(2,4)]
sequenceA≡sequenceAOftraverse≡traverseidsequenceAOfl ≡traverseOflid≡ lid
sequenceAOf::Functorf =>Isos t (f b) b -> s -> f tsequenceAOf::Functorf =>Lenss t (f b) b -> s -> f tsequenceAOf::Applicativef =>Traversals t (f b) b -> s -> f t
mapMOf :: LensLike (WrappedMonad m) s t a b -> (a -> m b) -> s -> m t #
Map each element of a structure targeted by a Lens to a monadic action,
evaluate these actions from left to right, and collect the results.
>>>mapMOf both (\x -> [x, x + 1]) (1,3)[(1,3),(1,4),(2,3),(2,4)]
mapM≡mapMOftraverseimapMOfl ≡forMl.Indexed
mapMOf::Monadm =>Isos t a b -> (a -> m b) -> s -> m tmapMOf::Monadm =>Lenss t a b -> (a -> m b) -> s -> m tmapMOf::Monadm =>Traversals t a b -> (a -> m b) -> s -> m t
forMOf :: LensLike (WrappedMonad m) s t a b -> s -> (a -> m b) -> m t #
forMOf is a flipped version of mapMOf, consistent with the definition of forM.
>>>forMOf both (1,3) $ \x -> [x, x + 1][(1,3),(1,4),(2,3),(2,4)]
forM≡forMOftraverseforMOfl ≡flip(mapMOfl)iforMOfl s ≡forMl s.Indexed
forMOf::Monadm =>Isos t a b -> s -> (a -> m b) -> m tforMOf::Monadm =>Lenss t a b -> s -> (a -> m b) -> m tforMOf::Monadm =>Traversals t a b -> s -> (a -> m b) -> m t
sequenceOf :: LensLike (WrappedMonad m) s t (m b) b -> s -> m t #
Sequence the (monadic) effects targeted by a Lens in a container from left to right.
>>>sequenceOf each ([1,2],[3,4],[5,6])[(1,3,5),(1,3,6),(1,4,5),(1,4,6),(2,3,5),(2,3,6),(2,4,5),(2,4,6)]
sequence≡sequenceOftraversesequenceOfl ≡mapMOflidsequenceOfl ≡unwrapMonad.lWrapMonad
sequenceOf::Monadm =>Isos t (m b) b -> s -> m tsequenceOf::Monadm =>Lenss t (m b) b -> s -> m tsequenceOf::Monadm =>Traversals t (m b) b -> s -> m t
transposeOf :: LensLike ZipList s t [a] a -> s -> [t] #
This generalizes transpose to an arbitrary Traversal.
Note: transpose handles ragged inputs more intelligently, but for non-ragged inputs:
>>>transposeOf traverse [[1,2,3],[4,5,6]][[1,4],[2,5],[3,6]]
transpose≡transposeOftraverse
Since every Lens is a Traversal, we can use this as a form of
monadic strength as well:
transposeOf_2:: (b, [a]) -> [(b, a)]
mapAccumROf :: LensLike (Backwards (State acc)) s t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t) #
This generalizes mapAccumR to an arbitrary Traversal.
mapAccumR≡mapAccumROftraverse
mapAccumROf accumulates State from right to left.
mapAccumROf::Isos t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t)mapAccumROf::Lenss t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t)mapAccumROf::Traversals t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t)
mapAccumROf::LensLike(Backwards(Stateacc)) s t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t)
mapAccumLOf :: LensLike (State acc) s t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t) #
This generalizes mapAccumL to an arbitrary Traversal.
mapAccumL≡mapAccumLOftraverse
mapAccumLOf accumulates State from left to right.
mapAccumLOf::Isos t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t)mapAccumLOf::Lenss t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t)mapAccumLOf::Traversals t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t)
mapAccumLOf::LensLike(Stateacc) s t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t)mapAccumLOfl f acc0 s =swap(runState(l (a ->state(acc ->swap(f acc a))) s) acc0)
loci :: Traversal (Bazaar ((->) :: Type -> Type -> Type) a c s) (Bazaar ((->) :: Type -> Type -> Type) b c s) a b #
iloci :: IndexedTraversal i (Bazaar (Indexed i) a c s) (Bazaar (Indexed i) b c s) a b #
This IndexedTraversal allows you to traverse the individual stores in
a Bazaar with access to their indices.
partsOf :: Functor f => Traversing ((->) :: Type -> Type -> Type) f s t a a -> LensLike f s t [a] [a] #
partsOf turns a Traversal into a Lens that resembles an early version of the uniplate (or biplate) type.
Note: You should really try to maintain the invariant of the number of children in the list.
>>>(a,b,c) & partsOf each .~ [x,y,z](x,y,z)
Any extras will be lost. If you do not supply enough, then the remainder will come from the original structure.
>>>(a,b,c) & partsOf each .~ [w,x,y,z](w,x,y)
>>>(a,b,c) & partsOf each .~ [x,y](x,y,c)
>>>('b', 'a', 'd', 'c') & partsOf each %~ sort('a','b','c','d')
So technically, this is only a Lens if you do not change the number of results it returns.
When applied to a Fold the result is merely a Getter.
partsOf::Iso's a ->Lens's [a]partsOf::Lens's a ->Lens's [a]partsOf::Traversal's a ->Lens's [a]partsOf::Folds a ->Getters [a]partsOf::Getters a ->Getters [a]
ipartsOf :: (Indexable [i] p, Functor f) => Traversing (Indexed i) f s t a a -> Over p f s t [a] [a] #
An indexed version of partsOf that receives the entire list of indices as its index.
partsOf' :: ATraversal s t a a -> Lens s t [a] [a] #
ipartsOf' :: (Indexable [i] p, Functor f) => Over (Indexed i) (Bazaar' (Indexed i) a) s t a a -> Over p f s t [a] [a] #
A type-restricted version of ipartsOf that can only be used with an IndexedTraversal.
unsafePartsOf :: Functor f => Traversing ((->) :: Type -> Type -> Type) f s t a b -> LensLike f s t [a] [b] #
unsafePartsOf turns a Traversal into a uniplate (or biplate) family.
If you do not need the types of s and t to be different, it is recommended that
you use partsOf.
It is generally safer to traverse with the Bazaar rather than use this
combinator. However, it is sometimes convenient.
This is unsafe because if you don't supply at least as many b's as you were
given a's, then the reconstruction of t will result in an error!
When applied to a Fold the result is merely a Getter (and becomes safe).
unsafePartsOf::Isos t a b ->Lenss t [a] [b]unsafePartsOf::Lenss t a b ->Lenss t [a] [b]unsafePartsOf::Traversals t a b ->Lenss t [a] [b]unsafePartsOf::Folds a ->Getters [a]unsafePartsOf::Getters a ->Getters [a]
iunsafePartsOf :: (Indexable [i] p, Functor f) => Traversing (Indexed i) f s t a b -> Over p f s t [a] [b] #
An indexed version of unsafePartsOf that receives the entire list of indices as its index.
unsafePartsOf' :: ATraversal s t a b -> Lens s t [a] [b] #
iunsafePartsOf' :: Over (Indexed i) (Bazaar (Indexed i) a b) s t a b -> IndexedLens [i] s t [a] [b] #
unsafeSingular :: (HasCallStack, Conjoined p, Functor f) => Traversing p f s t a b -> Over p f s t a b #
This converts a Traversal that you "know" will target only one element to a Lens. It can also be
used to transform a Fold into a Getter.
The resulting Lens or Getter will be partial if the Traversal targets nothing
or more than one element.
>>>Left (ErrorCall "unsafeSingular: empty traversal") <- try (evaluate ([] & unsafeSingular traverse .~ 0)) :: IO (Either ErrorCall [Integer])
unsafeSingular::Traversals t a b ->Lenss t a bunsafeSingular::Folds a ->Getters aunsafeSingular::IndexedTraversali s t a b ->IndexedLensi s t a bunsafeSingular::IndexedFoldi s a ->IndexedGetteri s a
holesOf :: Conjoined p => Over p (Bazaar p a a) s t a a -> s -> [Pretext p a a t] #
The one-level version of contextsOf. This extracts a
list of the immediate children according to a given Traversal as editable
contexts.
Given a context you can use pos to see the
values, peek at what the structure would be
like with an edited result, or simply extract the original structure.
propChildren l x =toListOfl x==mappos(holesOfl x) propId l x =all(==x) [extractw | w <-holesOfl x]
holesOf::Iso's a -> s -> [Pretext'(->) a s]holesOf::Lens's a -> s -> [Pretext'(->) a s]holesOf::Traversal's a -> s -> [Pretext'(->) a s]holesOf::IndexedLens'i s a -> s -> [Pretext'(Indexedi) a s]holesOf::IndexedTraversal'i s a -> s -> [Pretext'(Indexedi) a s]
holes1Of :: Conjoined p => Over p (Bazaar1 p a a) s t a a -> s -> NonEmpty (Pretext p a a t) #
The non-empty version of holesOf.
This extract a non-empty list of immediate children accroding to a given
Traversal1 as editable contexts.
>>>let head1 f s = runPretext (NonEmpty.head $ holes1Of traversed1 s) f>>>('a' :| "bc") ^. head1'a'
>>>('a' :| "bc") & head1 %~ toUpper'A' :| "bc"
holes1Of::Iso's a -> s ->NonEmpty(Pretext'(->) a s)holes1Of::Lens's a -> s ->NonEmpty(Pretext'(->) a s)holes1Of::Traversal1's a -> s ->NonEmpty(Pretext'(->) a s)holes1Of::IndexedLens'i s a -> s ->NonEmpty(Pretext'(Indexedi) a s)holes1Of::IndexedTraversal1'i s a -> s ->NonEmpty(Pretext'(Indexedi) a s)
both :: Bitraversable r => Traversal (r a a) (r b b) a b #
Traverse both parts of a Bitraversable container with matching types.
Usually that type will be a pair.
>>>(1,2) & both *~ 10(10,20)
>>>over both length ("hello","world")(5,5)
>>>("hello","world")^.both"helloworld"
both::Traversal(a, a) (b, b) a bboth::Traversal(Eithera a) (Eitherb b) a b
both1 :: Bitraversable1 r => Traversal1 (r a a) (r b b) a b #
Traverse both parts of a Bitraversable1 container with matching types.
Usually that type will be a pair.
both1::Traversal1(a, a) (b, b) a bboth1::Traversal1(Eithera a) (Eitherb b) a b
taking :: (Conjoined p, Applicative f) => Int -> Traversing p f s t a a -> Over p f s t a a #
Visit the first n targets of a Traversal, Fold, Getter or Lens.
>>>[("hello","world"),("!!!","!!!")]^.. taking 2 (traverse.both)["hello","world"]
>>>timingOut $ [1..] ^.. taking 3 traverse[1,2,3]
>>>over (taking 5 traverse) succ "hello world""ifmmp world"
taking::Int->Traversal's a ->Traversal's ataking::Int->Lens's a ->Traversal's ataking::Int->Iso's a ->Traversal's ataking::Int->Prism's a ->Traversal's ataking::Int->Getters a ->Folds ataking::Int->Folds a ->Folds ataking::Int->IndexedTraversal'i s a ->IndexedTraversal'i s ataking::Int->IndexedLens'i s a ->IndexedTraversal'i s ataking::Int->IndexedGetteri s a ->IndexedFoldi s ataking::Int->IndexedFoldi s a ->IndexedFoldi s a
dropping :: (Conjoined p, Applicative f) => Int -> Over p (Indexing f) s t a a -> Over p f s t a a #
Visit all but the first n targets of a Traversal, Fold, Getter or Lens.
>>>("hello","world") ^? dropping 1 bothJust "world"
Dropping works on infinite traversals as well:
>>>[1..] ^? dropping 1 foldedJust 2
dropping::Int->Traversal's a ->Traversal's adropping::Int->Lens's a ->Traversal's adropping::Int->Iso's a ->Traversal's adropping::Int->Prism's a ->Traversal's adropping::Int->Getters a ->Folds adropping::Int->Folds a ->Folds adropping::Int->IndexedTraversal'i s a ->IndexedTraversal'i s adropping::Int->IndexedLens'i s a ->IndexedTraversal'i s adropping::Int->IndexedGetteri s a ->IndexedFoldi s adropping::Int->IndexedFoldi s a ->IndexedFoldi s a
cloneTraversal :: ATraversal s t a b -> Traversal s t a b #
A Traversal is completely characterized by its behavior on a Bazaar.
Cloning a Traversal is one way to make sure you aren't given
something weaker, such as a Fold and can be
used as a way to pass around traversals that have to be monomorphic in f.
Note: This only accepts a proper Traversal (or Lens). To clone a Lens
as such, use cloneLens.
Note: It is usually better to use ReifiedTraversal and
runTraversal than to cloneTraversal. The
former can execute at full speed, while the latter needs to round trip through
the Bazaar.
>>>let foo l a = (view (getting (cloneTraversal l)) a, set (cloneTraversal l) 10 a)>>>foo both ("hello","world")("helloworld",(10,10))
cloneTraversal::LensLike(Bazaar(->) a b) s t a b ->Traversals t a b
cloneIndexPreservingTraversal :: ATraversal s t a b -> IndexPreservingTraversal s t a b #
Clone a Traversal yielding an IndexPreservingTraversal that passes through
whatever index it is composed with.
cloneIndexedTraversal :: AnIndexedTraversal i s t a b -> IndexedTraversal i s t a b #
Clone an IndexedTraversal yielding an IndexedTraversal with the same index.
cloneTraversal1 :: ATraversal1 s t a b -> Traversal1 s t a b #
A Traversal1 is completely characterized by its behavior on a Bazaar1.
cloneIndexPreservingTraversal1 :: ATraversal1 s t a b -> IndexPreservingTraversal1 s t a b #
Clone a Traversal1 yielding an IndexPreservingTraversal1 that passes through
whatever index it is composed with.
cloneIndexedTraversal1 :: AnIndexedTraversal1 i s t a b -> IndexedTraversal1 i s t a b #
Clone an IndexedTraversal1 yielding an IndexedTraversal1 with the same index.
itraverseOf :: (Indexed i a (f b) -> s -> f t) -> (i -> a -> f b) -> s -> f t #
Traversal with an index.
NB: When you don't need access to the index then you can just apply your IndexedTraversal
directly as a function!
itraverseOf≡withIndextraverseOfl =itraverseOfl.const=id
itraverseOf::Functorf =>IndexedLensi s t a b -> (i -> a -> f b) -> s -> f titraverseOf::Applicativef =>IndexedTraversali s t a b -> (i -> a -> f b) -> s -> f titraverseOf::Applyf =>IndexedTraversal1i s t a b -> (i -> a -> f b) -> s -> f t
iforOf :: (Indexed i a (f b) -> s -> f t) -> s -> (i -> a -> f b) -> f t #
Traverse with an index (and the arguments flipped).
forOfl a ≡iforOfl a.constiforOf≡flip.itraverseOf
iforOf::Functorf =>IndexedLensi s t a b -> s -> (i -> a -> f b) -> f tiforOf::Applicativef =>IndexedTraversali s t a b -> s -> (i -> a -> f b) -> f tiforOf::Applyf =>IndexedTraversal1i s t a b -> s -> (i -> a -> f b) -> f t
imapMOf :: Over (Indexed i) (WrappedMonad m) s t a b -> (i -> a -> m b) -> s -> m t #
Map each element of a structure targeted by a Lens to a monadic action,
evaluate these actions from left to right, and collect the results, with access
its position.
When you don't need access to the index mapMOf is more liberal in what it can accept.
mapMOfl ≡imapMOfl.const
imapMOf::Monadm =>IndexedLensi s t a b -> (i -> a -> m b) -> s -> m timapMOf::Monadm =>IndexedTraversali s t a b -> (i -> a -> m b) -> s -> m timapMOf::Bindm =>IndexedTraversal1i s t a b -> (i -> a -> m b) -> s -> m t
iforMOf :: (Indexed i a (WrappedMonad m b) -> s -> WrappedMonad m t) -> s -> (i -> a -> m b) -> m t #
Map each element of a structure targeted by a Lens to a monadic action,
evaluate these actions from left to right, and collect the results, with access
its position (and the arguments flipped).
forMOfl a ≡iforMOfl a.constiforMOf≡flip.imapMOf
iforMOf::Monadm =>IndexedLensi s t a b -> s -> (i -> a -> m b) -> m tiforMOf::Monadm =>IndexedTraversali s t a b -> s -> (i -> a -> m b) -> m t
imapAccumROf :: Over (Indexed i) (Backwards (State acc)) s t a b -> (i -> acc -> a -> (acc, b)) -> acc -> s -> (acc, t) #
Generalizes mapAccumR to an arbitrary IndexedTraversal with access to the index.
imapAccumROf accumulates state from right to left.
mapAccumROfl ≡imapAccumROfl.const
imapAccumROf::IndexedLensi s t a b -> (i -> acc -> a -> (acc, b)) -> acc -> s -> (acc, t)imapAccumROf::IndexedTraversali s t a b -> (i -> acc -> a -> (acc, b)) -> acc -> s -> (acc, t)
imapAccumLOf :: Over (Indexed i) (State acc) s t a b -> (i -> acc -> a -> (acc, b)) -> acc -> s -> (acc, t) #
Generalizes mapAccumL to an arbitrary IndexedTraversal with access to the index.
imapAccumLOf accumulates state from left to right.
mapAccumLOfl ≡imapAccumLOfl.const
imapAccumLOf::IndexedLensi s t a b -> (i -> acc -> a -> (acc, b)) -> acc -> s -> (acc, t)imapAccumLOf::IndexedTraversali s t a b -> (i -> acc -> a -> (acc, b)) -> acc -> s -> (acc, t)
traversed :: Traversable f => IndexedTraversal Int (f a) (f b) a b #
Traverse any Traversable container. This is an IndexedTraversal that is indexed by ordinal position.
traversed1 :: Traversable1 f => IndexedTraversal1 Int (f a) (f b) a b #
Traverse any Traversable1 container. This is an IndexedTraversal1 that is indexed by ordinal position.
traversed64 :: Traversable f => IndexedTraversal Int64 (f a) (f b) a b #
Traverse any Traversable container. This is an IndexedTraversal that is indexed by ordinal position.
ignored :: Applicative f => pafb -> s -> f s #
elementOf :: Applicative f => LensLike (Indexing f) s t a a -> Int -> IndexedLensLike Int f s t a a #
Traverse the nth elementOf a Traversal, Lens or
Iso if it exists.
>>>[[1],[3,4]] & elementOf (traverse.traverse) 1 .~ 5[[1],[5,4]]
>>>[[1],[3,4]] ^? elementOf (folded.folded) 1Just 3
>>>timingOut $ ['a'..] ^?! elementOf folded 5'f'
>>>timingOut $ take 10 $ elementOf traverse 3 .~ 16 $ [0..][0,1,2,16,4,5,6,7,8,9]
elementOf::Traversal's a ->Int->IndexedTraversal'Ints aelementOf::Folds a ->Int->IndexedFoldInts a
element :: Traversable t => Int -> IndexedTraversal' Int (t a) a #
Traverse the nth element of a Traversable container.
element≡elementOftraverse
elementsOf :: Applicative f => LensLike (Indexing f) s t a a -> (Int -> Bool) -> IndexedLensLike Int f s t a a #
Traverse (or fold) selected elements of a Traversal (or Fold) where their ordinal positions match a predicate.
elementsOf::Traversal's a -> (Int->Bool) ->IndexedTraversal'Ints aelementsOf::Folds a -> (Int->Bool) ->IndexedFoldInts a
elements :: Traversable t => (Int -> Bool) -> IndexedTraversal' Int (t a) a #
Traverse elements of a Traversable container where their ordinal positions match a predicate.
elements≡elementsOftraverse
failover :: Alternative m => LensLike ((,) Any) s t a b -> (a -> b) -> s -> m t #
Try to map a function over this Traversal, failing if the Traversal has no targets.
>>>failover (element 3) (*2) [1,2] :: Maybe [Int]Nothing
>>>failover _Left (*2) (Right 4) :: Maybe (Either Int Int)Nothing
>>>failover _Right (*2) (Right 4) :: Maybe (Either Int Int)Just (Right 8)
failover :: Alternative m => Traversal s t a b -> (a -> b) -> s -> m t
ifailover :: Alternative m => Over (Indexed i) ((,) Any) s t a b -> (i -> a -> b) -> s -> m t #
Try to map a function which uses the index over this IndexedTraversal, failing if the IndexedTraversal has no targets.
ifailover :: Alternative m => IndexedTraversal i s t a b -> (i -> a -> b) -> s -> m t
failing :: (Conjoined p, Applicative f) => Traversing p f s t a b -> Over p f s t a b -> Over p f s t a b infixl 5 #
Try the first Traversal (or Fold), falling back on the second Traversal (or Fold) if it returns no entries.
This is only a valid Traversal if the second Traversal is disjoint from the result of the first or returns
exactly the same results. These conditions are trivially met when given a Lens, Iso, Getter, Prism or "affine" Traversal -- one that
has 0 or 1 target.
Mutatis mutandis for Fold.
>>>[0,1,2,3] ^? failing (ix 1) (ix 2)Just 1
>>>[0,1,2,3] ^? failing (ix 42) (ix 2)Just 2
failing::Traversals t a b ->Traversals t a b ->Traversals t a bfailing::Prisms t a b ->Prisms t a b ->Traversals t a bfailing::Folds a ->Folds a ->Folds a
These cases are also supported, trivially, but are boring, because the left hand side always succeeds.
failing::Lenss t a b ->Traversals t a b ->Traversals t a bfailing::Isos t a b ->Traversals t a b ->Traversals t a bfailing::Equalitys t a b ->Traversals t a b ->Traversals t a bfailing::Getters a ->Folds a ->Folds a
If both of the inputs are indexed, the result is also indexed, so you can apply this to a pair of indexed traversals or indexed folds, obtaining an indexed traversal or indexed fold.
failing::IndexedTraversali s t a b ->IndexedTraversali s t a b ->IndexedTraversali s t a bfailing::IndexedFoldi s a ->IndexedFoldi s a ->IndexedFoldi s a
These cases are also supported, trivially, but are boring, because the left hand side always succeeds.
failing::IndexedLensi s t a b ->IndexedTraversali s t a b ->IndexedTraversali s t a bfailing::IndexedGetteri s a ->IndexedGetteri s a ->IndexedFoldi s a
deepOf :: (Conjoined p, Applicative f) => LensLike f s t s t -> Traversing p f s t a b -> Over p f s t a b #
Try the second traversal. If it returns no entries, try again with all entries from the first traversal, recursively.
deepOf::Folds s ->Folds a ->Folds adeepOf::Traversal's s ->Traversal's a ->Traversal's adeepOf::Traversals t s t ->Traversals t a b ->Traversals t a bdeepOf::Folds s ->IndexedFoldi s a ->IndexedFoldi s adeepOf::Traversals t s t ->IndexedTraversali s t a b ->IndexedTraversali s t a b
confusing :: Applicative f => LensLike (Curried (Yoneda f) (Yoneda f)) s t a b -> LensLike f s t a b #
Fuse a Traversal by reassociating all of the ( operations to the
left and fusing all of the <*>)fmap calls into one. This is particularly
useful when constructing a Traversal using operations from GHC.Generics.
Given a pair of Traversals foo and bar,
confusing (foo.bar) = foo.bar
However, foo and bar are each going to use the Applicative they are given.
confusing exploits the Yoneda lemma to merge their separate uses of fmap into a single fmap.
and it further exploits an interesting property of the right Kan lift (or Curried) to left associate
all of the uses of ( to make it possible to fuse together more fmaps.<*>)
This is particularly effective when the choice of functor f is unknown at compile
time or when the Traversal foo.bar in the above description is recursive or complex
enough to prevent inlining.
fusing is a version of this combinator suitable for fusing lenses.
confusing::Traversals t a b ->Traversals t a b
traverseByOf :: Traversal s t a b -> (forall x. x -> f x) -> (forall x y. f (x -> y) -> f x -> f y) -> (a -> f b) -> s -> f t #
Traverse a container using a specified Applicative.
This is like traverseBy where the Traversable instance can be specified by any Traversal
traverseByOftraverse≡traverseBy
sequenceByOf :: Traversal s t (f b) b -> (forall x. x -> f x) -> (forall x y. f (x -> y) -> f x -> f y) -> s -> f t #
Sequence a container using a specified Applicative.
This is like traverseBy where the Traversable instance can be specified by any Traversal
sequenceByOftraverse≡sequenceBy
ilevels :: Applicative f => Traversing (Indexed i) f s t a b -> IndexedLensLike Int f s t (Level i a) (Level j b) #
This provides a breadth-first Traversal or Fold of the individual
levels of any other Traversal or Fold via iterative deepening depth-first
search. The levels are returned to you in a compressed format.
This is similar to levels, but retains the index of the original IndexedTraversal, so you can
access it when traversing the levels later on.
>>>["dog","cat"]^@..ilevels (traversed<.>traversed).itraversed[((0,0),'d'),((0,1),'o'),((1,0),'c'),((0,2),'g'),((1,1),'a'),((1,2),'t')]
The resulting Traversal of the levels which is indexed by the depth of each Level.
>>>["dog","cat"]^@..ilevels (traversed<.>traversed)<.>itraversed[((2,(0,0)),'d'),((3,(0,1)),'o'),((3,(1,0)),'c'),((4,(0,2)),'g'),((4,(1,1)),'a'),((5,(1,2)),'t')]
ilevels::IndexedTraversali s t a b ->IndexedTraversalInts t (Leveli a) (Leveli b)ilevels::IndexedFoldi s a ->IndexedFoldInts (Leveli a)
Note: Internally this is implemented by using an illegal Applicative, as it extracts information
in an order that violates the Applicative laws.
type ReifiedPrism' s a = ReifiedPrism s s a a #
typeReifiedPrism'=SimpleReifiedPrism
newtype ReifiedPrism s t a b #
Reify a ReifiedPrism so it can be stored safely in a container.
type ReifiedIso' s a = ReifiedIso s s a a #
typeReifiedIso'=SimpleReifiedIso
newtype ReifiedIso s t a b #
Reify an ReifiedIso so it can be stored safely in a container.
type ReifiedIndexedSetter' i s a = ReifiedIndexedSetter i s s a a #
typeReifiedIndexedSetter'i =Simple(ReifiedIndexedSetteri)
newtype ReifiedIndexedSetter i s t a b #
Reify an ReifiedIndexedSetter so it can be stored safely in a container.
Constructors
| IndexedSetter | |
Fields
| |
type ReifiedSetter' s a = ReifiedSetter s s a a #
typeReifiedSetter'=SimpleReifiedSetter
newtype ReifiedSetter s t a b #
Reify a ReifiedSetter so it can be stored safely in a container.
newtype ReifiedIndexedFold i s a #
Constructors
| IndexedFold | |
Fields
| |
Instances
newtype ReifiedFold s a #
Reify a ReifiedFold so it can be stored safely in a container.
This can also be useful for creatively combining folds as
is isomorphic to ReifiedFold sReaderT s [] and provides similar
instances.
>>>("hello","world")^..runFold ((,) <$> Fold _2 <*> Fold both)[("world","hello"),("world","world")]
Instances
newtype ReifiedIndexedGetter i s a #
Reify an ReifiedIndexedGetter so it can be stored safely in a container.
Constructors
| IndexedGetter | |
Fields
| |
Instances
newtype ReifiedGetter s a #
Reify a ReifiedGetter so it can be stored safely in a container.
This can also be useful when combining getters in novel ways, as
ReifiedGetter is isomorphic to '(->)' and provides similar instances.
>>>("hello","world","!!!")^.runGetter ((,) <$> Getter _2 <*> Getter (_1.to length))("world",5)
Instances
type ReifiedTraversal' s a = ReifiedTraversal s s a a #
newtype ReifiedTraversal s t a b #
A form of ReifiedTraversal that can be stored monomorphically in a container.
Constructors
| Traversal | |
Fields
| |
type ReifiedIndexedTraversal' i s a = ReifiedIndexedTraversal i s s a a #
typeReifiedIndexedTraversal'i =Simple(ReifiedIndexedTraversali)
newtype ReifiedIndexedTraversal i s t a b #
Reify an ReifiedIndexedTraversal so it can be stored safely in a container.
Constructors
| IndexedTraversal | |
Fields
| |
type ReifiedIndexedLens' i s a = ReifiedIndexedLens i s s a a #
typeReifiedIndexedLens'i =Simple(ReifiedIndexedLensi)
newtype ReifiedIndexedLens i s t a b #
Reify an ReifiedIndexedLens so it can be stored safely in a container.
Constructors
| IndexedLens | |
Fields
| |
type ReifiedLens' s a = ReifiedLens s s a a #
typeReifiedLens'=SimpleReifiedLens
newtype ReifiedLens s t a b #
Reify a ReifiedLens so it can be stored safely in a container.
class (FunctorWithIndex i t, FoldableWithIndex i t, Traversable t) => TraversableWithIndex i (t :: Type -> Type) | t -> i where #
A Traversable with an additional index.
An instance must satisfy a (modified) form of the Traversable laws:
itraverse(constIdentity) ≡Identityfmap(itraversef).itraverseg ≡getCompose.itraverse(\i ->Compose.fmap(f i).g i)
Minimal complete definition
Nothing
Methods
itraverse :: Applicative f => (i -> a -> f b) -> t a -> f (t b) #
Traverse an indexed container.
itraverse≡itraverseOfitraversed
itraversed :: IndexedTraversal i (t a) (t b) a b #
The IndexedTraversal of a TraversableWithIndex container.
Instances
class Foldable f => FoldableWithIndex i (f :: Type -> Type) | f -> i where #
A container that supports folding with an additional index.
Minimal complete definition
Nothing
Methods
ifoldMap :: Monoid m => (i -> a -> m) -> f a -> m #
Fold a container by mapping value to an arbitrary Monoid with access to the index i.
When you don't need access to the index then foldMap is more flexible in what it accepts.
foldMap≡ifoldMap.const
ifolded :: IndexedFold i (f a) a #
The IndexedFold of a FoldableWithIndex container.
is a fold over the keys of a ifolded . asIndexFoldableWithIndex.
>>>Data.Map.fromList [(2, "hello"), (1, "world")]^..ifolded.asIndex[1,2]
ifoldr :: (i -> a -> b -> b) -> b -> f a -> b #
Right-associative fold of an indexed container with access to the index i.
When you don't need access to the index then foldr is more flexible in what it accepts.
foldr≡ifoldr.const
ifoldl :: (i -> b -> a -> b) -> b -> f a -> b #
Left-associative fold of an indexed container with access to the index i.
When you don't need access to the index then foldl is more flexible in what it accepts.
foldl≡ifoldl.const
Instances
| FoldableWithIndex Int [] | |
Defined in Control.Lens.Indexed | |
| FoldableWithIndex Int ZipList | |
Defined in Control.Lens.Indexed | |
| FoldableWithIndex Int NonEmpty | |
Defined in Control.Lens.Indexed | |
| FoldableWithIndex Int Vector | |
Defined in Control.Lens.Indexed | |
| FoldableWithIndex Int IntMap | |
Defined in Control.Lens.Indexed | |
| FoldableWithIndex Int Seq | |
| FoldableWithIndex () Maybe | |
| FoldableWithIndex () Par1 | |
| FoldableWithIndex () Identity | |
Defined in Control.Lens.Indexed | |
| FoldableWithIndex k (Map k) | |
| FoldableWithIndex k (HashMap k) | |
Defined in Control.Lens.Indexed | |
| FoldableWithIndex k ((,) k) | |
Defined in Control.Lens.Indexed | |
| FoldableWithIndex i (Level i) | |
| Ix i => FoldableWithIndex i (Array i) | |
| FoldableWithIndex Void (V1 :: Type -> Type) | |
| FoldableWithIndex Void (U1 :: Type -> Type) | |
| FoldableWithIndex Void (Proxy :: Type -> Type) | |
Defined in Control.Lens.Indexed | |
| FoldableWithIndex Int (V n) | |
| FoldableWithIndex () (Tagged a) | |
Defined in Control.Lens.Indexed | |
| FoldableWithIndex i f => FoldableWithIndex i (Reverse f) | |
Defined in Control.Lens.Indexed | |
| FoldableWithIndex i f => FoldableWithIndex i (Rec1 f) | |
| FoldableWithIndex i m => FoldableWithIndex i (IdentityT m) | |
Defined in Control.Lens.Indexed | |
| FoldableWithIndex i f => FoldableWithIndex i (Backwards f) | |
Defined in Control.Lens.Indexed | |
| FoldableWithIndex i (Magma i t b) | |
Defined in Control.Lens.Indexed Methods ifoldMap :: Monoid m => (i -> a -> m) -> Magma i t b a -> m # ifolded :: IndexedFold i (Magma i t b a) a # ifoldr :: (i -> a -> b0 -> b0) -> b0 -> Magma i t b a -> b0 # ifoldl :: (i -> b0 -> a -> b0) -> b0 -> Magma i t b a -> b0 # ifoldr' :: (i -> a -> b0 -> b0) -> b0 -> Magma i t b a -> b0 # ifoldl' :: (i -> b0 -> a -> b0) -> b0 -> Magma i t b a -> b0 # | |
| FoldableWithIndex Void (K1 i c :: Type -> Type) | |
Defined in Control.Lens.Indexed | |
| FoldableWithIndex [Int] Tree | |
Defined in Control.Lens.Indexed | |
| FoldableWithIndex (E V2) V2 | |
| FoldableWithIndex (E V3) V3 | |
| FoldableWithIndex (E Plucker) Plucker | |
Defined in Linear.Plucker Methods ifoldMap :: Monoid m => (E Plucker -> a -> m) -> Plucker a -> m # ifolded :: IndexedFold (E Plucker) (Plucker a) a # ifoldr :: (E Plucker -> a -> b -> b) -> b -> Plucker a -> b # ifoldl :: (E Plucker -> b -> a -> b) -> b -> Plucker a -> b # ifoldr' :: (E Plucker -> a -> b -> b) -> b -> Plucker a -> b # ifoldl' :: (E Plucker -> b -> a -> b) -> b -> Plucker a -> b # | |
| FoldableWithIndex (E Quaternion) Quaternion | |
Defined in Linear.Quaternion Methods ifoldMap :: Monoid m => (E Quaternion -> a -> m) -> Quaternion a -> m # ifolded :: IndexedFold (E Quaternion) (Quaternion a) a # ifoldr :: (E Quaternion -> a -> b -> b) -> b -> Quaternion a -> b # ifoldl :: (E Quaternion -> b -> a -> b) -> b -> Quaternion a -> b # ifoldr' :: (E Quaternion -> a -> b -> b) -> b -> Quaternion a -> b # ifoldl' :: (E Quaternion -> b -> a -> b) -> b -> Quaternion a -> b # | |
| FoldableWithIndex (E V0) V0 | |
| FoldableWithIndex (E V4) V4 | |
| FoldableWithIndex (E V1) V1 | |
| FoldableWithIndex i f => FoldableWithIndex [i] (Free f) | |
Defined in Control.Lens.Indexed | |
| FoldableWithIndex i f => FoldableWithIndex [i] (Cofree f) | |
Defined in Control.Lens.Indexed | |
| (FoldableWithIndex i f, FoldableWithIndex j g) => FoldableWithIndex (Either i j) (Sum f g) | |
Defined in Control.Lens.Indexed Methods ifoldMap :: Monoid m => (Either i j -> a -> m) -> Sum f g a -> m # ifolded :: IndexedFold (Either i j) (Sum f g a) a # ifoldr :: (Either i j -> a -> b -> b) -> b -> Sum f g a -> b # ifoldl :: (Either i j -> b -> a -> b) -> b -> Sum f g a -> b # ifoldr' :: (Either i j -> a -> b -> b) -> b -> Sum f g a -> b # ifoldl' :: (Either i j -> b -> a -> b) -> b -> Sum f g a -> b # | |
| (FoldableWithIndex i f, FoldableWithIndex j g) => FoldableWithIndex (Either i j) (Product f g) | |
Defined in Control.Lens.Indexed Methods ifoldMap :: Monoid m => (Either i j -> a -> m) -> Product f g a -> m # ifolded :: IndexedFold (Either i j) (Product f g a) a # ifoldr :: (Either i j -> a -> b -> b) -> b -> Product f g a -> b # ifoldl :: (Either i j -> b -> a -> b) -> b -> Product f g a -> b # ifoldr' :: (Either i j -> a -> b -> b) -> b -> Product f g a -> b # ifoldl' :: (Either i j -> b -> a -> b) -> b -> Product f g a -> b # | |
| (FoldableWithIndex i f, FoldableWithIndex j g) => FoldableWithIndex (Either i j) (f :+: g) | |
Defined in Control.Lens.Indexed Methods ifoldMap :: Monoid m => (Either i j -> a -> m) -> (f :+: g) a -> m # ifolded :: IndexedFold (Either i j) ((f :+: g) a) a # ifoldr :: (Either i j -> a -> b -> b) -> b -> (f :+: g) a -> b # ifoldl :: (Either i j -> b -> a -> b) -> b -> (f :+: g) a -> b # ifoldr' :: (Either i j -> a -> b -> b) -> b -> (f :+: g) a -> b # ifoldl' :: (Either i j -> b -> a -> b) -> b -> (f :+: g) a -> b # | |
| (FoldableWithIndex i f, FoldableWithIndex j g) => FoldableWithIndex (Either i j) (f :*: g) | |
Defined in Control.Lens.Indexed Methods ifoldMap :: Monoid m => (Either i j -> a -> m) -> (f :*: g) a -> m # ifolded :: IndexedFold (Either i j) ((f :*: g) a) a # ifoldr :: (Either i j -> a -> b -> b) -> b -> (f :*: g) a -> b # ifoldl :: (Either i j -> b -> a -> b) -> b -> (f :*: g) a -> b # ifoldr' :: (Either i j -> a -> b -> b) -> b -> (f :*: g) a -> b # ifoldl' :: (Either i j -> b -> a -> b) -> b -> (f :*: g) a -> b # | |
| (FoldableWithIndex i f, FoldableWithIndex j g) => FoldableWithIndex (i, j) (Compose f g) | |
Defined in Control.Lens.Indexed Methods ifoldMap :: Monoid m => ((i, j) -> a -> m) -> Compose f g a -> m # ifolded :: IndexedFold (i, j) (Compose f g a) a # ifoldr :: ((i, j) -> a -> b -> b) -> b -> Compose f g a -> b # ifoldl :: ((i, j) -> b -> a -> b) -> b -> Compose f g a -> b # ifoldr' :: ((i, j) -> a -> b -> b) -> b -> Compose f g a -> b # ifoldl' :: ((i, j) -> b -> a -> b) -> b -> Compose f g a -> b # | |
| (FoldableWithIndex i f, FoldableWithIndex j g) => FoldableWithIndex (i, j) (f :.: g) | |
Defined in Control.Lens.Indexed Methods ifoldMap :: Monoid m => ((i, j) -> a -> m) -> (f :.: g) a -> m # ifolded :: IndexedFold (i, j) ((f :.: g) a) a # ifoldr :: ((i, j) -> a -> b -> b) -> b -> (f :.: g) a -> b # ifoldl :: ((i, j) -> b -> a -> b) -> b -> (f :.: g) a -> b # ifoldr' :: ((i, j) -> a -> b -> b) -> b -> (f :.: g) a -> b # ifoldl' :: ((i, j) -> b -> a -> b) -> b -> (f :.: g) a -> b # | |
class Functor f => FunctorWithIndex i (f :: Type -> Type) | f -> i where #
A Functor with an additional index.
Instances must satisfy a modified form of the Functor laws:
imapf.imapg ≡imap(\i -> f i.g i)imap(\_ a -> a) ≡id
Minimal complete definition
Nothing
Methods
imap :: (i -> a -> b) -> f a -> f b #
Map with access to the index.
imapped :: IndexedSetter i (f a) (f b) a b #
The IndexedSetter for a FunctorWithIndex.
If you don't need access to the index, then mapped is more flexible in what it accepts.
Instances
(<.) :: Indexable i p => (Indexed i s t -> r) -> ((a -> b) -> s -> t) -> p a b -> r infixr 9 #
Compose an Indexed function with a non-indexed function.
Mnemonically, the < points to the indexing we want to preserve.
>>>let nestedMap = (fmap Map.fromList . Map.fromList) [(1, [(10, "one,ten"), (20, "one,twenty")]), (2, [(30, "two,thirty"), (40,"two,forty")])]>>>nestedMap^..(itraversed<.itraversed).withIndex[(1,"one,ten"),(1,"one,twenty"),(2,"two,thirty"),(2,"two,forty")]
selfIndex :: Indexable a p => p a fb -> a -> fb #
Use a value itself as its own index. This is essentially an indexed version of id.
Note: When used to modify the value, this can break the index requirements assumed by indices and similar,
so this is only properly an IndexedGetter, but it can be used as more.
selfIndex::IndexedGettera a b
icompose :: Indexable p c => (i -> j -> p) -> (Indexed i s t -> r) -> (Indexed j a b -> s -> t) -> c a b -> r #
Composition of Indexed functions with a user supplied function for combining indices.
index :: (Indexable i p, Eq i, Applicative f) => i -> Optical' p (Indexed i) f a a #
This allows you to filter an IndexedFold, IndexedGetter, IndexedTraversal or IndexedLens based on an index.
>>>["hello","the","world","!!!"]^?traversed.index 2Just "world"
iany :: FoldableWithIndex i f => (i -> a -> Bool) -> f a -> Bool #
iall :: FoldableWithIndex i f => (i -> a -> Bool) -> f a -> Bool #
inone :: FoldableWithIndex i f => (i -> a -> Bool) -> f a -> Bool #
itraverse_ :: (FoldableWithIndex i t, Applicative f) => (i -> a -> f b) -> t a -> f () #
ifor_ :: (FoldableWithIndex i t, Applicative f) => t a -> (i -> a -> f b) -> f () #
imapM_ :: (FoldableWithIndex i t, Monad m) => (i -> a -> m b) -> t a -> m () #
Run monadic actions for each target of an IndexedFold or IndexedTraversal with access to the index,
discarding the results.
When you don't need access to the index then mapMOf_ is more flexible in what it accepts.
mapM_≡imapM.const
iforM_ :: (FoldableWithIndex i t, Monad m) => t a -> (i -> a -> m b) -> m () #
Run monadic actions for each target of an IndexedFold or IndexedTraversal with access to the index,
discarding the results (with the arguments flipped).
iforM_≡flipimapM_
When you don't need access to the index then forMOf_ is more flexible in what it accepts.
forMOf_l a ≡iforMOfl a.const
iconcatMap :: FoldableWithIndex i f => (i -> a -> [b]) -> f a -> [b] #
Concatenate the results of a function of the elements of an indexed container with access to the index.
When you don't need access to the index then concatMap is more flexible in what it accepts.
concatMap≡iconcatMap.consticoncatMap≡ifoldMap
ifind :: FoldableWithIndex i f => (i -> a -> Bool) -> f a -> Maybe (i, a) #
ifoldrM :: (FoldableWithIndex i f, Monad m) => (i -> a -> b -> m b) -> b -> f a -> m b #
ifoldlM :: (FoldableWithIndex i f, Monad m) => (i -> b -> a -> m b) -> b -> f a -> m b #
itoList :: FoldableWithIndex i f => f a -> [(i, a)] #
ifor :: (TraversableWithIndex i t, Applicative f) => t a -> (i -> a -> f b) -> f (t b) #
imapM :: (TraversableWithIndex i t, Monad m) => (i -> a -> m b) -> t a -> m (t b) #
iforM :: (TraversableWithIndex i t, Monad m) => t a -> (i -> a -> m b) -> m (t b) #
imapAccumR :: TraversableWithIndex i t => (i -> s -> a -> (s, b)) -> s -> t a -> (s, t b) #
Generalizes mapAccumR to add access to the index.
imapAccumROf accumulates state from right to left.
mapAccumR≡imapAccumR.const
imapAccumL :: TraversableWithIndex i t => (i -> s -> a -> (s, b)) -> s -> t a -> (s, t b) #
Generalizes mapAccumL to add access to the index.
imapAccumLOf accumulates state from left to right.
mapAccumLOf≡imapAccumL.const
ifoldMapBy :: FoldableWithIndex i t => (r -> r -> r) -> r -> (i -> a -> r) -> t a -> r #
ifoldMapByOf :: IndexedFold i t a -> (r -> r -> r) -> r -> (i -> a -> r) -> t -> r #
itraverseBy :: TraversableWithIndex i t => (forall x. x -> f x) -> (forall x y. f (x -> y) -> f x -> f y) -> (i -> a -> f b) -> t a -> f (t b) #
itraverseByOf :: IndexedTraversal i s t a b -> (forall x. x -> f x) -> (forall x y. f (x -> y) -> f x -> f y) -> (i -> a -> f b) -> s -> f t #
type AnEquality' (s :: k2) (a :: k2) = AnEquality s s a a #
A Simple AnEquality.
type AnEquality (s :: k1) (t :: k2) (a :: k1) (b :: k2) = Identical a (Proxy b) a (Proxy b) -> Identical a (Proxy b) s (Proxy t) #
When you see this as an argument to a function, it expects an Equality.
data Identical (a :: k) (b :: k1) (s :: k) (t :: k1) :: forall k k1. k -> k1 -> k -> k1 -> Type where #
Provides witness that (s ~ a, b ~ t) holds.
runEq :: AnEquality s t a b -> Identical s t a b #
Extract a witness of type Equality.
substEq :: AnEquality s t a b -> ((s ~ a) -> (t ~ b) -> r) -> r #
Substituting types with Equality.
mapEq :: AnEquality s t a b -> f s -> f a #
We can use Equality to do substitution into anything.
fromEq :: AnEquality s t a b -> Equality b a t s #
Equality is symmetric.
simply :: (Optic' p f s a -> r) -> Optic' p f s a -> r #
This is an adverb that can be used to modify many other Lens combinators to make them require
simple lenses, simple traversals, simple prisms or simple isos as input.
class Strict lazy strict | lazy -> strict, strict -> lazy where #
Ad hoc conversion between "strict" and "lazy" versions of a structure,
such as Text or ByteString.
class Bifunctor p => Swapped (p :: Type -> Type -> Type) where #
This class provides for symmetric bifunctors.
Methods
type AnIso s t a b = Exchange a b a (Identity b) -> Exchange a b s (Identity t) #
When you see this as an argument to a function, it expects an Iso.
withIso :: AnIso s t a b -> ((s -> a) -> (b -> t) -> r) -> r #
Extract the two functions, one from s -> a and
one from b -> t that characterize an Iso.
cloneIso :: AnIso s t a b -> Iso s t a b #
Convert from AnIso back to any Iso.
This is useful when you need to store an isomorphism as a data type inside a container and later reconstitute it as an overloaded function.
See cloneLens or cloneTraversal for more information on why you might want to do this.
auf :: Optic (Costar f) g s t a b -> (f a -> g b) -> f s -> g t #
Based on ala' from Conor McBride's work on Epigram.
This version is generalized to accept any Iso, not just a newtype.
For a version you pass the name of the newtype constructor to, see alaf.
>>>auf (_Unwrapping Sum) (foldMapOf both) Prelude.length ("hello","world")10
Mnemonically, the German auf plays a similar role to à la, and the combinator
is au with an extra function argument:
auf::Isos t a b -> ((r -> a) -> e -> b) -> (r -> s) -> e -> t
but the signature is general.
enum :: Enum a => Iso' Int a #
This isomorphism can be used to convert to or from an instance of Enum.
>>>LT^.from enum0
>>>97^.enum :: Char'a'
Note: this is only an isomorphism from the numeric range actually used
and it is a bit of a pleasant fiction, since there are questionable
Enum instances for Double, and Float that exist solely for
[1.0 .. 4.0] sugar and the instances for those and Integer don't
cover all values in their range.
non :: Eq a => a -> Iso' (Maybe a) a #
If v is an element of a type a, and a' is a sans the element v, then is an isomorphism from
non v to Maybe a'a.
non≡non'.only
Keep in mind this is only a real isomorphism if you treat the domain as being .Maybe (a sans v)
This is practically quite useful when you want to have a Map where all the entries should have non-zero values.
>>>Map.fromList [("hello",1)] & at "hello" . non 0 +~ 2fromList [("hello",3)]
>>>Map.fromList [("hello",1)] & at "hello" . non 0 -~ 1fromList []
>>>Map.fromList [("hello",1)] ^. at "hello" . non 01
>>>Map.fromList [] ^. at "hello" . non 00
This combinator is also particularly useful when working with nested maps.
e.g. When you want to create the nested Map when it is missing:
>>>Map.empty & at "hello" . non Map.empty . at "world" ?~ "!!!"fromList [("hello",fromList [("world","!!!")])]
and when have deleting the last entry from the nested Map mean that we
should delete its entry from the surrounding one:
>>>fromList [("hello",fromList [("world","!!!")])] & at "hello" . non Map.empty . at "world" .~ NothingfromList []
It can also be used in reverse to exclude a given value:
>>>non 0 # rem 10 4Just 2
>>>non 0 # rem 10 5Nothing
non' :: APrism' a () -> Iso' (Maybe a) a #
generalizes non' p to take any unit non (p # ())Prism
This function generates an isomorphism between and Maybe (a | isn't p a)a.
>>>Map.singleton "hello" Map.empty & at "hello" . non' _Empty . at "world" ?~ "!!!"fromList [("hello",fromList [("world","!!!")])]
>>>fromList [("hello",fromList [("world","!!!")])] & at "hello" . non' _Empty . at "world" .~ NothingfromList []
anon :: a -> (a -> Bool) -> Iso' (Maybe a) a #
generalizes anon a p to take any value and a predicate.non a
This function assumes that p a holds and generates an isomorphism between True and Maybe (a | not (p a))a.
>>>Map.empty & at "hello" . anon Map.empty Map.null . at "world" ?~ "!!!"fromList [("hello",fromList [("world","!!!")])]
>>>fromList [("hello",fromList [("world","!!!")])] & at "hello" . anon Map.empty Map.null . at "world" .~ NothingfromList []
flipped :: Iso (a -> b -> c) (a' -> b' -> c') (b -> a -> c) (b' -> a' -> c') #
The isomorphism for flipping a function.
>>>((,)^.flipped) 1 2(2,1)
lazy :: Strict lazy strict => Iso' strict lazy #
An Iso between the strict variant of a structure and its lazy
counterpart.
lazy=fromstrict
See http://hackage.haskell.org/package/strict-base-types for an example use.
reversed :: Reversing a => Iso' a a #
An Iso between a list, ByteString, Text fragment, etc. and its reversal.
>>>"live" ^. reversed"evil"
>>>"live" & reversed %~ ('d':)"lived"
imagma :: Over (Indexed i) (Molten i a b) s t a b -> Iso s t' (Magma i t b a) (Magma j t' c c) #
This isomorphism can be used to inspect an IndexedTraversal to see how it associates
the structure and it can also be used to bake the IndexedTraversal into a Magma so
that you can traverse over it multiple times with access to the original indices.
contramapping :: Contravariant f => AnIso s t a b -> Iso (f a) (f b) (f s) (f t) #
Lift an Iso into a Contravariant functor.
contramapping ::Contravariantf =>Isos t a b ->Iso(f a) (f b) (f s) (f t) contramapping ::Contravariantf =>Iso's a ->Iso'(f a) (f s)
dimapping :: (Profunctor p, Profunctor q) => AnIso s t a b -> AnIso s' t' a' b' -> Iso (p a s') (q b t') (p s a') (q t b') #
Lift two Isos into both arguments of a Profunctor simultaneously.
dimapping ::Profunctorp =>Isos t a b ->Isos' t' a' b' ->Iso(p a s') (p b t') (p s a') (p t b') dimapping ::Profunctorp =>Iso's a ->Iso's' a' ->Iso'(p a s') (p s a')
lmapping :: (Profunctor p, Profunctor q) => AnIso s t a b -> Iso (p a x) (q b y) (p s x) (q t y) #
Lift an Iso contravariantly into the left argument of a Profunctor.
lmapping ::Profunctorp =>Isos t a b ->Iso(p a x) (p b y) (p s x) (p t y) lmapping ::Profunctorp =>Iso's a ->Iso'(p a x) (p s x)
rmapping :: (Profunctor p, Profunctor q) => AnIso s t a b -> Iso (p x s) (q y t) (p x a) (q y b) #
Lift an Iso covariantly into the right argument of a Profunctor.
rmapping ::Profunctorp =>Isos t a b ->Iso(p x s) (p y t) (p x a) (p y b) rmapping ::Profunctorp =>Iso's a ->Iso'(p x s) (p x a)
bimapping :: (Bifunctor f, Bifunctor g) => AnIso s t a b -> AnIso s' t' a' b' -> Iso (f s s') (g t t') (f a a') (g b b') #
seconding :: (Bifunctor f, Bifunctor g) => AnIso s t a b -> Iso (f x s) (g y t) (f x a) (g y b) #
Lift an Iso into the second argument of a Bifunctor. This is
essentially the same as mapping, but it takes a 'Bifunctor p'
constraint instead of a 'Functor (p a)' one.
seconding ::Bifunctorp =>Isos t a b ->Iso(p x s) (p y t) (p x a) (p y b) seconding ::Bifunctorp =>Iso's a ->Iso'(p x s) (p x a)
coerced :: (Coercible s a, Coercible t b) => Iso s t a b #
Data types that are representationally equal are isomorphic.
This is only available on GHC 7.8+
Since: lens-4.13
Minimal complete definition
Nothing
Instances
class Snoc s t a b | s -> a, t -> b, s b -> t, t a -> s where #
This class provides a way to attach or detach elements on the right side of a structure in a flexible manner.
Methods
Instances
class Cons s t a b | s -> a, t -> b, s b -> t, t a -> s where #
This class provides a way to attach or detach elements on the left side of a structure in a flexible manner.
Methods
Instances
cons :: Cons s s a a => a -> s -> s infixr 5 #
cons an element onto a container.
>>>cons a [][a]
>>>cons a [b, c][a,b,c]
>>>cons a (Seq.fromList [])fromList [a]
>>>cons a (Seq.fromList [b, c])fromList [a,b,c]
uncons :: Cons s s a a => s -> Maybe (a, s) #
Attempt to extract the left-most element from a container, and a version of the container without that element.
>>>uncons []Nothing
>>>uncons [a, b, c]Just (a,[b,c])
_head :: Cons s s a a => Traversal' s a #
A Traversal reading and writing to the head of a non-empty container.
>>>[a,b,c]^? _headJust a
>>>[a,b,c] & _head .~ d[d,b,c]
>>>[a,b,c] & _head %~ f[f a,b,c]
>>>[] & _head %~ f[]
>>>[1,2,3]^?!_head1
>>>[]^?_headNothing
>>>[1,2]^?_headJust 1
>>>[] & _head .~ 1[]
>>>[0] & _head .~ 2[2]
>>>[0,1] & _head .~ 2[2,1]
This isn't limited to lists.
For instance you can also traverse the head of a Seq:
>>>Seq.fromList [a,b,c,d] & _head %~ ffromList [f a,b,c,d]
>>>Seq.fromList [] ^? _headNothing
>>>Seq.fromList [a,b,c,d] ^? _headJust a
_head::Traversal'[a] a_head::Traversal'(Seqa) a_head::Traversal'(Vectora) a
_tail :: Cons s s a a => Traversal' s s #
A Traversal reading and writing to the tail of a non-empty container.
>>>[a,b] & _tail .~ [c,d,e][a,c,d,e]
>>>[] & _tail .~ [a,b][]
>>>[a,b,c,d,e] & _tail.traverse %~ f[a,f b,f c,f d,f e]
>>>[1,2] & _tail .~ [3,4,5][1,3,4,5]
>>>[] & _tail .~ [1,2][]
>>>[a,b,c]^?_tailJust [b,c]
>>>[1,2]^?!_tail[2]
>>>"hello"^._tail"ello"
>>>""^._tail""
This isn't limited to lists. For instance you can also traverse the tail of a Seq.
>>>Seq.fromList [a,b] & _tail .~ Seq.fromList [c,d,e]fromList [a,c,d,e]
>>>Seq.fromList [a,b,c] ^? _tailJust (fromList [b,c])
>>>Seq.fromList [] ^? _tailNothing
_tail::Traversal'[a] [a]_tail::Traversal'(Seqa) (Seqa)_tail::Traversal'(Vectora) (Vectora)
_init :: Snoc s s a a => Traversal' s s #
A Traversal reading and replacing all but the a last element of a non-empty container.
>>>[a,b,c,d]^?_initJust [a,b,c]
>>>[]^?_initNothing
>>>[a,b] & _init .~ [c,d,e][c,d,e,b]
>>>[] & _init .~ [a,b][]
>>>[a,b,c,d] & _init.traverse %~ f[f a,f b,f c,d]
>>>[1,2,3]^?_initJust [1,2]
>>>[1,2,3,4]^?!_init[1,2,3]
>>>"hello"^._init"hell"
>>>""^._init""
_init::Traversal'[a] [a]_init::Traversal'(Seqa) (Seqa)_init::Traversal'(Vectora) (Vectora)
_last :: Snoc s s a a => Traversal' s a #
A Traversal reading and writing to the last element of a non-empty container.
>>>[a,b,c]^?!_lastc
>>>[]^?_lastNothing
>>>[a,b,c] & _last %~ f[a,b,f c]
>>>[1,2]^?_lastJust 2
>>>[] & _last .~ 1[]
>>>[0] & _last .~ 2[2]
>>>[0,1] & _last .~ 2[0,2]
This Traversal is not limited to lists, however. We can also work with other containers, such as a Vector.
>>>Vector.fromList "abcde" ^? _lastJust 'e'
>>>Vector.empty ^? _lastNothing
>>>(Vector.fromList "abcde" & _last .~ 'Q') == Vector.fromList "abcdQ"True
_last::Traversal'[a] a_last::Traversal'(Seqa) a_last::Traversal'(Vectora) a
snoc :: Snoc s s a a => s -> a -> s infixl 5 #
snoc an element onto the end of a container.
>>>snoc (Seq.fromList []) afromList [a]
>>>snoc (Seq.fromList [b, c]) afromList [b,c,a]
>>>snoc (LazyT.pack "hello") '!'"hello!"
unsnoc :: Snoc s s a a => s -> Maybe (s, a) #
Attempt to extract the right-most element from a container, and a version of the container without that element.
>>>unsnoc (LazyT.pack "hello!")Just ("hello",'!')
>>>unsnoc (LazyT.pack "")Nothing
>>>unsnoc (Seq.fromList [b,c,a])Just (fromList [b,c],a)
>>>unsnoc (Seq.fromList [])Nothing
class (Rewrapped s t, Rewrapped t s) => Rewrapping s t #
Instances
| (Rewrapped s t, Rewrapped t s) => Rewrapping s t | |
Defined in Control.Lens.Wrapped | |
class Wrapped s => Rewrapped s t #
Instances
Wrapped provides isomorphisms to wrap and unwrap newtypes or
data types with one constructor.
Minimal complete definition
Nothing
Methods
_Wrapped' :: Iso' s (Unwrapped s) #
An isomorphism between s and a.
If your type has a Generic instance, _Wrapped' will default to _GWrapped',
and you can choose to not override it with your own definition.
Instances
_GWrapped' :: (Generic s, D1 d (C1 c (S1 s' (Rec0 a))) ~ Rep s, Unwrapped s ~ GUnwrapped (Rep s)) => Iso' s (Unwrapped s) #
_Unwrapped' :: Wrapped s => Iso' (Unwrapped s) s #
_Wrapped :: Rewrapping s t => Iso s t (Unwrapped s) (Unwrapped t) #
Work under a newtype wrapper.
>>>Const "hello" & _Wrapped %~ Prelude.length & getConst5
_Wrapped≡from_Unwrapped_Unwrapped≡from_Wrapped
_Unwrapped :: Rewrapping s t => Iso (Unwrapped t) (Unwrapped s) t s #
_Wrapping' :: Wrapped s => (Unwrapped s -> s) -> Iso' s (Unwrapped s) #
This is a convenient version of _Wrapped with an argument that's ignored.
The user supplied function is ignored, merely its type is used.
_Unwrapping' :: Wrapped s => (Unwrapped s -> s) -> Iso' (Unwrapped s) s #
This is a convenient version of _Wrapped with an argument that's ignored.
The user supplied function is ignored, merely its type is used.
_Wrapping :: Rewrapping s t => (Unwrapped s -> s) -> Iso s t (Unwrapped s) (Unwrapped t) #
This is a convenient version of _Wrapped with an argument that's ignored.
The user supplied function is ignored, merely its types are used.
_Unwrapping :: Rewrapping s t => (Unwrapped s -> s) -> Iso (Unwrapped t) (Unwrapped s) t s #
This is a convenient version of _Unwrapped with an argument that's ignored.
The user supplied function is ignored, merely its types are used.
ala :: (Functor f, Rewrapping s t) => (Unwrapped s -> s) -> ((Unwrapped t -> t) -> f s) -> f (Unwrapped s) #
This combinator is based on ala from Conor McBride's work on Epigram.
As with _Wrapping, the user supplied function for the newtype is ignored.
>>>ala Sum foldMap [1,2,3,4]10
>>>ala All foldMap [True,True]True
>>>ala All foldMap [True,False]False
>>>ala Any foldMap [False,False]False
>>>ala Any foldMap [True,False]True
>>>ala Product foldMap [1,2,3,4]24
You may want to think of this combinator as having the following, simpler, type.
ala :: Rewrapping s t => (Unwrapped s -> s) -> ((Unwrapped t -> t) -> e -> s) -> e -> Unwrapped s
alaf :: (Functor f, Functor g, Rewrapping s t) => (Unwrapped s -> s) -> (f t -> g s) -> f (Unwrapped t) -> g (Unwrapped s) #
This combinator is based on ala' from Conor McBride's work on Epigram.
As with _Wrapping, the user supplied function for the newtype is ignored.
alaf :: Rewrapping s t => (Unwrapped s -> s) -> ((r -> t) -> e -> s) -> (r -> Unwrapped t) -> e -> Unwrapped s
>>>alaf Sum foldMap Prelude.length ["hello","world"]10
class (Magnified m ~ Magnified n, MonadReader b m, MonadReader a n) => Magnify (m :: Type -> Type) (n :: Type -> Type) b a | m -> b, n -> a, m a -> n, n b -> m where #
This class allows us to use magnify part of the environment, changing the environment supplied by
many different Monad transformers. Unlike zoom this can change the environment of a deeply nested Monad transformer.
Also, unlike zoom, this can be used with any valid Getter, but cannot be used with a Traversal or Fold.
Methods
magnify :: LensLike' (Magnified m c) a b -> m c -> n c infixr 2 #
Run a monadic action in a larger environment than it was defined in, using a Getter.
This acts like local, but can in many cases change the type of the environment as well.
This is commonly used to lift actions in a simpler Reader Monad into a Monad with a larger environment type.
This can be used to edit pretty much any Monad transformer stack with an environment in it:
>>>(1,2) & magnify _2 (+1)3
>>>flip Reader.runReader (1,2) $ magnify _1 Reader.ask1
>>>flip Reader.runReader (1,2,[10..20]) $ magnify (_3._tail) Reader.ask[11,12,13,14,15,16,17,18,19,20]
magnify::Getters a -> (a -> r) -> s -> rmagnify::Monoidr =>Folds a -> (a -> r) -> s -> r
magnify::Monoidw =>Getters t ->RWSt w st c ->RWSs w st cmagnify:: (Monoidw,Monoidc) =>Folds a ->RWSa w st c ->RWSs w st c ...
Instances
| Magnify m n b a => Magnify (IdentityT m) (IdentityT n) b a | |
| Magnify ((->) b :: Type -> Type) ((->) a :: Type -> Type) b a |
|
Defined in Control.Lens.Zoom | |
| Monad m => Magnify (ReaderT b m) (ReaderT a m) b a | |
| (Monad m, Monoid w) => Magnify (RWST b w s m) (RWST a w s m) b a | |
| (Monad m, Monoid w) => Magnify (RWST b w s m) (RWST a w s m) b a | |
class (MonadState s m, MonadState t n) => Zoom (m :: Type -> Type) (n :: Type -> Type) s t | m -> s, n -> t, m t -> n, n s -> m where #
This class allows us to use zoom in, changing the State supplied by
many different Monad transformers, potentially quite
deep in a Monad transformer stack.
Methods
zoom :: LensLike' (Zoomed m c) t s -> m c -> n c infixr 2 #
Run a monadic action in a larger State than it was defined in,
using a Lens' or Traversal'.
This is commonly used to lift actions in a simpler State
Monad into a State Monad with a larger State type.
When applied to a Traversal' over
multiple values, the actions for each target are executed sequentially
and the results are aggregated.
This can be used to edit pretty much any Monad transformer stack with a State in it!
>>>flip State.evalState (a,b) $ zoom _1 $ use ida
>>>flip State.execState (a,b) $ zoom _1 $ id .= c(c,b)
>>>flip State.execState [(a,b),(c,d)] $ zoom traverse $ _2 %= f[(a,f b),(c,f d)]
>>>flip State.runState [(a,b),(c,d)] $ zoom traverse $ _2 <%= f(f b <> f d <> mempty,[(a,f b),(c,f d)])
>>>flip State.evalState (a,b) $ zoom both (use id)a <> b
zoom::Monadm =>Lens's t ->StateTt m a ->StateTs m azoom:: (Monadm,Monoidc) =>Traversal's t ->StateTt m c ->StateTs m czoom:: (Monadm,Monoidw) =>Lens's t ->RWSTr w t m c ->RWSTr w s m czoom:: (Monadm,Monoidw,Monoidc) =>Traversal's t ->RWSTr w t m c ->RWSTr w s m czoom:: (Monadm,Monoidw,Errore) =>Lens's t ->ErrorTe (RWSTr w t m) c ->ErrorTe (RWSTr w s m) czoom:: (Monadm,Monoidw,Monoidc,Errore) =>Traversal's t ->ErrorTe (RWSTr w t m) c ->ErrorTe (RWSTr w s m) c ...
Instances
| Zoom m n s t => Zoom (MaybeT m) (MaybeT n) s t | |
| Zoom m n s t => Zoom (ListT m) (ListT n) s t | |
| Zoom m n s t => Zoom (IdentityT m) (IdentityT n) s t | |
| Zoom m n s t => Zoom (ExceptT e m) (ExceptT e n) s t | |
| (Functor f, Zoom m n s t) => Zoom (FreeT f m) (FreeT f n) s t | |
| (Error e, Zoom m n s t) => Zoom (ErrorT e m) (ErrorT e n) s t | |
| Monad z => Zoom (StateT s z) (StateT t z) s t | |
| (Monoid w, Zoom m n s t) => Zoom (WriterT w m) (WriterT w n) s t | |
| Monad z => Zoom (StateT s z) (StateT t z) s t | |
| (Monoid w, Zoom m n s t) => Zoom (WriterT w m) (WriterT w n) s t | |
| Zoom m n s t => Zoom (ReaderT e m) (ReaderT e n) s t | |
| (Monoid w, Monad z) => Zoom (RWST r w s z) (RWST r w t z) s t | |
| (Monoid w, Monad z) => Zoom (RWST r w s z) (RWST r w t z) s t | |
type family Magnified (m :: Type -> Type) :: Type -> Type -> Type #
This type family is used by Magnify to describe the common effect type.
Instances
| type Magnified (IdentityT m) | |
Defined in Control.Lens.Zoom | |
| type Magnified ((->) b :: Type -> Type) | |
| type Magnified (ReaderT b m) | |
Defined in Control.Lens.Zoom | |
| type Magnified (RWST a w s m) | |
Defined in Control.Lens.Zoom | |
| type Magnified (RWST a w s m) | |
Defined in Control.Lens.Zoom | |
type family Zoomed (m :: Type -> Type) :: Type -> Type -> Type #
This type family is used by Zoom to describe the common effect type.
Instances
| type Zoomed (MaybeT m) | |
Defined in Control.Lens.Zoom | |
| type Zoomed (ListT m) | |
Defined in Control.Lens.Zoom | |
| type Zoomed (IdentityT m) | |
Defined in Control.Lens.Zoom | |
| type Zoomed (ExceptT e m) | |
Defined in Control.Lens.Zoom | |
| type Zoomed (FreeT f m) | |
Defined in Control.Lens.Zoom | |
| type Zoomed (ErrorT e m) | |
Defined in Control.Lens.Zoom | |
| type Zoomed (StateT s z) | |
Defined in Control.Lens.Zoom | |
| type Zoomed (WriterT w m) | |
Defined in Control.Lens.Zoom | |
| type Zoomed (StateT s z) | |
Defined in Control.Lens.Zoom | |
| type Zoomed (WriterT w m) | |
Defined in Control.Lens.Zoom | |
| type Zoomed (ReaderT e m) | |
Defined in Control.Lens.Zoom | |
| type Zoomed (RWST r w s z) | |
Defined in Control.Lens.Zoom | |
| type Zoomed (RWST r w s z) | |
Defined in Control.Lens.Zoom | |
class GPlated1 (f :: k -> Type) (g :: k -> Type) #
Minimal complete definition
gplate1'
Instances
| GPlated1 (f :: k -> Type) (V1 :: k -> Type) | ignored |
Defined in Control.Lens.Plated Methods gplate1' :: Traversal' (V1 a) (f a) | |
| GPlated1 (f :: k -> Type) (U1 :: k -> Type) | ignored |
Defined in Control.Lens.Plated Methods gplate1' :: Traversal' (U1 a) (f a) | |
| GPlated1 (f :: k -> Type) (URec a :: k -> Type) | ignored |
Defined in Control.Lens.Plated Methods gplate1' :: Traversal' (URec a a0) (f a0) | |
| GPlated1 (f :: k -> Type) (Rec1 f :: k -> Type) | match |
Defined in Control.Lens.Plated Methods gplate1' :: Traversal' (Rec1 f a) (f a) | |
| GPlated1 (f :: k -> Type) (Rec1 g :: k -> Type) | ignored |
Defined in Control.Lens.Plated Methods gplate1' :: Traversal' (Rec1 g a) (f a) | |
| GPlated1 (f :: k -> Type) (K1 i a :: k -> Type) | ignored |
Defined in Control.Lens.Plated Methods gplate1' :: Traversal' (K1 i a a0) (f a0) | |
| (GPlated1 f g, GPlated1 f h) => GPlated1 (f :: k -> Type) (g :+: h :: k -> Type) | recursive match |
Defined in Control.Lens.Plated Methods gplate1' :: Traversal' ((g :+: h) a) (f a) | |
| (GPlated1 f g, GPlated1 f h) => GPlated1 (f :: k -> Type) (g :*: h :: k -> Type) | recursive match |
Defined in Control.Lens.Plated Methods gplate1' :: Traversal' ((g :*: h) a) (f a) | |
| GPlated1 f g => GPlated1 (f :: k -> Type) (M1 i c g :: k -> Type) | recursive match |
Defined in Control.Lens.Plated Methods gplate1' :: Traversal' (M1 i c g a) (f a) | |
| (Traversable t, GPlated1 f g) => GPlated1 (f :: k1 -> Type) (t :.: g :: k1 -> Type) | recursive match under outer |
Defined in Control.Lens.Plated Methods gplate1' :: Traversal' ((t :.: g) a) (f a) | |
| GPlated1 (f :: Type -> Type) Par1 | ignored |
Defined in Control.Lens.Plated Methods gplate1' :: Traversal' (Par1 a) (f a) | |
class GPlated a (g :: k -> Type) #
Minimal complete definition
gplate'
Instances
| GPlated a (V1 :: k -> Type) | |
Defined in Control.Lens.Plated Methods gplate' :: Traversal' (V1 p) a | |
| GPlated a (U1 :: k -> Type) | |
Defined in Control.Lens.Plated Methods gplate' :: Traversal' (U1 p) a | |
| GPlated a (URec b :: k -> Type) | |
Defined in Control.Lens.Plated Methods gplate' :: Traversal' (URec b p) a | |
| GPlated a (K1 i a :: k -> Type) | |
Defined in Control.Lens.Plated Methods gplate' :: Traversal' (K1 i a p) a | |
| GPlated a (K1 i b :: k -> Type) | |
Defined in Control.Lens.Plated Methods gplate' :: Traversal' (K1 i b p) a | |
| (GPlated a f, GPlated a g) => GPlated a (f :+: g :: k -> Type) | |
Defined in Control.Lens.Plated Methods gplate' :: Traversal' ((f :+: g) p) a | |
| (GPlated a f, GPlated a g) => GPlated a (f :*: g :: k -> Type) | |
Defined in Control.Lens.Plated Methods gplate' :: Traversal' ((f :*: g) p) a | |
| GPlated a f => GPlated a (M1 i c f :: k -> Type) | |
Defined in Control.Lens.Plated Methods gplate' :: Traversal' (M1 i c f p) a | |
A Plated type is one where we know how to extract its immediate self-similar children.
Example 1:
import Control.Applicative
import Control.Lens
import Control.Lens.Plated
import Data.Data
import Data.Data.Lens (uniplate)
data Expr = ValInt| Neg Expr | Add Expr Expr deriving (Eq,Ord,Show,Read,Data,Typeable)
instancePlatedExpr whereplatef (Neg e) = Neg<$>f eplatef (Add a b) = Add<$>f a<*>f bplate_ a =purea
or
instancePlatedExpr whereplate=uniplate
Example 2:
import Control.Applicative
import Control.Lens
import Control.Lens.Plated
import Data.Data
import Data.Data.Lens (uniplate)
data Tree a = Bin (Tree a) (Tree a) | Tip a deriving (Eq,Ord,Show,Read,Data,Typeable)
instancePlated(Tree a) whereplatef (Bin l r) = Bin<$>f l<*>f rplate_ t =puret
or
instanceDataa =>Plated(Tree a) whereplate=uniplate
Note the big distinction between these two implementations.
The former will only treat children directly in this tree as descendents, the latter will treat trees contained in the values under the tips also as descendants!
When in doubt, pick a Traversal and just use the various ...Of combinators
rather than pollute Plated with orphan instances!
If you want to find something unplated and non-recursive with biplate
use the ...OnOf variant with ignored, though those usecases are much better served
in most cases by using the existing Lens combinators! e.g.
toListOfbiplate≡universeOnOfbiplateignored
This same ability to explicitly pass the Traversal in question is why there is no
analogue to uniplate's Biplate.
Moreover, since we can allow custom traversals, we implement reasonable defaults for
polymorphic data types, that only traverse into themselves, and not their
polymorphic arguments.
Minimal complete definition
Nothing
Methods
plate :: Traversal' a a #
Instances
deep :: (Conjoined p, Applicative f, Plated s) => Traversing p f s s a b -> Over p f s s a b #
Try to apply a traversal to all transitive descendants of a Plated container, but
do not recurse through matching descendants.
deep::Plateds =>Folds a ->Folds adeep::Plateds =>IndexedFolds a ->IndexedFolds adeep::Plateds =>Traversals s a b ->Traversals s a bdeep::Plateds =>IndexedTraversals s a b ->IndexedTraversals s a b
rewrite :: Plated a => (a -> Maybe a) -> a -> a #
Rewrite by applying a rule everywhere you can. Ensures that the rule cannot be applied anywhere in the result:
propRewrite r x =all(isNothing.r) (universe(rewriter x))
Usually transform is more appropriate, but rewrite can give better
compositionality. Given two single transformations f and g, you can
construct \a -> f a which performs both rewrites until a fixed point.<|> g a
rewriteOf :: ASetter a b a b -> (b -> Maybe a) -> a -> b #
Rewrite by applying a rule everywhere you can. Ensures that the rule cannot be applied anywhere in the result:
propRewriteOf l r x =all(isNothing.r) (universeOfl (rewriteOfl r x))
Usually transformOf is more appropriate, but rewriteOf can give better
compositionality. Given two single transformations f and g, you can
construct \a -> f a which performs both rewrites until a fixed point.<|> g a
rewriteOf::Iso'a a -> (a ->Maybea) -> a -> arewriteOf::Lens'a a -> (a ->Maybea) -> a -> arewriteOf::Traversal'a a -> (a ->Maybea) -> a -> arewriteOf::Setter'a a -> (a ->Maybea) -> a -> a
rewriteOn :: Plated a => ASetter s t a a -> (a -> Maybe a) -> s -> t #
Rewrite recursively over part of a larger structure.
rewriteOn::Plateda =>Iso's a -> (a ->Maybea) -> s -> srewriteOn::Plateda =>Lens's a -> (a ->Maybea) -> s -> srewriteOn::Plateda =>Traversal's a -> (a ->Maybea) -> s -> srewriteOn::Plateda =>ASetter's a -> (a ->Maybea) -> s -> s
rewriteOnOf :: ASetter s t a b -> ASetter a b a b -> (b -> Maybe a) -> s -> t #
Rewrite recursively over part of a larger structure using a specified Setter.
rewriteOnOf::Iso's a ->Iso'a a -> (a ->Maybea) -> s -> srewriteOnOf::Lens's a ->Lens'a a -> (a ->Maybea) -> s -> srewriteOnOf::Traversal's a ->Traversal'a a -> (a ->Maybea) -> s -> srewriteOnOf::Setter's a ->Setter'a a -> (a ->Maybea) -> s -> s
rewriteM :: (Monad m, Plated a) => (a -> m (Maybe a)) -> a -> m a #
Rewrite by applying a monadic rule everywhere you can. Ensures that the rule cannot be applied anywhere in the result.
rewriteMOf :: Monad m => LensLike (WrappedMonad m) a b a b -> (b -> m (Maybe a)) -> a -> m b #
Rewrite by applying a monadic rule everywhere you recursing with a user-specified Traversal.
Ensures that the rule cannot be applied anywhere in the result.
rewriteMOn :: (Monad m, Plated a) => LensLike (WrappedMonad m) s t a a -> (a -> m (Maybe a)) -> s -> m t #
Rewrite by applying a monadic rule everywhere inside of a structure located by a user-specified Traversal.
Ensures that the rule cannot be applied anywhere in the result.
rewriteMOnOf :: Monad m => LensLike (WrappedMonad m) s t a b -> LensLike (WrappedMonad m) a b a b -> (b -> m (Maybe a)) -> s -> m t #
universe :: Plated a => a -> [a] #
Retrieve all of the transitive descendants of a Plated container, including itself.
universeOf :: Getting [a] a a -> a -> [a] #
Given a Fold that knows how to locate immediate children, retrieve all of the transitive descendants of a node, including itself.
universeOf::Folda a -> a -> [a]
universeOn :: Plated a => Getting [a] s a -> s -> [a] #
universeOnOf :: Getting [a] s a -> Getting [a] a a -> s -> [a] #
Given a Fold that knows how to locate immediate children, retrieve all of the transitive descendants of a node, including itself that lie
in a region indicated by another Fold.
toListOfl ≡universeOnOflignored
cosmos :: Plated a => Fold a a #
Fold over all transitive descendants of a Plated container, including itself.
cosmosOf :: (Applicative f, Contravariant f) => LensLike' f a a -> LensLike' f a a #
cosmosOn :: (Applicative f, Contravariant f, Plated a) => LensLike' f s a -> LensLike' f s a #
cosmosOnOf :: (Applicative f, Contravariant f) => LensLike' f s a -> LensLike' f a a -> LensLike' f s a #
transformOn :: Plated a => ASetter s t a a -> (a -> a) -> s -> t #
Transform every element in the tree in a bottom-up manner over a region indicated by a Setter.
transformOn::Plateda =>Traversal's a -> (a -> a) -> s -> stransformOn::Plateda =>Setter's a -> (a -> a) -> s -> s
transformOf :: ASetter a b a b -> (b -> b) -> a -> b #
Transform every element by recursively applying a given Setter in a bottom-up manner.
transformOf::Traversal'a a -> (a -> a) -> a -> atransformOf::Setter'a a -> (a -> a) -> a -> a
transformOnOf :: ASetter s t a b -> ASetter a b a b -> (b -> b) -> s -> t #
Transform every element in a region indicated by a Setter by recursively applying another Setter
in a bottom-up manner.
transformOnOf::Setter's a ->Traversal'a a -> (a -> a) -> s -> stransformOnOf::Setter's a ->Setter'a a -> (a -> a) -> s -> s
transformM :: (Monad m, Plated a) => (a -> m a) -> a -> m a #
Transform every element in the tree, in a bottom-up manner, monadically.
transformMOn :: (Monad m, Plated a) => LensLike (WrappedMonad m) s t a a -> (a -> m a) -> s -> m t #
Transform every element in the tree in a region indicated by a supplied Traversal, in a bottom-up manner, monadically.
transformMOn:: (Monadm,Plateda) =>Traversal's a -> (a -> m a) -> s -> m s
transformMOf :: Monad m => LensLike (WrappedMonad m) a b a b -> (b -> m b) -> a -> m b #
Transform every element in a tree using a user supplied Traversal in a bottom-up manner with a monadic effect.
transformMOf::Monadm =>Traversal'a a -> (a -> m a) -> a -> m a
transformMOnOf :: Monad m => LensLike (WrappedMonad m) s t a b -> LensLike (WrappedMonad m) a b a b -> (b -> m b) -> s -> m t #
Transform every element in a tree that lies in a region indicated by a supplied Traversal, walking with a user supplied Traversal in
a bottom-up manner with a monadic effect.
transformMOnOf::Monadm =>Traversal's a ->Traversal'a a -> (a -> m a) -> s -> m s
contextsOf :: ATraversal' a a -> a -> [Context a a a] #
Return a list of all of the editable contexts for every location in the structure, recursively, using a user-specified Traversal to walk each layer.
propUniverse l x =universeOfl x==mappos(contextsOfl x) propId l x =all(==x) [extractw | w <-contextsOfl x]
contextsOf::Traversal'a a -> a -> [Contexta a a]
contextsOn :: Plated a => ATraversal s t a a -> s -> [Context a a t] #
Return a list of all of the editable contexts for every location in the structure in an areas indicated by a user supplied Traversal, recursively using plate.
contextsOnb ≡contextsOnOfbplate
contextsOn::Plateda =>Traversal's a -> s -> [Contexta a s]
contextsOnOf :: ATraversal s t a a -> ATraversal' a a -> s -> [Context a a t] #
Return a list of all of the editable contexts for every location in the structure in an areas indicated by a user supplied Traversal, recursively using
another user-supplied Traversal to walk each layer.
contextsOnOf::Traversal's a ->Traversal'a a -> s -> [Contexta a s]
holes :: Plated a => a -> [Pretext ((->) :: Type -> Type -> Type) a a a] #
The one-level version of context. This extracts a list of the immediate children as editable contexts.
Given a context you can use pos to see the values, peek at what the structure would be like with an edited result, or simply extract the original structure.
propChildren x =childrenl x==mappos(holesl x) propId x =all(==x) [extractw | w <-holesl x]
holes=holesOfplate
holesOn :: Conjoined p => Over p (Bazaar p a a) s t a a -> s -> [Pretext p a a t] #
An alias for holesOf, provided for consistency with the other combinators.
holesOn≡holesOf
holesOn::Iso's a -> s -> [Pretext(->) a a s]holesOn::Lens's a -> s -> [Pretext(->) a a s]holesOn::Traversal's a -> s -> [Pretext(->) a a s]holesOn::IndexedLens'i s a -> s -> [Pretext(Indexedi) a a s]holesOn::IndexedTraversal'i s a -> s -> [Pretext(Indexedi) a a s]
holesOnOf :: Conjoined p => LensLike (Bazaar p r r) s t a b -> Over p (Bazaar p r r) a b r r -> s -> [Pretext p r r t] #
Extract one level of holes from a container in a region specified by one Traversal, using another.
holesOnOfb l ≡holesOf(b.l)
holesOnOf::Iso's a ->Iso'a a -> s -> [Pretext(->) a a s]holesOnOf::Lens's a ->Lens'a a -> s -> [Pretext(->) a a s]holesOnOf::Traversal's a ->Traversal'a a -> s -> [Pretext(->) a a s]holesOnOf::Lens's a ->IndexedLens'i a a -> s -> [Pretext(Indexedi) a a s]holesOnOf::Traversal's a ->IndexedTraversal'i a a -> s -> [Pretext(Indexedi) a a s]
composOpFold :: Plated a => b -> (b -> b -> b) -> (a -> b) -> a -> b #
Fold the immediate children of a Plated container.
composOpFoldz c f =foldrOfplate(c.f) z
class Each s t a b | s -> a, t -> b, s b -> t, t a -> s where #
Extract each element of a (potentially monomorphic) container.
Notably, when applied to a tuple, this generalizes both to arbitrary homogeneous tuples.
>>>(1,2,3) & each *~ 10(10,20,30)
It can also be used on monomorphic containers like Text or ByteString.
>>>over each Char.toUpper ("hello"^.Text.packed)"HELLO"
>>>("hello","world") & each.each %~ Char.toUpper("HELLO","WORLD")
Minimal complete definition
Nothing
Instances
| (a ~ Word8, b ~ Word8) => Each ByteString ByteString a b |
|
Defined in Control.Lens.Each Methods each :: Traversal ByteString ByteString a b # | |
| (a ~ Word8, b ~ Word8) => Each ByteString ByteString a b |
|
Defined in Control.Lens.Each Methods each :: Traversal ByteString ByteString a b # | |
| (a ~ Char, b ~ Char) => Each Text Text a b |
|
| (a ~ Char, b ~ Char) => Each Text Text a b |
|
| Each Name Name AName AName | |
| Each [a] [b] a b |
|
Defined in Control.Lens.Each | |
| Each (Maybe a) (Maybe b) a b |
|
| Each (Identity a) (Identity b) a b |
|
| (Storable a, Storable b) => Each (Vector a) (Vector b) a b |
|
| Each (Complex a) (Complex b) a b |
|
| Each (NonEmpty a) (NonEmpty b) a b |
|
| Each (Vector a) (Vector b) a b |
|
| Each (IntMap a) (IntMap b) a b |
|
| Each (Tree a) (Tree b) a b |
|
| Each (Seq a) (Seq b) a b |
|
| (Unbox a, Unbox b) => Each (Vector a) (Vector b) a b |
|
| Each (V2 a) (V2 b) a b | |
| Each (V3 a) (V3 b) a b | |
| (Prim a, Prim b) => Each (Vector a) (Vector b) a b |
|
| Each (Plucker a) (Plucker b) a b | |
| Each (Quaternion a) (Quaternion b) a b | |
Defined in Linear.Quaternion Methods each :: Traversal (Quaternion a) (Quaternion b) a b # | |
| Each (V0 a) (V0 b) a b | |
| Each (V4 a) (V4 b) a b | |
| Each (V1 a) (V1 b) a b | |
| (a ~ a', b ~ b') => Each (a, a') (b, b') a b |
|
Defined in Control.Lens.Each | |
| c ~ d => Each (Map c a) (Map d b) a b |
|
| c ~ d => Each (HashMap c a) (HashMap d b) a b |
|
| (Ix i, IArray UArray a, IArray UArray b, i ~ j) => Each (UArray i a) (UArray j b) a b |
|
| (Ix i, i ~ j) => Each (Array i a) (Array j b) a b |
|
| Traversable f => Each (Point f a) (Point f b) a b | |
| Each (Path v n) (Path v' n') (Located (Trail v n)) (Located (Trail v' n')) | |
| Each (Style v n) (Style v' n') (Attribute v n) (Attribute v' n') | |
| (Additive v', Foldable v', Ord n') => Each (BoundingBox v n) (BoundingBox v' n') (Point v n) (Point v' n') | Only valid if the second point is not smaller than the first. |
Defined in Diagrams.BoundingBox Methods each :: Traversal (BoundingBox v n) (BoundingBox v' n') (Point v n) (Point v' n') # | |
| Each (FixedSegment v n) (FixedSegment v' n') (Point v n) (Point v' n') | |
Defined in Diagrams.Segment Methods each :: Traversal (FixedSegment v n) (FixedSegment v' n') (Point v n) (Point v' n') # | |
| (a ~ a2, a ~ a3, b ~ b2, b ~ b3) => Each (a, a2, a3) (b, b2, b3) a b |
|
Defined in Control.Lens.Each | |
| Each (V n a) (V n b) a b | |
| Each (Offset c v n) (Offset c v' n') (v n) (v' n') | |
| Each (Segment c v n) (Segment c v' n') (v n) (v' n') | |
| (a ~ a2, a ~ a3, a ~ a4, b ~ b2, b ~ b3, b ~ b4) => Each (a, a2, a3, a4) (b, b2, b3, b4) a b |
|
Defined in Control.Lens.Each | |
| (a ~ a2, a ~ a3, a ~ a4, a ~ a5, b ~ b2, b ~ b3, b ~ b4, b ~ b5) => Each (a, a2, a3, a4, a5) (b, b2, b3, b4, b5) a b |
|
Defined in Control.Lens.Each | |
| (a ~ a2, a ~ a3, a ~ a4, a ~ a5, a ~ a6, b ~ b2, b ~ b3, b ~ b4, b ~ b5, b ~ b6) => Each (a, a2, a3, a4, a5, a6) (b, b2, b3, b4, b5, b6) a b |
|
Defined in Control.Lens.Each | |
| (a ~ a2, a ~ a3, a ~ a4, a ~ a5, a ~ a6, a ~ a7, b ~ b2, b ~ b3, b ~ b4, b ~ b5, b ~ b6, b ~ b7) => Each (a, a2, a3, a4, a5, a6, a7) (b, b2, b3, b4, b5, b6, b7) a b |
|
Defined in Control.Lens.Each | |
| (a ~ a2, a ~ a3, a ~ a4, a ~ a5, a ~ a6, a ~ a7, a ~ a8, b ~ b2, b ~ b3, b ~ b4, b ~ b5, b ~ b6, b ~ b7, b ~ b8) => Each (a, a2, a3, a4, a5, a6, a7, a8) (b, b2, b3, b4, b5, b6, b7, b8) a b |
|
Defined in Control.Lens.Each | |
| (a ~ a2, a ~ a3, a ~ a4, a ~ a5, a ~ a6, a ~ a7, a ~ a8, a ~ a9, b ~ b2, b ~ b3, b ~ b4, b ~ b5, b ~ b6, b ~ b7, b ~ b8, b ~ b9) => Each (a, a2, a3, a4, a5, a6, a7, a8, a9) (b, b2, b3, b4, b5, b6, b7, b8, b9) a b |
|
Defined in Control.Lens.Each | |
At provides a Lens that can be used to read,
write or delete the value associated with a key in a Map-like
container on an ad hoc basis.
An instance of At should satisfy:
ixk ≡atk.traverse
Minimal complete definition
Provides a simple Traversal lets you traverse the value at a given
key in a Map or element at an ordinal position in a list or Seq.
Minimal complete definition
Nothing
Methods
ix :: Index m -> Traversal' m (IxValue m) #
NB: Setting the value of this Traversal will only set the value in
at if it is already present.
If you want to be able to insert missing values, you want at.
>>>Seq.fromList [a,b,c,d] & ix 2 %~ ffromList [a,b,f c,d]
>>>Seq.fromList [a,b,c,d] & ix 2 .~ efromList [a,b,e,d]
>>>Seq.fromList [a,b,c,d] ^? ix 2Just c
>>>Seq.fromList [] ^? ix 2Nothing
Instances
| Ixed ByteString | |
Defined in Control.Lens.At Methods ix :: Index ByteString -> Traversal' ByteString (IxValue ByteString) # | |
| Ixed ByteString | |
Defined in Control.Lens.At Methods ix :: Index ByteString -> Traversal' ByteString (IxValue ByteString) # | |
| Ixed Text | |
Defined in Control.Lens.At | |
| Ixed Text | |
Defined in Control.Lens.At | |
| Ixed IntSet | |
Defined in Control.Lens.At | |
| Ixed [a] | |
Defined in Control.Lens.At Methods ix :: Index [a] -> Traversal' [a] (IxValue [a]) # | |
| Ixed (Maybe a) | |
Defined in Control.Lens.At | |
| Ord k => Ixed (Set k) | |
Defined in Control.Lens.At | |
| Ixed (Identity a) | |
Defined in Control.Lens.At | |
| Storable a => Ixed (Vector a) | |
Defined in Control.Lens.At | |
| Ixed (NonEmpty a) | |
Defined in Control.Lens.At | |
| Ixed (Vector a) | |
Defined in Control.Lens.At | |
| Ixed (IntMap a) | |
Defined in Control.Lens.At | |
| Ixed (Tree a) | |
Defined in Control.Lens.At | |
| Ixed (Seq a) | |
Defined in Control.Lens.At | |
| Unbox a => Ixed (Vector a) | |
Defined in Control.Lens.At | |
| Ixed (V2 a) | |
| Ixed (V3 a) | |
| Prim a => Ixed (Vector a) | |
Defined in Control.Lens.At | |
| (Eq k, Hashable k) => Ixed (HashSet k) | |
Defined in Control.Lens.At | |
| Ixed (Plucker a) | |
Defined in Linear.Plucker | |
| Ixed (Quaternion a) | |
Defined in Linear.Quaternion Methods ix :: Index (Quaternion a) -> Traversal' (Quaternion a) (IxValue (Quaternion a)) # | |
| Ixed (V0 a) | |
| Ixed (V4 a) | |
| Ixed (V1 a) | |
| Eq e => Ixed (e -> a) | |
Defined in Control.Lens.At Methods ix :: Index (e -> a) -> Traversal' (e -> a) (IxValue (e -> a)) # | |
| a ~ a2 => Ixed (a, a2) | |
Defined in Control.Lens.At Methods ix :: Index (a, a2) -> Traversal' (a, a2) (IxValue (a, a2)) # | |
| Ord k => Ixed (Map k a) | |
Defined in Control.Lens.At | |
| (Eq k, Hashable k) => Ixed (HashMap k a) | |
Defined in Control.Lens.At | |
| (IArray UArray e, Ix i) => Ixed (UArray i e) | arr |
Defined in Control.Lens.At | |
| Ix i => Ixed (Array i e) | arr |
Defined in Control.Lens.At | |
| Ixed (Style v n) | |
Defined in Diagrams.Core.Style | |
| Ixed (f a) => Ixed (Point f a) | |
Defined in Linear.Affine | |
| (a ~ a2, a ~ a3) => Ixed (a, a2, a3) | |
Defined in Control.Lens.At Methods ix :: Index (a, a2, a3) -> Traversal' (a, a2, a3) (IxValue (a, a2, a3)) # | |
| Ixed (V n a) | |
| (a ~ a2, a ~ a3, a ~ a4) => Ixed (a, a2, a3, a4) | |
Defined in Control.Lens.At Methods ix :: Index (a, a2, a3, a4) -> Traversal' (a, a2, a3, a4) (IxValue (a, a2, a3, a4)) # | |
| (a ~ a2, a ~ a3, a ~ a4, a ~ a5) => Ixed (a, a2, a3, a4, a5) | |
Defined in Control.Lens.At Methods ix :: Index (a, a2, a3, a4, a5) -> Traversal' (a, a2, a3, a4, a5) (IxValue (a, a2, a3, a4, a5)) # | |
| (a ~ a2, a ~ a3, a ~ a4, a ~ a5, a ~ a6) => Ixed (a, a2, a3, a4, a5, a6) | |
Defined in Control.Lens.At Methods ix :: Index (a, a2, a3, a4, a5, a6) -> Traversal' (a, a2, a3, a4, a5, a6) (IxValue (a, a2, a3, a4, a5, a6)) # | |
| (a ~ a2, a ~ a3, a ~ a4, a ~ a5, a ~ a6, a ~ a7) => Ixed (a, a2, a3, a4, a5, a6, a7) | |
Defined in Control.Lens.At Methods ix :: Index (a, a2, a3, a4, a5, a6, a7) -> Traversal' (a, a2, a3, a4, a5, a6, a7) (IxValue (a, a2, a3, a4, a5, a6, a7)) # | |
| (a ~ a2, a ~ a3, a ~ a4, a ~ a5, a ~ a6, a ~ a7, a ~ a8) => Ixed (a, a2, a3, a4, a5, a6, a7, a8) | |
Defined in Control.Lens.At Methods ix :: Index (a, a2, a3, a4, a5, a6, a7, a8) -> Traversal' (a, a2, a3, a4, a5, a6, a7, a8) (IxValue (a, a2, a3, a4, a5, a6, a7, a8)) # | |
| (a ~ a2, a ~ a3, a ~ a4, a ~ a5, a ~ a6, a ~ a7, a ~ a8, a ~ a9) => Ixed (a, a2, a3, a4, a5, a6, a7, a8, a9) | |
Defined in Control.Lens.At Methods ix :: Index (a, a2, a3, a4, a5, a6, a7, a8, a9) -> Traversal' (a, a2, a3, a4, a5, a6, a7, a8, a9) (IxValue (a, a2, a3, a4, a5, a6, a7, a8, a9)) # | |
type family IxValue m :: Type #
Instances
| type IxValue ByteString | |
Defined in Control.Lens.At | |
| type IxValue ByteString | |
Defined in Control.Lens.At | |
| type IxValue Text | |
Defined in Control.Lens.At | |
| type IxValue Text | |
Defined in Control.Lens.At | |
| type IxValue IntSet | |
Defined in Control.Lens.At | |
| type IxValue [a] | |
Defined in Control.Lens.At type IxValue [a] = a | |
| type IxValue (Maybe a) | |
Defined in Control.Lens.At | |
| type IxValue (Set k) | |
Defined in Control.Lens.At | |
| type IxValue (Identity a) | |
Defined in Control.Lens.At | |
| type IxValue (Vector a) | |
Defined in Control.Lens.At | |
| type IxValue (NonEmpty a) | |
Defined in Control.Lens.At | |
| type IxValue (Vector a) | |
Defined in Control.Lens.At | |
| type IxValue (IntMap a) | |
Defined in Control.Lens.At | |
| type IxValue (Tree a) | |
Defined in Control.Lens.At | |
| type IxValue (Seq a) | |
Defined in Control.Lens.At | |
| type IxValue (Vector a) | |
Defined in Control.Lens.At | |
| type IxValue (V2 a) | |
| type IxValue (V3 a) | |
| type IxValue (Vector a) | |
Defined in Control.Lens.At | |
| type IxValue (HashSet k) | |
Defined in Control.Lens.At | |
| type IxValue (Plucker a) | |
Defined in Linear.Plucker | |
| type IxValue (Quaternion a) | |
Defined in Linear.Quaternion | |
| type IxValue (V0 a) | |
| type IxValue (V4 a) | |
| type IxValue (V1 a) | |
| type IxValue (e -> a) | |
Defined in Control.Lens.At type IxValue (e -> a) = a | |
| type IxValue (a, a2) |
|
Defined in Control.Lens.At type IxValue (a, a2) = a | |
| type IxValue (Map k a) | |
Defined in Control.Lens.At | |
| type IxValue (HashMap k a) | |
Defined in Control.Lens.At | |
| type IxValue (UArray i e) | |
Defined in Control.Lens.At | |
| type IxValue (Array i e) | |
Defined in Control.Lens.At | |
| type IxValue (Style v n) | |
Defined in Diagrams.Core.Style | |
| type IxValue (Point f a) | |
Defined in Linear.Affine | |
| type IxValue (a, a2, a3) |
|
Defined in Control.Lens.At type IxValue (a, a2, a3) = a | |
| type IxValue (V n a) | |
| type IxValue (a, a2, a3, a4) |
|
Defined in Control.Lens.At type IxValue (a, a2, a3, a4) = a | |
| type IxValue (a, a2, a3, a4, a5) |
|
Defined in Control.Lens.At type IxValue (a, a2, a3, a4, a5) = a | |
| type IxValue (a, a2, a3, a4, a5, a6) |
|
Defined in Control.Lens.At type IxValue (a, a2, a3, a4, a5, a6) = a | |
| type IxValue (a, a2, a3, a4, a5, a6, a7) |
|
Defined in Control.Lens.At type IxValue (a, a2, a3, a4, a5, a6, a7) = a | |
| type IxValue (a, a2, a3, a4, a5, a6, a7, a8) |
|
Defined in Control.Lens.At type IxValue (a, a2, a3, a4, a5, a6, a7, a8) = a | |
| type IxValue (a, a2, a3, a4, a5, a6, a7, a8, a9) |
|
Defined in Control.Lens.At type IxValue (a, a2, a3, a4, a5, a6, a7, a8, a9) = a | |
This class provides a simple Lens that lets you view (and modify)
information about whether or not a container contains a given Index.
Minimal complete definition
Instances
| type Index ByteString | |
Defined in Control.Lens.At | |
| type Index ByteString | |
Defined in Control.Lens.At | |
| type Index Text | |
Defined in Control.Lens.At | |
| type Index Text | |
Defined in Control.Lens.At | |
| type Index IntSet | |
Defined in Control.Lens.At | |
| type Index [a] | |
Defined in Control.Lens.At | |
| type Index (Maybe a) | |
Defined in Control.Lens.At | |
| type Index (Set a) | |
Defined in Control.Lens.At | |
| type Index (Identity a) | |
Defined in Control.Lens.At | |
| type Index (Vector a) | |
Defined in Control.Lens.At | |
| type Index (Complex a) | |
Defined in Control.Lens.At | |
| type Index (NonEmpty a) | |
Defined in Control.Lens.At | |
| type Index (Vector a) | |
Defined in Control.Lens.At | |
| type Index (IntMap a) | |
Defined in Control.Lens.At | |
| type Index (Tree a) | |
Defined in Control.Lens.At | |
| type Index (Seq a) | |
Defined in Control.Lens.At | |
| type Index (Vector a) | |
Defined in Control.Lens.At | |
| type Index (V2 a) | |
| type Index (V3 a) | |
| type Index (Vector a) | |
Defined in Control.Lens.At | |
| type Index (HashSet a) | |
Defined in Control.Lens.At | |
| type Index (Plucker a) | |
Defined in Linear.Plucker | |
| type Index (Quaternion a) | |
Defined in Linear.Quaternion | |
| type Index (V0 a) | |
| type Index (V4 a) | |
| type Index (V1 a) | |
| type Index (e -> a) | |
Defined in Control.Lens.At type Index (e -> a) = e | |
| type Index (a, b) | |
Defined in Control.Lens.At | |
| type Index (Map k a) | |
Defined in Control.Lens.At | |
| type Index (HashMap k a) | |
Defined in Control.Lens.At | |
| type Index (UArray i e) | |
Defined in Control.Lens.At | |
| type Index (Array i e) | |
Defined in Control.Lens.At | |
| type Index (Style v n) | |
Defined in Diagrams.Core.Style | |
| type Index (Point f a) | |
Defined in Linear.Affine | |
| type Index (a, b, c) | |
Defined in Control.Lens.At | |
| type Index (V n a) | |
| type Index (a, b, c, d) | |
Defined in Control.Lens.At | |
| type Index (a, b, c, d, e) | |
Defined in Control.Lens.At | |
| type Index (a, b, c, d, e, f) | |
Defined in Control.Lens.At | |
| type Index (a, b, c, d, e, f, g) | |
Defined in Control.Lens.At | |
| type Index (a, b, c, d, e, f, g, h) | |
Defined in Control.Lens.At | |
| type Index (a, b, c, d, e, f, g, h, i) | |
Defined in Control.Lens.At | |
icontains :: Contains m => Index m -> IndexedLens' (Index m) m Bool #
An indexed version of contains.
>>>IntSet.fromList [1,2,3,4] ^@. icontains 3(3,True)
>>>IntSet.fromList [1,2,3,4] ^@. icontains 5(5,False)
>>>IntSet.fromList [1,2,3,4] & icontains 3 %@~ \i x -> if odd i then not x else xfromList [1,2,4]
>>>IntSet.fromList [1,2,3,4] & icontains 3 %@~ \i x -> if even i then not x else xfromList [1,2,3,4]
iix :: Ixed m => Index m -> IndexedTraversal' (Index m) m (IxValue m) #
An indexed version of ix.
>>>Seq.fromList [a,b,c,d] & iix 2 %@~ f'fromList [a,b,f' 2 c,d]
>>>Seq.fromList [a,b,c,d] & iix 2 .@~ hfromList [a,b,h 2,d]
>>>Seq.fromList [a,b,c,d] ^@? iix 2Just (2,c)
>>>Seq.fromList [] ^@? iix 2Nothing
iat :: At m => Index m -> IndexedLens' (Index m) m (Maybe (IxValue m)) #
An indexed version of at.
>>>Map.fromList [(1,"world")] ^@. iat 1(1,Just "world")
>>>iat 1 %@~ (\i x -> if odd i then Just "hello" else Nothing) $ Map.emptyfromList [(1,"hello")]
>>>iat 2 %@~ (\i x -> if odd i then Just "hello" else Nothing) $ Map.emptyfromList []
Generate a Prism for each constructor of a data type.
Isos generated when possible.
Reviews are created for constructors with existentially
quantified constructors and GADTs.
e.g.
data FooBarBaz a = Foo Int | Bar a | Baz Int Char makePrisms ''FooBarBaz
will create
_Foo :: Prism' (FooBarBaz a) Int _Bar :: Prism (FooBarBaz a) (FooBarBaz b) a b _Baz :: Prism' (FooBarBaz a) (Int, Char)
Generate a Prism for each constructor of a data type
and combine them into a single class. No Isos are created.
Reviews are created for constructors with existentially
quantified constructors and GADTs.
e.g.
data FooBarBaz a = Foo Int | Bar a | Baz Int Char makeClassyPrisms ''FooBarBaz
will create
class AsFooBarBaz s a | s -> a where _FooBarBaz :: Prism' s (FooBarBaz a) _Foo :: Prism' s Int _Bar :: Prism' s a _Baz :: Prism' s (Int,Char) _Foo = _FooBarBaz . _Foo _Bar = _FooBarBaz . _Bar _Baz = _FooBarBaz . _Baz instance AsFooBarBaz (FooBarBaz a) a
Generate an As class of prisms. Names are selected by prefixing the constructor name with an underscore. Constructors with multiple fields will construct Prisms to tuples of those fields.
type ClassyNamer #
Arguments
| = Name | Name of the data type that lenses are being generated for. |
| -> Maybe (Name, Name) | Names of the class and the main method it generates, respectively. |
The optional rule to create a class and method around a monomorphic data type. If this naming convention is provided, it generates a "classy" lens.
Name to give to generated field optics.
Constructors
| TopName Name | Simple top-level definiton name |
| MethodName Name Name | makeFields-style class name and method name |
type FieldNamer #
Arguments
| = Name | Name of the data type that lenses are being generated for. |
| -> [Name] | Names of all fields (including the field being named) in the data type. |
| -> Name | Name of the field being named. |
| -> [DefName] | Name(s) of the lens functions. If empty, no lens is created for that field. |
The rule to create function names of lenses for data fields.
Although it's sometimes useful, you won't need the first two arguments most of the time.
generateSignatures :: Lens' LensRules Bool #
Indicate whether or not to supply the signatures for the generated lenses.
Disabling this can be useful if you want to provide a more restricted type signature or if you want to supply hand-written haddocks.
generateLazyPatterns :: Lens' LensRules Bool #
Generate optics using lazy pattern matches. This can allow fields of an undefined value to be initialized with lenses:
data Foo = Foo {_x :: Int, _y :: Bool}
deriving Show
makeLensesWith (lensRules & generateLazyPatterns .~ True) ''Foo
> undefined & x .~ 8 & y .~ True
Foo {_x = 8, _y = True}
The downside of this flag is that it can lead to space-leaks and code-size/compile-time increases when generated for large records. By default this flag is turned off, and strict optics are generated.
When using lazy optics the strict optic can be recovered by composing
with $!:
strictOptic = ($!) . lazyOptic
Rules for making fairly simple partial lenses, ignoring the special cases
for isomorphisms and traversals, and not making any classes.
It uses underscoreNoPrefixNamer.
underscoreNoPrefixNamer :: FieldNamer #
A FieldNamer that strips the _ off of the field name,
lowercases the name, and skips the field if it doesn't start with
an '_'.
Construct a LensRules value for generating top-level definitions
using the given map from field names to definition names.
lookingupNamer :: [(String, String)] -> FieldNamer #
Create a FieldNamer from explicit pairings of (fieldName, lensName).
Arguments
| :: (String -> [String]) | A function that maps a |
| -> FieldNamer |
Create a FieldNamer from a mapping function. If the function
returns [], it creates no lens for the field.
Rules for making lenses and traversals that precompose another Lens.
A LensRules used by makeClassy_.
makeLenses :: Name -> DecsQ #
Build lenses (and traversals) with a sensible default configuration.
e.g.
data FooBar
= Foo { _x, _y :: Int }
| Bar { _x :: Int }
makeLenses ''FooBar
will create
x ::Lens'FooBarIntx f (Foo a b) = (\a' -> Foo a' b) <$> f a x f (Bar a) = Bar <$> f a y ::Traversal'FooBarInty f (Foo a b) = (\b' -> Foo a b') <$> f b y _ c@(Bar _) = pure c
makeLenses=makeLensesWithlensRules
makeClassy :: Name -> DecsQ #
Make lenses and traversals for a type, and create a class when the type has no arguments.
e.g.
data Foo = Foo { _fooX, _fooY :: Int }
makeClassy ''Foo
will create
class HasFoo t where foo ::Lens't Foo fooX ::Lens'tIntfooX = foo . go where go f (Foo x y) = (\x' -> Foo x' y) <$> f x fooY ::Lens'tIntfooY = foo . go where go f (Foo x y) = (\y' -> Foo x y') <$> f y instance HasFoo Foo where foo = id
makeClassy=makeLensesWithclassyRules
makeClassy_ :: Name -> DecsQ #
Make lenses and traversals for a type, and create a class when the type
has no arguments. Works the same as makeClassy except that (a) it
expects that record field names do not begin with an underscore, (b) all
record fields are made into lenses, and (c) the resulting lens is prefixed
with an underscore.
makeLensesFor :: [(String, String)] -> Name -> DecsQ #
Derive lenses and traversals, specifying explicit pairings
of (fieldName, lensName).
If you map multiple names to the same label, and it is present in the same
constructor then this will generate a Traversal.
e.g.
makeLensesFor[("_foo", "fooLens"), ("baz", "lbaz")] ''FoomakeLensesFor[("_barX", "bar"), ("_barY", "bar")] ''Bar
makeClassyFor :: String -> String -> [(String, String)] -> Name -> DecsQ #
Derive lenses and traversals, using a named wrapper class, and
specifying explicit pairings of (fieldName, traversalName).
Example usage:
makeClassyFor "HasFoo" "foo" [("_foo", "fooLens"), ("bar", "lbar")] ''Foo
makeLensesWith :: LensRules -> Name -> DecsQ #
Build lenses with a custom configuration.
declareLenses :: DecsQ -> DecsQ #
declareLensesFor :: [(String, String)] -> DecsQ -> DecsQ #
Similar to makeLensesFor, but takes a declaration quote.
declareClassy :: DecsQ -> DecsQ #
For each record in the declaration quote, make lenses and traversals for it, and create a class when the type has no arguments. All record syntax in the input will be stripped off.
e.g.
declareClassy [d|
data Foo = Foo { fooX, fooY :: Int }
deriving Show
|]
will create
data Foo = FooIntIntderivingShowclass HasFoo t where foo ::Lens't Foo instance HasFoo Foo where foo =idfooX, fooY :: HasFoo t =>Lens'tInt
declareClassyFor :: [(String, (String, String))] -> [(String, String)] -> DecsQ -> DecsQ #
Similar to makeClassyFor, but takes a declaration quote.
declarePrisms :: DecsQ -> DecsQ #
Generate a Prism for each constructor of each data type.
e.g.
declarePrisms [d|
data Exp = Lit Int | Var String | Lambda{ bound::String, body::Exp }
|]
will create
data Exp = Lit Int | Var String | Lambda { bound::String, body::Exp }
_Lit :: Prism' Exp Int
_Var :: Prism' Exp String
_Lambda :: Prism' Exp (String, Exp)
declareWrapped :: DecsQ -> DecsQ #
Build Wrapped instance for each newtype.
declareFields :: DecsQ -> DecsQ #
declareFields =declareLensesWithdefaultFieldRules
declareLensesWith :: LensRules -> DecsQ -> DecsQ #
Declare lenses for each records in the given declarations, using the
specified LensRules. Any record syntax in the input will be stripped
off.
makeWrapped :: Name -> DecsQ #
Build Wrapped instance for a given newtype
underscoreFields :: LensRules #
Field rules for fields in the form _prefix_fieldname
underscoreNamer :: FieldNamer #
A FieldNamer for underscoreFields.
camelCaseFields :: LensRules #
Field rules for fields in the form prefixFieldname or _prefixFieldname
If you want all fields to be lensed, then there is no reason to use an _ before the prefix.
If any of the record fields leads with an _ then it is assume a field without an _ should not have a lens created.
Note: The prefix must be the same as the typename (with the first
letter lowercased). This is a change from lens versions before lens 4.5.
If you want the old behaviour, use makeLensesWith abbreviatedFields
camelCaseNamer :: FieldNamer #
A FieldNamer for camelCaseFields.
classUnderscoreNoPrefixFields :: LensRules #
Field rules for fields in the form _fieldname (the leading
underscore is mandatory).
Note: The primary difference to camelCaseFields is that for
classUnderscoreNoPrefixFields the field names are not expected to
be prefixed with the type name. This might be the desired behaviour
when the DuplicateRecordFields extension is enabled.
abbreviatedFields :: LensRules #
Field rules fields in the form prefixFieldname or _prefixFieldname
If you want all fields to be lensed, then there is no reason to use an _ before the prefix.
If any of the record fields leads with an _ then it is assume a field without an _ should not have a lens created.
Note that prefix may be any string of characters that are not uppercase
letters. (In particular, it may be arbitrary string of lowercase letters
and numbers) This is the behavior that defaultFieldRules had in lens
4.4 and earlier.
makeFields :: Name -> DecsQ #
Generate overloaded field accessors.
e.g
data Foo a = Foo { _fooX :: Int, _fooY :: a }
newtype Bar = Bar { _barX :: Char }
makeFields ''Foo
makeFields ''Bar
will create
_fooXLens :: Lens' (Foo a) Int _fooYLens :: Lens (Foo a) (Foo b) a b class HasX s a | s -> a where x :: Lens' s a instance HasX (Foo a) Int where x = _fooXLens class HasY s a | s -> a where y :: Lens' s a instance HasY (Foo a) a where y = _fooYLens _barXLens :: Iso' Bar Char instance HasX Bar Char where x = _barXLens
For details, see camelCaseFields.
makeFields =makeLensesWithdefaultFieldRules
makeFieldsNoPrefix :: Name -> DecsQ #
Generate overloaded field accessors based on field names which
are only prefixed with an underscore (e.g. _name), not
additionally with the type name (e.g. _fooName).
This might be the desired behaviour in case the
DuplicateRecordFields language extension is used in order to get
rid of the necessity to prefix each field name with the type name.
As an example:
data Foo a = Foo { _x :: Int, _y :: a }
newtype Bar = Bar { _x :: Char }
makeFieldsNoPrefix ''Foo
makeFieldsNoPrefix ''Bar
will create classes
class HasX s a | s -> a where x :: Lens' s a class HasY s a | s -> a where y :: Lens' s a
together with instances
instance HasX (Foo a) Int instance HasY (Foo a) a where instance HasX Bar Char where
For details, see classUnderscoreNoPrefixFields.
makeFieldsNoPrefix =makeLensesWithclassUnderscoreNoPrefixFields
class Profunctor (p :: Type -> Type -> Type) where #
Formally, the class Profunctor represents a profunctor
from Hask -> Hask.
Intuitively it is a bifunctor where the first argument is contravariant and the second argument is covariant.
You can define a Profunctor by either defining dimap or by defining both
lmap and rmap.
If you supply dimap, you should ensure that:
dimapidid≡id
If you supply lmap and rmap, ensure:
lmapid≡idrmapid≡id
If you supply both, you should also ensure:
dimapf g ≡lmapf.rmapg
These ensure by parametricity:
dimap(f.g) (h.i) ≡dimapg h.dimapf ilmap(f.g) ≡lmapg.lmapfrmap(f.g) ≡rmapf.rmapg
Instances
| Profunctor Measured | |
Defined in Diagrams.Core.Measure | |
| Profunctor ReifiedFold | |
Defined in Control.Lens.Reified Methods dimap :: (a -> b) -> (c -> d) -> ReifiedFold b c -> ReifiedFold a d # lmap :: (a -> b) -> ReifiedFold b c -> ReifiedFold a c # rmap :: (b -> c) -> ReifiedFold a b -> ReifiedFold a c # (#.) :: Coercible c b => q b c -> ReifiedFold a b -> ReifiedFold a c # (.#) :: Coercible b a => ReifiedFold b c -> q a b -> ReifiedFold a c # | |
| Profunctor ReifiedGetter | |
Defined in Control.Lens.Reified Methods dimap :: (a -> b) -> (c -> d) -> ReifiedGetter b c -> ReifiedGetter a d # lmap :: (a -> b) -> ReifiedGetter b c -> ReifiedGetter a c # rmap :: (b -> c) -> ReifiedGetter a b -> ReifiedGetter a c # (#.) :: Coercible c b => q b c -> ReifiedGetter a b -> ReifiedGetter a c # (.#) :: Coercible b a => ReifiedGetter b c -> q a b -> ReifiedGetter a c # | |
| Monad m => Profunctor (Kleisli m) | |
Defined in Data.Profunctor.Unsafe Methods dimap :: (a -> b) -> (c -> d) -> Kleisli m b c -> Kleisli m a d # lmap :: (a -> b) -> Kleisli m b c -> Kleisli m a c # rmap :: (b -> c) -> Kleisli m a b -> Kleisli m a c # (#.) :: Coercible c b => q b c -> Kleisli m a b -> Kleisli m a c # (.#) :: Coercible b a => Kleisli m b c -> q a b -> Kleisli m a c # | |
| Functor h => Profunctor (OneColonnade h) | |
Defined in Colonnade.Encode Methods dimap :: (a -> b) -> (c -> d) -> OneColonnade h b c -> OneColonnade h a d # lmap :: (a -> b) -> OneColonnade h b c -> OneColonnade h a c # rmap :: (b -> c) -> OneColonnade h a b -> OneColonnade h a c # (#.) :: Coercible c b => q b c -> OneColonnade h a b -> OneColonnade h a c # (.#) :: Coercible b a => OneColonnade h b c -> q a b -> OneColonnade h a c # | |
| Functor h => Profunctor (Colonnade h) | |
Defined in Colonnade.Encode Methods dimap :: (a -> b) -> (c -> d) -> Colonnade h b c -> Colonnade h a d # lmap :: (a -> b) -> Colonnade h b c -> Colonnade h a c # rmap :: (b -> c) -> Colonnade h a b -> Colonnade h a c # (#.) :: Coercible c b => q b c -> Colonnade h a b -> Colonnade h a c # (.#) :: Coercible b a => Colonnade h b c -> q a b -> Colonnade h a c # | |
| Functor v => Profunctor (Query v) | |
Defined in Diagrams.Core.Query | |
| Profunctor (Indexed i) | |
Defined in Control.Lens.Internal.Indexed Methods dimap :: (a -> b) -> (c -> d) -> Indexed i b c -> Indexed i a d # lmap :: (a -> b) -> Indexed i b c -> Indexed i a c # rmap :: (b -> c) -> Indexed i a b -> Indexed i a c # (#.) :: Coercible c b => q b c -> Indexed i a b -> Indexed i a c # (.#) :: Coercible b a => Indexed i b c -> q a b -> Indexed i a c # | |
| Profunctor (ReifiedIndexedFold i) | |
Defined in Control.Lens.Reified Methods dimap :: (a -> b) -> (c -> d) -> ReifiedIndexedFold i b c -> ReifiedIndexedFold i a d # lmap :: (a -> b) -> ReifiedIndexedFold i b c -> ReifiedIndexedFold i a c # rmap :: (b -> c) -> ReifiedIndexedFold i a b -> ReifiedIndexedFold i a c # (#.) :: Coercible c b => q b c -> ReifiedIndexedFold i a b -> ReifiedIndexedFold i a c # (.#) :: Coercible b a => ReifiedIndexedFold i b c -> q a b -> ReifiedIndexedFold i a c # | |
| Profunctor (ReifiedIndexedGetter i) | |
Defined in Control.Lens.Reified Methods dimap :: (a -> b) -> (c -> d) -> ReifiedIndexedGetter i b c -> ReifiedIndexedGetter i a d # lmap :: (a -> b) -> ReifiedIndexedGetter i b c -> ReifiedIndexedGetter i a c # rmap :: (b -> c) -> ReifiedIndexedGetter i a b -> ReifiedIndexedGetter i a c # (#.) :: Coercible c b => q b c -> ReifiedIndexedGetter i a b -> ReifiedIndexedGetter i a c # (.#) :: Coercible b a => ReifiedIndexedGetter i b c -> q a b -> ReifiedIndexedGetter i a c # | |
| Profunctor p => Profunctor (TambaraSum p) | |
Defined in Data.Profunctor.Choice Methods dimap :: (a -> b) -> (c -> d) -> TambaraSum p b c -> TambaraSum p a d # lmap :: (a -> b) -> TambaraSum p b c -> TambaraSum p a c # rmap :: (b -> c) -> TambaraSum p a b -> TambaraSum p a c # (#.) :: Coercible c b => q b c -> TambaraSum p a b -> TambaraSum p a c # (.#) :: Coercible b a => TambaraSum p b c -> q a b -> TambaraSum p a c # | |
| Profunctor (PastroSum p) | |
Defined in Data.Profunctor.Choice Methods dimap :: (a -> b) -> (c -> d) -> PastroSum p b c -> PastroSum p a d # lmap :: (a -> b) -> PastroSum p b c -> PastroSum p a c # rmap :: (b -> c) -> PastroSum p a b -> PastroSum p a c # (#.) :: Coercible c b => q b c -> PastroSum p a b -> PastroSum p a c # (.#) :: Coercible b a => PastroSum p b c -> q a b -> PastroSum p a c # | |
| Profunctor (CotambaraSum p) | |
Defined in Data.Profunctor.Choice Methods dimap :: (a -> b) -> (c -> d) -> CotambaraSum p b c -> CotambaraSum p a d # lmap :: (a -> b) -> CotambaraSum p b c -> CotambaraSum p a c # rmap :: (b -> c) -> CotambaraSum p a b -> CotambaraSum p a c # (#.) :: Coercible c b => q b c -> CotambaraSum p a b -> CotambaraSum p a c # (.#) :: Coercible b a => CotambaraSum p b c -> q a b -> CotambaraSum p a c # | |
| Profunctor (CopastroSum p) | |
Defined in Data.Profunctor.Choice Methods dimap :: (a -> b) -> (c -> d) -> CopastroSum p b c -> CopastroSum p a d # lmap :: (a -> b) -> CopastroSum p b c -> CopastroSum p a c # rmap :: (b -> c) -> CopastroSum p a b -> CopastroSum p a c # (#.) :: Coercible c b => q b c -> CopastroSum p a b -> CopastroSum p a c # (.#) :: Coercible b a => CopastroSum p b c -> q a b -> CopastroSum p a c # | |
| Profunctor p => Profunctor (Tambara p) | |
Defined in Data.Profunctor.Strong Methods dimap :: (a -> b) -> (c -> d) -> Tambara p b c -> Tambara p a d # lmap :: (a -> b) -> Tambara p b c -> Tambara p a c # rmap :: (b -> c) -> Tambara p a b -> Tambara p a c # (#.) :: Coercible c b => q b c -> Tambara p a b -> Tambara p a c # (.#) :: Coercible b a => Tambara p b c -> q a b -> Tambara p a c # | |
| Profunctor (Pastro p) | |
Defined in Data.Profunctor.Strong | |
| Profunctor (Cotambara p) | |
Defined in Data.Profunctor.Strong Methods dimap :: (a -> b) -> (c -> d) -> Cotambara p b c -> Cotambara p a d # lmap :: (a -> b) -> Cotambara p b c -> Cotambara p a c # rmap :: (b -> c) -> Cotambara p a b -> Cotambara p a c # (#.) :: Coercible c b => q b c -> Cotambara p a b -> Cotambara p a c # (.#) :: Coercible b a => Cotambara p b c -> q a b -> Cotambara p a c # | |
| Profunctor (Copastro p) | |
Defined in Data.Profunctor.Strong Methods dimap :: (a -> b) -> (c -> d) -> Copastro p b c -> Copastro p a d # lmap :: (a -> b) -> Copastro p b c -> Copastro p a c # rmap :: (b -> c) -> Copastro p a b -> Copastro p a c # (#.) :: Coercible c b => q b c -> Copastro p a b -> Copastro p a c # (.#) :: Coercible b a => Copastro p b c -> q a b -> Copastro p a c # | |
| Functor f => Profunctor (Star f) | |
Defined in Data.Profunctor.Types | |
| Functor f => Profunctor (Costar f) | |
Defined in Data.Profunctor.Types | |
| Arrow p => Profunctor (WrappedArrow p) | |
Defined in Data.Profunctor.Types Methods dimap :: (a -> b) -> (c -> d) -> WrappedArrow p b c -> WrappedArrow p a d # lmap :: (a -> b) -> WrappedArrow p b c -> WrappedArrow p a c # rmap :: (b -> c) -> WrappedArrow p a b -> WrappedArrow p a c # (#.) :: Coercible c b => q b c -> WrappedArrow p a b -> WrappedArrow p a c # (.#) :: Coercible b a => WrappedArrow p b c -> q a b -> WrappedArrow p a c # | |
| Profunctor (Forget r) | |
Defined in Data.Profunctor.Types | |
| Profunctor (Tagged :: Type -> Type -> Type) | |
Defined in Data.Profunctor.Unsafe | |
| Profunctor ((->) :: Type -> Type -> Type) | |
| Functor h => Profunctor (Cornice h p) | |
Defined in Colonnade.Encode Methods dimap :: (a -> b) -> (c -> d) -> Cornice h p b c -> Cornice h p a d # lmap :: (a -> b) -> Cornice h p b c -> Cornice h p a c # rmap :: (b -> c) -> Cornice h p a b -> Cornice h p a c # (#.) :: Coercible c b => q b c -> Cornice h p a b -> Cornice h p a c # (.#) :: Coercible b a => Cornice h p b c -> q a b -> Cornice h p a c # | |
| Functor w => Profunctor (Cokleisli w) | |
Defined in Data.Profunctor.Unsafe Methods dimap :: (a -> b) -> (c -> d) -> Cokleisli w b c -> Cokleisli w a d # lmap :: (a -> b) -> Cokleisli w b c -> Cokleisli w a c # rmap :: (b -> c) -> Cokleisli w a b -> Cokleisli w a c # (#.) :: Coercible c b => q b c -> Cokleisli w a b -> Cokleisli w a c # (.#) :: Coercible b a => Cokleisli w b c -> q a b -> Cokleisli w a c # | |
| Profunctor (Exchange a b) | |
Defined in Control.Lens.Internal.Iso 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 # (#.) :: Coercible c b0 => q b0 c -> Exchange a b a0 b0 -> Exchange a b a0 c # (.#) :: Coercible b0 a0 => Exchange a b b0 c -> q a0 b0 -> Exchange a b a0 c # | |
| (Profunctor p, Profunctor q) => Profunctor (Procompose p q) | |
Defined in Data.Profunctor.Composition Methods dimap :: (a -> b) -> (c -> d) -> Procompose p q b c -> Procompose p q a d # lmap :: (a -> b) -> Procompose p q b c -> Procompose p q a c # rmap :: (b -> c) -> Procompose p q a b -> Procompose p q a c # (#.) :: Coercible c b => q0 b c -> Procompose p q a b -> Procompose p q a c # (.#) :: Coercible b a => Procompose p q b c -> q0 a b -> Procompose p q a c # | |
| (Profunctor p, Profunctor q) => Profunctor (Rift p q) | |
Defined in Data.Profunctor.Composition Methods dimap :: (a -> b) -> (c -> d) -> Rift p q b c -> Rift p q a d # lmap :: (a -> b) -> Rift p q b c -> Rift p q a c # rmap :: (b -> c) -> Rift p q a b -> Rift p q a c # (#.) :: Coercible c b => q0 b c -> Rift p q a b -> Rift p q a c # (.#) :: Coercible b a => Rift p q b c -> q0 a b -> Rift p q a c # | |
| Functor f => Profunctor (Joker f :: Type -> Type -> Type) | |
Defined in Data.Profunctor.Unsafe | |
| Contravariant f => Profunctor (Clown f :: Type -> Type -> Type) | |
Defined in Data.Profunctor.Unsafe | |
| (Profunctor p, Profunctor q) => Profunctor (Sum p q) | |
Defined in Data.Profunctor.Unsafe | |
| (Profunctor p, Profunctor q) => Profunctor (Product p q) | |
Defined in Data.Profunctor.Unsafe Methods dimap :: (a -> b) -> (c -> d) -> Product p q b c -> Product p q a d # lmap :: (a -> b) -> Product p q b c -> Product p q a c # rmap :: (b -> c) -> Product p q a b -> Product p q a c # (#.) :: Coercible c b => q0 b c -> Product p q a b -> Product p q a c # (.#) :: Coercible b a => Product p q b c -> q0 a b -> Product p q a c # | |
| (Functor f, Profunctor p) => Profunctor (Tannen f p) | |
Defined in Data.Profunctor.Unsafe Methods dimap :: (a -> b) -> (c -> d) -> Tannen f p b c -> Tannen f p a d # lmap :: (a -> b) -> Tannen f p b c -> Tannen f p a c # rmap :: (b -> c) -> Tannen f p a b -> Tannen f p a c # (#.) :: Coercible c b => q b c -> Tannen f p a b -> Tannen f p a c # (.#) :: Coercible b a => Tannen f p b c -> q a b -> Tannen f p a c # | |
| (Profunctor p, Functor f, Functor g) => Profunctor (Biff p f g) | |
Defined in Data.Profunctor.Unsafe Methods dimap :: (a -> b) -> (c -> d) -> Biff p f g b c -> Biff p f g a d # lmap :: (a -> b) -> Biff p f g b c -> Biff p f g a c # rmap :: (b -> c) -> Biff p f g a b -> Biff p f g a c # (#.) :: Coercible c b => q b c -> Biff p f g a b -> Biff p f g a c # (.#) :: Coercible b a => Biff p f g b c -> q a b -> Biff p f g a c # | |
module Diagrams.Backend.SVG
module Diagrams.Backend.SVG