----------------------------------------------------------------------------- -- -- Module : Data.List.Util.Listable -- Copyright : (c) 2014-16 Brian W Bush -- License : MIT -- -- Maintainer : Brian W Bush -- Stability : Experimental -- Portability : Portable -- -- | For CSV-like and TSV-like data. -- ----------------------------------------------------------------------------- {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE MonoLocalBinds #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE Safe #-} module Data.List.Util.Listable ( -- * Tabbed Strings tab , fromTabbed , toTabbed , fromTabbeds , toTabbeds -- * Converting to/from Lists , Listable(..) , fromStringList , toStringList , fromTabbedList , toTabbedList , fromStringLists , toStringLists , fromTabbedLists , toTabbedLists , fromTransposedTabbedLists , toTransposedTabbedLists -- * Dealing with Headers , WithHeader(..) , fromStringListsWithHeader , toStringListsWithHeader , fromTabbedListsWithHeader , toTabbedListsWithHeader , readTabbedListsWithHeader , writeTabbedListsWithHeader , fromTransposedTabbedListsWithHeader , toTransposedTabbedListsWithHeader , readTransposedTabbedListsWithHeader , writeTransposedTabbedListsWithHeader ) where import Control.Applicative (liftA2) import Control.Arrow ((&&&)) import Data.List (intercalate, transpose) import Data.List.Split (splitOn) import Data.String.Util (Stringy(..)) -- | Tab character. tab :: String tab = "\t" -- | Separate a tabbed string. fromTabbed :: String -- ^ The tabbed strings. -> [String] -- ^ The strings between the tabs. fromTabbed = splitOn tab -- | Intercalate tabs between strings. toTabbed :: [String] -- ^ The strings. -> String -- ^ The intercalated string. toTabbed = intercalate tab -- | Separate lines and tabs. fromTabbeds :: String -- ^ The string. -> [[String]] -- ^ The lines and strings between tabs. fromTabbeds = fmap fromTabbed . lines -- | Intercalte lines and tabs. toTabbeds :: [[String]] -- ^ The lines and strings between tabs. -> String -- ^ The intercalated string. toTabbeds = unlines . fmap toTabbed -- | Class for conversion to/from lists. class Listable a b | a -> b where -- | Convert from a list. fromList :: [b] -- ^ The list of values. -> a -- ^ The combined value. -- | Convert to a list. toList :: a -- ^ The value. -> [b] -- ^ THe list of values. -- | Convert from a list of strings. fromStringList :: (Listable a b, Stringy b) => [String] -- ^ The strings. -> a -- ^ The value. fromStringList = fromList . fmap fromString -- | Convert to a list of strings. toStringList :: (Listable a b, Stringy b) => a -- ^ The value. -> [String] -- ^ The strings. toStringList = fmap toString . toList -- | Convert from a tabbed lines. fromTabbedList :: (Listable a b, Stringy b) => String -- ^ The tabbed list. -> a -- ^ The value. fromTabbedList = fromStringList . fromTabbed -- | Convert to a tabbed lines. toTabbedList :: (Listable a b, Stringy b) => a -- ^ The value. -> String -- ^ The tabbed string. toTabbedList = toTabbed . toStringList -- | Convert from a list of strings. fromStringLists :: (Listable a b, Listable b c, Stringy c) => [[String]] -- ^ The lists of strings. -> a -- ^ The value. fromStringLists = fromList . fmap fromStringList -- | Convert to a list of strings. toStringLists :: (Listable a b, Listable b c, Stringy c) => a -- ^ The value. -> [[String]] -- ^ The lists of strings. toStringLists = fmap toStringList . toList -- | Convert from tabbed lines. fromTabbedLists :: (Listable a b, Listable b c, Stringy c) => String -- ^ The tabbed lines. -> a -- ^ The value. fromTabbedLists = fromStringLists . fromTabbeds -- | Convert to tabbed lines. toTabbedLists :: (Listable a b, Listable b c, Stringy c) => a -- ^ The value. -> String -- ^ The tabbed lines. toTabbedLists = toTabbeds . toStringLists -- | Convert from transposed tabbed lines. fromTransposedTabbedLists :: (Listable a b, Listable b c, Stringy c) => String -- ^ The tranposed tabbed lines. -> a -- ^ The value. fromTransposedTabbedLists = fromStringLists . transpose . fromTabbeds -- | Convert to transposed tabbed lines. toTransposedTabbedLists :: (Listable a b, Listable b c, Stringy c) => a -- ^ The value. -> String -- ^ The transposed tabbed lines. toTransposedTabbedLists = toTabbeds . transpose . toStringLists -- | Class for lists of strings with a headers. class WithHeader a b | a -> b where -- | Convert from a list of values with headers. fromHeaderLists :: ([String], [b]) -- ^ The headers and values. -> a -- ^ The combined value. -- | Convert to a list of values with headers. toHeaderLists :: a -- ^ The combined value. -> ([String], [b]) -- ^ The headers and values. -- | Convert from lists of strings with a header. fromStringListsWithHeader :: (WithHeader a b, Listable b c, Stringy c) => [[String]] -- ^ The lists of strings. -> a -- ^ The value. fromStringListsWithHeader = fromHeaderLists . (head &&& fmap fromStringList . tail) -- | Convert to lists of strings with a header. toStringListsWithHeader :: (WithHeader a b, Listable b c, Stringy c) => a -- ^ The value. -> [[String]] -- ^ The lists of strings. toStringListsWithHeader = liftA2 (:) fst (fmap toStringList . snd) . toHeaderLists -- | Convert from lines with a header. fromTabbedListsWithHeader :: (WithHeader a b, Listable b c, Stringy c) => String -- ^ The lines. -> a -- ^ The value. fromTabbedListsWithHeader = fromStringListsWithHeader . fromTabbeds -- | Convert to lines with a header. toTabbedListsWithHeader :: (WithHeader a b, Listable b c, Stringy c) => a -- ^ The value. -> String -- ^ The lines. toTabbedListsWithHeader = toTabbeds . toStringListsWithHeader -- | Read lines with a header. readTabbedListsWithHeader :: (WithHeader a b, Listable b c, Stringy c) => FilePath -- ^ The file. -> IO a -- ^ Action for reading the value. readTabbedListsWithHeader = fmap fromTabbedListsWithHeader . readFile -- | Write lines with a header. writeTabbedListsWithHeader :: (WithHeader a b, Listable b c, Stringy c) => FilePath -- ^ The file path. -> a -- ^ The value. -> IO () -- ^ The action for writing the value. writeTabbedListsWithHeader = (. toTabbedListsWithHeader) . writeFile -- | Convert from tabbed lines with a header. fromTransposedTabbedListsWithHeader :: (WithHeader a b, Listable b c, Stringy c) => String -- ^ The tabbed lines. -> a -- ^ The value. fromTransposedTabbedListsWithHeader = fromStringListsWithHeader . transpose . fromTabbeds -- | Convert to tabbed lines with a header. toTransposedTabbedListsWithHeader :: (WithHeader a b, Listable b c, Stringy c) => a -- ^ The value. -> String -- ^ The tabbed lines. toTransposedTabbedListsWithHeader = toTabbeds . transpose . toStringListsWithHeader -- | Read tabbed lines with a header. readTransposedTabbedListsWithHeader :: (WithHeader a b, Listable b c, Stringy c) => FilePath -- ^ The file path. -> IO a -- ^ Action for reading the value. readTransposedTabbedListsWithHeader = fmap fromTransposedTabbedListsWithHeader . readFile -- | Write tabbed lines with a header. writeTransposedTabbedListsWithHeader :: (WithHeader a b, Listable b c, Stringy c) => FilePath -- ^ The file path. -> a -- ^ The value. -> IO () -- ^ The action for writing the value. writeTransposedTabbedListsWithHeader = (. toTransposedTabbedListsWithHeader) . writeFile