Hello,

      I am seriously punching my way to build Swish via .cabal ... My head
is totally to the wall .... punch .. punch .....

Graham Lyle has written some seriously beautiful code .... I am trying to
get to adhere to contemporary Haskell namespace convention ..... I still
awaiting response from Graham vis-a-vis posting on Hackage ... I strongly
think that in bioinformatics and also oil/gas industry(<< I am stuck here
everyday ;^)) that Swish is a strong arena of discussion!   In any case ..
there are some issues:

1) I strongly suspect that in Swish 0.2.1 that some of Graham's libaries are
already superseded by the Haskell prelude , e.g. HUnit, Parsec(!!!), his
Sort directory/library .. Don ...please

2) Graham wrote a deterministic finite automaton ..... which is giving some
grieve namespace-wise ..... please see following

Swish/HaskellRDF/Dfa/Dfa.lhs:1:0:
    Failed to load interface for `Prelude':
      it is a member of package base, which is hidden
vigalchin

here is a fragement of Dfa.lhs:

> {-# OPTIONS -fglasgow-exts #-}
> {-# OPTIONS -fallow-undecidable-instances #-}

> module Swish.HaskellRDF.Dfa.Dfa (
>     Re(..),
>     matchRe,
>     matchRe2
> ) where
> {- ????
> import Control.Monad.Identity
> import Control.Monad.Reader
> import Control.Monad.State
> import Data.FiniteMap
> import List
> import Data.Array
> -}

import IOExts


The type of a regular expression.

> data Re t
"Dfa.lhs" 609 lines, 18871 characters

Very kind regards, Vasili
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to