{-# LANGUAGE OverloadedStrings #-}
module ELynx.Tree.Export.Nexus
( toNexusTrees,
)
where
import qualified Data.ByteString.Lazy.Char8 as BL
import ELynx.Export.Nexus
import ELynx.Tree.Export.Newick
import ELynx.Tree.Length
import ELynx.Tree.Name
import ELynx.Tree.Rooted
import ELynx.Tree.Support
toNexusTrees ::
(HasMaybeLength e, HasMaybeSupport e, HasName a) =>
[(BL.ByteString, Tree e a)] ->
BL.ByteString
toNexusTrees :: [(ByteString, Tree e a)] -> ByteString
toNexusTrees [(ByteString, Tree e a)]
ts = ByteString -> [ByteString] -> ByteString
toNexus ByteString
"TREES" (((ByteString, Tree e a) -> ByteString)
-> [(ByteString, Tree e a)] -> [ByteString]
forall a b. (a -> b) -> [a] -> [b]
map (ByteString, Tree e a) -> ByteString
forall e a.
(HasMaybeLength e, HasMaybeSupport e, HasName a) =>
(ByteString, Tree e a) -> ByteString
tree [(ByteString, Tree e a)]
ts)
tree :: (HasMaybeLength e, HasMaybeSupport e, HasName a) => (BL.ByteString, Tree e a) -> BL.ByteString
tree :: (ByteString, Tree e a) -> ByteString
tree (ByteString
n, Tree e a
t) = ByteString
" TREE " ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
n ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
" = " ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> Tree e a -> ByteString
forall e a.
(HasMaybeLength e, HasMaybeSupport e, HasName a) =>
Tree e a -> ByteString
toNewick Tree e a
t