dzen-utils-0.1.1: Utilities for creating inputs for dzen.

Portabilitysemi-portable (MPTC and type families)
Stabilityexperimental
Maintainerfelipe.lessa@gmail.com
Safe HaskellSafe-Infered

System.Dzen.Base

Contents

Description

This module contains most of the basic functions of this package. The data types presented here are:

DString
strings that support constant time concatenation, dzen attributes and some instropection.
Printer
encapsulates functions take take some input and produce a DString as a result, allowing them to be combined and applied.

Synopsis

Dzen Strings

data DString Source

A DString is used for constant string output, see str. The D on DString stands for dzen, as these strings may change depending on the state (and that's why you shouldn't rely on Show, as it just uses an empty state)

str :: String -> DStringSource

Converts a String into a DString, escaping characters if needed. This function is used in fromString from IsString, so DStrings created by OverloadedStrings extension will be escaped.

rawStr :: String -> DStringSource

Converts a String into a DString without escaping anything. You really don't need to use this, trust me!

toString :: DString -> StringSource

Converts a DString back into a String. Note that (toString . rawStr) is not id, otherwise toString would not work in some cases. Probably you don't need to use this, unless you want something like a static bar and nothing else.

size :: DString -> Maybe IntSource

Tries to get the number of characters of the DString. May return Nothing when there are graphical objects. Probably you don't need to use this function.

parens :: DString -> DString -> DString -> DStringSource

parens open close d is equivalent to mconcat [open, d, close].

Printers

data Printer a Source

A printer is used when the output depends on an input, so a Printer a generates a DString based on some input of type a (and possibly updates some internal state).

comap :: (a -> b) -> Printer b -> Printer aSource

A Printer is a cofunctor.

simple :: (a -> DString) -> Printer aSource

Constructs a Printer that depends only on the input.

simple' :: (a -> String) -> Printer aSource

Like simple, but using Strings.

inputPrinter :: (b -> a -> (DString, b)) -> b -> Printer aSource

Constructs a Printer that depends on the current and on the previous inputs.

inputPrinter' :: (b -> a -> (String, b)) -> b -> Printer aSource

Like inputPrinter, but with Strings.

cstr :: Printer StringSource

Works like str, but uses the input instead of being constant. In fact, it is defined as simple str.

cshow :: Show a => Printer aSource

Same as simple' show.

Combining printers

class Combine a b whereSource

Class used for combining DStrings and Printers exactly like mappend.

Note that we don't lift DString to Printer () and use a plain function of type Printer a -> Printer b -> Printer (a,b) because that would create types such as Printer ((),(a,((),(b,())))) instead of Printer (a,b).

Associated Types

type Combined a b :: *Source

The type of the combined input of a with b.

Methods

(+++) :: a -> b -> Combined a bSource

Combine a into b. Their outputs are concatenated.

We currently have the following Combined types:

 type Combined DString    Dstring      = DString
 type Combined DString    (Printer a)  = Printer a
 type Combined (Printer a) DString     = Printer a
 type Combined (Printer a) (Printer b) = Printer (a,b)

For example, if a :: DString, b,e :: Printer Int, c :: Printer Double and d :: DString, then

 (a +++ b +++ c +++ d +++ e) :: Printer (Int, (Double, Int))

(+=+) :: Printer a -> Printer a -> Printer aSource

Sometimes you want two printers having the same input, but p1 +++ p2 :: Printer (a,a) is not convenient. So p1 +=+ p2 :: Printer a works like +++ but gives the same input for both printers.

(+-+) :: Printer a -> Printer (a, b) -> Printer (a, b)Source

Works like +=+ but the second printer's input is a tuple.

(+/+) :: Printer a -> Printer b -> Printer (b, a)Source

While you may say p1 +=+ (ds1 +++ ds2 +++ p2), where p1,p2 :: Printer a and ds1,ds2 :: DString, you can't say p1 +=+ (po +++ p2) nor (p1 +++ po) +=+ p2 where po :: Printer b.

This operator works like +++ but shifts the tuple, giving you Printer (b,a) instead of Printer (a,b). In the example above you may write p1 +>+ po +/+ p2.

(+<+) :: Printer a -> Printer (b, c) -> Printer (b, (a, c))Source

This operator works like +/+ but the second printer's input is a tuple. Use it like

 pA1 +-+ pB +<+ pC +<+ pD +/+ pA2 :: Printer (a,(b,(c,d)))

where both pA1 and pA2 are of type Printer a.

combine :: (c -> (a, b)) -> Printer a -> Printer b -> Printer cSource

This is a general combine function for Printers. The outputs are always concatenated, but the inputs are given by the supplied function.

The combining operators above are defined as:

 (+++) = combine id    -- restricted to Printers
 (+=+) = combine (\x -> (    x, x))
 (+-+) = combine (\x -> (fst x, x))
 (+/+) = combine (\(a,b)     -> (b,a))
 (+<+) = combine (\(b,(a,c)) -> (a,(b,c)))

Note also the resamblence with comap. In fact, if we have (+++) and comap we may define

 combine f a b = comap f (a +++ b)       -- pointwise
 combine = flip (.) (+++) . (.) . comap  -- pointfree

and with combine and simple we may define

 comap f = combine (\i -> ((), f i)) (simple $ const mempty) -- pointwise
 comap = flip combine (simple $ const mempty) . ((,) () .)   -- pointfree

Applying printers

Note that applying should be the last thing you do, and you should never apply inside a DString or Printer. Doing so may cause undefined behaviour because both DString and Printer contain some internal state. We create a fresh internal state when applying, so applying inside them will not take their internal state into account. You've been warned!

apply :: Printer a -> a -> (String, Printer a)Source

Apply a printer to an appropriate input, returning the output string and the new printer.

applyMany :: Printer a -> [a] -> ([String], Printer a)Source

Apply a printer many times in sequence. Most of the time you would ignore the final printer using applyMany_, but it can be used to continue applying.

applyMany_ :: Printer a -> [a] -> [String]Source

Like applyMany but ignoring the final printer.

applyForever :: Monad m => Printer a -> m a -> (String -> m ()) -> m ()Source

Apply a printer forever inside a monad. The first action is used as a supply of inputs while the second action receives the output before the next input is requested.

Note that your supply may be anything. For example, inside IO you may use threadDelay:

 applyForever (threadDelay 100000 >> getInfo) (hPutStrLn dzenHandle)

Transforming

class Transform a whereSource

Transform is a specialization of Functor for DStrings. This class is used for functions that may receive DString or Printer a as an argument because they operate only on their outputs and internal states (and not on the inputs).

So, whenever you see a function of type

 func :: Transform a => Blah -> Bleh -> a -> a

it means that func can be used in two ways:

 func :: Blah -> Bleh -> DString -> DString
 func :: Blah -> Bleh -> Printer a -> Printer a  -- Printer of any input!

Try to have this in mind when reading the types.

Note: There is also a non-exported transformSt for transforming the state in this class, otherwise it would be meaningless to use a class only for transform (it would be better to make liftT :: (DString -> DString) -> (Printer a -> Printer a)).

Methods

transform :: (DString -> DString) -> a -> aSource

This function is id on DString and modifies the output of a Printer a.