{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
module Swish.RDF.Datatype.XSD.Decimal
( rdfDatatypeXsdDecimal
, rdfDatatypeValXsdDecimal
, typeNameXsdDecimal, namespaceXsdDecimal
, axiomsXsdDecimal, rulesXsdDecimal
)
where
import Swish.Datatype
( Datatype(..)
, DatatypeVal(..)
, DatatypeRel(..), DatatypeRelPr
, altArgs
, UnaryFnTable, unaryFnApp
, BinaryFnTable, binaryFnApp
, DatatypeMod(..)
, makeVmod11inv, makeVmod11
, makeVmod21inv, makeVmod21
, makeVmod20
)
import Swish.Namespace (Namespace, ScopedName)
import Swish.Namespace (namespaceToBuilder, makeNSScopedName)
import Swish.QName (LName)
import Swish.Ruleset (makeRuleset)
import Swish.RDF.Datatype (RDFDatatype, RDFDatatypeVal, RDFDatatypeMod)
import Swish.RDF.Datatype (makeRdfDtOpenVarBindingModifiers)
import Swish.RDF.Datatype.XSD.MapDecimal (mapXsdDecimal)
import Swish.RDF.Ruleset (RDFFormula, RDFRule, RDFRuleset)
import Swish.RDF.Ruleset (makeRDFGraphFromN3Builder, makeRDFFormula)
import Swish.RDF.ClassRestrictionRule (makeRDFDatatypeRestrictionRules)
import Swish.RDF.Vocabulary
( namespaceRDF
, namespaceRDFS
, namespaceRDFD
, namespaceXSD
, namespaceXsdType
)
#if (!defined(__GLASGOW_HASKELL__)) || (__GLASGOW_HASKELL__ < 710)
import Data.Monoid (Monoid(..))
#endif
import qualified Data.Text.Lazy.Builder as B
nameXsdDecimal :: LName
nameXsdDecimal :: LName
nameXsdDecimal = LName
"decimal"
typeNameXsdDecimal :: ScopedName
typeNameXsdDecimal :: ScopedName
typeNameXsdDecimal = Namespace -> LName -> ScopedName
makeNSScopedName Namespace
namespaceXSD LName
nameXsdDecimal
namespaceXsdDecimal :: Namespace
namespaceXsdDecimal :: Namespace
namespaceXsdDecimal = LName -> Namespace
namespaceXsdType LName
nameXsdDecimal
rdfDatatypeXsdDecimal :: RDFDatatype
rdfDatatypeXsdDecimal :: RDFDatatype
rdfDatatypeXsdDecimal = DatatypeVal RDFGraph Double RDFLabel RDFLabel -> RDFDatatype
forall ex lb vn vt. DatatypeVal ex vt lb vn -> Datatype ex lb vn
Datatype DatatypeVal RDFGraph Double RDFLabel RDFLabel
rdfDatatypeValXsdDecimal
rdfDatatypeValXsdDecimal :: RDFDatatypeVal Double
rdfDatatypeValXsdDecimal :: DatatypeVal RDFGraph Double RDFLabel RDFLabel
rdfDatatypeValXsdDecimal = DatatypeVal :: forall ex vt lb vn.
ScopedName
-> Ruleset ex
-> (ex -> [Rule ex])
-> [OpenVarBindingModify lb vn]
-> DatatypeMap vt
-> [DatatypeRel vt]
-> [DatatypeMod vt lb vn]
-> DatatypeVal ex vt lb vn
DatatypeVal
{ tvalName :: ScopedName
tvalName = ScopedName
typeNameXsdDecimal
, tvalRules :: Ruleset RDFGraph
tvalRules = Ruleset RDFGraph
rdfRulesetXsdDecimal
, tvalMkRules :: RDFGraph -> [Rule RDFGraph]
tvalMkRules = DatatypeVal RDFGraph Double RDFLabel RDFLabel
-> RDFGraph -> [Rule RDFGraph]
forall vt. RDFDatatypeVal vt -> RDFGraph -> [Rule RDFGraph]
makeRDFDatatypeRestrictionRules DatatypeVal RDFGraph Double RDFLabel RDFLabel
rdfDatatypeValXsdDecimal
, tvalMkMods :: [OpenVarBindingModify RDFLabel RDFLabel]
tvalMkMods = DatatypeVal RDFGraph Double RDFLabel RDFLabel
-> [OpenVarBindingModify RDFLabel RDFLabel]
forall vt.
RDFDatatypeVal vt -> [OpenVarBindingModify RDFLabel RDFLabel]
makeRdfDtOpenVarBindingModifiers DatatypeVal RDFGraph Double RDFLabel RDFLabel
rdfDatatypeValXsdDecimal
, tvalMap :: DatatypeMap Double
tvalMap = DatatypeMap Double
mapXsdDecimal
, tvalRel :: [DatatypeRel Double]
tvalRel = [DatatypeRel Double]
relXsdDecimal
, tvalMod :: [DatatypeMod Double RDFLabel RDFLabel]
tvalMod = [DatatypeMod Double RDFLabel RDFLabel]
modXsdDecimal
}
relXsdDecimal :: [DatatypeRel Double]
relXsdDecimal :: [DatatypeRel Double]
relXsdDecimal =
[ DatatypeRel Double
relXsdDecimalAbs
, DatatypeRel Double
relXsdDecimalNeg
, DatatypeRel Double
relXsdDecimalSum
, DatatypeRel Double
relXsdDecimalDiff
, DatatypeRel Double
relXsdDecimalProd
, DatatypeRel Double
relXsdDecimalPower
, DatatypeRel Double
relXsdDecimalEq
, DatatypeRel Double
relXsdDecimalNe
, DatatypeRel Double
relXsdDecimalLt
, DatatypeRel Double
relXsdDecimalLe
, DatatypeRel Double
relXsdDecimalGt
, DatatypeRel Double
relXsdDecimalGe
]
mkDecRel2 ::
LName -> DatatypeRelPr Double -> UnaryFnTable Double
-> DatatypeRel Double
mkDecRel2 :: LName
-> DatatypeRelPr Double
-> UnaryFnTable Double
-> DatatypeRel Double
mkDecRel2 LName
nam DatatypeRelPr Double
pr UnaryFnTable Double
fns = DatatypeRel :: forall vt. ScopedName -> DatatypeRelFn vt -> DatatypeRel vt
DatatypeRel
{ dtRelName :: ScopedName
dtRelName = Namespace -> LName -> ScopedName
makeNSScopedName Namespace
namespaceXsdDecimal LName
nam
, dtRelFunc :: DatatypeRelFn Double
dtRelFunc = DatatypeRelPr Double
-> UnaryFnTable Double
-> ((Double -> Bool)
-> UnaryFnDescr Double -> [Maybe Double] -> Maybe [Double])
-> DatatypeRelFn Double
forall vt b.
Eq vt =>
DatatypeRelPr vt
-> [(vt -> Bool, [b])]
-> ((vt -> Bool) -> b -> [Maybe vt] -> Maybe [vt])
-> DatatypeRelFn vt
altArgs DatatypeRelPr Double
pr UnaryFnTable Double
fns (Double -> Bool)
-> UnaryFnDescr Double -> [Maybe Double] -> Maybe [Double]
forall a. UnaryFnApply a
unaryFnApp
}
mkDecRel3 ::
LName -> DatatypeRelPr Double -> BinaryFnTable Double
-> DatatypeRel Double
mkDecRel3 :: LName
-> DatatypeRelPr Double
-> BinaryFnTable Double
-> DatatypeRel Double
mkDecRel3 LName
nam DatatypeRelPr Double
pr BinaryFnTable Double
fns = DatatypeRel :: forall vt. ScopedName -> DatatypeRelFn vt -> DatatypeRel vt
DatatypeRel
{ dtRelName :: ScopedName
dtRelName = Namespace -> LName -> ScopedName
makeNSScopedName Namespace
namespaceXsdDecimal LName
nam
, dtRelFunc :: DatatypeRelFn Double
dtRelFunc = DatatypeRelPr Double
-> BinaryFnTable Double
-> ((Double -> Bool)
-> BinaryFnDescr Double -> [Maybe Double] -> Maybe [Double])
-> DatatypeRelFn Double
forall vt b.
Eq vt =>
DatatypeRelPr vt
-> [(vt -> Bool, [b])]
-> ((vt -> Bool) -> b -> [Maybe vt] -> Maybe [vt])
-> DatatypeRelFn vt
altArgs DatatypeRelPr Double
pr BinaryFnTable Double
fns (Double -> Bool)
-> BinaryFnDescr Double -> [Maybe Double] -> Maybe [Double]
forall a. BinaryFnApply a
binaryFnApp
}
relXsdDecimalAbs :: DatatypeRel Double
relXsdDecimalAbs :: DatatypeRel Double
relXsdDecimalAbs = LName
-> DatatypeRelPr Double
-> UnaryFnTable Double
-> DatatypeRel Double
mkDecRel2 LName
"abs" (Bool -> DatatypeRelPr Double
forall a b. a -> b -> a
const Bool
True)
[ ( (Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
>=Double
0), [ (Double -> Double
forall a. Num a => a -> a
abs,Int
1) ] )
, ( Bool -> Double -> Bool
forall a b. a -> b -> a
const Bool
True, [ (Double -> Double
forall a. a -> a
id,Int
0), (Double -> Double
forall a. Num a => a -> a
negate,Int
0) ] )
]
relXsdDecimalNeg :: DatatypeRel Double
relXsdDecimalNeg :: DatatypeRel Double
relXsdDecimalNeg = LName
-> DatatypeRelPr Double
-> UnaryFnTable Double
-> DatatypeRel Double
mkDecRel2 LName
"neg" (Bool -> DatatypeRelPr Double
forall a b. a -> b -> a
const Bool
True)
[ ( Bool -> Double -> Bool
forall a b. a -> b -> a
const Bool
True, [ (Double -> Double
forall a. Num a => a -> a
negate,Int
1) ] )
, ( Bool -> Double -> Bool
forall a b. a -> b -> a
const Bool
True, [ (Double -> Double
forall a. Num a => a -> a
negate,Int
0) ] )
]
relXsdDecimalSum :: DatatypeRel Double
relXsdDecimalSum :: DatatypeRel Double
relXsdDecimalSum = LName
-> DatatypeRelPr Double
-> BinaryFnTable Double
-> DatatypeRel Double
mkDecRel3 LName
"sum" (Bool -> DatatypeRelPr Double
forall a b. a -> b -> a
const Bool
True)
[ ( Bool -> Double -> Bool
forall a b. a -> b -> a
const Bool
True, [ (Double -> Double -> Double
forall a. Num a => a -> a -> a
(+),Int
1,Int
2) ] )
, ( Bool -> Double -> Bool
forall a b. a -> b -> a
const Bool
True, [ ((-),Int
0,Int
2) ] )
, ( Bool -> Double -> Bool
forall a b. a -> b -> a
const Bool
True, [ ((-),Int
0,Int
1) ] )
]
relXsdDecimalDiff :: DatatypeRel Double
relXsdDecimalDiff :: DatatypeRel Double
relXsdDecimalDiff = LName
-> DatatypeRelPr Double
-> BinaryFnTable Double
-> DatatypeRel Double
mkDecRel3 LName
"diff" (Bool -> DatatypeRelPr Double
forall a b. a -> b -> a
const Bool
True)
[ ( Bool -> Double -> Bool
forall a b. a -> b -> a
const Bool
True, [ ((-),Int
1,Int
2) ] )
, ( Bool -> Double -> Bool
forall a b. a -> b -> a
const Bool
True, [ (Double -> Double -> Double
forall a. Num a => a -> a -> a
(+),Int
0,Int
2) ] )
, ( Bool -> Double -> Bool
forall a b. a -> b -> a
const Bool
True, [ ((-),Int
1,Int
0) ] )
]
relXsdDecimalProd :: DatatypeRel Double
relXsdDecimalProd :: DatatypeRel Double
relXsdDecimalProd = LName
-> DatatypeRelPr Double
-> BinaryFnTable Double
-> DatatypeRel Double
mkDecRel3 LName
"prod" (Bool -> DatatypeRelPr Double
forall a b. a -> b -> a
const Bool
True)
[ ( Bool -> Double -> Bool
forall a b. a -> b -> a
const Bool
True, [ (Double -> Double -> Double
forall a. Num a => a -> a -> a
(*),Int
1,Int
2) ] )
, ( Bool -> Double -> Bool
forall a b. a -> b -> a
const Bool
True, [ (Double -> Double -> Double
forall a. Fractional a => a -> a -> a
(/),Int
0,Int
2) ] )
, ( Bool -> Double -> Bool
forall a b. a -> b -> a
const Bool
True, [ (Double -> Double -> Double
forall a. Fractional a => a -> a -> a
(/),Int
0,Int
1) ] )
]
relXsdDecimalPower :: DatatypeRel Double
relXsdDecimalPower :: DatatypeRel Double
relXsdDecimalPower = LName
-> DatatypeRelPr Double
-> BinaryFnTable Double
-> DatatypeRel Double
mkDecRel3 LName
"power" (Bool -> DatatypeRelPr Double
forall a b. a -> b -> a
const Bool
True)
[ ( Bool -> Double -> Bool
forall a b. a -> b -> a
const Bool
True, [ (Double -> Double -> Double
forall a. Floating a => a -> a -> a
(**),Int
1,Int
2) ] )
, ( Bool -> Double -> Bool
forall a b. a -> b -> a
const Bool
True, [ ] )
, ( (Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
>=Double
0), [ ] )
]
liftL2 :: (a->a->Bool) -> ([a]->a) -> ([a]->a) -> [a] -> Bool
liftL2 :: (a -> a -> Bool) -> ([a] -> a) -> ([a] -> a) -> [a] -> Bool
liftL2 a -> a -> Bool
p [a] -> a
i1 [a] -> a
i2 [a]
as = a -> a -> Bool
p ([a] -> a
i1 [a]
as) ([a] -> a
i2 [a]
as)
lcomp :: (a->a->Bool) -> [a] -> Bool
lcomp :: (a -> a -> Bool) -> [a] -> Bool
lcomp a -> a -> Bool
p = (a -> a -> Bool) -> ([a] -> a) -> ([a] -> a) -> [a] -> Bool
forall a.
(a -> a -> Bool) -> ([a] -> a) -> ([a] -> a) -> [a] -> Bool
liftL2 a -> a -> Bool
p [a] -> a
forall a. [a] -> a
head ([a] -> a
forall a. [a] -> a
head ([a] -> a) -> ([a] -> [a]) -> [a] -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [a] -> [a]
forall a. [a] -> [a]
tail)
relXsdDecimalEq :: DatatypeRel Double
relXsdDecimalEq :: DatatypeRel Double
relXsdDecimalEq = LName
-> DatatypeRelPr Double
-> UnaryFnTable Double
-> DatatypeRel Double
mkDecRel2 LName
"eq" ((Double -> Double -> Bool) -> DatatypeRelPr Double
forall a. (a -> a -> Bool) -> [a] -> Bool
lcomp Double -> Double -> Bool
forall a. Eq a => a -> a -> Bool
(==))
( (Double -> Bool, [UnaryFnDescr Double]) -> UnaryFnTable Double
forall a. a -> [a]
repeat (Bool -> Double -> Bool
forall a b. a -> b -> a
const Bool
True, []) )
relXsdDecimalNe :: DatatypeRel Double
relXsdDecimalNe :: DatatypeRel Double
relXsdDecimalNe = LName
-> DatatypeRelPr Double
-> UnaryFnTable Double
-> DatatypeRel Double
mkDecRel2 LName
"ne" ((Double -> Double -> Bool) -> DatatypeRelPr Double
forall a. (a -> a -> Bool) -> [a] -> Bool
lcomp Double -> Double -> Bool
forall a. Eq a => a -> a -> Bool
(/=))
( (Double -> Bool, [UnaryFnDescr Double]) -> UnaryFnTable Double
forall a. a -> [a]
repeat (Bool -> Double -> Bool
forall a b. a -> b -> a
const Bool
True, []) )
relXsdDecimalLt :: DatatypeRel Double
relXsdDecimalLt :: DatatypeRel Double
relXsdDecimalLt = LName
-> DatatypeRelPr Double
-> UnaryFnTable Double
-> DatatypeRel Double
mkDecRel2 LName
"lt" ((Double -> Double -> Bool) -> DatatypeRelPr Double
forall a. (a -> a -> Bool) -> [a] -> Bool
lcomp Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
(<))
( (Double -> Bool, [UnaryFnDescr Double]) -> UnaryFnTable Double
forall a. a -> [a]
repeat (Bool -> Double -> Bool
forall a b. a -> b -> a
const Bool
True, []) )
relXsdDecimalLe :: DatatypeRel Double
relXsdDecimalLe :: DatatypeRel Double
relXsdDecimalLe = LName
-> DatatypeRelPr Double
-> UnaryFnTable Double
-> DatatypeRel Double
mkDecRel2 LName
"le" ((Double -> Double -> Bool) -> DatatypeRelPr Double
forall a. (a -> a -> Bool) -> [a] -> Bool
lcomp Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
(<=))
( (Double -> Bool, [UnaryFnDescr Double]) -> UnaryFnTable Double
forall a. a -> [a]
repeat (Bool -> Double -> Bool
forall a b. a -> b -> a
const Bool
True, []) )
relXsdDecimalGt :: DatatypeRel Double
relXsdDecimalGt :: DatatypeRel Double
relXsdDecimalGt = LName
-> DatatypeRelPr Double
-> UnaryFnTable Double
-> DatatypeRel Double
mkDecRel2 LName
"gt" ((Double -> Double -> Bool) -> DatatypeRelPr Double
forall a. (a -> a -> Bool) -> [a] -> Bool
lcomp Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
(>))
( (Double -> Bool, [UnaryFnDescr Double]) -> UnaryFnTable Double
forall a. a -> [a]
repeat (Bool -> Double -> Bool
forall a b. a -> b -> a
const Bool
True, []) )
relXsdDecimalGe :: DatatypeRel Double
relXsdDecimalGe :: DatatypeRel Double
relXsdDecimalGe = LName
-> DatatypeRelPr Double
-> UnaryFnTable Double
-> DatatypeRel Double
mkDecRel2 LName
"ge" ((Double -> Double -> Bool) -> DatatypeRelPr Double
forall a. (a -> a -> Bool) -> [a] -> Bool
lcomp Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
(>=))
( (Double -> Bool, [UnaryFnDescr Double]) -> UnaryFnTable Double
forall a. a -> [a]
repeat (Bool -> Double -> Bool
forall a b. a -> b -> a
const Bool
True, []) )
modXsdDecimal :: [RDFDatatypeMod Double]
modXsdDecimal :: [DatatypeMod Double RDFLabel RDFLabel]
modXsdDecimal =
[ DatatypeMod Double RDFLabel RDFLabel
modXsdDecimalAbs
, DatatypeMod Double RDFLabel RDFLabel
modXsdDecimalNeg
, DatatypeMod Double RDFLabel RDFLabel
modXsdDecimalSum
, DatatypeMod Double RDFLabel RDFLabel
modXsdDecimalDiff
, DatatypeMod Double RDFLabel RDFLabel
modXsdDecimalProd
, DatatypeMod Double RDFLabel RDFLabel
modXsdDecimalPower
, DatatypeMod Double RDFLabel RDFLabel
modXsdDecimalEq
, DatatypeMod Double RDFLabel RDFLabel
modXsdDecimalNe
, DatatypeMod Double RDFLabel RDFLabel
modXsdDecimalLt
, DatatypeMod Double RDFLabel RDFLabel
modXsdDecimalLe
, DatatypeMod Double RDFLabel RDFLabel
modXsdDecimalGt
, DatatypeMod Double RDFLabel RDFLabel
modXsdDecimalGe
]
modXsdDecimalAbs :: RDFDatatypeMod Double
modXsdDecimalAbs :: DatatypeMod Double RDFLabel RDFLabel
modXsdDecimalAbs = DatatypeMod :: forall vt lb vn.
ScopedName
-> [ModifierFn vt] -> ApplyModifier lb vn -> DatatypeMod vt lb vn
DatatypeMod
{ dmName :: ScopedName
dmName = Namespace -> LName -> ScopedName
makeNSScopedName Namespace
namespaceXsdDecimal LName
"abs"
, dmModf :: [ModifierFn Double]
dmModf = [ ModifierFn Double
forall a. (Eq a, Num a) => [a] -> [a]
f0, ModifierFn Double
forall a. Num a => [a] -> [a]
f1 ]
, dmAppf :: ApplyModifier RDFLabel RDFLabel
dmAppf = ApplyModifier RDFLabel RDFLabel
forall lb vn. (Ord lb, Ord vn) => ApplyModifier lb vn
makeVmod11
}
where
f0 :: [a] -> [a]
f0 vs :: [a]
vs@[a
v1,a
v2] = if a
v1 a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a -> a
forall a. Num a => a -> a
abs a
v2 then [a]
vs else []
f0 [a]
_ = []
f1 :: [a] -> [a]
f1 [a
v2] = [a -> a
forall a. Num a => a -> a
abs a
v2]
f1 [a]
_ = []
modXsdDecimalNeg :: RDFDatatypeMod Double
modXsdDecimalNeg :: DatatypeMod Double RDFLabel RDFLabel
modXsdDecimalNeg = DatatypeMod :: forall vt lb vn.
ScopedName
-> [ModifierFn vt] -> ApplyModifier lb vn -> DatatypeMod vt lb vn
DatatypeMod
{ dmName :: ScopedName
dmName = Namespace -> LName -> ScopedName
makeNSScopedName Namespace
namespaceXsdDecimal LName
"neg"
, dmModf :: [ModifierFn Double]
dmModf = [ ModifierFn Double
forall a. (Eq a, Num a) => [a] -> [a]
f0, ModifierFn Double
forall a. Num a => [a] -> [a]
f1, ModifierFn Double
forall a. Num a => [a] -> [a]
f1 ]
, dmAppf :: ApplyModifier RDFLabel RDFLabel
dmAppf = ApplyModifier RDFLabel RDFLabel
forall lb vn. (Ord lb, Ord vn) => ApplyModifier lb vn
makeVmod11inv
}
where
f0 :: [a] -> [a]
f0 vs :: [a]
vs@[a
v1,a
v2] = if a
v1 a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a -> a
forall a. Num a => a -> a
negate a
v2 then [a]
vs else []
f0 [a]
_ = []
f1 :: [a] -> [a]
f1 [a
vi] = [-a
vi]
f1 [a]
_ = []
modXsdDecimalSum :: RDFDatatypeMod Double
modXsdDecimalSum :: DatatypeMod Double RDFLabel RDFLabel
modXsdDecimalSum = DatatypeMod :: forall vt lb vn.
ScopedName
-> [ModifierFn vt] -> ApplyModifier lb vn -> DatatypeMod vt lb vn
DatatypeMod
{ dmName :: ScopedName
dmName = Namespace -> LName -> ScopedName
makeNSScopedName Namespace
namespaceXsdDecimal LName
"sum"
, dmModf :: [ModifierFn Double]
dmModf = [ ModifierFn Double
forall a. (Eq a, Num a) => [a] -> [a]
f0, ModifierFn Double
forall a. Num a => [a] -> [a]
f1, ModifierFn Double
forall a. Num a => [a] -> [a]
f2, ModifierFn Double
forall a. Num a => [a] -> [a]
f2 ]
, dmAppf :: ApplyModifier RDFLabel RDFLabel
dmAppf = ApplyModifier RDFLabel RDFLabel
forall lb vn. (Ord lb, Ord vn) => ApplyModifier lb vn
makeVmod21inv
}
where
f0 :: [a] -> [a]
f0 vs :: [a]
vs@[a
v1,a
v2,a
v3] = if a
v1 a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
v2a -> a -> a
forall a. Num a => a -> a -> a
+a
v3 then [a]
vs else []
f0 [a]
_ = []
f1 :: [a] -> [a]
f1 [a
v2,a
v3] = [a
v2a -> a -> a
forall a. Num a => a -> a -> a
+a
v3]
f1 [a]
_ = []
f2 :: [a] -> [a]
f2 [a
v1,a
vi] = [a
v1a -> a -> a
forall a. Num a => a -> a -> a
-a
vi]
f2 [a]
_ = []
modXsdDecimalDiff :: RDFDatatypeMod Double
modXsdDecimalDiff :: DatatypeMod Double RDFLabel RDFLabel
modXsdDecimalDiff = DatatypeMod :: forall vt lb vn.
ScopedName
-> [ModifierFn vt] -> ApplyModifier lb vn -> DatatypeMod vt lb vn
DatatypeMod
{ dmName :: ScopedName
dmName = Namespace -> LName -> ScopedName
makeNSScopedName Namespace
namespaceXsdDecimal LName
"diff"
, dmModf :: [ModifierFn Double]
dmModf = [ ModifierFn Double
forall a. (Eq a, Num a) => [a] -> [a]
f0, ModifierFn Double
forall a. Num a => [a] -> [a]
f1, ModifierFn Double
forall a. Num a => [a] -> [a]
f2, ModifierFn Double
forall a. Num a => [a] -> [a]
f3 ]
, dmAppf :: ApplyModifier RDFLabel RDFLabel
dmAppf = ApplyModifier RDFLabel RDFLabel
forall lb vn. (Ord lb, Ord vn) => ApplyModifier lb vn
makeVmod21inv
}
where
f0 :: [a] -> [a]
f0 vs :: [a]
vs@[a
v1,a
v2,a
v3] = if a
v1 a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
v2a -> a -> a
forall a. Num a => a -> a -> a
-a
v3 then [a]
vs else []
f0 [a]
_ = []
f1 :: [a] -> [a]
f1 [a
v2,a
v3] = [a
v2a -> a -> a
forall a. Num a => a -> a -> a
-a
v3]
f1 [a]
_ = []
f2 :: [a] -> [a]
f2 [a
v1,a
v3] = [a
v1a -> a -> a
forall a. Num a => a -> a -> a
+a
v3]
f2 [a]
_ = []
f3 :: [a] -> [a]
f3 [a
v1,a
v2] = [a
v2a -> a -> a
forall a. Num a => a -> a -> a
-a
v1]
f3 [a]
_ = []
modXsdDecimalProd :: RDFDatatypeMod Double
modXsdDecimalProd :: DatatypeMod Double RDFLabel RDFLabel
modXsdDecimalProd = DatatypeMod :: forall vt lb vn.
ScopedName
-> [ModifierFn vt] -> ApplyModifier lb vn -> DatatypeMod vt lb vn
DatatypeMod
{ dmName :: ScopedName
dmName = Namespace -> LName -> ScopedName
makeNSScopedName Namespace
namespaceXsdDecimal LName
"prod"
, dmModf :: [ModifierFn Double]
dmModf = [ ModifierFn Double
forall a. (Eq a, Num a) => [a] -> [a]
f0, ModifierFn Double
forall a. Num a => [a] -> [a]
f1, ModifierFn Double
forall a. Fractional a => [a] -> [a]
f2, ModifierFn Double
forall a. Fractional a => [a] -> [a]
f2 ]
, dmAppf :: ApplyModifier RDFLabel RDFLabel
dmAppf = ApplyModifier RDFLabel RDFLabel
forall lb vn. (Ord lb, Ord vn) => ApplyModifier lb vn
makeVmod21inv
}
where
f0 :: [a] -> [a]
f0 vs :: [a]
vs@[a
v1,a
v2,a
v3] = if a
v1 a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
v2a -> a -> a
forall a. Num a => a -> a -> a
*a
v3 then [a]
vs else []
f0 [a]
_ = []
f1 :: [a] -> [a]
f1 [a
v2,a
v3] = [a
v2a -> a -> a
forall a. Num a => a -> a -> a
*a
v3]
f1 [a]
_ = []
f2 :: [a] -> [a]
f2 [a
v1,a
vi] = [a
v1a -> a -> a
forall a. Fractional a => a -> a -> a
/a
vi]
f2 [a]
_ = []
modXsdDecimalPower :: RDFDatatypeMod Double
modXsdDecimalPower :: DatatypeMod Double RDFLabel RDFLabel
modXsdDecimalPower = DatatypeMod :: forall vt lb vn.
ScopedName
-> [ModifierFn vt] -> ApplyModifier lb vn -> DatatypeMod vt lb vn
DatatypeMod
{ dmName :: ScopedName
dmName = Namespace -> LName -> ScopedName
makeNSScopedName Namespace
namespaceXsdDecimal LName
"power"
, dmModf :: [ModifierFn Double]
dmModf = [ ModifierFn Double
f0, ModifierFn Double
f1 ]
, dmAppf :: ApplyModifier RDFLabel RDFLabel
dmAppf = ApplyModifier RDFLabel RDFLabel
forall lb vn. (Ord lb, Ord vn) => ApplyModifier lb vn
makeVmod21
}
where
f0 :: ModifierFn Double
f0 vs :: [Double]
vs@[Double
v1,Double
v2,Double
v3] = if Double
v1 Double -> Double -> Bool
forall a. Eq a => a -> a -> Bool
== (Double
v2Double -> Double -> Double
forall a. Floating a => a -> a -> a
**Double
v3 :: Double) then [Double]
vs else []
f0 [Double]
_ = []
f1 :: ModifierFn Double
f1 [Double
v2,Double
v3] = [Double
v2Double -> Double -> Double
forall a. Floating a => a -> a -> a
**Double
v3 :: Double]
f1 [Double]
_ = []
modXsdDecimalEq, modXsdDecimalNe, modXsdDecimalLt, modXsdDecimalLe, modXsdDecimalGt, modXsdDecimalGe :: RDFDatatypeMod Double
modXsdDecimalEq :: DatatypeMod Double RDFLabel RDFLabel
modXsdDecimalEq = LName
-> (Double -> Double -> Bool)
-> DatatypeMod Double RDFLabel RDFLabel
modXsdDecimalCompare LName
"eq" Double -> Double -> Bool
forall a. Eq a => a -> a -> Bool
(==)
modXsdDecimalNe :: DatatypeMod Double RDFLabel RDFLabel
modXsdDecimalNe = LName
-> (Double -> Double -> Bool)
-> DatatypeMod Double RDFLabel RDFLabel
modXsdDecimalCompare LName
"ne" Double -> Double -> Bool
forall a. Eq a => a -> a -> Bool
(/=)
modXsdDecimalLt :: DatatypeMod Double RDFLabel RDFLabel
modXsdDecimalLt = LName
-> (Double -> Double -> Bool)
-> DatatypeMod Double RDFLabel RDFLabel
modXsdDecimalCompare LName
"lt" Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
(<)
modXsdDecimalLe :: DatatypeMod Double RDFLabel RDFLabel
modXsdDecimalLe = LName
-> (Double -> Double -> Bool)
-> DatatypeMod Double RDFLabel RDFLabel
modXsdDecimalCompare LName
"le" Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
(<=)
modXsdDecimalGt :: DatatypeMod Double RDFLabel RDFLabel
modXsdDecimalGt = LName
-> (Double -> Double -> Bool)
-> DatatypeMod Double RDFLabel RDFLabel
modXsdDecimalCompare LName
"gt" Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
(>)
modXsdDecimalGe :: DatatypeMod Double RDFLabel RDFLabel
modXsdDecimalGe = LName
-> (Double -> Double -> Bool)
-> DatatypeMod Double RDFLabel RDFLabel
modXsdDecimalCompare LName
"ge" Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
(>=)
modXsdDecimalCompare ::
LName -> (Double->Double->Bool) -> RDFDatatypeMod Double
modXsdDecimalCompare :: LName
-> (Double -> Double -> Bool)
-> DatatypeMod Double RDFLabel RDFLabel
modXsdDecimalCompare LName
nam Double -> Double -> Bool
rel = DatatypeMod :: forall vt lb vn.
ScopedName
-> [ModifierFn vt] -> ApplyModifier lb vn -> DatatypeMod vt lb vn
DatatypeMod
{ dmName :: ScopedName
dmName = Namespace -> LName -> ScopedName
makeNSScopedName Namespace
namespaceXsdDecimal LName
nam
, dmModf :: [ModifierFn Double]
dmModf = [ ModifierFn Double
f0 ]
, dmAppf :: ApplyModifier RDFLabel RDFLabel
dmAppf = ApplyModifier RDFLabel RDFLabel
forall lb vn.
(Eq lb, Show lb, Eq vn, Show vn) =>
ApplyModifier lb vn
makeVmod20
}
where
f0 :: ModifierFn Double
f0 vs :: [Double]
vs@[Double
v1,Double
v2] = if Double -> Double -> Bool
rel Double
v1 Double
v2 then [Double]
vs else []
f0 [Double]
_ = []
rdfRulesetXsdDecimal :: RDFRuleset
rdfRulesetXsdDecimal :: Ruleset RDFGraph
rdfRulesetXsdDecimal =
Namespace
-> [Formula RDFGraph] -> [Rule RDFGraph] -> Ruleset RDFGraph
forall ex. Namespace -> [Formula ex] -> [Rule ex] -> Ruleset ex
makeRuleset Namespace
namespaceXsdDecimal [Formula RDFGraph]
axiomsXsdDecimal [Rule RDFGraph]
rulesXsdDecimal
prefixXsdDecimal :: B.Builder
prefixXsdDecimal :: Builder
prefixXsdDecimal =
[Builder] -> Builder
forall a. Monoid a => [a] -> a
mconcat ([Builder] -> Builder) -> [Builder] -> Builder
forall a b. (a -> b) -> a -> b
$ (Namespace -> Builder) -> [Namespace] -> [Builder]
forall a b. (a -> b) -> [a] -> [b]
map Namespace -> Builder
namespaceToBuilder
[ Namespace
namespaceRDF
, Namespace
namespaceRDFS
, Namespace
namespaceRDFD
, Namespace
namespaceXSD
, Namespace
namespaceXsdDecimal
]
mkAxiom :: LName -> B.Builder -> RDFFormula
mkAxiom :: LName -> Builder -> Formula RDFGraph
mkAxiom LName
local Builder
gr =
Namespace -> LName -> Builder -> Formula RDFGraph
makeRDFFormula Namespace
namespaceXsdDecimal LName
local (Builder
prefixXsdDecimal Builder -> Builder -> Builder
forall a. Monoid a => a -> a -> a
`mappend` Builder
gr)
axiomsXsdDecimal :: [RDFFormula]
axiomsXsdDecimal :: [Formula RDFGraph]
axiomsXsdDecimal =
[ LName -> Builder -> Formula RDFGraph
mkAxiom LName
"dt"
Builder
"xsd:decimal rdf:type rdfs:Datatype ."
]
rulesXsdDecimal :: [RDFRule]
rulesXsdDecimal :: [Rule RDFGraph]
rulesXsdDecimal = DatatypeVal RDFGraph Double RDFLabel RDFLabel
-> RDFGraph -> [Rule RDFGraph]
forall vt. RDFDatatypeVal vt -> RDFGraph -> [Rule RDFGraph]
makeRDFDatatypeRestrictionRules DatatypeVal RDFGraph Double RDFLabel RDFLabel
rdfDatatypeValXsdDecimal RDFGraph
gr
where
gr :: RDFGraph
gr = Builder -> RDFGraph
makeRDFGraphFromN3Builder Builder
rulesXsdDecimalBuilder
rulesXsdDecimalBuilder :: B.Builder
rulesXsdDecimalBuilder :: Builder
rulesXsdDecimalBuilder =
[Builder] -> Builder
forall a. Monoid a => [a] -> a
mconcat
[ Builder
prefixXsdDecimal
, Builder
"xsd_decimal:Abs a rdfd:GeneralRestriction ; "
, Builder
" rdfd:onProperties (rdf:_1 rdf:_2) ; "
, Builder
" rdfd:constraint xsd_decimal:abs ; "
, Builder
" rdfd:maxCardinality \"1\"^^xsd:nonNegativeInteger . "
, Builder
"xsd_decimal:Neg a rdfd:GeneralRestriction ; "
, Builder
" rdfd:onProperties (rdf:_1 rdf:_2) ; "
, Builder
" rdfd:constraint xsd_decimal:neg ; "
, Builder
" rdfd:maxCardinality \"1\"^^xsd:nonNegativeInteger . "
, Builder
"xsd_decimal:Sum a rdfd:GeneralRestriction ; "
, Builder
" rdfd:onProperties (rdf:_1 rdf:_2 rdf:_3) ; "
, Builder
" rdfd:constraint xsd_decimal:sum ; "
, Builder
" rdfd:maxCardinality \"1\"^^xsd:nonNegativeInteger . "
, Builder
"xsd_decimal:Diff a rdfd:GeneralRestriction ; "
, Builder
" rdfd:onProperties (rdf:_1 rdf:_2 rdf:_3) ; "
, Builder
" rdfd:constraint xsd_decimal:diff ; "
, Builder
" rdfd:maxCardinality \"1\"^^xsd:nonNegativeInteger . "
, Builder
"xsd_decimal:Prod a rdfd:GeneralRestriction ; "
, Builder
" rdfd:onProperties (rdf:_1 rdf:_2 rdf:_3) ; "
, Builder
" rdfd:constraint xsd_decimal:prod ; "
, Builder
" rdfd:maxCardinality \"1\"^^xsd:nonNegativeInteger . "
, Builder
"xsd_decimal:DivMod a rdfd:GeneralRestriction ; "
, Builder
" rdfd:onProperties (rdf:_1 rdf:_2 rdf:_3 rdf:_4) ; "
, Builder
" rdfd:constraint xsd_decimal:divmod ; "
, Builder
" rdfd:maxCardinality \"1\"^^xsd:nonNegativeInteger . "
, Builder
"xsd_decimal:Power a rdfd:GeneralRestriction ; "
, Builder
" rdfd:onProperties (rdf:_1 rdf:_2 rdf:_3) ; "
, Builder
" rdfd:constraint xsd_decimal:power ; "
, Builder
" rdfd:maxCardinality \"1\"^^xsd:nonNegativeInteger . "
, Builder
"xsd_decimal:Eq a rdfd:GeneralRestriction ; "
, Builder
" rdfd:onProperties (rdf:_1 rdf:_2) ; "
, Builder
" rdfd:constraint xsd_decimal:eq ; "
, Builder
" rdfd:maxCardinality \"1\"^^xsd:nonNegativeInteger . "
, Builder
"xsd_decimal:Ne a rdfd:GeneralRestriction ; "
, Builder
" rdfd:onProperties (rdf:_1 rdf:_2) ; "
, Builder
" rdfd:constraint xsd_decimal:ne ; "
, Builder
" rdfd:maxCardinality \"1\"^^xsd:nonNegativeInteger . "
, Builder
"xsd_decimal:Lt a rdfd:GeneralRestriction ; "
, Builder
" rdfd:onProperties (rdf:_1 rdf:_2) ; "
, Builder
" rdfd:constraint xsd_decimal:lt ; "
, Builder
" rdfd:maxCardinality \"1\"^^xsd:nonNegativeInteger . "
, Builder
"xsd_decimal:Le a rdfd:GeneralRestriction ; "
, Builder
" rdfd:onProperties (rdf:_1 rdf:_2) ; "
, Builder
" rdfd:constraint xsd_decimal:le ; "
, Builder
" rdfd:maxCardinality \"1\"^^xsd:nonNegativeInteger . "
, Builder
"xsd_decimal:Gt a rdfd:GeneralRestriction ; "
, Builder
" rdfd:onProperties (rdf:_1 rdf:_2) ; "
, Builder
" rdfd:constraint xsd_decimal:gt ; "
, Builder
" rdfd:maxCardinality \"1\"^^xsd:nonNegativeInteger . "
, Builder
"xsd_decimal:Ge a rdfd:GeneralRestriction ; "
, Builder
" rdfd:onProperties (rdf:_1 rdf:_2) ; "
, Builder
" rdfd:constraint xsd_decimal:ge ; "
, Builder
" rdfd:maxCardinality \"1\"^^xsd:nonNegativeInteger . "
]