{-# LANGUAGE OverloadedStrings #-} module Funcons.Core.Values.Composite.Collections.TuplesBuiltin where import Funcons.EDSL import Funcons.Types library = libFromList [ ("discard-empty-tuples", ValueOp discard_empty_tuples_op) , ("tuple-index", ValueOp stepTupleIndex) ] discard_empty_tuples_ = FApp "discard-empty-tuples" . FTuple discard_empty_tuples_op vs = rewriteTo $ FValue $ safe_tuple_val (filter (/= EmptyTuple) vs) -- | /tuple-index(_,N)/ selects the /N/th component of a tuple. -- e.g. /tuple-index((true,"hello",'B'),2)/ = `"hello" tuple_index_ :: [Funcons] -> Funcons tuple_index_ = applyFuncon "tuple-index" stepTupleIndex args@[NonEmptyTuple v1 v2 vs, vn] | Nat n <- upcastNaturals vn = let vals = v1:v2:vs i = fromInteger n in if i > 0 && i <= length vals then rewriteTo (FValue (vals !! (i-1))) else partialOp (tuple_index_ (fvalues args)) "index out of range" stepTupleIndex args = sortErr (tuple_index_ (fvalues args)) "tuple-index must be applied to a (non-empty) tuple and a natural number"