{-  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 FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TemplateHaskell #-}

module Text.GrammarCombinators.Transform.UnfoldDead (
  unfoldDead,
  unfoldDeadE,
  unfoldDeadLE
  ) where

import Text.GrammarCombinators.Base
import Text.GrammarCombinators.Utils.IsDead 

newtype UnfoldDeadRule p (phi :: * -> *) (r :: * -> *) t v = 
    UDRule { unUDRule :: (forall ix. phi ix -> Bool) -> p v }

instance (ProductionRule p) =>
         ProductionRule (UnfoldDeadRule p phi r t) where
  a >>> b = UDRule $ \g -> unUDRule a g >>> unUDRule b g
  a ||| b = UDRule $ \g -> unUDRule a g ||| unUDRule b g
  die = UDRule $ \_ -> die
  endOfInput = UDRule $ \_ -> endOfInput

instance (EpsProductionRule p) =>
         EpsProductionRule (UnfoldDeadRule p phi r t) where
  epsilon v = UDRule $ \_ -> epsilon v

instance (LiftableProductionRule p) =>
         LiftableProductionRule (UnfoldDeadRule p phi r t) where
  epsilonL v q = UDRule $ \_ -> epsilonL v q

instance (TokenProductionRule p t) =>
         TokenProductionRule (UnfoldDeadRule p phi r t) t where
  token t = UDRule $ \_ -> token t
  anyToken = UDRule $ \_ -> anyToken

instance (ProductionRule p, 
          RecProductionRule p phi r) =>
         RecProductionRule (UnfoldDeadRule p phi r t) phi r where
  ref idx = UDRule $ \g -> if g idx then die else ref idx

instance (ProductionRule p, 
          LiftableProductionRule p, 
          LoopProductionRule p phi r) =>
         LoopProductionRule (UnfoldDeadRule p phi r t) phi r where
  manyRef idx = UDRule $ \g -> if g idx then epsilonL [] [| [] |] else manyRef idx 
  many1Ref idx = UDRule $ \g -> if g idx then die else many1Ref idx 

-- | Unfold dead non-terminals in a given extended context-
-- free grammar, such
-- that the unfolded references can be filtered with the
-- 'filterDies' algorithm. This uses the 'isDead' algorithm
-- to detect dead non-terminals.
unfoldDeadE :: (EqFam phi, FoldFam phi, MemoFam phi) => 
  GExtendedContextFreeGrammar phi r t rr -> 
  GExtendedContextFreeGrammar phi r t rr
unfoldDeadE gram idx = unUDRule (gram idx) $ isDead gram

-- | Unfold dead non-terminals in a given extended liftable context-
-- free grammar, such
-- that the unfolded references can be filtered with the
-- 'filterDies' algorithm. This uses the 'isDead' algorithm
-- to detect dead non-terminals.
unfoldDeadLE :: (EqFam phi, FoldFam phi, MemoFam phi) => 
  GLExtendedContextFreeGrammar phi r t rr -> 
  GLExtendedContextFreeGrammar phi r t rr
unfoldDeadLE gram idx = unUDRule (gram idx) $ isDead gram

-- | Unfold dead non-terminals in a given context-
-- free grammar, such
-- that the unfolded references can be filtered with the
-- 'filterDies' algorithm. This uses the 'isDead' algorithm
-- to detect dead non-terminals.
unfoldDead :: (EqFam phi, FoldFam phi, MemoFam phi) => 
  GContextFreeGrammar phi r t rr -> 
  GContextFreeGrammar phi r t rr
unfoldDead gram idx = unUDRule (gram idx) $ isDead gram