aboutsummaryrefslogtreecommitdiffhomepage
path: root/scaffolder/src/Text/Edifact/Scaffolder/Messages
diff options
context:
space:
mode:
Diffstat (limited to 'scaffolder/src/Text/Edifact/Scaffolder/Messages')
-rw-r--r--scaffolder/src/Text/Edifact/Scaffolder/Messages/Dependencies.hs47
-rw-r--r--scaffolder/src/Text/Edifact/Scaffolder/Messages/Elements.hs22
-rw-r--r--scaffolder/src/Text/Edifact/Scaffolder/Messages/Implementation.hs114
-rw-r--r--scaffolder/src/Text/Edifact/Scaffolder/Messages/Specification.hs129
-rw-r--r--scaffolder/src/Text/Edifact/Scaffolder/Messages/Types.hs36
5 files changed, 348 insertions, 0 deletions
diff --git a/scaffolder/src/Text/Edifact/Scaffolder/Messages/Dependencies.hs b/scaffolder/src/Text/Edifact/Scaffolder/Messages/Dependencies.hs
new file mode 100644
index 0000000..fbcc56b
--- /dev/null
+++ b/scaffolder/src/Text/Edifact/Scaffolder/Messages/Dependencies.hs
@@ -0,0 +1,47 @@
1{-# LANGUAGE OverloadedStrings #-}
2
3module Text.Edifact.Scaffolder.Messages.Dependencies
4 ( -- *
5 mkDependenciesHaddock
6 , mkDependenciesImports
7 , mkDependenciesReexports
8 ) where
9
10import Text.Edifact.Scaffolder.Commons
11import Text.Edifact.Scaffolder.Messages.Types
12
13import Control.Monad ((>=>))
14import Data.List (isPrefixOf)
15import Data.List.NonEmpty as NE (nonEmpty, toList)
16import Data.Maybe (mapMaybe)
17
18unlessIsCommon :: SegmentCode -> Maybe SegmentCode
19unlessIsCommon sc@(SegmentCode code) | "U" `isPrefixOf` code = Nothing
20 | otherwise = Just sc
21
22mkDependenciesReexports :: NonEmpty Element -> Scaffolding [Export]
23mkDependenciesReexports = mkSegmentDependencies mkSegmentDependenciesReexports
24
25mkSegmentDependenciesReexports :: NonEmpty SegmentCode -> Scaffolding [Export]
26mkSegmentDependenciesReexports = reexportDependencies fSegmentParserFunction
27
28mkDependenciesImports :: NonEmpty Element -> Scaffolding [ImportGroup]
29mkDependenciesImports = mkSegmentDependencies mkSegmentDependenciesImports
30
31mkSegmentDependencies :: (NonEmpty SegmentCode -> Scaffolding [output])
32 -> (NonEmpty Element -> Scaffolding [output])
33mkSegmentDependencies mk = maybe (pure []) mk . filterSegmentDependencies
34
35filterSegmentDependencies :: NonEmpty Element -> Maybe (NonEmpty SegmentCode)
36filterSegmentDependencies =
37 fmap nub . nonEmpty . mapMaybe (getSegment >=> unlessIsCommon) . NE.toList
38
39mkSegmentDependenciesImports :: NonEmpty SegmentCode -> Scaffolding [ImportGroup]
40mkSegmentDependenciesImports =
41 fmap (pure . singleImport) . importDependencies "Segments" fSegmentParserFunction
42
43mkDependenciesHaddock :: NonEmpty Element -> Scaffolding [Text]
44mkDependenciesHaddock = mkSegmentDependencies mkSegmentDependenciesHaddock
45
46mkSegmentDependenciesHaddock :: NonEmpty SegmentCode -> Scaffolding [Text]
47mkSegmentDependenciesHaddock = haddockDependencies fSegmentParserFunction
diff --git a/scaffolder/src/Text/Edifact/Scaffolder/Messages/Elements.hs b/scaffolder/src/Text/Edifact/Scaffolder/Messages/Elements.hs
new file mode 100644
index 0000000..fb590ad
--- /dev/null
+++ b/scaffolder/src/Text/Edifact/Scaffolder/Messages/Elements.hs
@@ -0,0 +1,22 @@
1module Text.Edifact.Scaffolder.Messages.Elements
2 ( listMessages
3 ) where
4
5import Text.Edifact.Scaffolder.Commons
6
7import Data.Char (toUpper)
8import Text.Parsec (count, eof, lower, string,
9 (<?>))
10import Text.Parsec.String (Parser)
11
12-- | List elements
13listMessages :: Scaffolding [ElementWithDefinition MessageCode]
14listMessages = listElements "messages" messageFilenameParser
15
16messageFilenameParser :: Parser MessageCode
17messageFilenameParser =
18 let mkCode = MessageCode . fmap toUpper
19 in mkCode <$> count 6 lower
20 <* string "_s.txt"
21 <* eof
22 <?> "MessageCode"
diff --git a/scaffolder/src/Text/Edifact/Scaffolder/Messages/Implementation.hs b/scaffolder/src/Text/Edifact/Scaffolder/Messages/Implementation.hs
new file mode 100644
index 0000000..121aa45
--- /dev/null
+++ b/scaffolder/src/Text/Edifact/Scaffolder/Messages/Implementation.hs
@@ -0,0 +1,114 @@
1{-# LANGUAGE OverloadedStrings #-}
2
3module Text.Edifact.Scaffolder.Messages.Implementation
4 ( -- *
5 toImplementation
6 ) where
7
8import Text.Edifact.Scaffolder.Commons
9import Text.Edifact.Scaffolder.Messages.Types
10
11import Control.Monad.State.Strict (State, evalState, gets,
12 modify)
13import Data.List.NonEmpty as NE (NonEmpty (..),
14 fromList, head,
15 toList, (<|))
16import Formatting
17
18toImplementation :: MessageCode -> NonEmpty Dependency -> [Text]
19toImplementation _ =
20 let closeList deps = deps <> [ "]" ]
21 in closeList . render . fmap concat . traverse callDependency . NE.toList
22
23render :: Rendering a -> a
24render r =
25 let initialState = RenderingContext 0 0 :| []
26 in evalState r initialState
27
28type Trail = NonEmpty
29
30data RenderingContext = RenderingContext { listPosition :: Int
31 , indentLevel :: Int
32 }
33
34type Rendering = State (Trail RenderingContext)
35
36callDependency :: Dependency -> Rendering [Text]
37callDependency (Dependency element) = renderElement element
38
39increment :: Rendering ()
40increment =
41 let mapHead f (v :| t) = f v :| t
42 in modify (mapHead (\ ctx -> ctx { listPosition = listPosition ctx + 1 }))
43
44pushIndent :: Rendering ()
45pushIndent =
46 let indentState t@(previous :| _) = RenderingContext 0 (indentLevel previous + 2) <| t
47 in modify indentState
48
49popIndent :: Rendering ()
50popIndent =
51 let pop (_ :| []) = error "Incoherent state: can't unindent anymore (this shouldn't happen)"
52 pop (_ :| up) = NE.fromList up
53 in modify pop
54
55getCurrentIndex :: Rendering Int
56getCurrentIndex = gets (listPosition . NE.head)
57
58getCurrentIndentation :: Rendering Int
59getCurrentIndentation = gets (indentLevel . NE.head)
60
61renderElement :: Element -> Rendering [Text]
62renderElement (Segment code positional) =
63 let output index indentation =
64 [ sformat (fIndentation % fIndex % " " % fPositional % " " % fSegmentParserFunction) indentation index positional code
65 ]
66 in output <$> getCurrentIndex
67 <*> getCurrentIndentation
68 <* increment
69renderElement (GroupStart code positional) =
70 let output index indentation =
71 [ sformat (fIndentation % fIndex % " " % fPositional % " (") indentation index positional
72 , sformat (fIndentation % fSegmentGroupFunction) (indentation + 1) code
73 ]
74 in output <$> getCurrentIndex
75 <*> getCurrentIndentation
76 <* increment
77 <* pushIndent
78renderElement (GroupEnd _) =
79 let output indentation =
80 [ sformat (fIndentation % "]") indentation
81 , sformat (fIndentation % ")") (indentation - 1)
82 ]
83 in output <$> getCurrentIndentation
84 <* popIndent
85
86fIndentation :: Format r (Int -> r)
87fIndentation =
88 let buildIndentation n = fromString (replicate (n * 2) ' ')
89 in later buildIndentation
90
91fIndex :: Format r (Int -> r)
92fIndex =
93 let buildIndex 0 = "["
94 buildIndex _ = ","
95 in later buildIndex
96
97fPositional :: Format r (Positional -> r)
98fPositional =
99 let buildPositional (Positional p r) = bprint (quoted fPosition % " .@ " % fRepetition) p r
100 in later buildPositional
101
102fSegmentGroupFunction :: Format r (GroupCode -> r)
103fSegmentGroupFunction = "segmentGroup " % quoted fGroupCode
104
105fRepetition :: Format r (Repetition -> r)
106fRepetition =
107 let buildRepetition (Repetition Mandatory 1) = bprint "once"
108 buildRepetition (Repetition Optional 1) = bprint "maybeOnce"
109 buildRepetition (Repetition Mandatory c) = bprint ("repeatedAtLeastOnce" % " " % fCardinality) c
110 buildRepetition (Repetition Optional c) = bprint ("repeated" % " " % fCardinality) c
111 in later buildRepetition
112
113fCardinality :: Format r (Cardinality -> r)
114fCardinality = mapf getCardinality int
diff --git a/scaffolder/src/Text/Edifact/Scaffolder/Messages/Specification.hs b/scaffolder/src/Text/Edifact/Scaffolder/Messages/Specification.hs
new file mode 100644
index 0000000..b1e5c2a
--- /dev/null
+++ b/scaffolder/src/Text/Edifact/Scaffolder/Messages/Specification.hs
@@ -0,0 +1,129 @@
1{-# LANGUAGE DerivingStrategies #-}
2{-# LANGUAGE GeneralizedNewtypeDeriving #-}
3
4module Text.Edifact.Scaffolder.Messages.Specification
5 ( -- *
6 specificationParser
7 , messageNameParser
8 , listSegments
9 ) where
10
11import Text.Edifact.Scaffolder.Commons
12import Text.Edifact.Scaffolder.Messages.Types
13
14import Data.Maybe (mapMaybe)
15import Text.Parsec
16
17type Parser = Parsec String GroupTrail
18
19newtype GroupTrail = GroupTrail [GroupCode]
20 deriving stock Show
21 deriving newtype (Semigroup, Monoid)
22
23messageNameParser :: Parser MessageCode
24messageNameParser = scanUntil [
25 manyTill anyChar (string "Message Type : ") >> MessageCode <$> count 6 upper
26 ]
27
28specificationParser :: Parser [Dependency]
29specificationParser =
30 let scanElements = scan [ segmentInLine segmentElementParser
31 , groupInLine groupStartElementParser
32 ]
33 in interpretDependencies <$> scanElements <?> "Messages specification"
34
35listSegments :: Parser [SegmentCode]
36listSegments = mapMaybe (getSegment . getElement) <$> specificationParser
37
38interpretDependencies :: [Element] -> [Dependency]
39interpretDependencies = fmap Dependency
40
41groupInLine :: Parser a -> Parser [a]
42groupInLine p = single (many (string " ") *> p <* countClosingGroups)
43
44countClosingGroups :: Parser Int
45countClosingGroups =
46 let parser = many1 (char '-')
47 *> many1 (char '+')
48 <* many (char '|')
49 in length <$> parser
50
51closingGroupTrail :: Parser [Element]
52closingGroupTrail =
53 let groupEndParser = GroupEnd <$> popFromTrail
54 in countClosingGroups >>= flip count groupEndParser
55
56groupStartElementParser :: Parser Element
57groupStartElementParser =
58 let parseStart pos code rep = GroupStart code (Positional pos rep)
59 in parseStart <$> positionParser
60 <* many1 (choice [ () <$ try (oneOf "+*#|X "), () <$ try (string "- ") ])
61 <*> groupCodeParser
62 <* many1 (char ' ')
63 <*> repetitionParser
64 <?> "GroupElement"
65
66groupCodeParser :: Parser GroupCode
67groupCodeParser =
68 let parser = manyTill (char '-') (try $ string "-- Segment group")
69 *> many1 (char ' ')
70 *> many1 digit
71 <* many1 space
72 <* many1 (char '-')
73 group = GroupCode <$> parser
74 in group >>= appendToTrail <?> "GroupCodeParser"
75
76appendToTrail :: GroupCode -> Parser GroupCode
77appendToTrail code =
78 let append (GroupTrail trail) = GroupTrail (code : trail)
79 in code <$ modifyState append
80
81popFromTrail :: Parser GroupCode
82popFromTrail = do
83 previous <- getState
84 case previous of
85 GroupTrail (current : trail) -> current <$ putState (GroupTrail trail)
86 GroupTrail [] -> unexpected "GroupEnd, when state is currently clear"
87
88segmentTrail :: Parser [a]
89segmentTrail = [] <$ (many1 (char ' ') <* many (char '|'))
90
91segmentInLine :: Parser Element -> Parser [Element]
92segmentInLine p = do
93 segment <- many (string " ") *> p
94 trail <- choice [ try closingGroupTrail
95 , try segmentTrail
96 ]
97 pure (segment : trail)
98
99repetitionParser :: Parser Repetition
100repetitionParser =
101 Repetition <$> presenceParser
102 <* many1 (string " ")
103 <*> cardinalityParser
104 <?> "Repetition"
105
106positionParser :: Parser Position
107positionParser =
108 fromString <$> many1 digit
109 <?> "Position"
110
111segmentElementParser :: Parser Element
112segmentElementParser =
113 let parseSegment pos code rep = Segment code (Positional pos rep)
114 in parseSegment <$> positionParser
115 <* many1 (oneOf "+*#|-X ")
116 <*> segmentCodeParser
117 <* many1 (string " ")
118 <* stringToPresenceParser
119 <* many1 (string " ")
120 <*> repetitionParser
121 <?> "SegmentElement"
122
123segmentCodeParser :: Parser SegmentCode
124segmentCodeParser =
125 fromString <$> count 3 upper
126 <?> "SegmentCode"
127
128cardinalityParser :: Parser Cardinality
129cardinalityParser = Cardinality . read <$> many1 digit
diff --git a/scaffolder/src/Text/Edifact/Scaffolder/Messages/Types.hs b/scaffolder/src/Text/Edifact/Scaffolder/Messages/Types.hs
new file mode 100644
index 0000000..73cc702
--- /dev/null
+++ b/scaffolder/src/Text/Edifact/Scaffolder/Messages/Types.hs
@@ -0,0 +1,36 @@
1{-# LANGUAGE DerivingStrategies #-}
2{-# LANGUAGE GeneralizedNewtypeDeriving #-}
3
4module Text.Edifact.Scaffolder.Messages.Types where
5
6import Text.Edifact.Scaffolder.Commons
7
8import Data.Function (on)
9import Data.Ord (comparing)
10
11newtype Dependency = Dependency { getElement :: Element } deriving newtype (Show, Ord, Eq)
12
13data Repetition = Repetition Presence Cardinality deriving Show
14
15data Positional = Positional { positionalPosition :: Position
16 , positionalRepetition :: Repetition
17 } deriving (Show)
18
19instance Eq Positional where
20 (==) = (==) `on` positionalPosition
21
22instance Ord Positional where
23 compare = comparing positionalPosition
24
25data Element = Segment SegmentCode Positional
26 | GroupStart GroupCode Positional
27 | GroupEnd GroupCode
28 deriving (Show, Ord, Eq)
29
30getSegment :: Element -> Maybe SegmentCode
31getSegment (Segment code _) = Just code
32getSegment _ = Nothing
33
34newtype Cardinality = Cardinality { getCardinality :: Int }
35 deriving stock (Show)
36 deriving newtype (Eq, Num)