Monday, April 30, 2012

HaTeX 3.3: Release notes

I was really really wishing this release! I put a lot of efforts on it and now I feel pretty good! All right, let's see quickly what's new. A list of changes is contained in the package source distribution, in the ReleaseNotes file.

Class system

Where are all those .Monad modules? They are missing!

Yes, yes. There is not .Monad modules now! Instead, there is a new class: LaTeXC. Both LaTeX and LaTeXT are instances of it, so a single module can contain both interfaces. More details in a previous post.

Trees

I have a tree in Haskell and I want to print it nicely. What can I do?

Now you can use HaTeX! How? Simple. Use directly the tree type defined in HaTeX or transform the one you have to it, choose a function to render the nodes and, finally, use the tree function to obtain the LaTeX code that prints the tree.

The HaTeX User's Guide

Finally I wrote a guide for HaTeX! At least, a stub of the guide.  And I made it open source! So you can contribute also to the guide!

I will change it, extend it and improve it all the time. A ready-to-read PDF version is also available.

Till the next time

I am going to continue working improving the library and the guide. I think HaTeX has reached a point of more stability. Good news, I guess. Now, I hope you enjoy these changes. I will write here any news.

Good luck,
Daniel Díaz.

Saturday, April 28, 2012

HaTeX 3.3: HaTeX with class

So I finally decided to merge the normal (what sometimes I called applicative) interface with the monadic one. It was not easy to me, but I feel like doing the right thing. I thought: "If I would release this library for the first time, how you would like it to be?" The answer then was "merge both interfaces!".

As a consequence of this decision, I have to admit that my work as maintainer has been reduced considerably. Now HaTeX-meta is deprecated, until HaTeX needs a similar tool, and I have about the half of modules to maintain.

Although the version has been bumped to 3.3 (being a major revision), everything code that worked until today must to work now. The only change you may need to do is to drop de .Monad in the import list. If you have some issue, please, make me know it.

I hope all you feel happy with this.

About the implementation

All I did is to define the following class:

class (Monoid l,IsString l) => LaTeXC l where
 liftListL :: ([LaTeX] -> LaTeX) -> [l] -> l

It allows to lift any function over LaTeX to a function over any type l of the class, as follows:

fromLaTeX :: LaTeXC l => LaTeX -> l
fromLaTeX l = liftListL (\_ -> l) []

liftL :: LaTeXC l => (LaTeX -> LaTeX) -> l -> l
liftL f x = liftListL (\[x] -> f x) [x]

liftL2 :: LaTeXC l => (LaTeX -> LaTeX -> LaTeX) -> l -> l -> l
liftL2 f x y = liftListL (\[x,y] -> f x y) [x,y]

And you can continue with number of arguments of your desire. For N arguments:

liftLN :: LaTeXC l => (LaTeX -> ... -> LaTeX) -> l -> ... -> l
liftLN f x1 ... xN = liftListL (\[x1 ... xN] -> f x1 ... xN) [x1 ... xN]

Now we are ready to express all functions changing each LaTeX with a type l instance of LaTeXC. The idea is to separate LaTeX arguments and other arguments and apply a liftLN function in the following way:

foo :: LaTeXC l => l -> A -> B -> l -> C -> l
foo l1 a b l2 c = liftL2 (\l1 l2 -> old l1 a b l2 c) l1 l2
 where
  old :: LaTeX -> A -> B -> LaTeX -> C -> LaTeX

Here, the function old is the original definition of foo. There are plenty of examples in the library (all funcions are now defined this way). As a contributor you may want to see it.

Since LaTeX and LaTeXT are instances of LaTeXC, now all functions work at the same time for both types.

The User's Guide

I started to write the HaTeX User's Guide. I'm doing it open source. It contains an introduction and explain some basics of HaTeX. The source code repository lives here.

The release in Hackage will be done when the User's Guide becomes more complete.

Saturday, April 21, 2012

Parsing with Haskell

I really LOVE to create parsers in Haskell!

Below, an example of a simple markdown parser (using the parsec library).

module Syntax (
   Syntax (..)
 , Text
 , parseSyntax
 , ParseError
   ) where

import Data.Text
import Data.String
import Text.Parsec
import Text.Parsec.Text
import Control.Monad (join)

{- Syntax Table

Italic: /.../
Bold: *...*
Language switch: $...$
Quote: {...}
Link: <...|...>
Image: [...]
Paragraph: |...|
Big: ^...^

-}

data Syntax =
   Raw Text
 | Italic Syntax
 | Bold Syntax
 | Lang Syntax
 | Quote Syntax
 | Link Text Text
 | Image Text
 | Par Syntax
 | Big Syntax
 | Seq Syntax Syntax
   deriving Show -- For debugging

reschars :: [Char]
reschars = "/*${}<>[]|^"

p_Syntax :: Parser Syntax
p_Syntax = fmap (Prelude.foldr1 Seq) $ many1 $ choice $ fmap try [
   p_Raw
 , p_Chars   Italic '/'     '/'
 , p_Chars   Bold   '*'     '*'
 , p_Chars   Lang   '$'     '$'
 , p_Chars   Quote  '{'     '}'
 , p_CharsT2 Link   '<' '|' '>'
 , p_CharsT  Image  '['     ']'
 , p_Chars   Par    '|'     '|'
 , p_Chars   Big    '^'     '^'
   ]

parseSyntax :: Text -> Either ParseError Syntax
parseSyntax = parse (withEOF p_Syntax) "SyntaxSource"

----------------------------------------------------

p_Chars :: (Syntax -> a) -> Char -> Char -> Parser a
p_Chars f c1 c2 = fmap f $ between (char c1) (char c2) $ p_Syntax

p_CharsT :: (Text -> a) -> Char -> Char -> Parser a
p_CharsT f c1 c2 = char c1 >> (fmap (f . fromString) $ many1 $ noneOf [c2])
                           >>= (char c2 >>) . return

p_CharsT2 :: (Text -> Text -> a) -> Char -> Char -> Char -> Parser a
p_CharsT2 f c1 c c2 = do
 char c1
 l <- many1 $ noneOf [c] 
 char c
 s <- many1 $ noneOf [c2]
 char c2
 return $ f (fromString l) (fromString s)

p_Raw :: Parser Syntax
p_Raw = fmap (Raw . fromString) $ many1 $
           try (char '\\' >> choice (fmap char reschars))
       <|> noneOf reschars

withEOF :: (Stream s m t, Show t) => ParsecT s u m b -> ParsecT s u m b
withEOF = (>>= (eof >>) . return)

Sunday, April 15, 2012

HaTeX: Trees and problems

Trees

Since a time ago, I wanted to add trees to HaTeX. Some way to, given a Haskell tree, create a LaTeX output according to it. So I created the datatype:

data Tree a =
   Leaf a
 | Node (Maybe a) [Tree a]

and started thinking about what LaTeX package I should to use in order to drawing trees. Since there are several good options, I decided to keep the Tree datatype in a separated module and write different implementations in different modules with similar interfaces. Then, I started with the qtree package and, in a few minutes, I had an example working. So I was happy for the moment.

The problem

But my happiness did not last long. The method used to transform a Haskell tree into a LaTeX value was to have a function that creates a LaTeX value from each node and, then, build the tree following the LaTeX tree syntax. So, the type of the function, called tree, was:

tree :: (a -> LaTeX) -> Tree a -> LaTeX

And this worked pretty well. The problem came out when I wanted to run metahatex in order to create the analogous monadic version. The modus operandi of metahatex is to read the type of the functions and infer from it their monadic implementation, re-using the original implementation. For example, if we have:

foo :: LaTeX -> a -> LaTeX

then, metahatex (importing the former qualified as App) do:

foo :: Monad m => LaTeXT_ m -> a -> LaTeXT_ m
foo lm a = do
 l <- extractLaTeX_ lm
 textell $ App.foo l a

where extractLaTeX_ gets the LaTeX value produced by the LaTeXT monad and textell puts LaTeX values again in the monad (like the tell method of the writer monad).

This method has worked perfectly until now. But, what happens if we try to apply it to the tree function? As we needed to transform a value of type LaTeX to another of type LaTeXT_ m for foo, we will need to do so from a a -> LaTeXT_ m typed value to a a -> LaTeX typed value. And that is impossible!

Searching a solution

I never liked the idea of write the monadic code manually, that would be write duplicated code. I went then to eat a pizza and think about it. Typeclasses came to my mind. When I returned to my computer, I started to search what minimal functions I need to render the tree. Then, I wrote a typeclass and made LaTeX and LaTeXT_ instances of it. See the definition of the resulting typeclass:

class (Monoid l, IsString l) => LaTeXTree l where
  texbraces :: l -> l
  texcomms :: String -> l
  totex :: Render a => a -> l

The first and second method are abstractions of the TeXBraces and TeXCommS type constructors! And the other is the abstraction of the rendertex function! Making LaTeX and LaTeXT instances of this typeclass allow us to construct a tree function valid to both types. But this is not the end. The same idea is applicable to the whole library, so normal and .Monad modules can be merged using a typeclass with abstractions of all LaTeX constructors!

Conclusion

Well, this idea had come to me a time ago, but I just realized today how useful it can be. And now, I feel a bit odd taking this approach only to trees. What should I do?