-- GeNeRaTeD fOr: ../../CBS/Funcons/Computations/Control flow/Normal/Iterating/Definite/Mapping collections/lists-map.aterm {-# LANGUAGE OverloadedStrings #-} module Funcons.Core.Computations.ControlFlow.Normal.Iterating.Definite.MappingCollections.ListsMap where import Funcons.EDSL entities = [] types = typeEnvFromList [] funcons = libFromList [("lists-map",PartiallyStrictFuncon [NonStrict,Strict] stepLists_map)] -- | -- /lists-map(F,(List+))/ maps the computation /F/ over N lists of equal length -- L, in parallel from left to right. /F/ is evaluated L times, once for each -- given tuple of argument values, where the Nth component of each tuple is -- drawn from the Nth argument list. lists_map_ fargs = FApp "lists-map" (FTuple fargs) stepLists_map fargs@[arg1,arg2] = evalRules [rewrite1,rewrite2] [] where rewrite1 = do let env = emptyEnv env <- fsMatch fargs [PMetaVar "F",PAnnotated (PMetaVar "L") (TApp "lists" (TTuple [TName "values"]))] env rewriteTermTo (TApp "list-map" (TTuple [TVar "F",TVar "L"])) env rewrite2 = do let env = emptyEnv env <- fsMatch fargs [PMetaVar "F",PAnnotated (PMetaVar "LS") (TTuple [TApp "lists" (TTuple [TName "values"]),TSortSeq (TApp "lists" (TTuple [TName "values"])) PlusOp])] env rewriteTermTo (TApp "give" (TTuple [TApp "tuple-map" (TTuple [TApp "is-nil" (TTuple [TName "given"]),TVar "LS"]),TApp "if-then-else" (TTuple [TApp "and" (TTuple [TName "given"]),TName "nil",TApp "if-then-else" (TTuple [TApp "or" (TTuple [TName "given"]),TName "fail",TApp "cons" (TTuple [TApp "left-to-right" (TTuple [TApp "give" (TTuple [TApp "tuple-map" (TTuple [TApp "head" (TTuple [TName "given"]),TVar "LS"]),TVar "F"]),TApp "lists-map" (TTuple [TVar "F",TApp "tuple-map" (TTuple [TApp "tail" (TTuple [TName "given"]),TVar "LS"])])])])])])])) env stepLists_map fargs = sortErr (FApp "lists-map" (FTuple fargs)) "invalid number of arguments"