{-  Copyright 2010 Dominique Devriese

    This file is part of the grammar-combinators library.

    The grammar-combinators library is free software: you can
    redistribute it and/or modify it under the terms of the GNU
    Lesser General Public License as published by the Free
    Software Foundation, either version 3 of the License, or (at
    your option) any later version.

    Foobar is distributed in the hope that it will be useful, but
    WITHOUT ANY WARRANTY; without even the implied warranty of
    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
    GNU Lesser General Public License for more details.

    You should have received a copy of the GNU Lesser General
    Public License along with Foobar. If not, see
    <http://www.gnu.org/licenses/>.
-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE RelaxedPolyRec #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RankNTypes #-}

module Text.GrammarCombinators.Parser.LL1TH (
  prepareLL1TableTH
  ) where  

import Language.Haskell.TH.Syntax

import Data.Map
  
import Text.GrammarCombinators.Base
import Text.GrammarCombinators.Parser.LL1

instance (Lift k, Lift a) => Lift (Map k a) where
  lift v = [| fromAscList $(lift $ toAscList v)|]

prepareLL1TableTH :: (Domain phi,
                      Token t,
                      Lift (Memo phi (K0 (Map t Int))),
                      Lift (Memo phi (K0 (Maybe Int)))
                      ) =>
                     GContextFreeGrammar phi t r rr -> Q Exp
prepareLL1TableTH grammar = liftLL1Table $ calcLL1Table grammar

liftLL1Table :: (MemoFam phi,
                 Token t,
                 Lift (Memo phi (K0 (Map t Int))),
                 Lift (Memo phi (K0 (Maybe Int)))) =>
                LL1Table phi t -> Q Exp 
liftLL1Table (LL1Table a b c) = [| LL1Table $(lift a) $(lift b) $(lift c)|]