[Haskell-beginners] Nullable attribute of a language grammar howto

Daniel Fischer daniel.is.fischer at web.de
Tue Sep 2 13:11:06 EDT 2008


Am Dienstag, 2. September 2008 18:30 schrieb Larry Evans:
> On 09/01/08 13:21, Daniel Fischer wrote:
> > Jason beat me, but I can elaborate on the matter:
> >
> > Am Montag, 1. September 2008 18:22 schrieb Larry Evans:
> >> expr2null :: (GramExpr inp_type var_type) -> (GramNull inp_type
> >> var_type)
> >> {-
> >>   expr2null GramExpr
> >>   returns a GramNull expression which indicates whether the GramExpr
> >>   can derive the empty string.
> >> -}
>
> [snip]
>
> > expr2null :: forall inp_type var_type. GramExpr inp_type var_type ->
> > GramNull inp_type var_type
> >
> > Cheers,
> > Daniel
>
> Thanks Jason and Daniel.  It works beautifully.
>
> Now, I'm trying to figure how to use Functor to define expr2null
> (renamed to gram2null in 1st attachement).
> My motivation for this goal is  I've read that  a Functor as defined
> in category theory is somewhat like a homomorphism, and gram2null
> is, AFAICT, a homomorphism between GramExpr adn NullExpr.

You can't do that :(
We have
class Functor f where
	fmap :: (a -> b) -> f a -> f b

So a Functor is a type constructor, f, which takes one type, a, as argument 
and from that constructs another type, f a, in such a way that for any 
function fun :: a -> b you can define a function (fmap fun) :: f a -> f b 
(generically, i.e. you can't use any special properties of fun).
The type of expr2null is
GramExpr a b -> GramNull a b,
so there are different type constructors applied to b on the two sides of the 
arrow, (GramExpr a) on the left and (GramNull a) on the right, while fmap 
requires the same type constructor applied to possibly different types.

You can make (GramExpr inp_type) a Functor like
instance Functor (GramExpr i) where
    fmap _ GramOne = GramOne
    fmap _ (GramInp i) = GramInp i
    fmap f (GramVar v) = GramVar (f v)
    fmap f (a :| b) = (fmap f a) :| (fmap f b)
    fmap f (a :>> b) = (fmap f a) :>> (fmap f b)

analogously for NullableExpr, but that's something entirely different (maybe 
useful, maybe not).
>
> However, I can't figure how to do it.  The 2nd attachment how
> an example with comments which, I hope, explains where I'm
> stuck.
Perhaps you're looking for something like

data Alg ty
    = Op0_0
    | Op0_1
    | Op1_0 ty
    | Op2_0 (Alg ty) (Alg ty)
    deriving (Show)

instance Functor Alg where
    fmap _ Op0_0 = Op0_0
    fmap _ Op0_1 = Op0_1
    fmap f (Op1_0 v) = Op1_0 (f v)
    fmap f (Op2_0 a b) = Op2_0 (fmap f a) (fmap f b)
?
>
> I've also looked at happy's sources and found no use of Functor; so,
> maybe haskell's Functor is not similar to category theory's Functor.

It is, with the restriction that Haskell only has Endofunctors, where the 
source category and the target category are the same, the category of Haskell 
types where the morphisms are functions between those types (glossing over 
the fact that this is not quite accurate).
>
> Any help would be appreciated.
>
> -regards,
> Larry
>



More information about the Beginners mailing list