{-
     FCA - A generator of a Formal Concept Analysis Lattice
     Copyright (C) 2014  Raymond Racine

     This program is free software: you can redistribute it and/or modify
     it under the terms of the GNU Affero General Public License as
     published by the Free Software Foundation, either version 3 of the
     License, or (at your option) any later version.

     This program 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 Affero General Public License for more details.

     You should have received a copy of the GNU Affero General Public License
     along with this program.  If not, see <http://www.gnu.org/licenses/>.
-}

module Data.Fca.Lattice (
  Lattice,
  Neighborhood (..),
  emptyLattice,
  appendNeighbors
) where

import           Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as Map
import           Data.Monoid

import           Data.Fca.Cid        (Cid (..))

type Lattice = HashMap Cid Neighborhood

data Neighborhood = Neighborhood { upper :: [Cid],
                                   lower :: [Cid] }
                    deriving Show

instance Monoid Neighborhood where
  mempty = emptyNeighborhood
  n1 `mappend` n2 = let Neighborhood u1 l1 = n1
                        Neighborhood u2 l2 = n2
                    in Neighborhood (u1 `mappend` u2) (l1 `mappend` l2)

emptyLattice :: Lattice
emptyLattice = Map.empty

emptyNeighborhood :: Neighborhood
emptyNeighborhood = Neighborhood [] []

appendNeighbors :: Lattice -> Cid -> Neighborhood -> Lattice
appendNeighbors lattice cid neighbors =
  Map.insertWith mappend cid neighbors lattice