module Text.HTML5.MetaData.Schema.GovernmentOrganization where
import Text.HTML5.MetaData.Class
import Text.HTML5.MetaData.Type
import Data.Text
import Data.Typeable
import qualified Text.HTML5.MetaData.Schema.Thing
import qualified Text.HTML5.MetaData.Schema.Organization
data GovernmentOrganization = GovernmentOrganization { address :: Address
, aggregateRating :: AggregateRating
, alumni :: Alumni
, areaServed :: AreaServed
, award :: Award
, brand :: Brand
, contactPoint :: ContactPoint
, department :: Department
, dissolutionDate :: DissolutionDate
, duns :: Duns
, email :: Email
, employee :: Employee
, event :: Event
, faxNumber :: FaxNumber
, founder :: Founder
, foundingDate :: FoundingDate
, foundingLocation :: FoundingLocation
, globalLocationNumber :: GlobalLocationNumber
, hasOfferCatalog :: HasOfferCatalog
, hasPOS :: HasPOS
, isicV4 :: IsicV4
, legalName :: LegalName
, location :: Location
, logo :: Logo
, makesOffer :: MakesOffer
, member :: Member
, memberOf :: MemberOf
, naics :: Naics
, numberOfEmployees :: NumberOfEmployees
, owns :: Owns
, parentOrganization :: ParentOrganization
, review :: Review
, seeks :: Seeks
, subOrganization :: SubOrganization
, taxID :: TaxID
, telephone :: Telephone
, vatID :: VatID
, additionalType :: AdditionalType
, alternateName :: AlternateName
, description :: Description
, image :: Image
, mainEntityOfPage :: MainEntityOfPage
, name :: Name
, potentialAction :: PotentialAction
, sameAs :: SameAs
, url :: Url
}
deriving (Show, Read, Eq, Typeable)
instance MetaData GovernmentOrganization where
_label = const "Government Organization"
_comment_plain = const "A governmental organization or agency."
_comment = const "A governmental organization or agency."
_url = const "http://schema.org/GovernmentOrganization"
_ancestors = const [typeOf (undefined :: Text.HTML5.MetaData.Schema.Thing.Thing)
,typeOf (undefined :: Text.HTML5.MetaData.Schema.Organization.Organization)]
_subtypes = const []
_supertypes = const [typeOf (undefined :: Text.HTML5.MetaData.Schema.Organization.Organization)]