aboutsummaryrefslogtreecommitdiffhomepage
path: root/core/src/Text/Edifact/Types.hs
diff options
context:
space:
mode:
Diffstat (limited to 'core/src/Text/Edifact/Types.hs')
-rw-r--r--core/src/Text/Edifact/Types.hs124
1 files changed, 124 insertions, 0 deletions
diff --git a/core/src/Text/Edifact/Types.hs b/core/src/Text/Edifact/Types.hs
new file mode 100644
index 0000000..d0bbe0d
--- /dev/null
+++ b/core/src/Text/Edifact/Types.hs
@@ -0,0 +1,124 @@
1{-# LANGUAGE DerivingStrategies #-}
2{-# LANGUAGE GeneralizedNewtypeDeriving #-}
3
4{-|
5 Data types to represent Edifact values.
6
7 See "Text.Edifact.Parsing" to learn how to build parsers and use such parsers.
8 -}
9module Text.Edifact.Types
10 ( -- * Values
11 Value(..)
12 , Primitive(..)
13 , Position(..)
14 -- ** Element codes
15 , MessageCode(..)
16 , GroupCode(..)
17 , SegmentCode(..)
18 , CompositeCode(..)
19 , SimpleCode(..)
20 -- * Syntax
21 , Syntax(..)
22 , defaultSyntax
23 ) where
24
25import Data.Scientific (Scientific)
26import Data.String (IsString (..))
27import Data.Text (Text)
28
29-- | Code for a message.
30--
31-- Content is expected to match this regexp: @[A-Z]{6}@.
32newtype MessageCode = MessageCode { getMessageCode :: String } deriving newtype (Eq, Show, IsString)
33
34-- | Code for a segment group.
35--
36-- It's a code local to the message definition.
37newtype GroupCode = GroupCode { getGroupCode :: String } deriving newtype (Eq, Show, IsString)
38
39-- | Code for a segment.
40--
41-- Content is expected to match this regexp: @[A-Z]{3}@.
42--
43-- Standard segment codes are expected to match this regexp: @UN[A-Z]@.
44newtype SegmentCode = SegmentCode { getSegmentCode :: String } deriving newtype (Eq, Show, IsString)
45
46-- | Code for a composite element.
47--
48-- Content is expected to match this regexp: @C[0-9]{3}@.
49--
50-- It can also be used for standalone composites, frequently in standard segment
51-- definitions. In this case the codes are expected to match this regexp: @S[0-9]{3}@.
52newtype CompositeCode = CompositeCode String deriving newtype (Eq, Show, IsString)
53
54-- | Code for a simple element.
55--
56-- Content is expected to match this regexp: @[0-9]{4}@.
57newtype SimpleCode = SimpleCode String deriving newtype (Eq, Show, IsString)
58
59-- | Annotation of the position of the value relative to the parent value.
60--
61-- Content is expected to match this regexp: @[0-9]{3,4}@.
62--
63-- Example values:
64--
65-- > "010" :: Position
66-- > "0210" :: Position
67--
68-- See 'Text.Edifact.Parsing.position' for how to parse one.
69newtype Position = Position { getPosition :: String } deriving newtype (Eq, Show, IsString)
70
71-- | Representation of a simple component.
72--
73-- When defined by the 'Text.Edifact.Parsing.numeric' combinator, the simple
74-- component will produce a 'Number'.
75--
76-- When parsed by the 'Text.Edifact.Parsing.alphaNumeric' or
77-- 'Text.Edifact.Parsing.alpha' combinators, the simple component will produce a
78-- 'Text.Edifact.Types.String' from the raw textual representation.
79data Primitive = String Text -- ^ Default representation of a simple component.
80 | Number Scientific -- ^ Representation of a numerical simple component.
81 deriving stock (Eq, Show)
82
83-- | String like primitive values can be constructed via overloaded strings.
84-- This is convenient, but might be removed.
85instance IsString Primitive where
86 fromString = String . fromString
87
88-- | Recursive data structure to represent parsed Edifact values.
89data Value = Message MessageCode [(Position, [Value])]
90 | Group GroupCode [(Position, [Value])]
91 | Segment SegmentCode [(Position, Maybe Value)]
92 | Composite CompositeCode [(Position, Maybe Value)]
93 | Simple SimpleCode Primitive
94 deriving stock (Show, Eq)
95
96-- | Defines the special charactors the parser should respect.
97--
98-- This is defined in every payload via the @UNA@ segment (first segment expected).
99data Syntax = Syntax { compositeSeparator :: Char
100 , elementSeparator :: Char
101 , decimalSign :: Char
102 , escape :: Char
103 , segmentSeparator :: Char
104 }
105
106-- | Default value to initialize the parser.
107--
108-- > Syntax { compositeSeparator = ':'
109-- > , elementSeparator = '+'
110-- > , decimalSign = '.'
111-- > , escape = '?'
112-- > , segmentSeparator = '\''
113-- > }
114--
115-- Those default charactors should be considered as recommended values rather
116-- than official default values.
117defaultSyntax :: Syntax
118defaultSyntax =
119 Syntax { compositeSeparator = ':'
120 , elementSeparator = '+'
121 , decimalSign = '.'
122 , escape = '?'
123 , segmentSeparator = '\''
124 }