{-# LANGUAGE DeriveDataTypeable #-} module Hcompta.Account where import Data.Data (Data) import Data.Eq (Eq(..)) import qualified Data.Foldable import qualified Data.List import Data.List.NonEmpty (NonEmpty(..)) import qualified Data.List.NonEmpty as NonEmpty import Data.Maybe (Maybe(..)) import Data.Text (Text) import Data.Typeable (Typeable) import Prelude (($), Integer, Num(..), const) import Text.Show (Show(..)) import qualified Hcompta.Lib.NonEmpty as NonEmpty import Hcompta.Lib.Regex (Regex) import Hcompta.Lib.TreeMap (TreeMap) -- * The 'Account' type -- | An 'Account' is a non-empty list of 'Account_Section'. type Account = Account_Path type Account_Path = NonEmpty Account_Section type Account_Section = Text type Account_Tree x = TreeMap Account_Section x -- | Return the 'Account' formed by the given 'Account_Section' and 'Account_Section's. account :: Account_Section -> [Account_Section] -> Account account = (:|) -- | Return the number of 'Account_Section's in the given 'Account'. depth :: Account -> Integer depth = Data.Foldable.foldl' (\d -> const $ d + 1) 0 -- | Return the given 'Account' without its last 'Account_Section' if any. ascending :: Account -> Maybe Account ascending = NonEmpty.ascending -- | Apply the given function to all the prefixes -- of the given 'Account' (including itself). foldr :: Account -> (Account -> a -> a) -> a -> a foldr (n0:|n0s) = go [] n0s where go :: [Account_Section] -> [Account_Section] -> (Account -> a -> a) -> a -> a go s [] f acc = f (n0:|s) acc go s (n:ns) f acc = go ((Data.List.++) s [n]) ns f (f (n0:|s) acc) -- | Return an 'Account' from the given list. from_List :: [Account_Section] -> Account from_List = NonEmpty.fromList -- * The 'Joker' type type Joker = [Joker_Section] data Joker_Section = Joker_Any | Joker_Section Account_Section deriving (Data, Eq, Show, Typeable) -- * Type 'Pattern' data Pattern = Pattern_Exact Account | Pattern_Joker Joker | Pattern_Regex Regex deriving (Show, Typeable)