Search code examples
haskellcardano

What is the syntax used in this function definition of Cardano?


How to interpret this function:

friendlyValidityRange
  :: CardanoEra era
  -> (TxValidityLowerBound era, TxValidityUpperBound era)
  -> Aeson.Value
friendlyValidityRange era = \case
  ShelleyTtl ttl -> object ["time to live" .= ttl]
  (lowerBound, upperBound)
    | isLowerBoundSupported || isUpperBoundSupported ->
        object
          [ ...
          ]
    | otherwise -> Null
 where
  isLowerBoundSupported = isJust $ validityLowerBoundSupportedInEra era
  isUpperBoundSupported = isJust $ validityUpperBoundSupportedInEra era

I thought the friendlyValidityRange function utilize the partial function concept, but still failed to understand it. How can friendlyValidityRange's era and (lowerBound, upperBound) parameters be passed in such separated way?

I try to mimic it use follow demo, still unable to finished it.


module Main where

data Age = Child | Adult

-- Function that accept two agrs: Age, (weightMin, weightMax) , and return health description string
weightAnalyse :: Age -> (Int, Int) -> String
weightAnalyse age = \case
    Child    ->  ?  -- how to comsume the (min, max) tuple
    Adult    ->  ? 
    
main :: IO ()
main = do
  weightAnalyse Child (30, 60)
  weightAnalyse Adult (60, 130)

Solution

  • You are missing Pattern Synonyms. Take a look at line 105

    {-# LANGUAGE PatternSynonyms #-}
    
    pattern ShelleyTtl
      :: SlotNo -> (TxValidityLowerBound era, TxValidityUpperBound era)
    pattern ShelleyTtl ttl <-
      ( TxValidityNoLowerBound
      , TxValidityUpperBound ValidityUpperBoundInShelleyEra ttl
      )
    

    This says that a tuple where the first component is TxValidityNoLowerBound and the second component is TxValidityUpperBound ValidityUpperBoundInShelleyEra ttl can be used as the pattern ShelleyTtl ttl with ttl bound to the correct value.

    So ShelleyTtl ttl in

    friendlyValidityRange era = \case
      ShelleyTtl ttl -> object ["time to live" .= ttl]
    

    matches a particular type of tuple!

    Your weightAnalyse does not really match the example you are referencing but would go along the lines of:

    {-# LANGUAGE LambdaCase, PatternSynonyms  #-}
    
    data Age = Child String | Adult
    
    pattern ChildPattern x <- (_, Child x)
    
    weightAnalyse :: Int -> (Int, Age) -> String
    weightAnalyse id = \case
      ChildPattern x -> x
      (a, age) -> "other"
    -- The parameter id is unused and could be removed but is kept
    -- to match the original version of the function.
    
    --  *> weightAnalyse 1 (30, Child "foo")
    -- "foo"
    --  *> weightAnalyse 2 (60, Adult)
    -- "other"