diff options
author | Frédéric Menou <frederic.menou@fretlink.com> | 2016-12-08 10:19:15 +0200 |
---|---|---|
committer | Ismaël Bouya <ismael.bouya@fretlink.com> | 2022-05-17 18:01:51 +0200 |
commit | a9d77a20008efe82862cc1adbfa7a6d4f09f8ff7 (patch) | |
tree | adf3186fdccaeef19151026cdfbd38a530cf9ecb /scaffolder/src/Text/Edifact/Scaffolder/Composites | |
download | edi-parser-a9d77a20008efe82862cc1adbfa7a6d4f09f8ff7.tar.gz edi-parser-a9d77a20008efe82862cc1adbfa7a6d4f09f8ff7.tar.zst edi-parser-a9d77a20008efe82862cc1adbfa7a6d4f09f8ff7.zip |
Diffstat (limited to 'scaffolder/src/Text/Edifact/Scaffolder/Composites')
5 files changed, 146 insertions, 0 deletions
diff --git a/scaffolder/src/Text/Edifact/Scaffolder/Composites/Dependencies.hs b/scaffolder/src/Text/Edifact/Scaffolder/Composites/Dependencies.hs new file mode 100644 index 0000000..51d45bf --- /dev/null +++ b/scaffolder/src/Text/Edifact/Scaffolder/Composites/Dependencies.hs | |||
@@ -0,0 +1,20 @@ | |||
1 | {-# LANGUAGE OverloadedStrings #-} | ||
2 | |||
3 | module Text.Edifact.Scaffolder.Composites.Dependencies | ||
4 | ( -- * | ||
5 | mkDependenciesHaddock | ||
6 | , mkDependenciesImports | ||
7 | , mkDependenciesReexports | ||
8 | ) where | ||
9 | |||
10 | import Text.Edifact.Scaffolder.Commons | ||
11 | import Text.Edifact.Scaffolder.Composites.Types | ||
12 | |||
13 | mkDependenciesReexports :: NonEmpty Element -> Scaffolding [Export] | ||
14 | mkDependenciesReexports = reexportDependencies fElement | ||
15 | |||
16 | mkDependenciesImports :: NonEmpty Element -> Scaffolding [ImportGroup] | ||
17 | mkDependenciesImports = fmap (pure . singleImport) . importDependencies "Simples" fElement | ||
18 | |||
19 | mkDependenciesHaddock :: NonEmpty Element -> Scaffolding [Text] | ||
20 | mkDependenciesHaddock = haddockDependencies fElement | ||
diff --git a/scaffolder/src/Text/Edifact/Scaffolder/Composites/Elements.hs b/scaffolder/src/Text/Edifact/Scaffolder/Composites/Elements.hs new file mode 100644 index 0000000..acfcbdb --- /dev/null +++ b/scaffolder/src/Text/Edifact/Scaffolder/Composites/Elements.hs | |||
@@ -0,0 +1,20 @@ | |||
1 | module Text.Edifact.Scaffolder.Composites.Elements | ||
2 | ( listComposites | ||
3 | ) where | ||
4 | |||
5 | import Text.Edifact.Scaffolder.Commons | ||
6 | |||
7 | import Data.Char (toUpper) | ||
8 | import Text.Parsec (count, digit, eof, oneOf, | ||
9 | string) | ||
10 | import Text.Parsec.String (Parser) | ||
11 | |||
12 | listComposites :: Scaffolding [ElementWithDefinition CompositeCode] | ||
13 | listComposites = listElements "composites" compositeCodeParser | ||
14 | |||
15 | compositeCodeParser :: Parser CompositeCode | ||
16 | compositeCodeParser = do | ||
17 | initial <- toUpper <$> oneOf "ce" | ||
18 | rest <- count 3 digit | ||
19 | _ <- string ".txt" | ||
20 | CompositeCode (initial : rest) <$ eof | ||
diff --git a/scaffolder/src/Text/Edifact/Scaffolder/Composites/Implementation.hs b/scaffolder/src/Text/Edifact/Scaffolder/Composites/Implementation.hs new file mode 100644 index 0000000..0f3e939 --- /dev/null +++ b/scaffolder/src/Text/Edifact/Scaffolder/Composites/Implementation.hs | |||
@@ -0,0 +1,19 @@ | |||
1 | {-# LANGUAGE OverloadedStrings #-} | ||
2 | |||
3 | module Text.Edifact.Scaffolder.Composites.Implementation | ||
4 | ( -- * | ||
5 | toImplementation | ||
6 | ) where | ||
7 | |||
8 | import Text.Edifact.Scaffolder.Commons | ||
9 | import Text.Edifact.Scaffolder.Composites.Types | ||
10 | |||
11 | import Data.List.NonEmpty as NE (toList) | ||
12 | import Formatting | ||
13 | |||
14 | toImplementation :: NonEmpty Dependency -> [Text] | ||
15 | toImplementation = haskellList . fmap callDependency . NE.toList | ||
16 | |||
17 | callDependency :: Dependency -> Text | ||
18 | callDependency (Dependency pos element presence) = | ||
19 | sformat (quoted fPosition % " .@ " % fPresence % " " % fElement) pos presence element | ||
diff --git a/scaffolder/src/Text/Edifact/Scaffolder/Composites/Specification.hs b/scaffolder/src/Text/Edifact/Scaffolder/Composites/Specification.hs new file mode 100644 index 0000000..0bb749d --- /dev/null +++ b/scaffolder/src/Text/Edifact/Scaffolder/Composites/Specification.hs | |||
@@ -0,0 +1,69 @@ | |||
1 | module Text.Edifact.Scaffolder.Composites.Specification | ||
2 | ( -- * | ||
3 | specificationParser | ||
4 | , listSimples | ||
5 | ) where | ||
6 | |||
7 | import Text.Edifact.Scaffolder.Commons | ||
8 | import Text.Edifact.Scaffolder.Composites.Types | ||
9 | |||
10 | import Text.Parsec as P (anyChar, count, | ||
11 | digit, | ||
12 | endOfLine, many, | ||
13 | many1, manyTill, | ||
14 | oneOf, skipMany, | ||
15 | string, try, | ||
16 | (<?>)) | ||
17 | import Text.Parsec.String (Parser) | ||
18 | |||
19 | specificationParser :: Parser ((CompositeCode, CompositeName), [Dependency]) | ||
20 | specificationParser = do | ||
21 | compositeInfo <- scanUntil [ compositeParser ] | ||
22 | dependencies <- scan [ inLine dependencyParser ] <?> "Composites specification" | ||
23 | pure (compositeInfo, dependencies) | ||
24 | |||
25 | listSimples :: Parser (CompositeCode, [SimpleCode]) | ||
26 | listSimples = do | ||
27 | parsed <- specificationParser | ||
28 | pure (fst $ fst parsed, getElementSimpleCode . dependencyElement <$> snd parsed) | ||
29 | |||
30 | compositeParser :: Parser (CompositeCode, CompositeName) | ||
31 | compositeParser = do | ||
32 | _ <- count 6 (oneOf "+*#|X ") | ||
33 | skipMany (string " ") | ||
34 | code <- compositeCodeParser | ||
35 | _ <- string " " | ||
36 | name <- CompositeName <$> manyTill anyChar (() <$ try endOfLine) | ||
37 | pure (code, name) | ||
38 | |||
39 | compositeCodeParser :: Parser CompositeCode | ||
40 | compositeCodeParser = do | ||
41 | initial <- oneOf "CE" | ||
42 | rest <- count 3 digit | ||
43 | pure (fromString (initial : rest)) | ||
44 | |||
45 | dependencyParser :: Parser Dependency | ||
46 | dependencyParser = | ||
47 | Dependency <$> positionParser | ||
48 | <* many1 (oneOf "+*#|-X ") | ||
49 | <*> elementParser | ||
50 | <* stringToPresenceParser | ||
51 | <* many1 (string " ") | ||
52 | <*> presenceParser | ||
53 | <?> "Dependency" | ||
54 | |||
55 | inLine :: Parser a -> Parser [a] | ||
56 | inLine p = single (many (string " ") *> p <* filler) | ||
57 | |||
58 | filler :: Parser () | ||
59 | filler = () <$ many (oneOf "an.0123456789 ") | ||
60 | |||
61 | positionParser :: Parser Position | ||
62 | positionParser = | ||
63 | fromString <$> count 3 digit | ||
64 | <?> "Position" | ||
65 | |||
66 | elementParser :: Parser Element | ||
67 | elementParser = | ||
68 | fromString <$> count 4 digit | ||
69 | <?> "Element" | ||
diff --git a/scaffolder/src/Text/Edifact/Scaffolder/Composites/Types.hs b/scaffolder/src/Text/Edifact/Scaffolder/Composites/Types.hs new file mode 100644 index 0000000..c7a676f --- /dev/null +++ b/scaffolder/src/Text/Edifact/Scaffolder/Composites/Types.hs | |||
@@ -0,0 +1,18 @@ | |||
1 | {-# LANGUAGE DerivingStrategies #-} | ||
2 | {-# LANGUAGE GeneralizedNewtypeDeriving #-} | ||
3 | |||
4 | module Text.Edifact.Scaffolder.Composites.Types where | ||
5 | |||
6 | import Text.Edifact.Scaffolder.Commons | ||
7 | |||
8 | import Formatting | ||
9 | |||
10 | data Dependency = Dependency { dependencyPosition :: Position | ||
11 | , dependencyElement :: Element | ||
12 | , dependencyPresence :: Presence | ||
13 | } deriving Show | ||
14 | |||
15 | newtype Element = Simple { getElementSimpleCode :: SimpleCode } deriving newtype (Show, Eq, Ord, IsString) | ||
16 | |||
17 | fElement :: Format r (Element -> r) | ||
18 | fElement = mapf getElementSimpleCode fSimpleParserFunction | ||