-- GeNeRaTeD fOr: ../../CBS/Funcons/Abstractions/Functions/uncurry.aterm
{-# LANGUAGE OverloadedStrings #-}

module Funcons.Core.Abstractions.Functions.Uncurry where

import Funcons.EDSL

entities = []

types = typeEnvFromList
    []

funcons = libFromList
    [("uncurry",StrictFuncon stepUncurry)]

-- |
-- /uncurry(F)/ converts a function that computes a function into a single
--   function that takes both arguments as a pair.
uncurry_ fargs = FApp "uncurry" (FTuple fargs)
stepUncurry fargs =
    evalRules [rewrite1] []
    where rewrite1 = do
            let env = emptyEnv
            env <- vsMatch fargs [VPAnnotated (VPMetaVar "F") (TName "values")] env
            rewriteTermTo (TApp "thunk" (TTuple [TApp "apply" (TTuple [TApp "apply" (TTuple [TVar "F",TName "given1"]),TName "given2"])])) env