module Text.ProtocolBuffers.Reflections
  ( ProtoName(..),ProtoFName(..),ProtoInfo(..),DescriptorInfo(..),FieldInfo(..),KeyInfo
  , HsDefault(..),SomeRealFloat(..),EnumInfo(..),EnumInfoApp
  , ReflectDescriptor(..),ReflectEnum(..),GetMessageInfo(..)
  , OneofInfo(..)
  , makePNF, toRF, fromRF
  ) where
import Text.ProtocolBuffers.Basic
import Text.ProtocolBuffers.Identifiers
import Data.List(sort)
import qualified Data.Foldable as F(toList)
import Data.Set(Set)
import qualified Data.Set as Set(fromDistinctAscList)
import Data.Generics(Data)
import Data.Typeable(Typeable)
import Data.Map(Map)
makePNF :: ByteString -> [String] -> [String] -> String -> ProtoName
makePNF a bs cs d =
  ProtoName (FIName (Utf8 a))
            (map MName bs)
            (map MName cs)
            (MName d)
data ProtoName = ProtoName { protobufName :: FIName Utf8     
                           , haskellPrefix :: [MName String] 
                           , parentModule :: [MName String]  
                           , baseName :: MName String
                           }
  deriving (Show,Read,Eq,Ord,Data,Typeable)
data ProtoFName = ProtoFName { protobufName' :: FIName Utf8     
                             , haskellPrefix' :: [MName String] 
                             , parentModule' :: [MName String]  
                             , baseName' :: FName String
                             , baseNamePrefix' :: String 
                             }
  deriving (Show,Read,Eq,Ord,Data,Typeable)
data ProtoInfo = ProtoInfo { protoMod :: ProtoName        
                           , protoFilePath :: [FilePath]  
                           , protoSource :: FilePath      
                           , extensionKeys :: Seq KeyInfo 
                           , messages :: [DescriptorInfo] 
                           , enums :: [EnumInfo]          
                           , oneofs :: [OneofInfo]
                           , knownKeyMap :: Map ProtoName (Seq FieldInfo) 
                           }
  deriving (Show,Read,Eq,Ord,Data,Typeable)
data DescriptorInfo = DescriptorInfo { descName :: ProtoName
                                     , descFilePath :: [FilePath]
                                     , isGroup :: Bool
                                     , fields :: Seq FieldInfo
                                     , descOneofs :: Seq OneofInfo 
                                     , keys :: Seq KeyInfo
                                     , extRanges :: [(FieldId,FieldId)]
                                     , knownKeys :: Seq FieldInfo
                                     , storeUnknown :: Bool
                                     , lazyFields :: Bool
                                     , makeLenses :: Bool
                                     }
  deriving (Show,Read,Eq,Ord,Data,Typeable)
data GetMessageInfo = GetMessageInfo { requiredTags :: Set WireTag
                                     , allowedTags :: Set WireTag
                                     }
  deriving (Show,Read,Eq,Ord,Data,Typeable)
type KeyInfo = (ProtoName,FieldInfo) 
data FieldInfo = FieldInfo { fieldName     :: ProtoFName
                           , fieldNumber   :: FieldId
                           , wireTag       :: WireTag          
                           , packedTag     :: Maybe (WireTag,WireTag) 
                           , wireTagLength :: WireSize         
                           , isPacked      :: Bool
                           , isRequired    :: Bool
                           , canRepeat     :: Bool             
                           , mightPack     :: Bool             
                           , typeCode      :: FieldType        
                           , typeName      :: Maybe ProtoName  
                           , hsRawDefault  :: Maybe ByteString 
                           , hsDefault     :: Maybe HsDefault  
                           }
  deriving (Show,Read,Eq,Ord,Data,Typeable)
data HsDefault = HsDef'Bool Bool
               | HsDef'ByteString ByteString
               | HsDef'RealFloat SomeRealFloat
               | HsDef'Integer Integer
               | HsDef'Enum String
  deriving (Show,Read,Eq,Ord,Data,Typeable)
data SomeRealFloat = SRF'Rational Rational | SRF'nan | SRF'ninf | SRF'inf
  deriving (Show,Read,Eq,Ord,Data,Typeable)
toRF :: (RealFloat a, Fractional a) => SomeRealFloat -> a
toRF (SRF'Rational r) = fromRational r
toRF SRF'nan = (0/0)
toRF SRF'ninf = (1/0)
toRF SRF'inf = (1/0)
fromRF :: (RealFloat a, Fractional a) => a -> SomeRealFloat
fromRF x | isNaN x = SRF'nan
         | isInfinite x = if 0 < x then SRF'inf else SRF'ninf
         | otherwise = SRF'Rational (toRational x)
data OneofInfo = OneofInfo { oneofName :: ProtoName
                           , oneofFName :: ProtoFName  
                           , oneofFilePath :: [FilePath]
                           , oneofFields :: Seq (ProtoName,FieldInfo)
                           , oneofMakeLenses :: Bool
                           }
  deriving (Show,Read,Eq,Ord,Data,Typeable)
data EnumInfo = EnumInfo { enumName :: ProtoName
                         , enumFilePath :: [FilePath]
                         , enumValues :: [(EnumCode,String)] 
                         }
  deriving (Show,Read,Eq,Ord,Data,Typeable)
type EnumInfoApp e = [(EnumCode,String,e)]
class ReflectEnum e where
  reflectEnum :: EnumInfoApp e
  reflectEnumInfo :: e -> EnumInfo            
  parentOfEnum :: e -> Maybe DescriptorInfo   
  parentOfEnum _ = Nothing
class ReflectDescriptor m where
  
  
  
  
  getMessageInfo :: m -> GetMessageInfo
  getMessageInfo x = cached
    where cached = makeMessageInfo (reflectDescriptorInfo (undefined `asTypeOf` x))
          makeMessageInfo :: DescriptorInfo -> GetMessageInfo
          makeMessageInfo di = GetMessageInfo { requiredTags = Set.fromDistinctAscList . sort $
                                                  [ wireTag f | f <- F.toList (fields di), isRequired f]
                                              , allowedTags = Set.fromDistinctAscList . sort $
                                                  [ wireTag f | f <- F.toList (fields di)] ++
                                                  [ wireTag f | f <- F.toList (knownKeys di)]
                                              }
  reflectDescriptorInfo :: m -> DescriptorInfo