{-# LANGUAGE OverloadedStrings #-}

{-
     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.Concept (
 Concept (..),
 lecticC
) where


import qualified Data.HashSet         as Set
import           Data.List            (sort)

import           Data.Fca.CElem
import           Data.Fca.SimpleTypes (G, M)

data Concept o a = Concept { cG :: G o,
                             cM :: M a }
                   deriving (Eq, Show)

instance (CElem o, CElem a) => Ord (Concept o a) where
  compare = lecticC

lecticC :: (Ord o) => Concept o a -> Concept o a -> Ordering
lecticC c1 c2 =
  lecticG (cG c1) (cG c2)

-- Note here we go until we hit the first different element
compareG :: (Eq o, Ord o) => [o] -> [o] -> Ordering
compareG [] [] = EQ
compareG [] _  = LT
compareG _  [] = GT
compareG (g1:gs1) (g2:gs2) =
  if g1 == g2
     then compareG gs1 gs2
     else if g2 < g1 -- A is smaller than B if the first smallest different element is in B!!
             then LT
             else GT

lecticG :: (Ord o) => G o -> G o -> Ordering
lecticG c1 c2 =
  let o1 = sortG c1
      o2 = sortG c2
  in compareG o1 o2
  where
    sortG = sort . Set.toList