-----------------------------------------------------------------------------
--
-- Module      :  Data.Relational
-- Copyright   :  (c) 2015-16 Brian W Bush
-- License     :  MIT
--
-- Maintainer  :  Brian W Bush <consult@brianwbush.info>
-- Stability   :  Experimental
-- Portability :  Portable
--
-- | Tuples and relations.
--
-----------------------------------------------------------------------------


{-# LANGUAGE FlexibleContexts       #-}
{-# LANGUAGE FlexibleInstances      #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE TypeFamilies           #-}
{-# LANGUAGE UndecidableInstances   #-}

{-# OPTIONS_GHC -fno-warn-orphans   #-}


module Data.Relational {-# DEPRECATED "This module will be replaced in a future release." #-} (
-- * Classes
  Tuple(..)
, Relation(..)
) where


import Control.Applicative (liftA2)
import Control.Arrow ((&&&))
import Data.List.Util.Listable (Listable(..), WithHeader(..))
import Data.Maybe (fromMaybe)
import Data.String.Util (Stringy(..))


-- | Class for tuples.
class Tuple t where

  -- | Type for attributes.
  type Attribute t :: *

  -- | Make a tuple.
  makeTuple :: [Attribute t] -> t

  -- | Retrieve attributes.
  attributes :: t -> [Attribute t]

instance (Attribute t ~ a, Tuple t) => Listable t a where 
  fromList = makeTuple
  toList = attributes


-- | Class for relations.
class Tuple t => Relation n t r | r -> t, r -> n where

  -- | Names for tuples.
  names :: r -> [n]

  -- | An empty relation.
  empty :: [n] -> r

  -- | Make a relation.
  makeRelation :: [n] -> [t] -> r

  -- | Retrieve tuples.
  tuples :: r -> [t]

  -- | Lookup an attribute.
  attributeMaybe :: r -> n -> t -> Maybe (Attribute t)

  -- | Lookup an attribute.
  attribute :: r -> n -> t -> Attribute t
  attribute = ((fromMaybe (error "Attribute missing from relation.") .) .) . attributeMaybe

instance (Relation n t r, Stringy n) => WithHeader r t where
  fromHeaderLists = liftA2 makeRelation (fmap fromString . fst) snd
  toHeaderLists = (fmap toString . names) &&& tuples