[Template-haskell] recover and get error message? - parsing th
syntax trees
Simon Peyton-Jones
simonpj at microsoft.com
Wed Jun 4 11:50:46 EDT 2008
Good point. I've created a feature-request ticket http://hackage.haskell.org/trac/ghc/ticket/2340. Any comments from other TH folk?
Simon
| -----Original Message-----
| From: template-haskell-bounces at haskell.org [mailto:template-haskell-bounces at haskell.org] On Behalf Of
| Marc Weber
| Sent: 25 May 2008 18:27
| To: template-haskell at haskell.org
| Subject: [Template-haskell] recover and get error message? - parsing th syntax trees
|
| I'd like to implement a simple helper function
| -- helper pasring the reify output
| thChoice :: a -> [ a -> Q r ] -> Q r
| thChoice a list = thChoice' list
| where
| thChoice' [] = fail $ "no parser did match"
| thChoice' (p:ps) = (p a) `recover` (thChoice' ps)
|
| However there I can't get the result of why a parser has failed this
| way:
| thChoice :: [ a -> Q r ] -> Q r
| thChoice a list = thChoice' [] list
| where
| thChoice' errors [] = fail $ "no parser did match: error messages " ++ (show errors)
| thChoice' errors (p:ps) = (p a) `recover` \e -> (thChoice' (e:errors) ps)
| ^^ unfotunately recover
| doesn't support passing this \e
|
| To show a nice list
| expected either
| a) ...
| b) ...
| c) ...
| but no parser did match the passed arg
| ...
|
| I've also tried `catchError` but there was no instance..
| Is there another way handling this or should I just use
| Either Error result and
| return . Left $
| return . Right $
| or put kind of ErrorMonad on top of the Q monad myself?
|
| My use case:
| Parse different settings specified by using different types such as
| UniqKey or (Key Foo ()) or relation settings
|
| type Tickets = Table (Autoinc, Surname, TestCase.Name)
| (Key Name (), Key Surname ())
| (Rel Inbound Flights, Rel Outbound ( Maybe Flights) )
|
| type <name> = Table <cols>
| <keys>
| <master tables>
|
| <keys> : the primary key field is added automatically
| example: key Foo (-> Map Foo row)
| double index (Foo2, Bar) (-> Map Foo2 ( Map Bar row ) ) )
| ( UniqKey Foo
| , Key Foo2 ( Key Bar () )
| )
| <master tables>:
| ( TableMaster
| , Rel IdType TableMaster2
| -- optional relation (eg a ticket may have a retour, but doesn't have to have)
| , Maybe TableMaster4
| , (Rel IdType (Maybe TableMaster5))
| )
|
| Is there alreay a library providing this kind of error reporting for
| parsing haskell template syntax trees?
|
| Marc Weber
| _______________________________________________
| template-haskell mailing list
| template-haskell at haskell.org
| http://www.haskell.org/mailman/listinfo/template-haskell
More information about the template-haskell
mailing list