{-# LANGUAGE TypeOperators          #-}
{-# LANGUAGE FlexibleInstances      #-}
{-# LANGUAGE MultiParamTypeClasses  #-}
{-# LANGUAGE OverlappingInstances   #-}
{-# OPTIONS -fno-warn-orphans       #-}

-----------------------------------------------------------------------------
-- |
-- Module      :  Generics.EMGM.Data.List
-- Copyright   :  (c) 2008 Universiteit Utrecht
-- License     :  BSD3
--
-- Maintainer  :  generics@haskell.org
-- Stability   :  experimental
-- Portability :  non-portable
--
-- Summary: Generic representation and instances for @[a]@.
--
-- This module exports the reusable components of the @[a]@ representation.
-- These include the embedding-projection pair used in a type representation as
-- well as the type representations of @[a]@ for 'Generic', 'Generic2', and
-- 'Generic3'.
--
-- This module also exports the instances for the representation dispatchers
-- 'Rep', 'FRep', 'FRep2', and 'FRep3'.
-----------------------------------------------------------------------------

module Generics.EMGM.Data.List (

  -- * Embedding-projection pair
  epList,

  -- * Representations
  rList,
  rList2,
  rList3
) where

import Generics.EMGM.Common

-----------------------------------------------------------------------------
-- Embedding-projection pair
-----------------------------------------------------------------------------

fromList :: [a] -> Unit :+: (a :*: [a])
fromList []        =  L Unit
fromList (a : as)  =  R (a :*: as)

toList :: Unit :+: (a :*: [a]) -> [a]
toList (L Unit)        =  []
toList (R (a :*: as))  =  a : as

-- | Embedding-projection pair for @[a]@
epList :: EP [a] (Unit :+: (a :*: [a]))
epList = EP fromList toList

-----------------------------------------------------------------------------
-- Representation values
-----------------------------------------------------------------------------

conNil, conCons :: ConDescr
conNil  = ConDescr "[]" 0 [] Nonfix
conCons = ConDescr ":"  2 [] (Infixr 5)

-- | Representation for @[a]@ in 'Generic'
rList :: (Generic g) => g a -> g [a]
rList ra =
  rtype epList
    (rcon conNil runit `rsum` rcon conCons (ra `rprod` rList ra))

-- | Representation for @[a]@ in 'Generic2'
rList2 :: (Generic2 g) => g a b -> g [a] [b]
rList2 ra =
  rtype2 epList epList
    (rcon2 conNil runit2 `rsum2` rcon2 conCons (ra `rprod2` rList2 ra))

-- | Representation for @[a]@ in 'Generic3'
rList3 :: (Generic3 g) => g a b c -> g [a] [b] [c]
rList3 ra =
  rtype3 epList epList epList
    (rcon3 conNil runit3 `rsum3` rcon3 conCons (ra `rprod3` rList3 ra))

-----------------------------------------------------------------------------
-- Instance declarations
-----------------------------------------------------------------------------

instance (Generic g, Rep g a) => Rep g [a] where
  rep = rList rep

instance (Generic g) => FRep g [] where
  frep = rList

instance (Generic2 g) => FRep2 g [] where
  frep2 = rList2

instance (Generic3 g) => FRep3 g [] where
  frep3 = rList3