module Biobase.Secondary.New where
import Control.Applicative
import Control.Lens
import Control.Monad.Except
import Data.Attoparsec.ByteString.Char8
import Data.ByteString.Char8 (ByteString,pack)
import Data.Functor
import Data.Tree
import Data.Vector (Vector, fromList)
import GHC.Generics (Generic)
data SubStructure (t ∷ k) a
= Unpaired { _label ∷ !a }
| Paired { _label ∷ !a, _subStructures ∷ !(Vector (SubStructure t a)) }
deriving (Show, Read, Functor, Traversable, Foldable, Generic, Eq, Ord)
makeLenses ''SubStructure
makePrisms ''SubStructure
newtype FullStructure (t ∷ k) a
= FullStructure { _fullStructure ∷ Vector (SubStructure t a) }
deriving (Show, Read, Functor, Traversable, Foldable, Generic, Eq, Ord)
makeLenses ''FullStructure
pUnpaired ∷ Parser (SubStructure () ())
pUnpaired = Unpaired () <$ char '.'
{-# Inlinable pUnpaired #-}
pPaired ∷ Parser (SubStructure () ())
pPaired = Paired () <$ char '(' <*> (fromList <$> many pSubStructure) <* char ')'
{-# Inlinable pPaired #-}
pSubStructure ∷ Parser (SubStructure () ())
pSubStructure = pUnpaired <|> pPaired
{-# Inlinable pSubStructure #-}
pFullStructure ∷ Parser (FullStructure () ())
pFullStructure = FullStructure <$> fromList <$> many pSubStructure <* endOfInput
{-# Inlinable pFullStructure #-}
newtype StructureParseError = StructureParseError String
deriving (Show)
parseVienna ∷ MonadError StructureParseError m ⇒ ByteString → m (FullStructure () ())
parseVienna = either (throwError . StructureParseError) return . parseOnly pFullStructure
{-# Inlinable parseVienna #-}
toTree
∷ (SubStructure t a → Maybe b)
→ b
→ FullStructure (t ∷ k) a
→ Tree b
toTree f r (FullStructure ts) = Node r $ fmap go ts ^.. traverse . _Just
where
go u@Unpaired{} = (`Node` []) <$> f u
go p@Paired{} = case f p of
Nothing → Nothing
Just lbl → Just $ Node lbl $ (fmap go $ p^.subStructures) ^.. traverse . _Just
{-# Inlinable toTree #-}