module Generics.Instant.Functions.Empty (
    Empty(..), empty,
    HasRec(..)
  ) where
import Generics.Instant.Base
import Generics.Instant.Instances ()
class Empty a where
  empty' :: a
instance Empty U where
  empty' = U
  
instance (HasRec a, Empty a, Empty b) => Empty (a :+: b) where
  empty' = if hasRec' (empty' :: a) then R empty' else L empty'
  
instance (Empty a, Empty b) => Empty (a :*: b) where
  empty' = empty' :*: empty'
  
instance (Empty a) => Empty (CEq c p p a) where
  empty' = C empty'
instance (Empty a) => Empty (Var a) where
  empty' = Var empty'
instance (Empty a) => Empty (Rec a) where
  empty' = Rec empty'
instance Empty Int where
  empty' = 0
instance Empty Integer where
  empty' = 0
instance Empty Float where
  empty' = 0
instance Empty Double where
  empty' = 0
instance Empty Char where
  empty' = '\NUL'
  
instance Empty Bool where
  empty' = False
empty :: (Representable a, Empty (Rep a)) => a
empty = to empty'
instance (Empty a) => Empty (Maybe a)       where empty' = empty
instance (Empty a) => Empty [a]             where empty' = empty
instance (Empty a, Empty b) => Empty (a,b)  where empty' = empty
class HasRec a where
  hasRec' :: a -> Bool
  hasRec' _ = False
  
instance HasRec U
instance HasRec (Var a)
instance (HasRec a, HasRec b) => HasRec (a :*: b) where
  hasRec' (a :*: b) = hasRec' a || hasRec' b
  
instance (HasRec a, HasRec b) => HasRec (a :+: b) where
  hasRec' (L x) = hasRec' x
  hasRec' (R x) = hasRec' x
instance (HasRec a) => HasRec (CEq c p q a) where
  hasRec' (C x) = hasRec' x
  
instance HasRec (Rec a) where
  hasRec' _ = True
  
instance HasRec Int
instance HasRec Integer
instance HasRec Float
instance HasRec Double
instance HasRec Char