{-# LANGUAGE FlexibleContexts      #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-|
Module      : Model
Description : connects the context Lattice with observation frequencies of exemplars using a multiset
Maintainer  : hahn@geoinfo.tuwien.ac.at
Stability   : beta

This module implements the necessary functions to model a concept and the context influence. The concept is represented by several exemplars. For each influencing context the exemplars have different observation frequency. This conncetion is modeled here by a multiset.
-}
module Model where

import           ContextLattice

import           Algebra.Enumerable
import qualified Data.Function      as F
import qualified Data.List          as L
import qualified Data.MultiSet      as Mset

-- | Each experience is formed by a exemplar of type e and a context c this exemplar was observed at.
data Experience c e =
  -- | constructor;  establishes an experience from a context and an exemplar
  Exp c e deriving (Ord, Show, Eq)

-- | All experiences are hold in a multiset
type Experiences c e = Mset.MultiSet (Experience c e)

-- | type synonym for better readability
type Probability = Float

-- | the class defines the necessary functions needed for the context algebra
class (Ord c, Ord e, Show c, Show e)=> InterpretationModel c e where

-- | combines the observation amount of exemplars for one context
createExperiencesForContext :: (Show c,Ord c, Show e,Ord e) =>
 c      -- ^  context in which the experiences were made
 -> [e] -- ^  exemplars which are observed
 -> [Int] -- ^  amount of observations for one exemplar in this context
 -> Experiences c e -- ^  resulting experience type
createExperiencesForContext context exemplars amounts = Mset.unions $zipWith manyfoldExperiences experiencesOnce amounts
 where experiencesOnce = map (Exp context) exemplars

-- | If an experience is made several times the amount can be specified by the @amount@
manyfoldExperiences ::  (Ord c, Show c, Ord e, Show e) =>
 Experience c e  -- ^  experience that is observed several times
 -> Mset.Occur   -- ^  amount of observations of the experience
 -> Experiences c e -- ^ experiences with the given amount and type
manyfoldExperiences exp amount= Mset.insertMany exp amount Mset.empty

-- | calculates the amount of experiences that are present
amountExperiences ::
  Experiences (Context c) e -- ^ experinces to be counted
  -> Int -- ^ amount of experiences
amountExperiences = Mset.size

-- | filters experiences for a context, gets experiences for a finer context,
-- the context c has to be more finer than the context that are included in the experiences
lambda :: ((Enumerable c), Enumerable (Context c),Ord e, Eq c,Ord c) =>
 Context c                      -- ^ context used to filter the experiences
 -> Experiences (Context c) e   -- ^ experiences to filter
 -> Experiences (Context c) e   -- ^ filtered experiences, more finer experiences are returned
lambda context experiences = Mset.unions .
 L.map (\fctx -> (Mset.filter (\(Exp c1 _)-> c1 == fctx ) experiences ) )  $ allfinerContexts
 where allfinerContexts = getFinerContexts context

-- | returns a probability of an exemplar observed in a context for the given experiences
mu ::((Enumerable c), Enumerable (Context c),Ord e,Ord c)=>
 Experience (Context c) e        -- ^ exemplar and context to look for
 -> Experiences (Context c) e    -- ^ experiences that are considered
 -> Probability                       -- ^ probability of the exemplar in this context for the given experiences
mu (Exp context exemplar) experiences = if amountContext==0 then 0
                                                            else amountExemplar /amountContext
  where observationAmounttForContext = Mset.size experiencesForContext
        exemplarOservationAmountForContext = Mset.size $ filterExemplars exemplar experiencesForContext
        experiencesForContext = lambda context experiences
        amountExemplar= fromIntegral exemplarOservationAmountForContext
        amountContext = fromIntegral observationAmounttForContext

-- | returns experiences for the exemplar given in the first argument @e@
-- in quantum mechanics called projector
filterExemplars:: (Ord c, Ord e) =>
 e                   -- ^ exemplar used to filter the experiences
 -> Experiences c e  -- ^ experiences that are filtered
 -> Experiences c e  -- ^ experiences including values for the exemplar e
filterExemplars exemplar = Mset.filter (\(Exp _ actualExemplar)-> exemplar ==actualExemplar)


-- * functions to print and export
-- | returns the observation distribution for the context c, the type e is only used as type parameter
probAllExemplars4Context :: (Ord c, Ord e,Enum e,Bounded e,(Enumerable c), Enumerable (Context c))=>
 Context c  -- ^ context the distribution is made for
 -> e         -- ^ exemplar type, used as type parameter
 -> Experiences (Context c) e -- ^ experiences the distribution is made of
 -> [(e,Probability)] -- ^ returned distribution
probAllExemplars4Context ctx e t=  map (\e ->(e, mu (Exp ctx e) t) ) exemplars
 where exemplars= enumFromTo minBound $ maxBound `asTypeOf` e

-- | returns the most probable exemplar given by the list of tuples of (Exemplar, Probability)
getMostProbableExemplar :: (Ord e)=>
 [(e, Probability)]  -- ^ list of tupels of Exemplars and the probability value
 -> (e, Probability) -- ^ tupel with the highest probability value
getMostProbableExemplar  = L.maximumBy (compare `F.on` snd)

-- | converts the experiences type to a IO()
printExperiences :: (Show e, Show c) =>
 Experiences c e -- ^ experience to convert to IO
 -> IO() -- ^ returned IO()
printExperiences experiences = putStrLn $ Mset.showTreeWith True True experiences


-- * functions for further development of the model
-- | adds the @new@ experience to the given experiences
addExperience :: (Ord c,Ord e) =>
 Experience c e      -- ^  new experience to add
 -> Experiences c e  -- ^  given experiences where to add the new experience
 -> Experiences c e  -- ^  resulting experiences including the new and the given experiences
addExperience = Mset.insert