| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.Layout
- betweenWith :: (a -> a -> a) -> a -> a -> a -> a
- surroundedWith :: (a -> a -> a) -> a -> a -> a -> a
- between :: Semigroup a => a -> a -> a -> a
- between' :: Semigroup a => a -> a -> a
- space :: IsString a => a
- parensed :: (Semigroup a, IsString a) => a -> a
- bracked :: (Semigroup a, IsString a) => a -> a
- braced :: (Semigroup a, IsString a) => a -> a
- chevroned :: (Semigroup a, IsString a) => a -> a
- spaced :: (Semigroup a, IsString a) => a -> a
- quoted :: (Semigroup a, IsString a) => a -> a
- singleQuoted :: (Semigroup a, IsString a) => a -> a
- backticked :: (Semigroup a, IsString a) => a -> a
- enumerateWith :: (Monoid a, Foldable f) => a -> a -> f a -> a
- enumerateAlt :: (Monoid a, IsString a, Foldable f) => f a -> a
- enumerateSeq :: (Monoid a, IsString a, Foldable f) => f a -> a
- newtype Delta = Delta Word64
- class ElemBuilderT t m a where
- class ElemBuilder m a where
- class RenderT t m a where
- class Render m a where
- phantom :: (ElemBuilder t a, Mempty a) => t a
- data Bounds = Bounds {}
- data Bounded a = Bounded {}
- class HasBounds c where
- bounded_elem :: forall a a. Lens (Bounded a) (Bounded a) a a
- bounded_bounds :: forall a. Lens' (Bounded a) Bounds
- class Measurable a where
- bounded :: Lens (Bounded a) (Bounded b) a b
- unbound :: Bounded a -> a
- data Dir
- data CartTree t m a
- class Concatenable a where
- hcat :: Concatenable a => a -> a -> a
- vcat :: Concatenable a => a -> a -> a
- (</>) :: Concatenable a => a -> a -> a
- class Spacing a where
- hspacing :: (ElemBuilder t a, Spacing a) => Delta -> t a
- vspacing :: (ElemBuilder t a, Spacing a) => Delta -> t a
- (<+>) :: (ElemBuilder t a, Semigroup (t a), Spacing a) => t a -> t a -> t a
- (<//>) :: (Concatenable (t a), ElemBuilder t a, Spacing a) => t a -> t a -> t a
- (<///>) :: (Concatenable (t a), ElemBuilder t a, Spacing a) => t a -> t a -> t a
- (<////>) :: (Concatenable (t a), ElemBuilder t a, Spacing a) => t a -> t a -> t a
- data LineBlock a = LineBlock {}
- lines :: forall a a. Lens (LineBlock a) (LineBlock a) [a] [a]
- lineBlock_bounds :: forall a. Lens' (LineBlock a) Bounds
- renderLineBlock :: (IsString a, Monoid a, Item a ~ Char, FiniteSequence a) => LineBlock a -> a
- concatLineBlock :: (IsString a, Monoid a) => LineBlock a -> a
- type GenLineBlockConcatCtx a = (Convertible String a, Monoid a)
- type BlockBuilder = BlockBuilderT Identity
- newtype BlockBuilderT m a = BlockBuilderT (CartTree BlockBuilderT m a)
- append :: BlockBuilder a -> BlockBuilder a -> BlockBuilder a
- prepend :: BlockBuilder a -> BlockBuilder a -> BlockBuilder a
- type LineBuilder = LineBuilderT Identity
- newtype LineBuilderT m a = LineBuilderT (CartTree LineBuilderT m a)
- block :: (Render t a, Concatenable (t a), ElemBuilder t a, Mempty a) => t a -> t a
- indented :: (ElemBuilder t a, Spacing a, Semigroup (t a)) => t a -> t a
- type Doc a = LineBuilderT BlockBuilder (LineBlock a)
Documentation
betweenWith :: (a -> a -> a) -> a -> a -> a -> a Source #
surroundedWith :: (a -> a -> a) -> a -> a -> a -> a Source #
singleQuoted :: (Semigroup a, IsString a) => a -> a Source #
backticked :: (Semigroup a, IsString a) => a -> a Source #
enumerateWith :: (Monoid a, Foldable f) => a -> a -> f a -> a Source #
Instances
| Enum Delta Source # | |
| Eq Delta Source # | |
| Num Delta Source # | |
| Ord Delta Source # | |
| Show Delta Source # | |
| Generic Delta Source # | |
| Semigroup Delta Source # | |
| Default Delta Source # | |
| NFData Delta Source # | |
| Wrapped Delta Source # | |
| Mempty Delta Source # | |
| Convertible' a Word64 => Convertible a Delta Source # | |
| Convertible' Word64 a => Convertible Delta a Source # | |
| (~) * Delta t => Rewrapped Delta t Source # | |
| type Rep Delta Source # | |
| type Unwrapped Delta Source # | |
class ElemBuilder m a where Source #
Minimal complete definition
Instances
| ElemBuilder Identity a Source # | |
| (ElemBuilder m a, ElemBuilderT t m a) => ElemBuilder (t m) a Source # | |
class RenderT t m a where Source #
Minimal complete definition
Instances
| (Mempty (m a), Concatenable (m a)) => RenderT BlockBuilderT m a Source # | |
| (Concatenable (m a), Monoid (m a)) => RenderT LineBuilderT m a Source # | |
phantom :: (ElemBuilder t a, Mempty a) => t a Source #
class HasBounds c where Source #
Minimal complete definition
class Measurable a where Source #
Minimal complete definition
Instances
| Measurable Text Source # | |
| Measurable TermText Source # | |
| Measurable (Bounded a) Source # | |
| Measurable (LineBlock a) Source # | |
Instances
| (Functor (t m), Functor m) => Functor (CartTree t m) Source # | |
| (Foldable (t m), Foldable m) => Foldable (CartTree t m) Source # | |
| (Traversable (t m), Traversable m) => Traversable (CartTree t m) Source # | |
| Convertible2 (* -> *) * (CartTree BlockBuilderT) BlockBuilderT Source # | |
| Convertible2 (* -> *) * (CartTree LineBuilderT) LineBuilderT Source # | |
| (Show (t m a), Show (m a)) => Show (CartTree t m a) Source # | |
| Convertible2' (* -> *) * (CartTree t) t => Semigroup (CartTree t m a) Source # | |
| Convertible2' (* -> *) * (CartTree t) t => Monoid (CartTree t m a) Source # | |
| Mempty (CartTree t m a) Source # | |
| Convertible2' (* -> *) * (CartTree t) t => Concatenable (CartTree t m a) Source # | |
class Concatenable a where Source #
Minimal complete definition
Instances
| Concatenable Bounds Source # | |
| Concatenable a => Concatenable (Identity a) Source # | |
| GenLineBlockConcatCtx a => Concatenable (LineBlock a) Source # | |
| Concatenable (BlockBuilderT m a) Source # | |
| Concatenable (LineBuilderT m a) Source # | |
| Convertible2' (* -> *) * (CartTree t) t => Concatenable (CartTree t m a) Source # | |
hcat :: Concatenable a => a -> a -> a Source #
vcat :: Concatenable a => a -> a -> a Source #
(</>) :: Concatenable a => a -> a -> a infixr 6 Source #
(<//>) :: (Concatenable (t a), ElemBuilder t a, Spacing a) => t a -> t a -> t a infixr 6 Source #
(<///>) :: (Concatenable (t a), ElemBuilder t a, Spacing a) => t a -> t a -> t a infixr 6 Source #
(<////>) :: (Concatenable (t a), ElemBuilder t a, Spacing a) => t a -> t a -> t a infixr 6 Source #
Instances
| Functor LineBlock Source # | |
| Foldable LineBlock Source # | |
| Traversable LineBlock Source # | |
| (Convertible' Text a, Measurable a) => Convertible Text (LineBlock a) Source # | |
| Show a => Show (LineBlock a) Source # | |
| (IsString a, Measurable a) => IsString (LineBlock a) Source # | |
| GenLineBlockConcatCtx a => Semigroup (LineBlock a) Source # | |
| GenLineBlockConcatCtx a => Monoid (LineBlock a) Source # | |
| Mempty (LineBlock a) Source # | |
| Stylable a => Stylable (LineBlock a) Source # | |
| HasBounds (LineBlock a) Source # | |
| (Convertible String a, Mempty a) => Spacing (LineBlock a) Source # | |
| GenLineBlockConcatCtx a => Concatenable (LineBlock a) Source # | |
| Measurable (LineBlock a) Source # | |
renderLineBlock :: (IsString a, Monoid a, Item a ~ Char, FiniteSequence a) => LineBlock a -> a Source #
type GenLineBlockConcatCtx a = (Convertible String a, Monoid a) Source #
type BlockBuilder = BlockBuilderT Identity Source #
newtype BlockBuilderT m a Source #
Constructors
| BlockBuilderT (CartTree BlockBuilderT m a) |
Instances
append :: BlockBuilder a -> BlockBuilder a -> BlockBuilder a Source #
prepend :: BlockBuilder a -> BlockBuilder a -> BlockBuilder a Source #
type LineBuilder = LineBuilderT Identity Source #
newtype LineBuilderT m a Source #
Constructors
| LineBuilderT (CartTree LineBuilderT m a) |
Instances
block :: (Render t a, Concatenable (t a), ElemBuilder t a, Mempty a) => t a -> t a Source #
type Doc a = LineBuilderT BlockBuilder (LineBlock a) Source #
The Doc type is just an alias to predefined layouting transformers. It is unified type allowing many fancy utils, like inserting indented code blocks.