1 {-# LANGUAGE FlexibleInstances #-}
 
   2 {-# LANGUAGE GeneralizedNewtypeDeriving #-}
 
   3 {-# LANGUAGE OverloadedStrings #-}
 
   4 {-# LANGUAGE Rank2Types #-}
 
   5 {-# LANGUAGE StrictData #-}
 
   6 module RNC.Commoning where
 
   8 import Control.Applicative (Applicative(..), Alternative(..))
 
   9 import Control.Monad (Monad, void)
 
  10 import Data.Default.Class (Default(..))
 
  12 import Data.Function (($), (.))
 
  13 import Data.Functor ((<$>))
 
  14 import Data.Hashable (Hashable)
 
  15 import Data.Maybe (Maybe(..))
 
  17 import Data.Sequence (Seq)
 
  18 import Text.Show (Show)
 
  19 import qualified Data.Text.Lazy as TL
 
  20 import qualified Data.TreeSeq.Strict as TS
 
  21 import qualified Text.Megaparsec as P
 
  23 import Symantic.RNC (Sym_Permutation(..))
 
  24 import qualified Symantic.RNC as RNC
 
  25 import qualified Symantic.XML as XML
 
  30 data Commoning = Commoning
 
  31  { commoning_persons    :: Persons
 
  32  , commoning_opinions   :: Opinions
 
  33  , commoning_groups     :: Groups
 
  34  , commoning_operations :: Operations
 
  35  , commoning_resources  :: Resources
 
  41  , person_fields :: Seq Fields
 
  44 type Persons = [Person]
 
  47 type Group = TS.Tree NodeGroup
 
  48 -- *** Type 'NodeGroup'
 
  49 data NodeGroup = NodeGroup
 
  51  , group_name    :: Maybe Name
 
  52  , group_fields  :: Seq Fields
 
  53  , group_members :: Members
 
  56 type Groups = Seq Group
 
  59 newtype Member = Member
 
  60  { member_person :: Ident
 
  63 type Members = [Member]
 
  66 type Resource = TS.Tree NodeResource
 
  67 -- *** Type 'NodeResource'
 
  68 data NodeResource = NodeResource
 
  69  { resource_name     :: Name
 
  70  , resource_policies :: Policies
 
  72 -- *** Type 'Resources'
 
  73 type Resources = Seq Resource
 
  77  { policy_operation :: Name
 
  79  , policy_toward    :: (Maybe Ident)
 
  80  , policy_rules     :: Rules
 
  82 -- *** Type 'Policies'
 
  83 type Policies = [Policy]
 
  87  { rule_grades     :: Ident
 
  88  , rule_gradeRange :: GradeRange
 
  93 -- *** Type 'GradeRange'
 
  95  = GradeRange_Single Name
 
  98  | GradeRange Name Name
 
 102 type Opinions = [Grades]
 
 107  , grade_abbrev :: Maybe Name
 
 108  , grade_color  :: Maybe Color
 
 113  , grades_name :: Maybe Name
 
 114  , grades_list :: [Grade]
 
 119 -- ** Type 'Operation'
 
 120 type Operation = TS.Tree NodeOperation
 
 121 -- *** Type 'NodeOperation'
 
 122 newtype NodeOperation = NodeOperation
 
 123  { operation_id :: Ident
 
 125 -- *** Type 'Operations'
 
 126 type Operations = Seq Operation
 
 131  , field_value :: TL.Text
 
 134 type Fields = TS.Tree NodeField
 
 135 -- **** Type 'NodeField'
 
 138  | NodeFields { fields_name :: Name }
 
 142 newtype Ident = Ident TL.Text
 
 143  deriving (Eq,Ord,Show,Hashable)
 
 145 newtype Name  = Name  TL.Text
 
 146  deriving (Eq,Ord,Show,Hashable)
 
 148 -- * Class 'Sym_Commoning'
 
 149 xmlns_commoning :: XML.Namespace
 
 150 xmlns_commoning = "http://commonsoft.org/xml/2018/commoning.rnc"
 
 151 element :: RNC.Sym_RNC repr => XML.NCName -> repr a -> repr a
 
 152 element = RNC.element . XML.QName xmlns_commoning
 
 153 attribute :: RNC.Sym_RNC repr => XML.NCName -> repr a -> repr a
 
 154 attribute = RNC.attribute . XML.QName ""
 
 156 class RNC.Sym_RNC repr => Sym_Commoning repr where
 
 157         commoning  :: repr Commoning
 
 158         persons    :: repr Persons
 
 159         person     :: repr Person
 
 160         opinions   :: repr Opinions
 
 161         grades     :: repr Grades
 
 163         fields     :: repr Fields
 
 165         groups     :: repr Groups
 
 167         members    :: repr Members
 
 168         member     :: repr Member
 
 169         operations :: repr Operations
 
 170         operation  :: repr Operation
 
 171         resources  :: repr Resources
 
 172         resource   :: repr Resource
 
 173         policy     :: repr Policy
 
 179         commoning = RNC.rule "commoning" $
 
 180                 element "commoning" $
 
 188         persons = RNC.rule "persons" $
 
 189                 element "persons" $ RNC.many person
 
 190         person  = RNC.rule "person" $
 
 191                 element "person" $ attrs <*> RNC.manySeq fields
 
 196                          <$$> attribute "id" ident
 
 197         opinions = RNC.rule "opinions" $
 
 200         grades = RNC.rule "grades" $
 
 201                 element "grades" $ attrs <*> RNC.many grade
 
 206                          <$$> attribute "id" ident
 
 207                          <|?> (def, Just <$> attribute "name" name)
 
 208         grade = RNC.rule "grade" $
 
 209                 element "grade" $ attrs
 
 214                          <$$> attribute "name" name
 
 215                          <|?> (def, Just <$> attribute "abbrev" name)
 
 216                          <|?> (def, Just <$> attribute "color" color)
 
 217         fields = RNC.rule "fields" $
 
 219                         (TS.Tree <$> attrs <*>) $
 
 221                                 TS.tree0 . NodeField <$> field
 
 227                          <$$> attribute "name" name
 
 228         field = RNC.rule "field" $
 
 229                 element "field" $ attrs <*> RNC.text
 
 234                          <$$> attribute "name" name
 
 235         groups = RNC.rule "groups" $
 
 236                 element "groups" $ RNC.manySeq group
 
 237         group = RNC.rule "group" $
 
 239                         (((TS.Tree <$>) $ attrs <*> RNC.manySeq fields <*> members) <*>) $
 
 245                          <$$> attribute "id" ident
 
 246                          <|?> (def, Just <$> attribute "name" name)
 
 247         members = RNC.rule "members" $ RNC.many member
 
 248         member = RNC.rule "member" $
 
 249                 element "member" $ attrs
 
 254                          <$$> attribute "person" ident
 
 255         operations = RNC.rule "operations" $
 
 256                 element "operations" $ RNC.manySeq operation
 
 257         operation = RNC.rule "operation" $
 
 258                 element "operation" $
 
 259                         (((TS.Tree <$>) $ attrs) <*>) $
 
 260                                 RNC.manySeq operation
 
 265                          <$$> attribute "id" ident
 
 266         resources = RNC.rule "resources" $
 
 267                 element "resources" $ RNC.manySeq resource
 
 268         resource = RNC.rule "resource" $
 
 270                         (((TS.Tree <$>) $ attrs <*> RNC.many policy) <*>) $
 
 276                          <$$> attribute "name" name
 
 277         policy = RNC.rule "policy" $
 
 278                 element "policy" $ attrs
 
 283                          <$$> attribute "operation" name
 
 284                          <||> attribute "by" ident
 
 285                          <|?> (def, Just <$> attribute "toward" ident)
 
 287         rule = RNC.rule "rule" $
 
 288                 element "rule" $ attrs
 
 292                  <|> RNC.try attrsGradeMin
 
 297                          <$$> attribute "grades" ident
 
 298                          <||> (GradeRange_Single <$> attribute "grade" name)
 
 301                         (\gs gMin mgMax -> Rule gs $ case mgMax of
 
 302                                  Nothing -> GradeRange_Min gMin
 
 303                                  Just gMax -> GradeRange gMin gMax)
 
 304                          <$$> attribute "grades" ident
 
 305                          <||> attribute "gradeMin" name
 
 306                          <|?> (def, Just <$> attribute "gradeMax" name)
 
 309                         (\gs mgMin gMax -> Rule gs $ case mgMin of
 
 310                                  Nothing -> GradeRange_Max gMax
 
 311                                  Just gMin -> GradeRange gMin gMax)
 
 312                          <$$> attribute "grades" ident
 
 313                          <|?> (def, Just <$> attribute "gradeMin" name)
 
 314                          <||> attribute "gradeMax" name
 
 316         ident = RNC.rule "ident" $ Ident <$> RNC.text
 
 317         name  = RNC.rule "name" $ Name <$> RNC.text
 
 318         color = RNC.rule "color" $ RNC.text
 
 319 instance Sym_Commoning RNC.NS
 
 320 instance Sym_Commoning RNC.Writer
 
 325  ) => Sym_Commoning (P.Parsec err (XML.XMLs src))
 
 327 -- newtype Forall cl a = Forall { unForall :: forall repr. cl repr => repr a }
 
 328 rnc :: forall repr. Sym_Commoning repr => [repr ()]
 
 330  [ void $ RNC.namespace Nothing xmlns_commoning