module Text.PCLT.Template where
import qualified Data.ByteString.Lazy.UTF8.Unified as Lazy (ByteString)
import qualified Data.ByteString.Lazy.UTF8.Unified as B hiding (ByteString)
import Data.List
import qualified Data.Map as M
import Data.Map (Map, (!))
import Data.MyHelpers
import Data.Typeable
import Text.PCLT.Parser.AdvancedSepBy
import Text.PCLT.Parser.ParserInternals
import Text.PCLT.CommonTypes
import Text.PCLT.Config
import Text.PCLT.SDL
data PCS_SpecificMarkings =
PlainText_LngTplM
| Parameter_LngTplM
| Composite_LngTplM
| Unsupported_LngTplM SeparatedSectorMarker
deriving (Eq, Show, Typeable)
ssm2ldtm :: SeparatedSectorMarker -> PCS_SpecificMarkings
ssm2ldtm ssm =
case ssm of
Error_SSM err_msg -> Unsupported_LngTplM ssm
InnerMarker_SSM i ->
if i == 0 then PlainText_LngTplM
else if i == 1 then Parameter_LngTplM
else if i == 2 then Composite_LngTplM
else Unsupported_LngTplM ssm
_ -> Unsupported_LngTplM ssm
type LngTpl_AbstractedString = [(PCS_SpecificMarkings, Lazy.ByteString, MarkedChunkLength)]
listOfParams :: LngTpl_AbstractedString -> [ParamName_LBS]
listOfParams str_struct = foldl (\ accum (marker, str, _) -> case marker == Parameter_LngTplM of {True -> str : accum; False -> accum }) [] str_struct
type ParserBadResult = String
data PCLT_ParserLowLevelFailure =
UnexpectedParserResult_PLLF_PCLT ParserBadResult
| BadMarker_PLLF_PCLT SeparatedSectorMarker Lazy.ByteString ChunkIndexInList_
deriving (Show, Typeable)
doTheParse :: PCLT_InnerConfig
-> Lazy.ByteString
-> ( [PCLT_ParserLowLevelFailure], Maybe ( LngTpl_AbstractedString, [PCLT_CompositeKey] ))
doTheParse pcsc_config str =
let parser = sepBySome
anyChar
standardMarkingStrategy
[ stringLBS $ pcsParameterPlaceholderWrapper pcsc_config
, stringLBS $ pcsCompositePlaceholderWrapper pcsc_config
]
in case parse parser str of
( IllegalInput , _ ) -> ([UnexpectedParserResult_PLLF_PCLT "IllegalInput"], Nothing)
( ReachedEOF , _ ) -> ([UnexpectedParserResult_PLLF_PCLT "ReachedEOF"] , Nothing)
( Success marked_chunks_list, _ ) ->
let _fixed_marked_chunks_list = standardMarkingStrategyFix_StripEmptyChunks marked_chunks_list
list_of_parser_errors = map (\ (ssm, s, idx) -> BadMarker_PLLF_PCLT ssm s idx) $ retrieveErrorsMarkingsList _fixed_marked_chunks_list
non_plain_markings_map = retrieveNonPlainMarkingsMap _fixed_marked_chunks_list
fixed_marked_chunks_list = map (\ (ssm, str, len) -> (ssm2ldtm ssm, str, len)) _fixed_marked_chunks_list
list_of_composites_keys = map B.unpack $ fst $ unzip $ getListOfMarkings non_plain_markings_map 2
in (list_of_parser_errors, Just (fixed_marked_chunks_list, list_of_composites_keys))
type PCLT_CatalogMap = Map PCLT_ID LocalizableTemplate
type LngTpl_SubCompositesMap = PCLT_CatalogMap
data LocalizedTemplate =
LocalizedTemplate {
ldtAbstractedString :: LngTpl_AbstractedString
, ldtSubcompositesMap :: LngTpl_SubCompositesMap
}
deriving (Show, Typeable)
type DefaultLngTpl = LocalizedTemplate
type NondefaultLngTpl = LocalizedTemplate
compareStrictOrientationOnDefault :: PCLT_ID -> StrictOrient_ofParamsAndCmpsts_onDfltLngTplsSets -> NondefaultLngTpl -> DefaultLngTpl -> Bool
compareStrictOrientationOnDefault tpl_id so nondflt_ldt dflt_ldt =
let ( dflt_subcomps , dflt_params ) = (fst . unzip . M.toList . ldtSubcompositesMap, listOfParams . ldtAbstractedString) `apFrom2ple` dflt_ldt
(nondflt_subcomps , nondflt_params ) = (fst . unzip . M.toList . ldtSubcompositesMap, listOfParams . ldtAbstractedString) `apFrom2ple` nondflt_ldt
in _compareStrictOrientationOnDefault tpl_id so (nondflt_subcomps, nondflt_params) (dflt_subcomps, dflt_params)
_compareStrictOrientationOnDefault :: PCLT_ID -> StrictOrient_ofParamsAndCmpsts_onDfltLngTplsSets -> ([PCLT_ID], [ParamName_LBS]) -> ([PCLT_ID], [ParamName_LBS]) -> Bool
_compareStrictOrientationOnDefault tpl_id so (nondflt_subcomps, nondflt_params) (dflt_subcomps, dflt_params) =
let memb = elem tpl_id $ soExcludingInComposites so
crit1 = soStrict_IsIt so && (not memb)
crit2 = (not $ soStrict_IsIt so) && memb
crit = crit1 || crit2
local_c_exclusions = soExcludingComposites so ++ (snd $ unzip $ filter
(\ (_tpl_id, _) -> _tpl_id == tpl_id)
(soExcludingCompComposites so)
)
local_p_exclusions =
map
B.pack
( soExcludingParameters so ++ (snd $ unzip $ filter
(\ (_tpl_id, _) -> _tpl_id == tpl_id)
(soExcludingCompParameters so)
) )
op :: Eq a => [a] -> [a] -> [a]
op = case crit of
True -> (\\)
False -> intersect
( so_dflt_subcomps , so_dflt_params ) = ( dflt_subcomps `op` local_c_exclusions, dflt_params `op` local_p_exclusions)
(so_nondflt_subcomps , so_nondflt_params ) = ( nondflt_subcomps `op` local_c_exclusions, nondflt_params `op` local_p_exclusions)
( so_union_subcomps , so_union_params ) = ( so_dflt_subcomps `union` so_nondflt_subcomps, so_dflt_params `union` so_nondflt_params)
(so_nondflt_subcomps_len, so_nondflt_params_len) = (length so_nondflt_subcomps, length so_nondflt_params)
( so_dflt_subcomps_len, so_dflt_params_len) = (length so_dflt_subcomps, length so_dflt_params)
( so_union_subcomps_len, so_union_params_len) = (length so_union_subcomps, length so_union_params)
in so_union_subcomps_len == so_dflt_subcomps_len && so_union_params_len == so_dflt_params_len
&& so_union_subcomps_len == so_nondflt_subcomps_len && so_union_params_len == so_nondflt_params_len
data PCLT_ShowDetalizationLevel =
PCLT_SDL ShowDetalizationLevel
| PCLT_SDL_ToTemplateLink PCLT_ID
| PCLT_SDL_ToParamCompositeLink PCLT_ParamKey
| PCLT_SDL_Errornous PCLT_ErrornousSDL
deriving (Eq, Show, Typeable)
type PCLT_RequiredShowDetalizationLevel = PCLT_ShowDetalizationLevel
type PCLT_AllocatedShowDetalizationLevel = PCLT_ShowDetalizationLevel
data PCLT_RawCatalogData = PCLT_RawCatalogData (Map PCLT_ID (Map LanguageName Lazy.ByteString, PCLT_RequiredShowDetalizationLevel)) deriving (Show, Typeable)
data PCLT_ErrornousSDL = UnreadableSDL_ESDL SDLModus String deriving (Eq, Show, Typeable)
__const_esdl_rawinputshowsize_inShowAsPCSI :: Int
__const_esdl_rawinputshowsize_inShowAsPCSI = 25
str2PCLT_SDL :: SDLModus -> String -> PCLT_InnerConfig -> PCLT_ShowDetalizationLevel
str2PCLT_SDL sdlm s cfg =
let cmpst_phw_str = B.unpack $ pcsCompositePlaceholderWrapper cfg
param_phw_str = B.unpack $ pcsParameterPlaceholderWrapper cfg
stripOfWrapper subj0 wrp =
let wrp_len = length wrp
subj1 = drop wrp_len subj0
subj1_len = length subj1
in take (subj1_len wrp_len) subj1
in case strict_str2sdl s of
Just n -> PCLT_SDL n
Nothing ->
case isPrefixOf cmpst_phw_str s && isSuffixOf cmpst_phw_str s of
True -> PCLT_SDL_ToTemplateLink (stripOfWrapper s cmpst_phw_str)
False -> case isPrefixOf param_phw_str s && isSuffixOf param_phw_str s of
True -> PCLT_SDL_ToParamCompositeLink (stripOfWrapper s param_phw_str)
False ->
let cond1 = pcsAllowEmptySDL_parseItByModusMargin cfg && null s
cond2 = pcsAllowUnreadableSDL_parseIdByModusMargin cfg
cond = cond1 || cond2
in case cond of
True -> PCLT_SDL $ marginOfSDLModus sdlm
False -> PCLT_SDL_Errornous $ UnreadableSDL_ESDL sdlm $ truncLiterary s __const_esdl_rawinputshowsize_inShowAsPCSI
data LocalizableTemplate =
LocalizableTemplate {
pcltLocalizationsMap :: Map LanguageName LocalizedTemplate
, pcltRequiredSDL :: PCLT_RequiredShowDetalizationLevel
}
deriving (Show, Typeable)